From gitlab at gitlab.haskell.org Tue Oct 1 00:14:01 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Mon, 30 Sep 2024 20:14:01 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] Link interface bytecode from package DBs if possible Message-ID: <66fb3ec82f985_103d46762b68875f@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC Commits: 28cb3574 by Torsten Schmits at 2024-10-01T02:13:45+02:00 Link interface bytecode from package DBs if possible Part of #25090. MR !????? When splices are executed with `-fprefer-byte-code`, the loader will compile Core bindings to bytecode if those are present in interfaces of module dependencies. So far, this only applied to local modules (i.e. home modules in make mode and non-package deps in oneshot mode). This patch extends support to interfaces loaded from a package DB. In `getLinkDeps`, the dependencies chosen for recursion were restricted to `dep_direct_mods`, which has been changed to include `mi_usages`. In order to unify treatment of the different link variants across make/oneshot mode, the algorithm's intermediate results have been abstracted into the data types `LinkDep` and `LinkModule`. At the moment, following package deps is only implemented for oneshot mode. - - - - - 22 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Module/WholeCoreBindings.hs - docs/users_guide/phases.rst - + testsuite/tests/bytecode/T25090/Dep.hs - + testsuite/tests/bytecode/T25090/DepApi.hs - + testsuite/tests/bytecode/T25090/Local.hs - testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25090/Num.hs - + testsuite/tests/bytecode/T25090/Num.hs-boot - + testsuite/tests/bytecode/T25090/PkgBytecode.hs - + testsuite/tests/bytecode/T25090/PkgBytecode.stdout - testsuite/tests/bytecode/T25090/all.T - + testsuite/tests/bytecode/T25090/dep.conf - + testsuite/tests/bytecode/T25090/prep.bash - + testsuite/tests/bytecode/T25090/run.bash - + testsuite/tests/bytecode/T25090/unit1 - + testsuite/tests/bytecode/T25090/unit2 Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -843,6 +843,7 @@ data GeneralFlag | Opt_BuildDynamicToo | Opt_WriteIfSimplifiedCore | Opt_UseBytecodeRatherThanObjects + | Opt_PackageDbBytecode -- safe haskell flags | Opt_DistrustAllPackages ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2540,6 +2540,7 @@ fFlagsDeps = [ flagSpec "link-rts" Opt_LinkRts, flagSpec "byte-code-and-object-code" Opt_ByteCodeAndObjectCode, flagSpec "prefer-byte-code" Opt_UseBytecodeRatherThanObjects, + flagSpec "pkgdb-byte-code" Opt_PackageDbBytecode, flagSpec' "compact-unwind" Opt_CompactUnwind (\turn_on -> updM (\dflags -> do unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -672,7 +672,11 @@ dontLeakTheHUG thing_inside = do in hsc_env { hsc_targets = panic "cleanTopEnv: hsc_targets" , hsc_mod_graph = panic "cleanTopEnv: hsc_mod_graph" - , hsc_IC = panic "cleanTopEnv: hsc_IC" + -- TODO this is needed for bytecode compilation of package deps + -- only. local EPS modules work fine. + -- Also it appears to work when the local modules use multiple + -- home units?!?!? + -- , hsc_IC = panic "cleanTopEnv: hsc_IC" , hsc_type_env_vars = case maybe_type_vars of Just vars -> vars Nothing -> panic "cleanTopEnv: hsc_type_env_vars" ===================================== compiler/GHC/Linker/Deps.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module GHC.Linker.Deps ( LinkDepsOpts (..) @@ -28,6 +29,7 @@ import GHC.Types.Unique.DSet import GHC.Types.Unique.DFM import GHC.Utils.Outputable +import qualified GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Error @@ -47,9 +49,11 @@ import GHC.Utils.Misc import GHC.Unit.Home import GHC.Data.Maybe -import Control.Monad import Control.Applicative +import Control.Monad.IO.Class (MonadIO (liftIO)) +import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE) +import Data.Foldable (traverse_) import qualified Data.Set as Set import qualified Data.Map as M import Data.List (isSuffixOf) @@ -64,19 +68,21 @@ data LinkDepsOpts = LinkDepsOpts , ldUnitEnv :: !UnitEnv , ldPprOpts :: !SDocContext -- ^ Rendering options for error messages , ldUseByteCode :: !Bool -- ^ Use bytecode rather than objects + , ldPkgByteCode :: !Bool -- ^ Use bytecode for external packages , ldMsgOpts :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics , ldWays :: !Ways -- ^ Enabled ways , ldFinderCache :: !FinderCache , ldFinderOpts :: !FinderOpts - , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)) - , ldLoadByteCode :: !(Module -> IO (Maybe Linkable)) + , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation))) + , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable))) + , ldDebugTrace :: !(SDoc -> IO ()) } data LinkDeps = LinkDeps { ldNeededLinkables :: [Linkable] , ldAllLinkables :: [Linkable] - , ldUnits :: [UnitId] - , ldNeededUnits :: UniqDSet UnitId + , ldNeededUnits :: [UnitId] + , ldAllUnits :: UniqDSet UnitId } -- | Find all the packages and linkables that a set of modules depends on @@ -102,7 +108,14 @@ getLinkDeps opts interp pls span mods = do get_link_deps opts pls maybe_normal_osuf span mods - +-- | Compute the linkables for the given module set's dependencies. +-- +-- Home modules in make mode are treated separately in a preprocessing step, +-- then all the remaining external deps are processed for both modes. +-- If bytecode is available, transitive external deps are included, otherwise +-- the module's library is linked and processing stops. +-- +-- The results are split into sets of needed/loaded modules/packages. get_link_deps :: LinkDepsOpts -> LoaderState @@ -111,46 +124,40 @@ get_link_deps -> [Module] -> IO LinkDeps get_link_deps opts pls maybe_normal_osuf span mods = do - -- 1. Find the dependent home-pkg-modules/packages from each iface - -- (omitting modules from the interactive package, which is already linked) - (mods_s, pkgs_s) <- - -- Why two code paths here? There is a significant amount of repeated work - -- performed calculating transitive dependencies - -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests) - if ldOneShotMode opts - then follow_deps (filterOut isInteractiveModule mods) - emptyUniqDSet emptyUniqDSet; - else do - (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods - return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs)) - - let - -- 2. Exclude ones already linked - -- Main reason: avoid findModule calls in get_linkable - (mods_needed, links_got) = partitionWith split_mods mods_s - pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls - - split_mods mod = - let is_linked = lookupModuleEnv (objs_loaded pls) mod - <|> lookupModuleEnv (bcos_loaded pls) mod - in case is_linked of - Just linkable -> Right linkable - Nothing -> Left mod - - -- 3. For each dependent module, find its linkable - -- This will either be in the HPT or (in the case of one-shot - -- compilation) we may need to use maybe_getFileLinkable - lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed - - return $ LinkDeps - { ldNeededLinkables = lnks_needed - , ldAllLinkables = links_got ++ lnks_needed - , ldUnits = pkgs_needed - , ldNeededUnits = pkgs_s - } + (link_deps_home, module_deps_external) <- separate_home_deps + link_deps_external <- external_deps opts module_deps_external + let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) = + classify_deps pls (link_deps_home ++ link_deps_external) + ldNeededLinkables <- mapM module_linkable needed_modules + pure LinkDeps { + ldNeededLinkables, + ldAllLinkables = loaded_modules ++ ldNeededLinkables, + ldNeededUnits, + ldAllUnits + } where mod_graph = ldModuleGraph opts unit_env = ldUnitEnv opts + noninteractive = filterOut isInteractiveModule mods + + -- Preprocess the dependencies in make mode to remove all home modules, + -- since the transitive dependency closure is already cached for those in + -- the HUG (see MultiLayerModulesTH_* tests for the performance impact). + -- + -- Returns the remaining, external, dependencies on the right, which is the + -- entire set for oneshot mode. + separate_home_deps = + if ldOneShotMode opts + then pure ([], noninteractive) + else make_deps + + make_deps = do + (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods + let + link_mods = + listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods] + ext = uniqDSetToList (unionManyUniqDSets (init_ext : dep_ext)) + pure ([LinkModules (LinkHomeModule <$> link_mods)], ext) -- This code is used in `--make` mode to calculate the home package and unit dependencies -- for a set of modules. @@ -160,9 +167,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- It is also a matter of correctness to use the module graph so that dependencies between home units -- is resolved correctly. - make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey) + make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey) make_deps_loop found [] = found - make_deps_loop found@(found_units, found_mods) (nk:nexts) + make_deps_loop found@(external, found_mods) (nk:nexts) | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts | otherwise = case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of @@ -171,85 +178,26 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- See #936 and the ghci.prog007 test for why we have to continue traversing through -- boot modules. todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps] - in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) + in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) Nothing -> - let (ModNodeKeyWithUid _ uid) = nk - in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts + let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk + in make_deps_loop (addOneToUniqDSet external (Module (RealUnit (Definite uid)) mod_name), found_mods) nexts mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m) - (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods) + (init_ext, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk noninteractive all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps] get_mod_info (ModNodeKeyWithUid gwib uid) = case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of - Just hmi -> - let iface = (hm_iface hmi) - mmod = case mi_hsc_src iface of - HsBootFile -> link_boot_mod_error (mi_module iface) - _ -> return $ Just (mi_module iface) - - in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$> mmod + Just hmi -> do + let iface = hm_iface hmi + case mi_hsc_src iface of + HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface) + _ -> pure (mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi) Nothing -> throwProgramError opts $ text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid - - -- This code is used in one-shot mode to traverse downwards through the HPT - -- to find all link dependencies. - -- The ModIface contains the transitive closure of the module dependencies - -- within the current package, *except* for boot modules: if we encounter - -- a boot module, we have to find its real interface and discover the - -- dependencies of that. Hence we need to traverse the dependency - -- tree recursively. See bug #936, testcase ghci/prog007. - follow_deps :: [Module] -- modules to follow - -> UniqDSet Module -- accum. module dependencies - -> UniqDSet UnitId -- accum. package dependencies - -> IO ([Module], UniqDSet UnitId) -- result - follow_deps [] acc_mods acc_pkgs - = return (uniqDSetToList acc_mods, acc_pkgs) - follow_deps (mod:mods) acc_mods acc_pkgs - = do - mb_iface <- ldLoadIface opts msg mod - iface <- case mb_iface of - Failed err -> throwProgramError opts $ - missingInterfaceErrorDiagnostic (ldMsgOpts opts) err - Succeeded iface -> return iface - - when (mi_boot iface == IsBoot) $ link_boot_mod_error mod - - let - pkg = moduleUnit mod - deps = mi_deps iface - - pkg_deps = dep_direct_pkgs deps - (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $ - \case - (_, GWIB m IsBoot) -> Left m - (_, GWIB m NotBoot) -> Right m - - mod_deps' = case ue_homeUnit unit_env of - Nothing -> [] - Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps)) - acc_mods' = case ue_homeUnit unit_env of - Nothing -> acc_mods - Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps) - acc_pkgs' = addListToUniqDSet acc_pkgs (Set.toList pkg_deps) - - case ue_homeUnit unit_env of - Just home_unit | isHomeUnit home_unit pkg -> follow_deps (mod_deps' ++ mods) - acc_mods' acc_pkgs' - _ -> follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg)) - where - msg = text "need to link module" <+> ppr mod <+> - text "due to use of Template Haskell" - - - - link_boot_mod_error :: Module -> IO a - link_boot_mod_error mod = throwProgramError opts $ - text "module" <+> ppr mod <+> - text "cannot be linked; it is only available as a boot module" - no_obj :: Outputable a => a -> IO b no_obj mod = dieWith opts span $ text "cannot find object file for module " <> @@ -258,6 +206,20 @@ get_link_deps opts pls maybe_normal_osuf span mods = do while_linking_expr = text "while linking an interpreted expression" + -- Extract the 'Linkable's for unlinked modules from the intermediate + -- results. + module_linkable = \case + LinkHomeModule hmi -> + adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi)) + + LinkObjectModule iface loc -> do + let mod = mi_module iface + findObjectLinkableMaybe mod loc >>= \case + Nothing -> no_obj mod + Just lnk -> adjust_linkable lnk + + LinkByteCodeModule _ load_bytecode -> + load_bytecode -- See Note [Using Byte Code rather than Object Code for Template Haskell] homeModLinkable :: HomeModInfo -> Maybe Linkable @@ -266,57 +228,257 @@ get_link_deps opts pls maybe_normal_osuf span mods = do then homeModInfoByteCode hmi <|> homeModInfoObject hmi else homeModInfoObject hmi <|> homeModInfoByteCode hmi - get_linkable osuf mod -- A home-package module - | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env) - = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info)) - | otherwise - = do -- It's not in the HPT because we are in one shot mode, - -- so use the Finder to get a ModLocation... - case ue_homeUnit unit_env of - Nothing -> no_obj mod - Just home_unit -> do - from_bc <- ldLoadByteCode opts mod - maybe (fallback_no_bytecode home_unit mod) pure from_bc - where - - fallback_no_bytecode home_unit mod = do - let fc = ldFinderCache opts - let fopts = ldFinderOpts opts - mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod) - case mb_stuff of - Found loc _ -> do - mb_lnk <- findObjectLinkableMaybe mod loc - case mb_lnk of - Nothing -> no_obj mod - Just lnk -> adjust_linkable lnk - _ -> no_obj (moduleName mod) - - adjust_linkable lnk - | Just new_osuf <- maybe_normal_osuf = do - new_parts <- mapM (adjust_part new_osuf) - (linkableParts lnk) - return lnk{ linkableParts=new_parts } - | otherwise = - return lnk - - adjust_part new_osuf part = case part of - DotO file ModuleObject -> do - massert (osuf `isSuffixOf` file) - let file_base = fromJust (stripExtension osuf file) - new_file = file_base <.> new_osuf - ok <- doesFileExist new_file - if (not ok) - then dieWith opts span $ - text "cannot find object file " - <> quotes (text new_file) $$ while_linking_expr - else return (DotO new_file ModuleObject) - DotO file ForeignObject -> pure (DotO file ForeignObject) - DotA fp -> panic ("adjust_ul DotA " ++ show fp) - DotDLL fp -> panic ("adjust_ul DotDLL " ++ show fp) - BCOs {} -> pure part - LazyBCOs{} -> pure part - CoreBindings WholeCoreBindings {wcb_module} -> - pprPanic "Unhydrated core bindings" (ppr wcb_module) + adjust_linkable lnk + | Just new_osuf <- maybe_normal_osuf = do + new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf) + (linkableParts lnk) + return lnk {linkableParts = new_uls} + | otherwise = + return lnk + + adjust_part osuf new_osuf part = case part of + DotO file ModuleObject -> do + massert (osuf `isSuffixOf` file) + let file_base = fromJust (stripExtension osuf file) + new_file = file_base <.> new_osuf + ok <- doesFileExist new_file + if (not ok) + then dieWith opts span $ + text "cannot find object file " + <> quotes (text new_file) $$ while_linking_expr + else return (DotO new_file ModuleObject) + DotO file ForeignObject -> pure (DotO file ForeignObject) + DotA fp -> panic ("adjust_part DotA " ++ show fp) + DotDLL fp -> panic ("adjust_part DotDLL " ++ show fp) + BCOs {} -> pure part + LazyBCOs{} -> pure part + CoreBindings WholeCoreBindings {wcb_module} -> + pprPanic "Unhydrated core bindings" (ppr wcb_module) + +data LinkModule = + LinkHomeModule !HomeModInfo + | + LinkObjectModule !ModIface !ModLocation + | + LinkByteCodeModule !ModIface !(IO Linkable) + +link_module_iface :: LinkModule -> ModIface +link_module_iface = \case + LinkHomeModule hmi -> hm_iface hmi + LinkObjectModule iface _ -> iface + LinkByteCodeModule iface _ -> iface + +instance Outputable LinkModule where + ppr = \case + LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI") + LinkObjectModule iface _ -> ppr (mi_module iface) + LinkByteCodeModule iface _ -> ppr (mi_module iface) <+> brackets (text "BC") + +data LinkDep = + LinkModules !(UniqDFM ModuleName LinkModule) + | + LinkLibrary !UnitId + +instance Outputable LinkDep where + ppr = \case + LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods) + LinkLibrary uid -> text "library:" <+> ppr uid + +data OneshotError = + NoLocation !Module + | + NoInterface !MissingInterfaceError + | + LinkBootModule !Module + +-- Compute the transitive dependency closure of the given modules. +-- +-- Used for all oneshot mode dependencies and for external dependencies of home +-- modules in make mode. +-- +-- TODO is the following still relevant? +-- The ModIface contains the transitive closure of the module dependencies +-- within the current package, *except* for boot modules: if we encounter +-- a boot module, we have to find its real interface and discover the +-- dependencies of that. Hence we need to traverse the dependency +-- tree recursively. See bug #936, testcase ghci/prog007. +external_deps :: + LinkDepsOpts -> + -- | Modules whose imports to follow + [Module] -> + IO [LinkDep] +external_deps opts mods = + runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case + Right a -> pure (eltsUDFM a) + Left err -> throwProgramError opts (message err) + where + message = \case + NoLocation mod -> + pprPanic "found iface but no location" (ppr mod) + NoInterface err -> + missingInterfaceErrorDiagnostic (ldMsgOpts opts) err + LinkBootModule mod -> + link_boot_mod_error mod + +external_deps_loop :: + LinkDepsOpts -> + [Module] -> + UniqDFM UnitId LinkDep -> + ExceptT OneshotError IO (UniqDFM UnitId LinkDep) +external_deps_loop _ [] acc = + pure acc +external_deps_loop opts (mod : mods) acc = do + (new_acc, new_mods, action) <- process_module + traverse_ debug_log action + external_deps_loop opts (new_mods ++ mods) new_acc + where + debug_log action = + liftIO $ ldDebugTrace opts $ + text "TH dep" <+> ppr mod <+> brackets (sep [ + if is_home then text "home" else Outputable.empty, + text action + ]) + + -- Decide how this module needs to be processed. + -- We only need an interface if we want to load bytecode or if we have to + -- link an object file (which happens for home unit modules, since those + -- have no libraries). + process_module + | already_seen = pure (acc, [], Nothing) + | is_home || prefer_bytecode = try_iface + | otherwise = add_library + + -- Check whether the current module was processed before. + -- Since the accumulator is keyed by unit ID, we have to perform two + -- lookups. + -- If another module from this module's unit has been determined to be + -- linked as a library previously, we skip this module, assuming that no + -- bytecode is available for the entire package. + already_seen + | Just (LinkModules mods) <- mod_dep + = elemUDFM mod_name mods + | Just (LinkLibrary _) <- mod_dep + = True + | otherwise + = False + + -- Load the iface and attempt to get bytecode from Core bindings. + try_iface = + liftIO (ldLoadIface opts load_reason mod) >>= \case + Failed err -> throwE (NoInterface err) + Succeeded (iface, loc) -> do + mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface)) + with_iface loc iface mb_load_bc + + -- Decide how to link this module. + -- If bytecode or an object file is available, use those in that order. + -- Otherwise fall back to linking a library. + with_iface loc iface mb_load_bc + | IsBoot <- mi_boot iface + = throwE (LinkBootModule mod) + + | prefer_bytecode + , Just load_bc <- mb_load_bc + = pure (add_module iface (LinkByteCodeModule iface load_bc) "bytecode") + + | is_home + = pure (add_module iface (LinkObjectModule iface loc) "object") + + | otherwise + = add_library + + add_library = + pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library") + + add_module iface lmod action = + (addListToUDFM with_mod (direct_pkgs iface), new_deps iface, Just action) + where + with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id + + add_package_module lmod = \case + Just (LinkLibrary u) -> Just (LinkLibrary u) + Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod)) + Nothing -> Just (LinkModules (unitUDFM mod_name lmod)) + + direct_pkgs iface + | prefer_bytecode + = [] + | otherwise + = [(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))] + + new_deps iface + | prefer_bytecode + -- TODO How can we better determine the external deps? + -- OTOH, we probably don't want to link unused dependencies anyway. + = [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface] ++ local + | is_home + = local + | otherwise + = [] + where + local = + [ + mkModule mod_unit m + -- TODO Somehow this just works, no idea what the deal was in the + -- old code with boot modules. + | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface)) + ] + + is_home + | Just home <- mb_home + = homeUnitAsUnit home == mod_unit + | otherwise + = False + + mod_dep = lookupUDFM acc mod_unit_id + mod_name = moduleName mod + mod_unit_id = moduleUnitId mod + mod_unit = moduleUnit mod + load_reason = + text "need to link module" <+> ppr mod <+> + text "due to use of Template Haskell" + + prefer_bytecode = ldUseByteCode opts && (is_home || ldPkgByteCode opts) + mb_home = ue_homeUnit (ldUnitEnv opts) + +link_boot_mod_error :: Module -> SDoc +link_boot_mod_error mod = + text "module" <+> ppr mod <+> + text "cannot be linked; it is only available as a boot module" + +-- | Split link dependencies into the sets of modules and packages that have +-- been linked previously and those that need to be linked now by checking for +-- their presence in the 'LoaderState': +-- +-- - For module dependencies, in the sets of loaded objects and BCOs +-- ('objs_loaded' and 'bcos_loaded') +-- - For package dependencies, in the set of loaded packages ('pkgs_loaded') +classify_deps :: + LoaderState -> + [LinkDep] -> + ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId]) +classify_deps pls deps = + (loaded_modules, needed_modules, all_packages, needed_packages) + where + (loaded_modules, needed_modules) = + partitionWith loaded_or_needed_module (concatMap eltsUDFM modules) + + needed_packages = + eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls) + + all_packages = mkUniqDSet packages + + (modules, packages) = flip partitionWith deps $ \case + LinkModules mods -> Left mods + LinkLibrary lib -> Right lib + + loaded_or_needed_module lm = + maybe (Right lm) Left (loaded_module (mi_module (link_module_iface lm))) + + loaded_module mod = + lookupModuleEnv (objs_loaded pls) mod + <|> + lookupModuleEnv (bcos_loaded pls) mod {- Note [Using Byte Code rather than Object Code for Template Haskell] ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -77,11 +77,13 @@ import GHC.Utils.TmpFs import GHC.Unit.Env import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode)) +import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.State as Packages import qualified GHC.Data.ShortText as ST import GHC.Data.FastString +import qualified GHC.Data.Maybe as Maybe import GHC.Linker.Deps import GHC.Linker.MacOS @@ -94,6 +96,7 @@ import Control.Monad import qualified Data.Set as Set import Data.Char (isSpace) import qualified Data.Foldable as Foldable +import Data.Functor ((<&>)) import Data.IORef import Data.List (intercalate, isPrefixOf, nub, partition) import Data.Maybe @@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - let this_pkgs_needed = ldNeededUnits deps + let this_pkgs_needed = ldAllUnits deps -- Link the packages and modules required - pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls + pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps) let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed all_pkgs_loaded = pkgs_loaded pls2 @@ -646,18 +649,39 @@ initLinkDepsOpts hsc_env = opts , ldFinderCache = hsc_FC hsc_env , ldFinderOpts = initFinderOpts dflags , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags + , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags , ldMsgOpts = initIfaceMessageOpts dflags , ldWays = ways dflags , ldLoadIface , ldLoadByteCode + , ldDebugTrace = debugTraceMsg (hsc_logger hsc_env) 3 } dflags = hsc_dflags hsc_env - ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env - $ loadInterface msg mod (ImportByUser NotBoot) + + ldLoadIface msg mod = + initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case + Maybe.Failed err -> pure (Maybe.Failed err) + Maybe.Succeeded iface -> + find_location mod <&> \case + InstalledFound loc _ -> Maybe.Succeeded (iface, loc) + err -> Maybe.Failed $ + cannotFindInterface unit_state home_unit + (targetProfile dflags) (moduleName mod) err + + find_location mod = + liftIO $ + findExactModule (hsc_FC hsc_env) (initFinderOpts dflags) + (initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env) + unit_state home_unit + (toUnitId <$> mod) + + unit_state = hsc_units hsc_env + + home_unit = ue_homeUnit (hsc_unit_env hsc_env) ldLoadByteCode mod = do EPS {eps_iface_bytecode} <- hscEPS hsc_env - sequence (lookupModuleEnv eps_iface_bytecode mod) + pure (lookupModuleEnv eps_iface_bytecode mod) ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -734,7 +734,7 @@ mkStubPaths fopts mod location = do src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location -- ----------------------------------------------------------------------------- --- findLinkable isn't related to the other stuff in here, +-- findObjectLinkable isn't related to the other stuff in here, -- but there's no other obvious place for it findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) ===================================== compiler/GHC/Unit/Module/WholeCoreBindings.hs ===================================== @@ -88,9 +88,10 @@ settings. 2. In oneshot mode, which compiles individual modules without a shared home unit graph, a previously compiled module is not reprocessed as described for make mode above. - When 'get_link_deps' encounters a dependency on a local module, it requests - its bytecode from the External Package State, who loads the interface - on-demand. + 'get_link_deps' requests the bytecode of dependencies from the External + Package State, who loads the interface on-demand. + This works for modules in local directories (via @-i@ and @-hidir@) as well + as those exposed from a package DB. Since the EPS stores interfaces for all package dependencies in addition to local modules in oneshot mode, it has a substantial memory footprint. @@ -210,7 +211,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op. Otherwise, the stub objects from the interface are compiled to objects in 'generateByteCode' and added to the 'HomeModLinkable' as well. -Case 3 is not implemented yet (!13042). +In case 3, Core bindings are loaded from the EPS, where stubs only exist in +their serialized form in the interface, so they must be regenerated like in case +2. Problem 3: ===================================== docs/users_guide/phases.rst ===================================== @@ -826,6 +826,14 @@ Options affecting code generation will generate byte-code rather than object code. +.. ghc-flag:: -fpkgdb-byte-code + :shortdesc: Use byte-code from package DB dependencies + :type: dynamic + :category: codegen + + Blah. + + .. _options-linker: Options affecting linking ===================================== testsuite/tests/bytecode/T25090/Dep.hs ===================================== @@ -0,0 +1,15 @@ +module Dep where + +data A = A Int + +used :: Int +used = 9681 + +dep :: A +dep = A used + +unused1 :: A +unused1 = A 1 + +unused2 :: A +unused2 = unused1 ===================================== testsuite/tests/bytecode/T25090/DepApi.hs ===================================== @@ -0,0 +1,7 @@ +module DepApi (A (A), dep) where + +import Dep (A (A)) +import qualified Dep + +dep :: A +dep = Dep.dep ===================================== testsuite/tests/bytecode/T25090/Local.hs ===================================== @@ -0,0 +1,15 @@ +{-# language PackageImports #-} + +module Local where + +import GHC.Prim +import Language.Haskell.TH (ExpQ) +import Language.Haskell.TH.Syntax (lift) +-- just to be sure that the file isn't accidentally picked up locally +import "dep" DepApi (dep, A (A)) +import {-# source #-} Num (num) + +splc :: ExpQ +splc = lift @_ @Int (num + d) + where + A d = dep ===================================== testsuite/tests/bytecode/T25090/Makefile ===================================== @@ -19,3 +19,35 @@ T25090a: T25090b: $(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0 ./exe + +DB := -package-db db -package dep +BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0 +BC := -fprefer-byte-code -fbyte-code-and-object-code +ARGS := $(BASIC) $(BC) + +T25090_pkg: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_empty: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_nolib: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none" + ./run.bash "$(TEST_HC)" "$(ARGS)" + +T25090_pkg_obj_code: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code" + +T25090_pkg_multi_unit: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + mkdir -p unit2-src/ + mv Local.hs Num.hs Num.hs-boot unit2-src/ + "$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -dynamic -unit @unit1 -unit @unit2 + ./PkgBytecode + +T25090_pkg_archive: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive" + ./run.bash "$(TEST_HC)" "$(ARGS)" ===================================== testsuite/tests/bytecode/T25090/Num.hs ===================================== @@ -0,0 +1,4 @@ +module Num where + +num :: Int +num = 48332 ===================================== testsuite/tests/bytecode/T25090/Num.hs-boot ===================================== @@ -0,0 +1,3 @@ +module Num where + +num :: Int ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.hs ===================================== @@ -0,0 +1,12 @@ +{-# language TemplateHaskell #-} + +module Main where + +import GHC.Prim +import Local (splc) + +a :: Int +a = $(splc) + +main :: IO () +main = putStrLn (show a) ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.stdout ===================================== @@ -0,0 +1 @@ +58013 ===================================== testsuite/tests/bytecode/T25090/all.T ===================================== @@ -16,3 +16,33 @@ def test_T25090(name): test_T25090('T25090a') test_T25090('T25090b') + +def test_pkg(name, files = []): + test( + name, + [ + extra_files([ + 'PkgBytecode.hs', + 'Local.hs', + 'Dep.hs', + 'DepApi.hs', + 'Num.hs', + 'Num.hs-boot', + 'dep.conf', + 'prep.bash', + 'run.bash', + ] + files), + use_specs({'stdout': 'PkgBytecode.stdout'}), + ], + makefile_test, + [], + ) + +test_pkg('T25090_pkg') +test_pkg('T25090_pkg_empty') +test_pkg('T25090_pkg_nolib') +test_pkg('T25090_pkg_obj_code') +test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2']) +# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a +# comment says "search for .so libraries _first_" (rather than "only"). +# test_pkg('T25090_pkg_archive') ===================================== testsuite/tests/bytecode/T25090/dep.conf ===================================== @@ -0,0 +1,8 @@ +name: dep +version: 1.0 +id: dep-1.0 +key: dep-1.0 +exposed: True +exposed-modules: DepApi +import-dirs: ${pkgroot}/dep +library-dirs: ${pkgroot}/dep ===================================== testsuite/tests/bytecode/T25090/prep.bash ===================================== @@ -0,0 +1,57 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" +ghc_pkg_cmd="$3" +library="$4" + +base="$PWD" +db="$base/db" +dep="$base/dep" +conf_dep="${dep}/dep.conf" + +mkdir -p "$dep" "$db" +mv Dep.hs DepApi.hs "$dep/" +cp dep.conf "$dep/" + +ghc_pkg() +{ + eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@" +} + +ghc() +{ + eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@" +} + +version=$(ghc "--numeric-version") + +ghc_pkg recache + +ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs" + +if [[ "$library" == 'shared' ]] +then + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'shared-empty' ]] +then + echo 'module Dummy where' > Dummy.hs + ghc "-dynamic-too -c Dummy.hs" + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'archive' ]] +then + $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'none' ]] +then + : +else + echo "Invalid argument for 'library': $library" + exit 1 +fi + +ghc_pkg -v0 register "${conf_dep at Q}" ===================================== testsuite/tests/bytecode/T25090/run.bash ===================================== @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" + +ghc() +{ + eval "${ghc_cmd at Q} $ghc_opts $@" +} + +ghc -c Num.hs-boot Num.hs Local.hs +ghc -fpkgdb-byte-code -c PkgBytecode.hs +ghc PkgBytecode.o -o PkgBytecode +./PkgBytecode ===================================== testsuite/tests/bytecode/T25090/unit1 ===================================== @@ -0,0 +1 @@ +-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2 ===================================== testsuite/tests/bytecode/T25090/unit2 ===================================== @@ -0,0 +1 @@ +-i -i./unit2-src Local Num -this-unit-id unit2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28cb357474b6b12ce56f16649765c05fef56ca73 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28cb357474b6b12ce56f16649765c05fef56ca73 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 01:18:02 2024 From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal)) Date: Mon, 30 Sep 2024 21:18:02 -0400 Subject: [Git][ghc/ghc][wip/T25243] Only allow (a => b) :: Constraint rather than CONSTRAINT rep Message-ID: <66fb4dca1bc64_103d46a57d0010636@gitlab.mail> Krzysztof Gogolewski pushed to branch wip/T25243 at Glasgow Haskell Compiler / GHC Commits: 8b436a00 by Krzysztof Gogolewski at 2024-10-01T03:17:51+02:00 Only allow (a => b) :: Constraint rather than CONSTRAINT rep Fixes #25243 - - - - - 4 changed files: - compiler/GHC/Tc/Gen/HsType.hs - + testsuite/tests/quantified-constraints/T25243.hs - + testsuite/tests/quantified-constraints/T25243.stderr - testsuite/tests/quantified-constraints/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1158,10 +1158,13 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind | null (unLoc ctxt) = tcLHsType mode rn_ty exp_kind -- See Note [Body kind of a HsQualTy] - | Check kind <- exp_kind, isConstraintLikeKind kind + | Check kind <- exp_kind -- Checking mode + , isConstraintLikeKind kind -- CONSTRAINT rep = do { ctxt' <- tc_hs_context mode ctxt ; ty' <- tc_check_lhs_type mode rn_ty constraintKind - ; return (tcMkDFunPhiTy ctxt' ty') } + ; let res_ty = tcMkDFunPhiTy ctxt' ty' + ; checkExpKind (unLoc rn_ty) res_ty + constraintKind exp_kind } | otherwise = do { ctxt' <- tc_hs_context mode ctxt @@ -2110,7 +2113,7 @@ However, consider instance Eq a => Eq [a] where ... or f :: (Eq a => Eq [a]) => blah -Here both body-kind of the HsQualTy is Constraint rather than *. +Here both body-kind and result kind of the HsQualTy is Constraint rather than *. Rather crudely we tell the difference by looking at exp_kind. It's very convenient to typecheck instance types like any other HsSigType. @@ -2121,11 +2124,21 @@ should be '*' we risk getting TWO error messages, one saying that Eq the left of the outer (=>). How do we figure out the right body kind? Well, it's a bit of a -kludge: I just look at the expected kind. If it's Constraint, we -must be in this instance situation context. It's a kludge because it -wouldn't work if any unification was involved to compute that result -kind -- but it isn't. (The true way might be to use the 'mode' -parameter, but that seemed like a sledgehammer to crack a nut.) +kludge: I just look at the expected kind. If we are in checking mode +(`exp_kind` = `Check k`), and the pushed-in kind `k` is `Constraint`, then +we check that the body type has kind `Constraint` too. +This is a kludge because it wouldn't work if any unification was +involved to compute that result kind -- but it isn't. +Actually, we only check whether `k` is a `CONSTRAINT rep`, but in that +case enforce that `rep` is a LiftedRep. This gives a better error message +in T25243. +At the moment, we don't really have support for constraints that are not +lifted: it's not possible to declare a class returning a different type +than CONSTRAINT LiftedRep, evidence is always lifted, the fat arrow c => t +requires c to be a lifted constraint. In a far future, if we add support +for non-lifted constraints, we could extend it to implication constraints +and allow c => c' where c :: CONSTRAINT rep1, c' :: CONSTRAINT rep2 +have arbitrary representations. Note [Inferring tuple kinds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== testsuite/tests/quantified-constraints/T25243.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-} +module T25243 where + +import GHC.Exts +import Data.Kind + +type T :: Constraint -> Constraint -> CONSTRAINT IntRep +type T a b = a => b ===================================== testsuite/tests/quantified-constraints/T25243.stderr ===================================== @@ -0,0 +1,5 @@ +T25243.hs:8:14: error: [GHC-83865] + • Expected an IntRep constraint, but ‘b’ is a lifted constraint + • In the type ‘a => b’ + In the type declaration for ‘T’ + ===================================== testsuite/tests/quantified-constraints/all.T ===================================== @@ -45,3 +45,4 @@ test('T23143', normal, compile, ['']) test('T23333', normal, compile, ['']) test('T23323', normal, compile, ['']) test('T22238', normal, compile, ['']) +test('T25243', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b436a004bc2bbc90579b2c879d419a3e0b27ad2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b436a004bc2bbc90579b2c879d419a3e0b27ad2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 05:14:18 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 01 Oct 2024 01:14:18 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fb852a78e19_103d46123386c196d8@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 42385ea0 by Andreas Klebinger at 2024-10-01T01:14:07-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - a712c622 by Andreas Klebinger at 2024-10-01T01:14:08-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 1bb257ae by Sylvain Henry at 2024-10-01T01:14:12-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 9 changed files: - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - rts/posix/ticker/TimerFd.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bdc963078be47ba1807ce9d135f76918b82a362...1bb257ae0b9d888c00d21bdc4e34480531f7d83a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bdc963078be47ba1807ce9d135f76918b82a362...1bb257ae0b9d888c00d21bdc4e34480531f7d83a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 08:38:15 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 01 Oct 2024 04:38:15 -0400 Subject: [Git][ghc/ghc][wip/T25281] Unused imports Message-ID: <66fbb4f789676_1649cf558d90696f8@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: ec99f417 by Simon Peyton Jones at 2024-10-01T09:37:56+01:00 Unused imports - - - - - 1 changed file: - compiler/GHC/HsToCore/Expr.hs Changes: ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -57,7 +57,6 @@ import GHC.Driver.Session import GHC.Types.SourceText import GHC.Types.Name hiding (varName) -import GHC.Types.Name.Reader( lookupGRE_FieldLabel ) import GHC.Types.CostCentre import GHC.Types.Id import GHC.Types.Id.Info @@ -77,7 +76,6 @@ import GHC.Utils.Misc import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import Control.Monad -import Data.Maybe( isJust ) import qualified Data.Set as S {- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ec99f417829f3bba5f84ffb59873df3efc8bfe51 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ec99f417829f3bba5f84ffb59873df3efc8bfe51 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 09:48:03 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 05:48:03 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] 2 commits: rename stuff Message-ID: <66fbc553940e6_24578b1845e8791fb@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 6353a174 by Hassan Al-Awwadi at 2024-09-30T16:26:59+02:00 rename stuff - - - - - ec2c3223 by Hassan Al-Awwadi at 2024-10-01T11:47:38+02:00 cleaned remnant AmbiguousFieldOcc -> UpdFieldOcc - - - - - 2 changed files: - compiler/GHC/Tc/Gen/Head.hs - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -597,19 +597,19 @@ addHeadCtxt fun_ctxt thing_inside tcInferRecSelId :: FieldOcc GhcRn -> TcM ( (HsExpr GhcTc, TcSigmaType)) -tcInferRecSelId (FieldOcc sel_name (L l n)) +tcInferRecSelId (FieldOcc lbl (L l sel_name)) = do { sel_id <- tc_rec_sel_id - ; let expr = XExpr (HsRecSelTc (FieldOcc sel_name (L l sel_id))) + ; let expr = XExpr (HsRecSelTc (FieldOcc lbl (L l sel_id))) ; return $ (expr, idType sel_id) } where occ :: OccName - occ = nameOccName n + occ = nameOccName sel_name tc_rec_sel_id :: TcM TcId -- Like tc_infer_id, but returns an Id not a HsExpr, -- so we can wrap it back up into a HsRecSel tc_rec_sel_id - = do { thing <- tcLookup n + = do { thing <- tcLookup sel_name ; case thing of ATcId { tct_id = id } -> do { check_naughty occ id -- See Note [Local record selectors] ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -53,6 +53,7 @@ import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Types (UpdFieldOcc(..), FieldOcc(..)) import Control.Monad (forM, when, unless) import Control.Monad.Identity (Identity(..)) @@ -4591,11 +4592,10 @@ instance ExactPrint (FieldOcc GhcPs) where -- --------------------------------------------------------------------- -instance ExactPrint (AmbiguousFieldOcc GhcPs) where +instance ExactPrint (UpdFieldOcc GhcPs) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a - exact f@(Unambiguous _ n) = markAnnotated n >> return f - exact f@(Ambiguous _ n) = markAnnotated n >> return f + exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f -- --------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/484fba49b0698a1b7c8de90d98a786d5f55b7814...ec2c3223e7261ba39462cce8bc883d041eff031a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/484fba49b0698a1b7c8de90d98a786d5f55b7814...ec2c3223e7261ba39462cce8bc883d041eff031a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 09:54:52 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 01 Oct 2024 05:54:52 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fbc6ec4a887_24578b1845e88108f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 9db94449 by Andreas Klebinger at 2024-10-01T05:54:39-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - d941d01a by Andreas Klebinger at 2024-10-01T05:54:39-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 446844a0 by Sylvain Henry at 2024-10-01T05:54:42-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - a9c80f03 by Rodrigo Mesquita at 2024-10-01T05:54:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - b7ddcae7 by Matthew Pickering at 2024-10-01T05:54:44-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 13 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - rts/posix/ticker/TimerFd.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1bb257ae0b9d888c00d21bdc4e34480531f7d83a...b7ddcae7304e9bbdedf4aee2ea315dc24f9024e8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1bb257ae0b9d888c00d21bdc4e34480531f7d83a...b7ddcae7304e9bbdedf4aee2ea315dc24f9024e8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 10:54:29 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Tue, 01 Oct 2024 06:54:29 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] Link interface bytecode from package DBs if possible Message-ID: <66fbd4e535141_93bcdc3e4c56293@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC Commits: 216f4773 by Torsten Schmits at 2024-10-01T12:54:11+02:00 Link interface bytecode from package DBs if possible Part of #25090. MR !????? When splices are executed with `-fprefer-byte-code`, the loader will compile Core bindings to bytecode if those are present in interfaces of module dependencies. So far, this only applied to local modules (i.e. home modules in make mode and non-package deps in oneshot mode). This patch extends support to interfaces loaded from a package DB. In `getLinkDeps`, the dependencies chosen for recursion were restricted to `dep_direct_mods`, which has been changed to include `mi_usages`. In order to unify treatment of the different link variants across make/oneshot mode, the algorithm's intermediate results have been abstracted into the data types `LinkDep` and `LinkModule`. At the moment, following package deps is only implemented for oneshot mode. - - - - - 22 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Module/WholeCoreBindings.hs - docs/users_guide/phases.rst - + testsuite/tests/bytecode/T25090/Dep.hs - + testsuite/tests/bytecode/T25090/DepApi.hs - + testsuite/tests/bytecode/T25090/Local.hs - testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25090/Num.hs - + testsuite/tests/bytecode/T25090/Num.hs-boot - + testsuite/tests/bytecode/T25090/PkgBytecode.hs - + testsuite/tests/bytecode/T25090/PkgBytecode.stdout - testsuite/tests/bytecode/T25090/all.T - + testsuite/tests/bytecode/T25090/dep.conf - + testsuite/tests/bytecode/T25090/prep.bash - + testsuite/tests/bytecode/T25090/run.bash - + testsuite/tests/bytecode/T25090/unit1 - + testsuite/tests/bytecode/T25090/unit2 Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -843,6 +843,7 @@ data GeneralFlag | Opt_BuildDynamicToo | Opt_WriteIfSimplifiedCore | Opt_UseBytecodeRatherThanObjects + | Opt_PackageDbBytecode -- safe haskell flags | Opt_DistrustAllPackages ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2540,6 +2540,7 @@ fFlagsDeps = [ flagSpec "link-rts" Opt_LinkRts, flagSpec "byte-code-and-object-code" Opt_ByteCodeAndObjectCode, flagSpec "prefer-byte-code" Opt_UseBytecodeRatherThanObjects, + flagSpec "pkgdb-byte-code" Opt_PackageDbBytecode, flagSpec' "compact-unwind" Opt_CompactUnwind (\turn_on -> updM (\dflags -> do unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -672,7 +672,9 @@ dontLeakTheHUG thing_inside = do in hsc_env { hsc_targets = panic "cleanTopEnv: hsc_targets" , hsc_mod_graph = panic "cleanTopEnv: hsc_mod_graph" - , hsc_IC = panic "cleanTopEnv: hsc_IC" + -- TODO this is needed for bytecode compilation of package deps + -- only. local EPS modules work fine. + -- , hsc_IC = panic "cleanTopEnv: hsc_IC" , hsc_type_env_vars = case maybe_type_vars of Just vars -> vars Nothing -> panic "cleanTopEnv: hsc_type_env_vars" ===================================== compiler/GHC/Linker/Deps.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module GHC.Linker.Deps ( LinkDepsOpts (..) @@ -28,6 +29,7 @@ import GHC.Types.Unique.DSet import GHC.Types.Unique.DFM import GHC.Utils.Outputable +import qualified GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Error @@ -47,9 +49,11 @@ import GHC.Utils.Misc import GHC.Unit.Home import GHC.Data.Maybe -import Control.Monad import Control.Applicative +import Control.Monad.IO.Class (MonadIO (liftIO)) +import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE) +import Data.Foldable (traverse_) import qualified Data.Set as Set import qualified Data.Map as M import Data.List (isSuffixOf) @@ -64,19 +68,21 @@ data LinkDepsOpts = LinkDepsOpts , ldUnitEnv :: !UnitEnv , ldPprOpts :: !SDocContext -- ^ Rendering options for error messages , ldUseByteCode :: !Bool -- ^ Use bytecode rather than objects + , ldPkgByteCode :: !Bool -- ^ Use bytecode for external packages , ldMsgOpts :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics , ldWays :: !Ways -- ^ Enabled ways , ldFinderCache :: !FinderCache , ldFinderOpts :: !FinderOpts - , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)) - , ldLoadByteCode :: !(Module -> IO (Maybe Linkable)) + , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation))) + , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable))) + , ldDebugTrace :: !(SDoc -> IO ()) } data LinkDeps = LinkDeps { ldNeededLinkables :: [Linkable] , ldAllLinkables :: [Linkable] - , ldUnits :: [UnitId] - , ldNeededUnits :: UniqDSet UnitId + , ldNeededUnits :: [UnitId] + , ldAllUnits :: UniqDSet UnitId } -- | Find all the packages and linkables that a set of modules depends on @@ -102,7 +108,14 @@ getLinkDeps opts interp pls span mods = do get_link_deps opts pls maybe_normal_osuf span mods - +-- | Compute the linkables for the given module set's dependencies. +-- +-- Home modules in make mode are treated separately in a preprocessing step, +-- then all the remaining external deps are processed for both modes. +-- If bytecode is available, transitive external deps are included, otherwise +-- the module's library is linked and processing stops. +-- +-- The results are split into sets of needed/loaded modules/packages. get_link_deps :: LinkDepsOpts -> LoaderState @@ -111,46 +124,40 @@ get_link_deps -> [Module] -> IO LinkDeps get_link_deps opts pls maybe_normal_osuf span mods = do - -- 1. Find the dependent home-pkg-modules/packages from each iface - -- (omitting modules from the interactive package, which is already linked) - (mods_s, pkgs_s) <- - -- Why two code paths here? There is a significant amount of repeated work - -- performed calculating transitive dependencies - -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests) - if ldOneShotMode opts - then follow_deps (filterOut isInteractiveModule mods) - emptyUniqDSet emptyUniqDSet; - else do - (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods - return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs)) - - let - -- 2. Exclude ones already linked - -- Main reason: avoid findModule calls in get_linkable - (mods_needed, links_got) = partitionWith split_mods mods_s - pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls - - split_mods mod = - let is_linked = lookupModuleEnv (objs_loaded pls) mod - <|> lookupModuleEnv (bcos_loaded pls) mod - in case is_linked of - Just linkable -> Right linkable - Nothing -> Left mod - - -- 3. For each dependent module, find its linkable - -- This will either be in the HPT or (in the case of one-shot - -- compilation) we may need to use maybe_getFileLinkable - lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed - - return $ LinkDeps - { ldNeededLinkables = lnks_needed - , ldAllLinkables = links_got ++ lnks_needed - , ldUnits = pkgs_needed - , ldNeededUnits = pkgs_s - } + (link_deps_home, module_deps_external) <- separate_home_deps + link_deps_external <- external_deps opts module_deps_external + let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) = + classify_deps pls (link_deps_home ++ link_deps_external) + ldNeededLinkables <- mapM module_linkable needed_modules + pure LinkDeps { + ldNeededLinkables, + ldAllLinkables = loaded_modules ++ ldNeededLinkables, + ldNeededUnits, + ldAllUnits + } where mod_graph = ldModuleGraph opts unit_env = ldUnitEnv opts + noninteractive = filterOut isInteractiveModule mods + + -- Preprocess the dependencies in make mode to remove all home modules, + -- since the transitive dependency closure is already cached for those in + -- the HUG (see MultiLayerModulesTH_* tests for the performance impact). + -- + -- Returns the remaining, external, dependencies on the right, which is the + -- entire set for oneshot mode. + separate_home_deps = + if ldOneShotMode opts + then pure ([], noninteractive) + else make_deps + + make_deps = do + (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods + let + link_mods = + listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods] + ext = uniqDSetToList (unionManyUniqDSets (init_ext : dep_ext)) + pure ([LinkModules (LinkHomeModule <$> link_mods)], ext) -- This code is used in `--make` mode to calculate the home package and unit dependencies -- for a set of modules. @@ -160,9 +167,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- It is also a matter of correctness to use the module graph so that dependencies between home units -- is resolved correctly. - make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey) + make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey) make_deps_loop found [] = found - make_deps_loop found@(found_units, found_mods) (nk:nexts) + make_deps_loop found@(external, found_mods) (nk:nexts) | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts | otherwise = case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of @@ -171,85 +178,26 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- See #936 and the ghci.prog007 test for why we have to continue traversing through -- boot modules. todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps] - in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) + in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) Nothing -> - let (ModNodeKeyWithUid _ uid) = nk - in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts + let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk + in make_deps_loop (addOneToUniqDSet external (Module (RealUnit (Definite uid)) mod_name), found_mods) nexts mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m) - (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods) + (init_ext, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk noninteractive all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps] get_mod_info (ModNodeKeyWithUid gwib uid) = case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of - Just hmi -> - let iface = (hm_iface hmi) - mmod = case mi_hsc_src iface of - HsBootFile -> link_boot_mod_error (mi_module iface) - _ -> return $ Just (mi_module iface) - - in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$> mmod + Just hmi -> do + let iface = hm_iface hmi + case mi_hsc_src iface of + HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface) + _ -> pure (mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi) Nothing -> throwProgramError opts $ text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid - - -- This code is used in one-shot mode to traverse downwards through the HPT - -- to find all link dependencies. - -- The ModIface contains the transitive closure of the module dependencies - -- within the current package, *except* for boot modules: if we encounter - -- a boot module, we have to find its real interface and discover the - -- dependencies of that. Hence we need to traverse the dependency - -- tree recursively. See bug #936, testcase ghci/prog007. - follow_deps :: [Module] -- modules to follow - -> UniqDSet Module -- accum. module dependencies - -> UniqDSet UnitId -- accum. package dependencies - -> IO ([Module], UniqDSet UnitId) -- result - follow_deps [] acc_mods acc_pkgs - = return (uniqDSetToList acc_mods, acc_pkgs) - follow_deps (mod:mods) acc_mods acc_pkgs - = do - mb_iface <- ldLoadIface opts msg mod - iface <- case mb_iface of - Failed err -> throwProgramError opts $ - missingInterfaceErrorDiagnostic (ldMsgOpts opts) err - Succeeded iface -> return iface - - when (mi_boot iface == IsBoot) $ link_boot_mod_error mod - - let - pkg = moduleUnit mod - deps = mi_deps iface - - pkg_deps = dep_direct_pkgs deps - (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $ - \case - (_, GWIB m IsBoot) -> Left m - (_, GWIB m NotBoot) -> Right m - - mod_deps' = case ue_homeUnit unit_env of - Nothing -> [] - Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps)) - acc_mods' = case ue_homeUnit unit_env of - Nothing -> acc_mods - Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps) - acc_pkgs' = addListToUniqDSet acc_pkgs (Set.toList pkg_deps) - - case ue_homeUnit unit_env of - Just home_unit | isHomeUnit home_unit pkg -> follow_deps (mod_deps' ++ mods) - acc_mods' acc_pkgs' - _ -> follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg)) - where - msg = text "need to link module" <+> ppr mod <+> - text "due to use of Template Haskell" - - - - link_boot_mod_error :: Module -> IO a - link_boot_mod_error mod = throwProgramError opts $ - text "module" <+> ppr mod <+> - text "cannot be linked; it is only available as a boot module" - no_obj :: Outputable a => a -> IO b no_obj mod = dieWith opts span $ text "cannot find object file for module " <> @@ -258,6 +206,20 @@ get_link_deps opts pls maybe_normal_osuf span mods = do while_linking_expr = text "while linking an interpreted expression" + -- Extract the 'Linkable's for unlinked modules from the intermediate + -- results. + module_linkable = \case + LinkHomeModule hmi -> + adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi)) + + LinkObjectModule iface loc -> do + let mod = mi_module iface + findObjectLinkableMaybe mod loc >>= \case + Nothing -> no_obj mod + Just lnk -> adjust_linkable lnk + + LinkByteCodeModule _ load_bytecode -> + load_bytecode -- See Note [Using Byte Code rather than Object Code for Template Haskell] homeModLinkable :: HomeModInfo -> Maybe Linkable @@ -266,57 +228,257 @@ get_link_deps opts pls maybe_normal_osuf span mods = do then homeModInfoByteCode hmi <|> homeModInfoObject hmi else homeModInfoObject hmi <|> homeModInfoByteCode hmi - get_linkable osuf mod -- A home-package module - | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env) - = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info)) - | otherwise - = do -- It's not in the HPT because we are in one shot mode, - -- so use the Finder to get a ModLocation... - case ue_homeUnit unit_env of - Nothing -> no_obj mod - Just home_unit -> do - from_bc <- ldLoadByteCode opts mod - maybe (fallback_no_bytecode home_unit mod) pure from_bc - where - - fallback_no_bytecode home_unit mod = do - let fc = ldFinderCache opts - let fopts = ldFinderOpts opts - mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod) - case mb_stuff of - Found loc _ -> do - mb_lnk <- findObjectLinkableMaybe mod loc - case mb_lnk of - Nothing -> no_obj mod - Just lnk -> adjust_linkable lnk - _ -> no_obj (moduleName mod) - - adjust_linkable lnk - | Just new_osuf <- maybe_normal_osuf = do - new_parts <- mapM (adjust_part new_osuf) - (linkableParts lnk) - return lnk{ linkableParts=new_parts } - | otherwise = - return lnk - - adjust_part new_osuf part = case part of - DotO file ModuleObject -> do - massert (osuf `isSuffixOf` file) - let file_base = fromJust (stripExtension osuf file) - new_file = file_base <.> new_osuf - ok <- doesFileExist new_file - if (not ok) - then dieWith opts span $ - text "cannot find object file " - <> quotes (text new_file) $$ while_linking_expr - else return (DotO new_file ModuleObject) - DotO file ForeignObject -> pure (DotO file ForeignObject) - DotA fp -> panic ("adjust_ul DotA " ++ show fp) - DotDLL fp -> panic ("adjust_ul DotDLL " ++ show fp) - BCOs {} -> pure part - LazyBCOs{} -> pure part - CoreBindings WholeCoreBindings {wcb_module} -> - pprPanic "Unhydrated core bindings" (ppr wcb_module) + adjust_linkable lnk + | Just new_osuf <- maybe_normal_osuf = do + new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf) + (linkableParts lnk) + return lnk {linkableParts = new_uls} + | otherwise = + return lnk + + adjust_part osuf new_osuf part = case part of + DotO file ModuleObject -> do + massert (osuf `isSuffixOf` file) + let file_base = fromJust (stripExtension osuf file) + new_file = file_base <.> new_osuf + ok <- doesFileExist new_file + if (not ok) + then dieWith opts span $ + text "cannot find object file " + <> quotes (text new_file) $$ while_linking_expr + else return (DotO new_file ModuleObject) + DotO file ForeignObject -> pure (DotO file ForeignObject) + DotA fp -> panic ("adjust_part DotA " ++ show fp) + DotDLL fp -> panic ("adjust_part DotDLL " ++ show fp) + BCOs {} -> pure part + LazyBCOs{} -> pure part + CoreBindings WholeCoreBindings {wcb_module} -> + pprPanic "Unhydrated core bindings" (ppr wcb_module) + +data LinkModule = + LinkHomeModule !HomeModInfo + | + LinkObjectModule !ModIface !ModLocation + | + LinkByteCodeModule !ModIface !(IO Linkable) + +link_module_iface :: LinkModule -> ModIface +link_module_iface = \case + LinkHomeModule hmi -> hm_iface hmi + LinkObjectModule iface _ -> iface + LinkByteCodeModule iface _ -> iface + +instance Outputable LinkModule where + ppr = \case + LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI") + LinkObjectModule iface _ -> ppr (mi_module iface) + LinkByteCodeModule iface _ -> ppr (mi_module iface) <+> brackets (text "BC") + +data LinkDep = + LinkModules !(UniqDFM ModuleName LinkModule) + | + LinkLibrary !UnitId + +instance Outputable LinkDep where + ppr = \case + LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods) + LinkLibrary uid -> text "library:" <+> ppr uid + +data OneshotError = + NoLocation !Module + | + NoInterface !MissingInterfaceError + | + LinkBootModule !Module + +-- Compute the transitive dependency closure of the given modules. +-- +-- Used for all oneshot mode dependencies and for external dependencies of home +-- modules in make mode. +-- +-- TODO is the following still relevant? +-- The ModIface contains the transitive closure of the module dependencies +-- within the current package, *except* for boot modules: if we encounter +-- a boot module, we have to find its real interface and discover the +-- dependencies of that. Hence we need to traverse the dependency +-- tree recursively. See bug #936, testcase ghci/prog007. +external_deps :: + LinkDepsOpts -> + -- | Modules whose imports to follow + [Module] -> + IO [LinkDep] +external_deps opts mods = + runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case + Right a -> pure (eltsUDFM a) + Left err -> throwProgramError opts (message err) + where + message = \case + NoLocation mod -> + pprPanic "found iface but no location" (ppr mod) + NoInterface err -> + missingInterfaceErrorDiagnostic (ldMsgOpts opts) err + LinkBootModule mod -> + link_boot_mod_error mod + +external_deps_loop :: + LinkDepsOpts -> + [Module] -> + UniqDFM UnitId LinkDep -> + ExceptT OneshotError IO (UniqDFM UnitId LinkDep) +external_deps_loop _ [] acc = + pure acc +external_deps_loop opts (mod : mods) acc = do + (new_acc, new_mods, action) <- process_module + traverse_ debug_log action + external_deps_loop opts (new_mods ++ mods) new_acc + where + debug_log action = + liftIO $ ldDebugTrace opts $ + text "TH dep" <+> ppr mod <+> brackets (sep [ + if is_home then text "home" else Outputable.empty, + text action + ]) + + -- Decide how this module needs to be processed. + -- We only need an interface if we want to load bytecode or if we have to + -- link an object file (which happens for home unit modules, since those + -- have no libraries). + process_module + | already_seen = pure (acc, [], Nothing) + | is_home || prefer_bytecode = try_iface + | otherwise = add_library + + -- Check whether the current module was processed before. + -- Since the accumulator is keyed by unit ID, we have to perform two + -- lookups. + -- If another module from this module's unit has been determined to be + -- linked as a library previously, we skip this module, assuming that no + -- bytecode is available for the entire package. + already_seen + | Just (LinkModules mods) <- mod_dep + = elemUDFM mod_name mods + | Just (LinkLibrary _) <- mod_dep + = True + | otherwise + = False + + -- Load the iface and attempt to get bytecode from Core bindings. + try_iface = + liftIO (ldLoadIface opts load_reason mod) >>= \case + Failed err -> throwE (NoInterface err) + Succeeded (iface, loc) -> do + mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface)) + with_iface loc iface mb_load_bc + + -- Decide how to link this module. + -- If bytecode or an object file is available, use those in that order. + -- Otherwise fall back to linking a library. + with_iface loc iface mb_load_bc + | IsBoot <- mi_boot iface + = throwE (LinkBootModule mod) + + | prefer_bytecode + , Just load_bc <- mb_load_bc + = pure (add_module iface (LinkByteCodeModule iface load_bc) "bytecode") + + | is_home + = pure (add_module iface (LinkObjectModule iface loc) "object") + + | otherwise + = add_library + + add_library = + pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library") + + add_module iface lmod action = + (addListToUDFM with_mod (direct_pkgs iface), new_deps iface, Just action) + where + with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id + + add_package_module lmod = \case + Just (LinkLibrary u) -> Just (LinkLibrary u) + Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod)) + Nothing -> Just (LinkModules (unitUDFM mod_name lmod)) + + direct_pkgs iface + | prefer_bytecode + = [] + | otherwise + = [(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))] + + new_deps iface + | prefer_bytecode + -- TODO How can we better determine the external deps? + -- OTOH, we probably don't want to link unused dependencies anyway. + = [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface] ++ local + | is_home + = local + | otherwise + = [] + where + local = + [ + mkModule mod_unit m + -- TODO Somehow this just works, no idea what the deal was in the + -- old code with boot modules. + | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface)) + ] + + is_home + | Just home <- mb_home + = homeUnitAsUnit home == mod_unit + | otherwise + = False + + mod_dep = lookupUDFM acc mod_unit_id + mod_name = moduleName mod + mod_unit_id = moduleUnitId mod + mod_unit = moduleUnit mod + load_reason = + text "need to link module" <+> ppr mod <+> + text "due to use of Template Haskell" + + prefer_bytecode = ldUseByteCode opts && (is_home || ldPkgByteCode opts) + mb_home = ue_homeUnit (ldUnitEnv opts) + +link_boot_mod_error :: Module -> SDoc +link_boot_mod_error mod = + text "module" <+> ppr mod <+> + text "cannot be linked; it is only available as a boot module" + +-- | Split link dependencies into the sets of modules and packages that have +-- been linked previously and those that need to be linked now by checking for +-- their presence in the 'LoaderState': +-- +-- - For module dependencies, in the sets of loaded objects and BCOs +-- ('objs_loaded' and 'bcos_loaded') +-- - For package dependencies, in the set of loaded packages ('pkgs_loaded') +classify_deps :: + LoaderState -> + [LinkDep] -> + ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId]) +classify_deps pls deps = + (loaded_modules, needed_modules, all_packages, needed_packages) + where + (loaded_modules, needed_modules) = + partitionWith loaded_or_needed_module (concatMap eltsUDFM modules) + + needed_packages = + eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls) + + all_packages = mkUniqDSet packages + + (modules, packages) = flip partitionWith deps $ \case + LinkModules mods -> Left mods + LinkLibrary lib -> Right lib + + loaded_or_needed_module lm = + maybe (Right lm) Left (loaded_module (mi_module (link_module_iface lm))) + + loaded_module mod = + lookupModuleEnv (objs_loaded pls) mod + <|> + lookupModuleEnv (bcos_loaded pls) mod {- Note [Using Byte Code rather than Object Code for Template Haskell] ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -77,11 +77,13 @@ import GHC.Utils.TmpFs import GHC.Unit.Env import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode)) +import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.State as Packages import qualified GHC.Data.ShortText as ST import GHC.Data.FastString +import qualified GHC.Data.Maybe as Maybe import GHC.Linker.Deps import GHC.Linker.MacOS @@ -94,6 +96,7 @@ import Control.Monad import qualified Data.Set as Set import Data.Char (isSpace) import qualified Data.Foldable as Foldable +import Data.Functor ((<&>)) import Data.IORef import Data.List (intercalate, isPrefixOf, nub, partition) import Data.Maybe @@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - let this_pkgs_needed = ldNeededUnits deps + let this_pkgs_needed = ldAllUnits deps -- Link the packages and modules required - pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls + pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps) let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed all_pkgs_loaded = pkgs_loaded pls2 @@ -646,18 +649,39 @@ initLinkDepsOpts hsc_env = opts , ldFinderCache = hsc_FC hsc_env , ldFinderOpts = initFinderOpts dflags , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags + , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags , ldMsgOpts = initIfaceMessageOpts dflags , ldWays = ways dflags , ldLoadIface , ldLoadByteCode + , ldDebugTrace = debugTraceMsg (hsc_logger hsc_env) 3 } dflags = hsc_dflags hsc_env - ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env - $ loadInterface msg mod (ImportByUser NotBoot) + + ldLoadIface msg mod = + initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case + Maybe.Failed err -> pure (Maybe.Failed err) + Maybe.Succeeded iface -> + find_location mod <&> \case + InstalledFound loc _ -> Maybe.Succeeded (iface, loc) + err -> Maybe.Failed $ + cannotFindInterface unit_state home_unit + (targetProfile dflags) (moduleName mod) err + + find_location mod = + liftIO $ + findExactModule (hsc_FC hsc_env) (initFinderOpts dflags) + (initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env) + unit_state home_unit + (toUnitId <$> mod) + + unit_state = hsc_units hsc_env + + home_unit = ue_homeUnit (hsc_unit_env hsc_env) ldLoadByteCode mod = do EPS {eps_iface_bytecode} <- hscEPS hsc_env - sequence (lookupModuleEnv eps_iface_bytecode mod) + pure (lookupModuleEnv eps_iface_bytecode mod) ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -734,7 +734,7 @@ mkStubPaths fopts mod location = do src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location -- ----------------------------------------------------------------------------- --- findLinkable isn't related to the other stuff in here, +-- findObjectLinkable isn't related to the other stuff in here, -- but there's no other obvious place for it findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) ===================================== compiler/GHC/Unit/Module/WholeCoreBindings.hs ===================================== @@ -88,9 +88,10 @@ settings. 2. In oneshot mode, which compiles individual modules without a shared home unit graph, a previously compiled module is not reprocessed as described for make mode above. - When 'get_link_deps' encounters a dependency on a local module, it requests - its bytecode from the External Package State, who loads the interface - on-demand. + 'get_link_deps' requests the bytecode of dependencies from the External + Package State, who loads the interface on-demand. + This works for modules in local directories (via @-i@ and @-hidir@) as well + as those exposed from a package DB. Since the EPS stores interfaces for all package dependencies in addition to local modules in oneshot mode, it has a substantial memory footprint. @@ -210,7 +211,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op. Otherwise, the stub objects from the interface are compiled to objects in 'generateByteCode' and added to the 'HomeModLinkable' as well. -Case 3 is not implemented yet (!13042). +In case 3, Core bindings are loaded from the EPS, where stubs only exist in +their serialized form in the interface, so they must be regenerated like in case +2. Problem 3: ===================================== docs/users_guide/phases.rst ===================================== @@ -826,6 +826,14 @@ Options affecting code generation will generate byte-code rather than object code. +.. ghc-flag:: -fpkgdb-byte-code + :shortdesc: Use byte-code from package DB dependencies + :type: dynamic + :category: codegen + + Blah. + + .. _options-linker: Options affecting linking ===================================== testsuite/tests/bytecode/T25090/Dep.hs ===================================== @@ -0,0 +1,15 @@ +module Dep where + +data A = A Int + +used :: Int +used = 9681 + +dep :: A +dep = A used + +unused1 :: A +unused1 = A 1 + +unused2 :: A +unused2 = unused1 ===================================== testsuite/tests/bytecode/T25090/DepApi.hs ===================================== @@ -0,0 +1,7 @@ +module DepApi (A (A), dep) where + +import Dep (A (A)) +import qualified Dep + +dep :: A +dep = Dep.dep ===================================== testsuite/tests/bytecode/T25090/Local.hs ===================================== @@ -0,0 +1,15 @@ +{-# language PackageImports #-} + +module Local where + +import GHC.Prim +import Language.Haskell.TH (ExpQ) +import Language.Haskell.TH.Syntax (lift) +-- just to be sure that the file isn't accidentally picked up locally +import "dep" DepApi (dep, A (A)) +import {-# source #-} Num (num) + +splc :: ExpQ +splc = lift @_ @Int (num + d) + where + A d = dep ===================================== testsuite/tests/bytecode/T25090/Makefile ===================================== @@ -19,3 +19,35 @@ T25090a: T25090b: $(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0 ./exe + +DB := -package-db db -package dep +BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0 +BC := -fprefer-byte-code -fbyte-code-and-object-code +ARGS := $(BASIC) $(BC) + +T25090_pkg: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_empty: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_nolib: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none" + ./run.bash "$(TEST_HC)" "$(ARGS)" + +T25090_pkg_obj_code: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code" + +T25090_pkg_multi_unit: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + mkdir -p unit2-src/ + mv Local.hs Num.hs Num.hs-boot unit2-src/ + "$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -dynamic -unit @unit1 -unit @unit2 + ./PkgBytecode + +T25090_pkg_archive: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive" + ./run.bash "$(TEST_HC)" "$(ARGS)" ===================================== testsuite/tests/bytecode/T25090/Num.hs ===================================== @@ -0,0 +1,4 @@ +module Num where + +num :: Int +num = 48332 ===================================== testsuite/tests/bytecode/T25090/Num.hs-boot ===================================== @@ -0,0 +1,3 @@ +module Num where + +num :: Int ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.hs ===================================== @@ -0,0 +1,12 @@ +{-# language TemplateHaskell #-} + +module Main where + +import GHC.Prim +import Local (splc) + +a :: Int +a = $(splc) + +main :: IO () +main = putStrLn (show a) ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.stdout ===================================== @@ -0,0 +1 @@ +58013 ===================================== testsuite/tests/bytecode/T25090/all.T ===================================== @@ -16,3 +16,33 @@ def test_T25090(name): test_T25090('T25090a') test_T25090('T25090b') + +def test_pkg(name, files = []): + test( + name, + [ + extra_files([ + 'PkgBytecode.hs', + 'Local.hs', + 'Dep.hs', + 'DepApi.hs', + 'Num.hs', + 'Num.hs-boot', + 'dep.conf', + 'prep.bash', + 'run.bash', + ] + files), + use_specs({'stdout': 'PkgBytecode.stdout'}), + ], + makefile_test, + [], + ) + +test_pkg('T25090_pkg') +test_pkg('T25090_pkg_empty') +test_pkg('T25090_pkg_nolib') +test_pkg('T25090_pkg_obj_code') +test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2']) +# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a +# comment says "search for .so libraries _first_" (rather than "only"). +# test_pkg('T25090_pkg_archive') ===================================== testsuite/tests/bytecode/T25090/dep.conf ===================================== @@ -0,0 +1,8 @@ +name: dep +version: 1.0 +id: dep-1.0 +key: dep-1.0 +exposed: True +exposed-modules: DepApi +import-dirs: ${pkgroot}/dep +library-dirs: ${pkgroot}/dep ===================================== testsuite/tests/bytecode/T25090/prep.bash ===================================== @@ -0,0 +1,57 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" +ghc_pkg_cmd="$3" +library="$4" + +base="$PWD" +db="$base/db" +dep="$base/dep" +conf_dep="${dep}/dep.conf" + +mkdir -p "$dep" "$db" +mv Dep.hs DepApi.hs "$dep/" +cp dep.conf "$dep/" + +ghc_pkg() +{ + eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@" +} + +ghc() +{ + eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@" +} + +version=$(ghc "--numeric-version") + +ghc_pkg recache + +ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs" + +if [[ "$library" == 'shared' ]] +then + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'shared-empty' ]] +then + echo 'module Dummy where' > Dummy.hs + ghc "-dynamic-too -c Dummy.hs" + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'archive' ]] +then + $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'none' ]] +then + : +else + echo "Invalid argument for 'library': $library" + exit 1 +fi + +ghc_pkg -v0 register "${conf_dep at Q}" ===================================== testsuite/tests/bytecode/T25090/run.bash ===================================== @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" + +ghc() +{ + eval "${ghc_cmd at Q} $ghc_opts $@" +} + +ghc -c Num.hs-boot Num.hs Local.hs +ghc -fpkgdb-byte-code -c PkgBytecode.hs +ghc PkgBytecode.o -o PkgBytecode +./PkgBytecode ===================================== testsuite/tests/bytecode/T25090/unit1 ===================================== @@ -0,0 +1 @@ +-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2 ===================================== testsuite/tests/bytecode/T25090/unit2 ===================================== @@ -0,0 +1 @@ +-i -i./unit2-src Local Num -this-unit-id unit2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/216f4773faa8565684c9f308282b22d57bb3abd0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/216f4773faa8565684c9f308282b22d57bb3abd0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 11:20:44 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 01 Oct 2024 07:20:44 -0400 Subject: [Git][ghc/ghc][wip/T25281] 3 commits: Wibbles Message-ID: <66fbdb0cc0796_93bcd309eb860592@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 315cd26b by Simon Peyton Jones at 2024-10-01T12:11:56+01:00 Wibbles - - - - - 66a1fde8 by Simon Peyton Jones at 2024-10-01T12:17:46+01:00 Wibble - - - - - 07c56357 by Simon Peyton Jones at 2024-10-01T12:20:28+01:00 Wibble - - - - - 3 changed files: - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/TyCl/Utils.hs Changes: ===================================== compiler/GHC/HsToCore/Pmc.hs ===================================== @@ -280,11 +280,9 @@ Here is how we achieve all this in the implementation: (Remember, the same field may occur in several constructors of the data type; hence the selector may succeed on more than one constructor.) -The next three items describe mechanisms for producing warnings on record -selectors and situations in which they trigger. -They are ordered by specificity, so we prefer (2) over (3) over (4). -Item (5) below describes how we resolve the overlap. -(-XOverloadedRecordDot is discussed separately in Item (6) and (7).) +We generate warnings for incomplete record selectors in two places: +* Mainly: in GHC.HsToCore.Expr.ds_app (see (IRS2-5) below) +* Plus: in GHC.Tc.Instance.Class.matchHassField (see (IRS6-7) below) (IRS2) In function `ldi`, we have a record selector application `sel arg`. This situation is detected `GHC.HsToCore.Expr.ds_app_rec_sel`, when the @@ -305,7 +303,7 @@ Item (5) below describes how we resolve the overlap. In case of `urgh`, `T1` is indeed the case that we report as inexhaustive. However, in function `ldi`, we have *both* the result type of - `arg::T a` (boring, but see (3)) as well as Note [Long-distance information] + `arg::T a` (boring, but see (IRS3)) as well as Note [Long-distance information] about `arg` from the ambient match, and the latter lists the constraint `arg /~ T1`. Consequently, since `arg` is neither `T1` nor `T2` in the reduced problem, the match is exhaustive and the use of the record selector @@ -313,70 +311,52 @@ Item (5) below describes how we resolve the overlap. (IRS3) In function `resTy`, the record selector is unsaturated, but the result type ensures a safe use of the selector. + This situation is also detected in `GHC.HsToCore.Expr.ds_app_rec_sel`. THe selector is elaborated with its type arguments; we simply match on desugared Core `sel @Bool :: T Bool -> Int` to learn the result type `T Bool`. We again call `pmcRecSel`, but this time with a fresh dummy Id `ds::T Bool`. (IRS4) In case of an unsaturated record selector that is *not* applied to any type - argument after elaboration (e.g. in `urgh2 = sel2 :: Dot -> Int`), we simply - produce a warning about all `sel_cons`; no need to call `pmcRecSel`. - This happens in the `HsRecSel` case of `dsExpr`. - - XXXX: this isn't right, is it? We might have - data T a where - T1 :: { sel1 :: Char } -> T Int - T2 :: T a - f :: T a -> T Int -> Char - f T1 = \_ -> 'x' - f T2 = sel1 - -We resolve the overlap between situations (2)-(4) by preferring (2) over (3) -over (4) as follows: - -Finally, there are 2 more items addressing -XOverloadedRecordDot: - - 6. -XOverloadedRecordDot such as in function `ldiDot` desugars as follows: - getField @GHC.Types.Symbol - @"sel2" - @Dot - @Int - ($dHasField :: HasField "sel2" Dot Int) - d - where + argument after elaboration (e.g. in `urgh2 = sel2 :: Dot -> Int`), we simply + produce a warning about all `sel_cons`; no need to call `pmcRecSel`. + This happens in `ds_app_rec_sel` + +Finally, there are two more items addressing -XOverloadedRecordDot: + +(IRS5) With -XOverloadedDot, all occurrences of (r.x), such as in `ldiDot` and + `accessDot` above, are warned about as follows. `r.x` is parsed as + `HsGetField` in `HsExpr`; which is then expanded (in `rnExpr`) to a call to + `getField`. For example, consider: + ldiDot No = 0 + ldiDot x = x.sel2 -- should not warn + The `d.sel2` in the RHS generates + getField @GHC.Types.Symbol @"sel2" @Dot @Int + ($dHasField :: HasField "sel2" Dot Int) x + where $dHasField = sel2 |> (co :: Dot -> Int ~R# HasField "sel2" Dot Int) - We want to catch these applications in the saturated (2) case. - (The unsaturated case is handled implicitly by (7).) - For example, we do not want to generate a warning for function `ldiDot`! - - Function `GHC.HsToCore.Expr.ds_app_var` spots the `getField` application, - and then treats the above expression similar to a vanilla (RecSel app sel2 d). - This is a bit nasty (it has to do instance lookup) since we cannot look at - the unfolding of `$dHasField`. Tested in T24891. - - 7. For `accessDot` above, `ds_app_var` will fail to find a record selector, - because type `t` is not obviously a record type. - - That's good, because it means we won't emit a warning for `accessDot`. - - But we really should emit a warning for `solveDot`! There, the - compiler solves a `HasField` constraint and without an immediate - `getField`, roughly `solveDot = accessDot @Dot $d`. It must be the job - of the solver to warn about incompleteness here, in - `GHC.Tc.Instance.Class.matchHasField`. - - What makes this complicated is that we do not *also* want to warn in the - example `dot d = d.sel2` above, which is covered by more precise case (6)! - We suppress the warning in this case as follows: - 1. The type-checker (`GHC.Tc.Gen.tcApp`) produces `getField @.. $d e` - (Remember that (6) will detect `getField @.. $d e` as well.) - 2. Through `tcl_suppress_incomplete_rec_sel`, we suppress warnings when - solving `$d`. - 3. ... but not when checking `e`, because `e` might itself be a field - access that would need to be checked individually. - 4. What complicates matters is that the solver runs *after* type-checking, - so we must persist `tcl_suppress_incomplete_rec_sel` in the `CtLocEnv`. - What a hassle. This is all tested in T24891. + We spot this `getField` application in `GHC.HsToCore.Expr.ds_app_var`, + and treat it exactly like (IRS2) and (IRS3). + + Note carefully that doing this in the desugarer allows us to account for the + long-distance info about `x`; even though `sel2` is partial, we don't want + to warn about `x.sel2` in this example. + +(IRS6) Finally we have + solveDot :: Dot -> Int + solveDot = accessDot + No field-accesses or selectors in sight! From the RHS we get the constraint + [W] HasField @"sel2" @Dot @Int` + The only time we can generate a warning is when we solve this constraint, + in `GHC.Tc.Instance.Class.matchHasField`, generating a call to the (partial) + selector. We have no hope of exploiting long-distance info here. + +(IRS7) BUT, look back at `ldiDot`. Doesn't `matchHasField` /also/ generate a + warning for the `HasField` constraint arising from `x.sel2`? We don't + want that, because the desugarer will catch it: see (IRS5). So we suppress + the (IRS6) warning in the typechecker for a `HasField` constraint that + arises from a record-dot HsGetField occurrence. Happily, this is easy to do + by looking at its `CtOrigin`. Tested in T24891. -} pmcRecSel :: Id -- ^ Id of the selector ===================================== compiler/GHC/Tc/Instance/Class.hs ===================================== @@ -151,7 +151,7 @@ matchGlobalInst dflags short_cut clas tys mb_loc | cls_name == typeableClassName = matchTypeable clas tys | cls_name == withDictClassName = matchWithDict tys | cls_name == dataToTagClassName = matchDataToTag clas tys - | cls_name == hasFieldClassName = matchHasField dflags short_cut clas tys mb_loc + | cls_name == hasFieldClassName = matchHasField dflags clas tys mb_loc | cls_name == unsatisfiableClassName = return NoInstance -- See (B) in Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors | otherwise = matchInstEnv dflags short_cut clas tys where @@ -1247,9 +1247,10 @@ addUsedGRE extends tcg_used_gres with imported GREs only. -} -- See Note [HasField instances] -matchHasField :: DynFlags -> Bool -> Class -> [Type] -> Maybe CtLoc +matchHasField :: DynFlags -> Class -> [Type] + -> Maybe CtLoc -- Nothing used only during type validity checking -> TcM ClsInstResult -matchHasField dflags short_cut clas tys mb_ct_loc +matchHasField dflags clas tys mb_ct_loc = do { fam_inst_envs <- tcGetFamInstEnvs ; rdr_env <- getGlobalRdrEnv ; case lookupHasFieldLabel fam_inst_envs rdr_env tys of @@ -1262,7 +1263,8 @@ matchHasField dflags short_cut clas tys mb_ct_loc -- the HasField x r a dictionary. The preds will -- typically be empty, but if the datatype has a -- "stupid theta" then we have to include it here. - ; let theta = mkPrimEqPred sel_ty (mkVisFunTyMany r_ty a_ty) : preds + ; let tvs = mkTyVarTys (map snd tv_prs) + theta = mkPrimEqPred sel_ty (mkVisFunTyMany r_ty a_ty) : preds -- Use the equality proof to cast the selector Id to -- type (r -> a), then use the newtype coercion to cast @@ -1273,35 +1275,41 @@ matchHasField dflags short_cut clas tys mb_ct_loc `mkTransCo` mkSymCo co2 mk_ev [] = panic "matchHasField.mk_ev" - Just (_, co2) = tcInstNewTyCon_maybe (classTyCon clas) - tys - - tvs = mkTyVarTys (map snd tv_prs) + Just (_, co2) = tcInstNewTyCon_maybe (classTyCon clas) tys -- The selector must not be "naughty" (i.e. the field - -- cannot have an existentially quantified type), and - -- it must not be higher-rank. - ; if not (isNaughtyRecordSelector sel_id) && isTauTy sel_ty - then do { -- See Note [Unused name reporting and HasField] - addUsedGRE AllDeprecationWarnings gre - ; keepAlive sel_name - ; warnIncompleteRecSel dflags sel_id mb_ct_loc - ; return OneInst { cir_new_theta = theta - , cir_mk_ev = mk_ev - , cir_canonical = EvCanonical - , cir_what = BuiltinInstance } } - else matchInstEnv dflags short_cut clas tys } - - Nothing -> matchInstEnv dflags short_cut clas tys } - -warnIncompleteRecSel :: DynFlags -> Id -> Maybe CtLoc -> TcM () -warnIncompleteRecSel dflags sel_id mb_ct_loc - | Just ct_loc <- mb_ct_loc - , not (isGetFieldOrigin (ctLocOrigin ct_loc)) + -- cannot have an existentially quantified type), + -- and it must not be higher-rank. + ; if (isNaughtyRecordSelector sel_id) && isTauTy sel_ty + then return NoInstance + else + do { case mb_ct_loc of + Nothing -> return () -- Nothing: only during type-validity checking + Just loc -> setCtLocM loc $ -- Set location for warnings + do { -- See Note [Unused name reporting and HasField] + addUsedGRE AllDeprecationWarnings gre + ; keepAlive sel_name + + -- Warn about incomplete record selection + ; warnIncompleteRecSel dflags sel_id loc } + + ; return OneInst { cir_new_theta = theta + , cir_mk_ev = mk_ev + , cir_canonical = EvCanonical + , cir_what = BuiltinInstance } } } + + Nothing -> return NoInstance } + +warnIncompleteRecSel :: DynFlags -> Id -> CtLoc -> TcM () +-- Warn about incomplete record selectors +-- See (IRS6) in Note [Detecting incomplete record selectors] in GHC.HsToCore.Pmc +warnIncompleteRecSel dflags sel_id ct_loc + | not (isGetFieldOrigin (ctLocOrigin ct_loc)) + -- isGetFieldOrigin: see (IRS7) in + -- Note [Detecting incomplete record selectors] in GHC.HsToCore.Pmc , not (null fallible_cons) - = traceTc "tc-warn" (ppr sel_id $$ ppr (ctLocOrigin ct_loc)) >> - (setCtLocM ct_loc $ addDiagnostic $ - TcRnHasFieldResolvedIncomplete (idName sel_id) fallible_cons maxCons) + = addDiagnostic $ + TcRnHasFieldResolvedIncomplete (idName sel_id) fallible_cons maxCons | otherwise = return () @@ -1320,25 +1328,27 @@ lookupHasFieldLabel , GlobalRdrElt -- GRE for the selector , Type -- Type of the record value , Type ) -- Type of the field of the record --- The call (lookupHasFieldLabel fam_envs (LitTy "fld") (T t1..tn)) --- returns the `Name` of record selector Id for field "fld" in the data type T. +-- If possible, decompose application +-- (HasField @k @rrep @arep @"fld" @(T t1..tn) @fld-ty), +-- or (getField @k @rrep @arep @"fld" @(T t1..tn) @fld-ty) +-- and return the pieces, if the record selector is in scope +-- -- A complication is that `T` might be a data family, so we need to -- look it up in the `fam_envs` to find its representation tycon. lookupHasFieldLabel fam_inst_envs rdr_env arg_tys | -- We are matching HasField {k} {r_rep} {a_rep} x r a... - (_k_ty : _r_rep : _a_rep : x_ty : r_ty : a_ty : _) <- arg_tys - -- Look up the field named x in the type r + (_k : _rec_rep : _fld_rep : x_ty : rec_ty : fld_ty : _) <- arg_tys -- x should be a literal string , Just x <- isStrLitTy x_ty -- r should be an applied type constructor - , Just (tc, args) <- tcSplitTyConApp_maybe r_ty - -- use representation tycon (if data family); it has the fields + , Just (tc, args) <- tcSplitTyConApp_maybe rec_ty + -- Use the representation tycon (if data family); it has the fields , let r_tc = fstOf3 (tcLookupDataFamInst fam_inst_envs tc args) -- x should be a field of r , Just fl <- lookupTyConFieldLabel (FieldLabelString x) r_tc - -- and ensure the field selector is in scope + -- Ensure the field selector is in scope , Just gre <- lookupGRE_FieldLabel rdr_env fl - = Just (flSelector fl, gre, r_ty, a_ty) + = Just (flSelector fl, gre, rec_ty, fld_ty) | otherwise = Nothing ===================================== compiler/GHC/Tc/TyCl/Utils.hs ===================================== @@ -890,7 +890,8 @@ mkOneRecordSelector all_cons idDetails fl has_sel , sel_naughty = is_naughty , sel_fieldLabel = fl , sel_cons = rec_sel_info } - -- See Note [Detecting incomplete record selectors] in GHC.HsToCore.Pmc + -- See (IRS1) in Note [Detecting incomplete record selectors] + -- in GHC.HsToCore.Pmc -- Selector type; Note [Polymorphic selectors] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ec99f417829f3bba5f84ffb59873df3efc8bfe51...07c5635740b840feaf9e677dc8f7c95297619b66 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ec99f417829f3bba5f84ffb59873df3efc8bfe51...07c5635740b840feaf9e677dc8f7c95297619b66 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 11:23:35 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 01 Oct 2024 07:23:35 -0400 Subject: [Git][ghc/ghc][wip/T25281] Add -Wwarn-incomplete-record-selectors to -Wall Message-ID: <66fbdbb7a2f75_93bcd373098627cc@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 276bf852 by Simon Peyton Jones at 2024-10-01T12:23:14+01:00 Add -Wwarn-incomplete-record-selectors to -Wall - - - - - 1 changed file: - compiler/GHC/Driver/Flags.hs Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1356,6 +1356,7 @@ minusWallOpts Opt_WarnIncompleteUniPatterns, Opt_WarnIncompletePatternsRecUpd, Opt_WarnIncompleteExportWarnings, + Opt_WarnIncompleteRecordSelectors, Opt_WarnDerivingTypeable ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/276bf852dfc40286b4a281fd25fc8eaad10a38b4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/276bf852dfc40286b4a281fd25fc8eaad10a38b4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 11:40:40 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 07:40:40 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] cleaned remnant AmbiguousFieldOcc -> UpdFieldOcc Message-ID: <66fbdfb8176f_93bcd6595a0674c1@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 69e564bf by Hassan Al-Awwadi at 2024-10-01T13:40:16+02:00 cleaned remnant AmbiguousFieldOcc -> UpdFieldOcc - - - - - 1 changed file: - utils/check-exact/ExactPrint.hs Changes: ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -53,6 +53,7 @@ import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Type (UpdFieldOcc(..), FieldOcc(..)) import Control.Monad (forM, when, unless) import Control.Monad.Identity (Identity(..)) @@ -4591,11 +4592,10 @@ instance ExactPrint (FieldOcc GhcPs) where -- --------------------------------------------------------------------- -instance ExactPrint (AmbiguousFieldOcc GhcPs) where +instance ExactPrint (UpdFieldOcc GhcPs) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a - exact f@(Unambiguous _ n) = markAnnotated n >> return f - exact f@(Ambiguous _ n) = markAnnotated n >> return f + exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f -- --------------------------------------------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69e564bf991d6188cfa021c837d4e2c747e9b38a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69e564bf991d6188cfa021c837d4e2c747e9b38a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 13:28:21 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 09:28:21 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/perf-notes-fixes Message-ID: <66fbf8f59f2e9_22646814bb3074b@gitlab.mail> Ben Gamari pushed new branch wip/perf-notes-fixes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/perf-notes-fixes You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 13:38:37 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 09:38:37 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 181 commits: haddock: decrease margin on top of small headings Message-ID: <66fbfb5dca5a7_2264683ceeac1238b@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 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. - - - - - d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00 ghc-internal: @since for backtraceDesired Fixes point 1 in #25052 - - - - - bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00 ghc-internal: No trailing whitespace in exceptions Fixes #25052 - - - - - 62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00 Add since annotation for -fkeep-auto-rules. This partially addresses #25082. - - - - - 5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00 Mention `-fkeep-auto-rules` in release notes. It was added earlier but hadn't appeared in any release notes yet. Partially addresses #25082. - - - - - 7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00 Cmm: don't perform unsound optimizations on 32-bit compiler hosts - beef61351b240967b49169d27a9a19565cf3c4af enabled the use of MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends - 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG backend However we store some literal values as `Int` in the compiler. As a result, some Cmm optimizations transformed target 64-bit literals into compiler `Int`. If the compiler is 32-bit, this leads to computing with wrong literals (see #24893 and #24700). This patch disables these Cmm optimizations for 32-bit compilers. This is unsatisfying (optimizations shouldn't be compiler-word-size dependent) but it fixes the bug and it makes the patch easy to backport. A proper fix would be much more invasive but it shall be implemented in the future. Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00 docs: Update info on RequiredTypeArguments Add a section on "types in terms" that were implemented in 8b2f70a202 and remove the now outdated suggestion of using `type` for them. - - - - - 39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00 JS: fix minor typo in base's jsbits - - - - - e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00 RTS: remove hack to force old cabal to build a library with only JS sources Need to extend JSC externs with Emscripten RTS definitions to avoid JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts. Fix #25138 Some recompilation avoidance tests now fail. This is tracked with the other instances of this failure in #23013. My hunch is that they were working by chance when we used the emcc linker. Metric Decrease: T24602_perf_size - - - - - d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00 Support multiline strings in type literals (#25132) - - - - - 610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00 JS: fix callback documentation (#24377) Fix #24377 - - - - - 6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00 haddock: Build haddock-api and haddock-library using hadrian We build these two packages as regular boot library dependencies rather than using the `in-ghc-tree` flag to include the source files into the haddock executable. The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built from hackage can still find the location of the GHC bindist using `ghc-paths`. Addresses #24834 This causes a metric decrease under non-release flavours because under these flavours libraries are compiled with optimisation but executables are not. Since we move the bulk of the code from the haddock executable to the haddock-api library, we see a metric decrease on the validate flavours. Metric Decrease: haddock.Cabal haddock.base haddock.compiler - - - - - 51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Add an extension field to HsRecFields This is the Right Thing to Do™. And it prepares for storing a multiplicity coercion there. First step of the plan outlined here and below https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091 - - - - - 4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Add test for #24961 - - - - - 623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00 Ensures that omitted record fields in pattern have multiplicity Many Omitted fields were simply ignored in the type checker and produced incorrect Core code. Fixes #24961 Metric Increase: RecordUpdPerf - - - - - c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00 AARCH64 linker: skip NONE relocations This patch is part of the patches upstreamed from haskell.nix. See https://github.com/input-output-hk/haskell.nix/pull/1960 for the original report/patch. - - - - - 682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00 Support multiline strings in TH - - - - - ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00 Extend -reexported-module flag to support module renaming The -reexported-module flag now supports renaming -rexported-modules. ``` -rexported-module "A as B" ``` This feature is only relevant to multi-component sessions. Fixes #25139 - - - - - e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00 Don't restrict eta-reduction of linear functions This commit simply removes code. All the supporting implementation has been done as part of !12883. Closes #25129 - - - - - 2bb4156e by sheaf at 2024-08-14T14:28:56-04:00 Allow @ character in C labels Generated symbol names can include the '@' character, for example when using `__attribute__((vectorcall))`. - - - - - 7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00 Linker: replace blind tuple with a datatype + docs - - - - - bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00 isIrrefutableHsPat: look up ConLikes in the HscEnv At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors in the RdrEnv, which meant that we lacked fallibility information for out-of-scope constructors (which can arise from Template Haskell splices). Instead, we use 'lookupGREInfo', which looks up the information in the type environment. This was the correct function to call all along, but was not used in 572fbc44 due to import cycle reasons. The appropriate functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env', which avoids import cycles. Fixes #25164 - - - - - 4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00 Linker: some refactoring to prepare for #24886 - Rename LoadedBCOs into LazyBCOs - Bundle SptEntries with CompiledByteCode and removed [SptEntry] field from the BCOs constructor - Rename Linkable's LM constructor into Linkable: in the past we had LM and LP for Module and Package, now we only have the former. - Rename Unlinked into LinkablePart (and linkableUnlinked into linkableParts) - Use NonEmpty to encode invariant in Linkable's linkableParts type - Add helpers: linkableLibs, linkableBCOs, etc. - Add documentation - Remove partial nameOfObject - Rename nameOfObject_maybe into linkablePartPath - Rename byteCodeOfObject into linkablePartAllBCOs. - Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C stub. Document the fact that LazyBCOs are returned in this case (contrary to linkableBCOs which only returns non-lazy ones) Refactoring done while trying to understand how to adapt the linker code to support the JS backend too (cf #24886). - - - - - fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00 Implements the Exportable Named Default proposal (#24305) This squashed commit adds support for exportable named defaults, the accepted GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409 The proposal extends the Haskell '98 declarations default (Int, Double) which were implicitly always applying to Num class alone, to allow specifying an arbitrary single-parameter class: default IsString (Text, String) The effect of this declaration would be to eliminate the ambiguous type errors around string literals when OverloadedStrings extension is active. The declaration by itself has effect only in its module, so the proposal also adds the ability to export class defaults: module MyModule (default IsIstring) Once the language extension is published and established, we can consider using it in base and other libraries. See Note [Named default declarations] in GHC.Tc.Gen.Default for implementation details. - - - - - 1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00 Make kick-out more selective This MR revised the crucial kick-out criteria in the constraint solver. Ticket #24984 showed an example in which * We were kicking out unnecessarily * That gave rise to extra work, of course * But it /also/ led to exponentially-sized coercions due to lack of sharing in coercions (something we want to fix separately #20264) This MR sharpens up the kick-out criteria; specifially in (KK2) we look only under type family applications if (fs>=fw). This forced me to understand the existing kick-out story, and I ended up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet. Especially look at the new `Note [The KickOut Criteria]` The proof of termination is not air-tight, but it is better than before, and both Richard and I think it's correct :-). - - - - - 88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00 testsuite: remove undesired -fasm flag from test ways This patch removes the -fasm flag from test ways, except ways like optasm that explicitly state they are meant to be compiled with NCG backend. Most test ways should use the default codegen backend, and the precense of -fasm can cause stderr mismatches like this when GHC is configured with the unregisterised backend: ``` --- /dev/null +++ /tmp/ghctest-3hydwldj/test spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised @@ -0,0 +1,2 @@ +when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)] + Target platform uses unregisterised ABI, so compiling via C *** unexpected failure for prof-late-cc(prof_no_auto) ``` This has been breaking the wasm unreg nightly job since !12595 landed. - - - - - 3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00 ghci: fix isMinTTY.h casing for Windows targets This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for Windows targets. While this looks harmless given Windows filesystems are case-insensitive by default, it does cause a compilation warning with recent versions of clang, so we might as well fix the casing: ``` driver\ghci\isMinTTY.c:10:10: error: warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path] | 10 | #include "isMINTTY.h" | ^ #include "isMINTTY.h" ^~~~~~~~~~~~ "isMinTTY.h" 1 warning generated. ``` - - - - - 5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00 compiler: Fix pretty printing of ticked prefix constructors (#24237) - - - - - ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00 Fix #15773 Clarify further -rtsopts 'defaults' in docs - - - - - 05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00 Improve efficiency of `assertError` (#24625) ... by moving `lazy` to the exception-throwing branch. It's all documented in `Note [Strictness of assertError]`. - - - - - c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00 GHCi debugger: drop record name spaces for Ids When binding new local variables at a breakpoint, we should create Ids with variable namespace, and not record field namespace. Otherwise the rest of the compiler falls over because the IdDetails are wrong. Fixes #25109 - - - - - bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00 base: Final deprecation of GHC.Pack The timeline mandated by #21461 has come to its term and after two years and four minor releases, we are finally removing GHC.Pack from base. Closes #21536 - - - - - 5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00 JS: support rubbish static literals (#25177) Support for rubbish dynamic literals was added in #24664. This patch does the same for static literals. Fix #25177 - - - - - b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00 haddock docs: prefix comes before, postfix comes after - - - - - 6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00 haddock: include package info with --show-interface - - - - - 7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00 Document the (x86) SIMD macros. Fixes #25021. - - - - - 05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00 ghc-internal: Derive version from ghc's version Fixes #25005 - - - - - 73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00 base: Deprecate GHC.Desugar See https://github.com/haskell/core-libraries-committee/issues/216. This will be removed in GHC 9.14. - - - - - 821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00 compiler: Store ForeignStubs and foreign C files in interfaces This data is used alongside Core bindings to reconstruct intermediate build products when linking Template Haskell splices with bytecode. Since foreign stubs and files are generated in the pipeline, they were lost with only Core bindings stored in interfaces. The interface codec type `IfaceForeign` contains a simplified representation of `ForeignStubs` and the set of foreign sources that were manually added by the user. When the backend phase writes an interface, `mkFullIface` calls `encodeIfaceForeign` to read foreign source file contents and assemble `IfaceForeign`. After the recompilation status check of an upstream module, `initWholeCoreBindings` calls `decodeIfaceForeign` to restore `ForeignStubs` and write the contents of foreign sources to the file system as temporary files. The restored foreign inputs are then processed by `hscInteractive` in the same manner as in a regular pipeline. When linking the stub objects for splices, they are excluded from suffix adjustment for the interpreter way through a new flag in `Unlinked`. For details about these processes, please consult Note [Foreign stubs and TH bytecode linking]. Metric Decrease: T13701 - - - - - f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00 git: remove a.out and include it in .gitignore a.out is a configure script byproduct. It was mistakenly checked into the tree in !13118. This patch removes it, and include it in .gitignore to prevent a similar error in the future. - - - - - 1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00 docs: Fix code-block syntax on old sphinx version This code-block directive breaks the deb9 sphinx build. Fixes #25201 - - - - - 27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00 JS: add basic support for POSIX *at functions (#25190) openat/fstatat/unlinkat/dup are now used in the recent release of the `directory` and `file-io` packages. As such, these functions are (indirectly) used in the following tests one we'll bump the `directory` submodule (see !13122): - openFile008 - jsOptimizer - T20509 - bkpcabal02 - bkpcabal03 - bkpcabal04 - - - - - c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00 Update directory submodule to latest master The primary reason for this bump is to fix the warning from `ghc-pkg check`: ``` Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory ``` This also requires adding the `file-io` package as a boot library (which is discussed in #25145) Fixes #23594 #25145 - - - - - 4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Fix aarch64-alpine target platform description We are producing bindists where the target triple is aarch64-alpine-linux when it should be aarch64-unknown-linux This is because the bootstrapped compiler originally set the target triple to `aarch64-alpine-linux` which is when propagated forwards by setting `bootstrap_target` from the bootstrap compiler target. In order to break this chain we explicitly specify build/host/target for aarch64-alpine. This requires a new configure flag `--enable-ignore-` which just switches off a validation check that the target platform of the bootstrap compiler is the same as the build platform. It is the same, but the name is just wrong. These commits can be removed when the bootstrap compiler has the correct target triple (I looked into patching this on ci-images, but it looked hard to do correctly as the build/host platform is not in the settings file). Fixes #25200 - - - - - e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Bump nixpkgs commit for gen_ci script - - - - - 63a27091 by doyougnu at 2024-08-26T20:39:30-04:00 rts: win32: emit additional debugging information -- migration from haskell.nix - - - - - aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00 Only export defaults when NamedDefaults are enabled (#25206) This is a reinterpretation of GHC Proposal #409 that avoids a breaking change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal" Consider a module M that has no explicit export list: module M where default (Rational) Should it export the default (Rational)? The proposal says "yes", and there's a test case for that: default/DefaultImport04.hs However, as it turns out, this change in behavior breaks existing programs, e.g. the colour-2.3.6 package can no longer be compiled, as reported in #25206. In this patch, we make implicit exports of defaults conditional on the NamedDefaults extension. This fix is unintrusive and compliant with the existing proposal text (i.e. it does not require a proposal amendment). Should the proposal be amended, we can go for a simpler solution, such as requiring all defaults to be exported explicitly. Test case: testsuite/tests/default/T25206.hs - - - - - 3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00 simplifier: Fix space leak during demand analysis The lazy structure (a list) in a strict field in `DmdType` is not fully forced which leads to a very large thunk build-up. It seems there is likely still more work to be done here as it seems we may be trading space usage for work done. For now, this is the right choice as rather than using all the memory on my computer, compilation just takes a little bit longer. See #25196 - - - - - c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00 Add missing parenthesizeHsType in cvtp's InvisP case We need to ensure that when we convert an `InvisP` (invisible type pattern) to a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as `@(a :: k)` will parse correctly when roundtripped back through the parser. Fixes #25209. - - - - - 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. - - - - - 768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00 Add functions to check for weakly pinned arrays. This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops. These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved by the user via compaction but won't be moved by the RTS. This moves us one more stop closer to nailing down #22255. - - - - - b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00 ghc-toolchain: Don't leave stranded a.outs when testing for -g0 This happened because, when ghc-toolchain tests for -g0, it does so by compiling an empty program. This compilation creates an a.out. Since we create a temporary directory, lets place the test program compilation in it also, so that it gets cleaned up. Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74 Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203 - - - - - 83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00 Build foreign objects for TH with interpreter's way when loading from iface Fixes #25211 When linking bytecode for TH from interface core bindings with `-fprefer-byte-code`, foreign sources are loaded from the interface as well and compiled to object code in an ad-hoc manner. The results are then loaded by the interpreter, whose way may differ from the current build's target way. This patch ensures that foreign objects are compiled with the interpreter's way. - - - - - 0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00 rts: fix checkClosure error message This patch fixes an error message in checkClosure() when the closure has already been evacuated. The previous logic was meant to print the evacuated closure's type in the error message, but it was completely wrong, given info was not really an info table, but a tagged pointer that points to the closure's new address. - - - - - fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00 MO_AcquireFence: Less restrictive barrier GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)` to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which also implies stores.) - - - - - a45f1488 by Fendor at 2024-09-04T20:22:00-04:00 testsuite: Add support to capture performance metrics via 'perf' Performance metrics collected via 'perf' can be more accurate for run-time performance than GHC's rts, due to the usage of hardware counters. We allow performance tests to also record PMU events according to 'perf list'. - - - - - ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00 gitlab-ci: Add nightly job for running the testsuite with perf profiling support - - - - - 6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00 Enable perf profiling for compiler performance tests - - - - - da306610 by sheaf at 2024-09-04T20:22:41-04:00 RecordCon lookup: don't allow a TyCon This commit adds extra logic when looking up a record constructor. If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to the logic explained in Note [Pattern to type (P2T) conversion]), we emit an error saying that the data constructor is not in scope. This avoids the compiler falling over shortly thereafter, in the call to 'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc', because the record constructor would not have been a ConLike. Fixes #25056 - - - - - 9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00 Use deterministic names for temporary files When there are multiple threads they can race to create a temporary file, in some situations the thread will create ghc_1.c and in some it will create ghc_2.c. This filename ends up in the debug info for object files after compiling a C file, therefore contributes to object nondeterminism. In order to fix this we store a prefix in `TmpFs` which serves to namespace temporary files. The prefix is populated from the counter in TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked outside the thread which consumes it, in a deterministic order, so each thread always receives a TmpFs with the same prefix. This assumes that after the initial TmpFs is created, all other TmpFs are created from forking the original TmpFs. Which should have been try anyway as otherwise there would be file collisions and non-determinism. Fixes #25224 - - - - - 59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 Silence x-partial in Haddock.Backends.Xhtml This is an unfortunate consequence of two mechanisms: * GHC provides (possibly-empty) lists of names * The functions that retrieve those names are not equipped to do error reporting, and thus accept these lists at face value. They will have to be attached an effect for error reporting in a later refactoring - - - - - 8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 hadrian: Support loading haddock in ghci There is one tricky aspect with wired-in packages where the boot package is built with `-this-unit-id ghc` but the dependency is reported as `-package-id ghc-9.6...`. This has never been fixed in GHC as the situation of loading wired-in packages into the multi-repl seems like quite a niche feature that is always just easier to workaround. - - - - - 6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00 hadrian/multi: Load all targets when ./hadrian/ghci-multi is called This seems to make a bit more sense than just loading `ghc` component (and dependencies). - - - - - 7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00 ci: Beef up determinism interface test There have recently been some determinism issues with the simplifier and documentation. We enable more things to test in the ABI test to check that we produce interface files deterministically. - - - - - 5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00 Transform some StgRhsClosure into StgRhsCon after unarisation (#25166) Before unarisation we may have code like: Test.foo :: Test.D [GblId, Unf=OtherCon []] = \u [] case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] { __DEFAULT -> Test.D [GHC.Types.True sat_sAw]; }; After unarisation we get: Test.foo :: Test.D [GblId, Unf=OtherCon []] = {} \u [] Test.D [GHC.Types.True 2#]; Notice that it's still an Updatable closure for no reason anymore. This patch transforms appropriate StgRhsClosures into StgRhsCons after unarisation, allowing these closures to be statically allocated. Now we get the expected: Test.foo :: Test.D [GblId, Unf=OtherCon []] = Test.D! [GHC.Types.True 2#]; Fix #25166 To avoid duplicating code, this patch refactors the mk(Top)StgRhs functions and put them in a GHC.Stg.Make module alongside the new mk(Top)StgRhsCon_maybe functions. - - - - - 958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00 haddock: Add missing requirements.txt for the online manual - - - - - 573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00 AArch64: Implement takeRegRegMoveInstr This has likely been forgotten. - - - - - 20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00 haddock: Configuration fix for ReadTheDocs - - - - - 03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00 JS: fake support for native adjustors (#25159) The JS backend doesn't support adjustors (I believe) and in any case if it ever supports them it will be a native support, not one via libffi. - - - - - 5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00 JS: remove redundant h$lstat It was introduced a second time by mistake in 27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190) - - - - - ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Refactor only newSysLocalDs * Change newSysLocalDs to take a scaled type * Add newSysLocalMDs that takes a type and makes a ManyTy local Lots of files touched, nothing deep. - - - - - 7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Don't introduce 'nospec' on the LHS of a RULE This patch address #25160. The main payload is: * When desugaring the LHS of a RULE, do not introduce the `nospec` call for non-canonical evidence. See GHC.Core.InstEnv Note [Coherence and specialisation: overview] The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it on the LHS of a RULE (that's what caused #25160). So now `dsHsWrapper` takes a flag to say if it's on the LHS of a RULE. See wrinkle (NC1) in `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds. But I think this flag will go away again when I have finished with my (entirely separate) speciaise-on-values patch (#24359). All this meant I had to re-understand the `nospec` stuff and coherence, and that in turn made me do some refactoring, and add a lot of new documentation The big change is that in GHC.Core.InstEnv, I changed the /type synonym/ `Canonical` into a /data type/ `CanonicalEvidence` and documented it a lot better. That in turn made me realise that CalLStacks were being treated with a bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`. - - - - - 663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Add defaulting of equalities This MR adds one new defaulting strategy to the top-level defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver. This resolves #25029 and #25125, which showed that users were accidentally relying on a GHC bug, which was fixed by commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4 Author: Simon Peyton Jones <simon.peytonjones at gmail.com> Date: Wed Jun 12 17:44:59 2024 +0100 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. This fix gave rise to a number of user complaints; but the improved defaulting story of this MR largely resolves them. On the way I did a bit of refactoring, of course * Completely restructure the extremely messy top-level defaulting code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much, much, much esaier to grok. - - - - - e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00 Don't name a binding pattern It's a keyword when PatternSynonyms are set. - - - - - b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00 Do not use an error thunk for an absent dictionary In worker/wrapper we were using an error thunk for an absent dictionary, but that works very badly for -XDictsStrict, or even (as #24934 showed) in some complicated cases involving strictness analysis and unfoldings. This MR just uses RubbishLit for dictionaries. Simple. No test case, sadly because our only repro case is rather complicated. - - - - - 8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00 haddock: Remove support for applehelp format in the Manual - - - - - 9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00 RTS linker: add support for hidden symbols (#25191) Add linker support for hidden symbols. We basically treat them as weak symbols. Patch upstreamed from haskell.nix Co-authored-by: Sylvain Henry <sylvain at haskus.fr> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00 Fix C warnings (#25237) GCC 14 treats the fixed warnings as errors by default. I.e. we're gaining GCC 14 compatibility with these fixes. - - - - - 05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00 JS: fix codegen of static string data Before this patch, when string literals are made trivial, we would generate `h$("foo")` instead of `h$str("foo")`. This was introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091. - - - - - 949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Re-organise cross-OS compatibility layer - - - - - 84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Remove CPP for obsolete GHC and Cabal versions - - - - - 370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file - - - - - cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00 Add ZonkAny and document it This MR fixed #24817 by adding ZonkAny, which takes a Nat argument. See Note [Any types] in GHC.Builtin.Types, especially wrinkle (Any4). - - - - - 0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00 hadrian: Make sure ffi headers are built before using a compiler When we are using ffi adjustors then we rely on `ffi.h` and `ffitarget.h` files during code generation when compiling stubs. Therefore we need to add this dependency to the build system (which this patch does). Reproducer, configure with `--enable-libffi-adjustors` and then build "_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o". Observe that this fails before this patch and works afterwards. Fixes #24864 Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - 0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00 base: Deprecate BCO primops exports from GHC.Exts See https://github.com/haskell/core-libraries-committee/issues/212. These reexports will be removed in GHC 9.14. - - - - - cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00 EPA: Remove Anchor = EpaLocation synonym This just causes confusion. - - - - - 8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00 Bump submodule deepseq to 1.5.1.0 - - - - - aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00 User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250) Fixes #25250. - - - - - 1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add Native Code Generator (NCG) This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00 Adjust test timings for slower computers Increase the delays a bit to be able to run these tests on slower computers. The reference was a Lichee Pi 4a RISCV64 machine. - - - - - a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add RTS linker This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Ignore divbyzero test The architecture's behaviour differs from the test's expectations. See comment in code why this is okay. - - - - - abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Enable MulMayOflo_full test It works and thus can be tested. - - - - - 38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: LibffiAdjustor: Ensure code caches are flushed RISCV64 needs a specific code flushing sequence (involving fence.i) when new code is created/loaded. - - - - - 7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add additional linker symbols for builtins We're relying on some GCC/Clang builtins. These need to be visible to the linker (and not be stripped away.) - - - - - 92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add GHCi support As we got a RTS linker for this architecture now, we can enable GHCi for it. - - - - - a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Set codeowners of the NCG - - - - - 8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00 Add test for C calling convention Ensure that parameters and return values are correctly processed. A dedicated test (like this) helps to get the subtleties of calling conventions easily right. The test is failing for WASM32 and marked as fragile to not forget to investigate this (#25249). - - - - - fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00 finder: Add `IsBootInterface` to finder cache keys - - - - - cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00 EPA: Sync ghc-exactprint to GHC - - - - - 1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00 DmdAnal: Fast path for `multDmdType` (#25196) This is in order to counter a regression exposed by SpecConstr. Fixes #25196. - - - - - 80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00 Bump submodule array to 0.5.8.0 - - - - - 49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00 Linker: add support for extra built-in symbols (#25155) See added Note [Extra RTS symbols] and new user guide entry. Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00 GNU/Hurd: Add getExecutablePath support GNU/Hurd exposes it as /proc/self/exe just like on Linux. - - - - - d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00 RTS: expose closure_sizeW_ (#25252) C code using the closure_sizeW macro can't be linked with the RTS linker without this patch. It fails with: ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_ Fix #25252 Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00 HsExpr: Inline `HsWrap` into `WrapExpr` This nice refactoring was suggested by Simon during review: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374 Fixes #25264. - - - - - 7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00 Pmc: Improve Desugaring of overloaded list patterns (#25257) This actually makes things simpler. Fixes #25257. - - - - - e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00 configure: Correctly report when subsections-via-symbols is disabled As noted in #24962, currently subsections-via-symbols is disabled on AArch64/Darwin due to alleged breakage. However, `configure` reports to the user that it is enabled. Fix this. - - - - - 9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00 Modified the default export implementation to match the amended spec - - - - - 35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00 FFI: don't ppr Id/Var symbols with debug info (#25255) Even if `-dpp-debug` is enabled we should still generate valid C code. So we disable debug info printing when rendering with Code style. - - - - - 9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00 Demand: Combine examples into Note (#25107) Just a leftover from !13060. Fixes #25107. - - - - - 21aaa34b by sheaf at 2024-09-21T17:48:36-04:00 Use x86_64-unknown-windows-gnu target for LLVM on Windows - - - - - 992a7624 by sheaf at 2024-09-21T17:48:36-04:00 LLVM: use -relocation-model=pic on Windows This is necessary to avoid the segfaults reported in #22487. Fixes #22487 - - - - - c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00 compiler: Use type abstractions when deriving For deriving newtype and deriving via, in order to bring type variables needed for the coercions into scope, GHC generates type signatures for derived class methods. As a simplification, drop the type signatures and instead use type abstractions to bring method type variables into scope. - - - - - f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00 driver: Ensure we run driverPlugin for staticPlugins (#25217) driverPlugins are only run when the plugin state changes. This meant they were never run for static plugins, as their state never changes. We need to keep track of whether a static plugin has been initialised to ensure we run static driver plugins at least once. This necessitates an additional field in the `StaticPlugin` constructor as this state has to be bundled with the plugin itself, as static plugins have no name/identifier we can use to otherwise reference them - - - - - 620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00 Allow unknown fd device types for setNonBlockingMode. This allows fds with a unknown device type to have blocking mode set. This happens for example for fds from the inotify subsystem. Fixes #25199. - - - - - c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00 Use Hackage version of Cabal 3.14.0.0 for Hadrian. We remove the vendored Cabal submodule. Also update the bootstrap plans Fixes #25086 - - - - - 6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00 ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh ci.sh sets up the toolchain environment, including paths for the cabal directory, the toolchain binaries etc. If we run any commands outside of ci.sh, unless we source ci.sh we will use the wrong values for these environment variables. In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was using an old index state despite `ci.sh setup` updating and setting the correct index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which is where the index was downloaded to, but we were using the default cabal directory outside ci.sh The solution is to source the correct environment `ci.sh` using `. ci.sh setup` - - - - - 9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00 ghc-toolchain: Set -fuse-ld even for ld.bfd This reflects the behaviour of the autoconf scripts. - - - - - d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00 Parser: be more careful when lexing extended literals (#25258) Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3]. A side-effect of this patch is that we now allow negative unsigned extended literals. They trigger an overflow warning later anyway. - - - - - ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00 rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog. To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID, and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new cost centres up to the one we already dumped in DUMPED_CC_ID. Fixes #24148 - - - - - c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00 EPA: Replace AnnsModule am_main with EpTokens Working towards removing `AddEpAnn` - - - - - 2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30 ci: Run abi-test on test-abi label - - - - - ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 testsuite: Add a test for object determinism Extends the abi_test with an object determinism check Also includes a standalone test to be run by developers manually when debugging issues with determinism. - - - - - d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Sampling uniques in the CG To achieve object determinism, the passes processing Cmm and the rest of the code generation pipeline musn't create new uniques which are non-deterministic. This commit changes occurrences of non-deterministic unique sampling within these code generation passes by a deterministic unique sampling strategy by propagating and threading through a deterministic incrementing counter in them. The threading is done implicitly with `UniqDSM` and `UniqDSMT`. Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded through all passes to guarantee uniques in different passes are unique amongst them altogether. Specifically, the same `DUniqSupply` must be threaded through the CG Streaming pipeline, starting with Driver.Main calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and `codeOutput` in sequence. To thread resources through the `Stream` abstraction, we use the `UniqDSMT` transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will thread the `DUniqSupply` through every pass applied to the `Stream`, for every element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in code generation which that carries through the deterministic unique supply. See Note [Deterministic Uniques in the CG] - - - - - 3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Cmm unique renaming pass To achieve object determinism, we need to prevent the non-deterministic uniques from leaking into the object code. We can do this by deterministically renaming the non-external uniques in the Cmm groups that are yielded right after StgToCmm. The key to deterministic renaming is observing that the order of declarations, instructions, and data in the Cmm groups are already deterministic (modulo other determinism bugs), regardless of the uniques. We traverse the Cmm AST in this deterministic order and rename the uniques, incrementally, in the order they are found, thus making them deterministic. This renaming is guarded by -fobject-determinism which is disabled by default for now. This is one of the key passes for object determinism. Read about the overview of object determinism and a more detailed explanation of this pass in: * Note [Object determinism] * Note [Renaming uniques deterministically] Significantly closes the gap to #12935 - - - - - 8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: DCmmGroup vs CmmGroup Part of our strategy in producing deterministic objects, namely, renaming all Cmm uniques in order, depend on the object code produced having a deterministic order (say, A_closure always comes before B_closure). However, the use of LabelMaps in the Cmm representation invalidated this requirement because the LabelMaps elements would already be in a non-deterministic order (due to the original uniques), and the renaming in sequence wouldn't work because of that non-deterministic order. Therefore, we now start off with lists in CmmGroup (which preserve the original order), and convert them into LabelMaps (for performance in the code generator) after the uniques of the list elements have been renamed. See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935. Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Don't print unique in pprFullName This unique was leaking as part of the profiling description in info tables when profiling was enabled, despite not providing information relevant to the profile. - - - - - 340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: UDFM for distinct-constructor-tables In order to produce deterministic objects when compiling with -distinct-constructor-tables, we also have to update the data constructor map to be backed by a deterministic unique map (UDFM) rather than a non-deterministic one (UniqMap). - - - - - 282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: InfoTableMap uniques in generateCgIPEStub Fixes object determinism when using -finfo-table-map Make sure to also deterministically rename the IPE map (as per Note [Renaming uniques deterministically]), and to use a deterministic unique supply when creating new labels for the IPE information to guarantee deterministic objects when IPE information is requested. Note that the Cmm group produced in generateCgIPEStub must /not/ be renamed because renaming uniques is not idempotent, and the references to the previously renamed code in the IPE Cmm group would be renamed twice and become invalid references to non-existent symbols. We do need to det-rename the InfoTableMap that is created in the conversion from Core to Stg. This is not a problem since that map won't refer any already renamed names (since it was created before the renaming). - - - - - 7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30 ci: Allow abi-test to fail. We are not fully deterministic yet, see #12935 for work that remains to be done. - - - - - a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00 Add Given injectivity for built-in type families Ticket #24845 asks (reasonably enough) that if we have [G] a+b ~ 0 then we also know [G] a ~ 0, b ~ 0 and similar injectivity-like facts for other built-in type families. The status quo was that we never generate evidence for injectivity among Givens -- but it is quite reasonnable to do so. All we need is to have /evidence/ for the new constraints This MR implements that goal. I also took the opportunity to * Address #24978: refactoring UnivCo * Fix #25248, which was a consequences of the previous formulation of UnivCo As a result this MR touches a lot of code. The big things are: * Coercion constructor UnivCo now takes a [Coercion] as argument to express the coercions on which the UnivCo depends. A nice consequence is that UnivCoProvenance now has no free variables, simpler in a number of places. * Coercion constructors AxiomInstCo and AxiomRuleCo are combined into AxiomCo. The new AxiomCo, carries a (slightly oddly named) CoAxiomRule, which itself is a sum type of the various forms of built-in axiom. See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom A merit of this is that we can separate the case of open and closed type families, and eliminate the redundant `BranchIndex` in the former case. * Much better representation for data BuiltInSynFamily, which means we no longer need to enumerate built-in axioms as well as built-in tycons. * There is a massive refactor in GHC.Builtin.Types.Literals, which contains all the built-in axioms for type-level operations (arithmetic, append, cons etc). A big change is that instead of redundantly having (a) a hand-written matcher, and (b) a template-based "proves" function, which were hard to keep in sync, the two are derive from one set of human-supplied info. See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends. * Significant changes in GHC.Tc.Solver.Equality to account for the new opportunity for Given/Given equalities. Smaller things * Improve pretty-printing to avoid parens around atomic coercions. * Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`. Looks like a bug, Richard agrees. * coercionLKind and coercionRKind are hot functions. I refactored the implementation (which I had to change anyway) to increase sharing. See Note [coercionKind performance] in GHC.Core.Coercion * I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan names * I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid calling tyConsOfType. I forget exactly why I did this, but it's definitely better now. * I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc - - - - - dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00 Resolve ambiguous method-bound type variables in vanilla defaults and GND When defining an instance of a class with a "vanilla" default, such as in the following example (from #14266): ```hs class A t where f :: forall x m. Monoid x => t m -> m f = <blah> instance A [] ``` We have to reckon with the fact that the type of `x` (bound by the type signature for the `f` method) is ambiguous. If we don't deal with the ambiguity somehow, then when we generate the following code: ```hs instance A [] where f = $dmf @[] -- NB: the type of `x` is still ambiguous ``` Then the generated code will not typecheck. (Issue #25148 is a more recent example of the same problem.) To fix this, we bind the type variables from the method's original type signature using `TypeAbstractions` and instantiate `$dmf` with them using `TypeApplications`: ```hs instance A [] where f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous ``` Note that we only do this for vanilla defaults and not for generic defaults (i.e., defaults using `DefaultSignatures`). For the full details, see `Note [Default methods in instances] (Wrinkle: Ambiguous types from vanilla method type signatures)`. The same problem arose in the code generated by `GeneralizedNewtypeDeriving`, as we also fix it here using the same technique. This time, we can take advantage of the fact that `GeneralizedNewtypeDeriving`-generated code _already_ brings method-bound type variables into scope via `TypeAbstractions` (after !13190), so it is very straightforward to visibly apply the type variables on the right-hand sides of equations. See `Note [GND and ambiguity]`. Fixes #14266. Fixes #25148. - - - - - 0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00 Document primitive string literals and desugaring of string literals Fixes #17474 and #17974 Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00 rts: Fix segfault when using non-moving GC with profiling `nonMovingCollect()` swaps out the `static_flag` value used as a sentinel for `gct->scavenged_static_objects`, but the subsequent call `resetStaticObjectForProfiling()` sees the old value of `static_flag` used as the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()` before calling `nonMovingCollect()` as otherwise it looks for the incorrect sentinel value Fixes #25232 and #23958 Also teach the testsuite driver about nonmoving profiling ways and stop disabling metric collection when nonmoving GC is enabled. - - - - - e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00 Fix interaction between fork and kqueue (#24672) A kqueue file descriptor isn't inherited by a child created with fork. As such we mustn't try to close this file descriptor as we would close a random one, e.g. the one used by timerfd. Fix #24672 - - - - - 6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00 Improve GHC.Tc.Solver.defaultEquality This MR improves GHC.Tc.Solver.defaultEquality to solve #25251. The main change is to use checkTyEqRhs to check the equality, so that we do promotion properly. But within that we needed a small enhancement to LC_Promote. See Note [Defaulting equalites] (DE4) and (DE5) The tricky case is (alas) hard to trigger, so I have not added a regression test. - - - - - 97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00 JS: fix h$withCStringOnHeap helper (#25288) strlen returns the length of the string without the \0 terminating byte, hence CString weren't properly allocated on the heap (ending \0 byte was missing). - - - - - 5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00 base: Propagate `error` CallStack to thrown exception Previously `errorCallWithCallStackException` failed to propagate its `CallStack` argument, which represents the call-chain of the preceding `error` call, to the exception that it returned. Consequently, the call-stack of `error` calls were quite useless. Unfortunately, this is the second time that I have fixed this but it seems the first must have been lost in rebasing. Fixes a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164> Fixes #24807. - - - - - c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00 driver: Fix -working-dir for foreign files -working-dir definitely needs more serious testing, there are some easy ways to test this. * Modify Cabal to call ghc using -working-dir rather than changing directory. * Modify the testsuite to run ghc using `-working-dir` rather than running GHC with cwd = temporary directory. However this will have to wait until after 9.12. Fixes #25150 - - - - - 88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: reuse predError, succError, toEnumError Reuse predError, succError, and toEnumError when deriving Enum instances to avoid generating different error strings per instance. E.g. before this patch for every instance for a type FOO we would generate a string: "pred{FOO}: tried to take `pred' of first tag in enumeration"# - - - - - e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: generate better code (#16364) Generate better code for Enum.toEnum: check both the lower and the upper bounds at once with an unsigned comparison. Initially I've used a type ascription with a call to 'fromIntegral', hence the slight refactoring of nlAscribe. Using 'fromIntegral' was problematic (too low in the module hierarchy) so 'enumIntToWord' was introduced instead. Combined with the previous commit, T21839c ghc/alloc decrease by 5% Metric Decrease: T21839c - - - - - 383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00 Core: add absorb rules for binary or/and (#16351) Rules: x or (x and y) ==> x x and (x or y) ==> x - - - - - 783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Don't compile `asBox` with -fprof-late The `asBox` function is intended to store exactly the closure which the user passes to it. Placing a cost centre on asBox introduces a thunk, which violates this expectation and can change the result of using asBox when profiling is enabled. See #25212 for more details and ample opportunity to discuss if this is a bug or not. - - - - - 0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Fix normalisation of .prof files Fix 1: If a cost centre contained CAF then the normalisation was corrupted, now only check if CAF is at the start of a line. Fix 2: "no location info" contain a space, which messed up the next normalisation logic which assumed that columns didn't have spaced in. - - - - - 9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00 testsuite: Fix normalisation of prof_files removing newlines These normalisation steps were collapsing lines together, which made subsequent normalisation steps fail. ``` foo x y z CAF x y z qux x y z ``` was getting normalised to ``` foo x y z qux x y z ``` which means that subsequent line based filters would not work correctly. - - - - - 2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00 packaging: Enable late-ccs for release flavour This enables late cost centres when building profiled libraries and subsequently greatly improves the resolution of cost centre stacks when profiling. This patch also introduces the `grep_prof` test modifier which is used to apply a further filter to the .prof file before they are compared. Fixes #21732 ------------------------- Metric Increase: libdir ------------------------- - - - - - bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00 Replace manual string lexing (#25158) Metric Increase: MultilineStringsPerf This commit replaces the manual string lexing logic with native Alex lexing syntax. This aligns the lexer much closer to the Haskell Report, making it easier to see how the implementation and spec relate. This slightly increases memory usage when compiling multiline strings because we now have two distinct phases: lexing the multiline string with Alex and post-processing the string afterwards. Before, these were done at the same time, but separating them allows us to push as much logic into normal Alex lexing as possible. Since multiline strings are a new feature, this regression shouldn't be too noticeable. We can optimize this over time. - - - - - 16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import This behaviour is problematic for the principle reason that `import Prelude` may not refer to the `base` package, and in which case importing an entirely unrelated module causing your implicit prelude to leave the scope is extremely surprising. See the added test for this example. Discussion on #17045. The secondary reason for reverting this patch is that "base" can't be a wired in package any more (see #24903), so we have to remove special logic which singles out base from the compiler. The rule for implicit shadowing is now simply: * If you write import Prelude (..) then you don't get an implicit prelude import * If you write import "foobar" Prelude (..) for all pkgs foobar, you get an implicit import of prelude. If you want to write a package import of Prelude, then you can enable `NoImplicitPrelude` for the module in question to recover the behaviour of ghc-9.2-9.10. Fixes #17045 - - - - - 57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE The COMPILING_BASE_PACKAGE macro is concerned with issues defining symbols and using symbols in the same compilation unit. However, these symbols now exist in ghc-internal rather than base, so we should rename the macro accordingly. The code is guards is likely never used as we never produce windows DLLs but it is simpler to just perform the renaming for now. These days there is little doubt that this macro defined in this ad-hoc manner would be permitted to exist, but these days are not those days. Fixes #25221 - - - - - 70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Preload ghc-internal rather than base This occurence of baseUnitId was missed when moving the bulk of internal definitions into `ghc-internal`. We need to remove this preloading of `base` now because `base` should not be wired in. Towards #24903 - - - - - 12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Remove Data.List compat warning There is currently a warning implemented in -Wcompat which warns you when importing Data.List in a non-qualified manner. ``` A.hs:3:8: warning: [-Wcompat-unqualified-imports] To ensure compatibility with future core libraries changes imports to Data.List should be either qualified or have an explicit import list. | 3 | import Data.List | ^^^^^^^^^ Ok, one module loaded. ``` GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244 CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E This warning was implemented as part of the migration to making Data.List monomorphic again (and to be used like Data.Set, Data.Map etc). That doesn't seem like it happened, and I imagine that the current CLC would require a new proposal anyway in order to do that now. It's not clear in any case what "future core libraries changes" we are waiting to happen before this warning can be removed. Given the first phase of the proposal has lasted 5 years it doesn't seem that anyone is motivated to carry the proposal to completion. It does seem a bit unnecessary to include a warning in the compiler about "future changes to the module" when there's no timeline or volunteer to implement these changes. The removal of this warning was discussed again at: https://github.com/haskell/core-libraries-committee/issues/269 During the discussion there was no new enthusiasm to move onto the next stages of the proposal so we are removing the warning to unblock the reinstallable "base" project (#24903) Fixes #24904 - - - - - d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Move Control.Monad.Zip into ghc-internal mzip is wired in and therefore needs to be in ghc-internal. Fixes #25222 Towards #24903 - - - - - d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00 Unwire the base package This patch just removes all the functions related to wiring-in the base package and the `-this-unit-id=base` flag from the cabal file. After this commit "base" becomes just like any other package and the door is opened to moving base into an external repo and releasing base on a separate schedule to the rest of ghc. Closes #24903 - - - - - 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - 28c0f9a4 by Ben Gamari at 2024-10-01T09:32:49-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 4aaf553b by Ben Gamari at 2024-10-01T09:37:40-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 23 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitmodules - CODEOWNERS - compiler/CodeGen.Platform.h - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9204fd6804ce649c2f5aef449874a8a5203867d7...4aaf553b3d97ca031a7fcb21630470e7976b151a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9204fd6804ce649c2f5aef449874a8a5203867d7...4aaf553b3d97ca031a7fcb21630470e7976b151a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 13:52:55 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 09:52:55 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 4 commits: ghc-internal: Drop GHC.Internal.Data.Enum Message-ID: <66fbfeb76a694_2264683db8641514b@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC Commits: 933d7133 by Ben Gamari at 2024-10-01T09:39:44-04:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - d773e1ad by Ben Gamari at 2024-10-01T09:45:18-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 475b4f11 by Ben Gamari at 2024-10-01T09:45:18-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 6f53d832 by Ben Gamari at 2024-10-01T09:45:18-04:00 base: Mention incorrect Data.Enum addition in changelog - - - - - 7 changed files: - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Data/Enum.hs - libraries/ghc-internal/ghc-internal.cabal.in - − libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - testsuite/tests/interface-stability/base-exports.stdout Changes: ===================================== libraries/base/base.cabal.in ===================================== @@ -46,8 +46,10 @@ Library , Data.Bifoldable1 , Data.Bifunctor , Data.Bitraversable + , Data.Bounded , Data.Char , Data.Complex + , Data.Enum , Data.Fixed , Data.Foldable1 , Data.Functor.Classes @@ -95,7 +97,6 @@ Library , Data.Dynamic , Data.Either , Data.Eq - , Data.Enum , Data.Foldable , Data.Function , Data.Functor ===================================== libraries/base/changelog.md ===================================== @@ -22,9 +22,11 @@ and [CLC proposal #261](https://github.com/haskell/core-libraries-committee/issues/261)) * The [deprecation process of GHC.Pack](https://gitlab.haskell.org/ghc/ghc/-/issues/21461) has come its term. The module has now been removed from `base`. * Propagate HasCallStack from `errorCallWithCallStackException` to exception backtraces, fixing a bug in the implementation of [CLC proposal #164](https://github.com/haskell/core-libraries-committee/issues/164). + * Introduce `Data.Bounded` module exporting the `Bounded` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) -## 4.20.0.0 May 2024 +## 4.20.0.0 *May 2024* * Shipped with GHC 9.10.1 + * Introduce `Data.Enum` module exporting both `Enum` and `Bounded`. Note that the export of `Bounded` will be deprecated in a future release ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) * Export `foldl'` from `Prelude` ([CLC proposal #167](https://github.com/haskell/core-libraries-committee/issues/167)) * The top-level handler for uncaught exceptions now displays the output of `displayException` rather than `show` ([CLC proposal #198](https://github.com/haskell/core-libraries-committee/issues/198)) ===================================== libraries/base/src/Data/Enum.hs ===================================== @@ -1,7 +1,7 @@ -{-# LANGUAGE Safe #-} +{-# LANGUAGE NoImplicitPrelude #-} +----------------------------------------------------------------------------- -- | --- -- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE @@ -10,12 +10,14 @@ -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Enum' class. -- +----------------------------------------------------------------------------- module Data.Enum - (Bounded(..), - Enum(..) - ) where + ( Enum(..) + {-# DEPRECATED "Bounded should be imported from Data.Bounded" #-} + , Bounded(..) + ) where -import GHC.Internal.Data.Enum \ No newline at end of file +import GHC.Internal.Enum ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -117,7 +117,6 @@ Library GHC.Internal.Data.Dynamic GHC.Internal.Data.Either GHC.Internal.Data.Eq - GHC.Internal.Data.Enum GHC.Internal.Data.Foldable GHC.Internal.Data.Function GHC.Internal.Data.Functor ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs deleted ===================================== @@ -1,22 +0,0 @@ -{-# LANGUAGE NoImplicitPrelude #-} - ------------------------------------------------------------------------------ --- | --- Module : GHC.Internal.Data.Enum --- Copyright : (c) The University of Glasgow, 1992-2002 --- License : see libraries/base/LICENSE --- --- Maintainer : ghc-devs at haskell.org --- Stability : stable --- Portability : non-portable (GHC extensions) --- --- The 'Enum' and 'Bounded' classes. --- ------------------------------------------------------------------------------ - -module GHC.Internal.Data.Enum - ( Bounded(..) - , Enum(..) - ) where - -import GHC.Internal.Enum ===================================== libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs ===================================== @@ -18,7 +18,7 @@ import GHC.Generics (Generic) import GHC.Internal.Base import GHC.Internal.Show import GHC.Internal.Generics -import GHC.Internal.Data.Enum +import GHC.Internal.Enum #endif -- | The language extensions known to GHC. ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -744,6 +744,14 @@ module Data.Bool where otherwise :: Bool (||) :: Bool -> Bool -> Bool +module Data.Bounded where + -- Safety: Safe-Inferred + type Bounded :: * -> Constraint + class Bounded a where + minBound :: a + maxBound :: a + {-# MINIMAL minBound, maxBound #-} + module Data.Char where -- Safety: Trustworthy type Char :: * @@ -947,7 +955,7 @@ module Data.Either where rights :: forall a b. [Either a b] -> [b] module Data.Enum where - -- Safety: Safe + -- Safety: Safe-Inferred type Bounded :: * -> Constraint class Bounded a where minBound :: a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4aaf553b3d97ca031a7fcb21630470e7976b151a...6f53d832eed89d9d35c60eb11a6d2f6ffa79a567 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4aaf553b3d97ca031a7fcb21630470e7976b151a...6f53d832eed89d9d35c60eb11a6d2f6ffa79a567 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 13:55:26 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 09:55:26 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 4 commits: ghc-internal: Drop GHC.Internal.Data.Enum Message-ID: <66fbff4eb4aea_22646863243c1596f@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC Commits: e5af3aed by Ben Gamari at 2024-10-01T09:54:56-04:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 05ea7a82 by Ben Gamari at 2024-10-01T09:54:56-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 271cf64f by Ben Gamari at 2024-10-01T09:54:56-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - f09d35dd by Ben Gamari at 2024-10-01T09:54:56-04:00 base: Mention incorrect Data.Enum addition in changelog - - - - - 7 changed files: - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - testsuite/tests/interface-stability/base-exports.stdout Changes: ===================================== libraries/base/base.cabal.in ===================================== @@ -46,8 +46,10 @@ Library , Data.Bifoldable1 , Data.Bifunctor , Data.Bitraversable + , Data.Bounded , Data.Char , Data.Complex + , Data.Enum , Data.Fixed , Data.Foldable1 , Data.Functor.Classes @@ -95,7 +97,6 @@ Library , Data.Dynamic , Data.Either , Data.Eq - , Data.Enum , Data.Foldable , Data.Function , Data.Functor ===================================== libraries/base/changelog.md ===================================== @@ -22,9 +22,11 @@ and [CLC proposal #261](https://github.com/haskell/core-libraries-committee/issues/261)) * The [deprecation process of GHC.Pack](https://gitlab.haskell.org/ghc/ghc/-/issues/21461) has come its term. The module has now been removed from `base`. * Propagate HasCallStack from `errorCallWithCallStackException` to exception backtraces, fixing a bug in the implementation of [CLC proposal #164](https://github.com/haskell/core-libraries-committee/issues/164). + * Introduce `Data.Bounded` module exporting the `Bounded` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) -## 4.20.0.0 May 2024 +## 4.20.0.0 *May 2024* * Shipped with GHC 9.10.1 + * Introduce `Data.Enum` module exporting both `Enum` and `Bounded`. Note that the export of `Bounded` will be deprecated in a future release ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) * Export `foldl'` from `Prelude` ([CLC proposal #167](https://github.com/haskell/core-libraries-committee/issues/167)) * The top-level handler for uncaught exceptions now displays the output of `displayException` rather than `show` ([CLC proposal #198](https://github.com/haskell/core-libraries-committee/issues/198)) ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs ===================================== @@ -2,21 +2,23 @@ ----------------------------------------------------------------------------- -- | --- Module : GHC.Internal.Data.Enum +-- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE -- --- Maintainer : ghc-devs at haskell.org +-- Maintainer : cvs-ghc at haskell.org -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Bounded' classes. +-- +-- @since 4.21.0.0 -- ----------------------------------------------------------------------------- -module GHC.Internal.Data.Enum +module Data.Bounded ( Bounded(..) - , Enum(..) ) where -import GHC.Internal.Enum +import GHC.Enum + ===================================== libraries/base/src/Data/Enum.hs ===================================== @@ -1,7 +1,7 @@ -{-# LANGUAGE Safe #-} +{-# LANGUAGE NoImplicitPrelude #-} +----------------------------------------------------------------------------- -- | --- -- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE @@ -10,12 +10,16 @@ -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Enum' class. +-- +-- @since 4.20.0.0 -- +----------------------------------------------------------------------------- module Data.Enum - (Bounded(..), - Enum(..) - ) where + ( Enum(..) + {-# DEPRECATED "Bounded should be imported from Data.Bounded" #-} + , Bounded(..) + ) where -import GHC.Internal.Data.Enum \ No newline at end of file +import GHC.Internal.Enum ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -117,7 +117,6 @@ Library GHC.Internal.Data.Dynamic GHC.Internal.Data.Either GHC.Internal.Data.Eq - GHC.Internal.Data.Enum GHC.Internal.Data.Foldable GHC.Internal.Data.Function GHC.Internal.Data.Functor ===================================== libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs ===================================== @@ -18,7 +18,7 @@ import GHC.Generics (Generic) import GHC.Internal.Base import GHC.Internal.Show import GHC.Internal.Generics -import GHC.Internal.Data.Enum +import GHC.Internal.Enum #endif -- | The language extensions known to GHC. ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -744,6 +744,14 @@ module Data.Bool where otherwise :: Bool (||) :: Bool -> Bool -> Bool +module Data.Bounded where + -- Safety: Safe-Inferred + type Bounded :: * -> Constraint + class Bounded a where + minBound :: a + maxBound :: a + {-# MINIMAL minBound, maxBound #-} + module Data.Char where -- Safety: Trustworthy type Char :: * @@ -947,7 +955,7 @@ module Data.Either where rights :: forall a b. [Either a b] -> [b] module Data.Enum where - -- Safety: Safe + -- Safety: Safe-Inferred type Bounded :: * -> Constraint class Bounded a where minBound :: a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6f53d832eed89d9d35c60eb11a6d2f6ffa79a567...f09d35dd200e5517688aabde97db4196baa541e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6f53d832eed89d9d35c60eb11a6d2f6ffa79a567...f09d35dd200e5517688aabde97db4196baa541e4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 14:00:42 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 10:00:42 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] 2 commits: More renaming. Message-ID: <66fc008a99d41_2264683c3ca01966e@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: c0165aa0 by Hassan Al-Awwadi at 2024-10-01T15:33:37+02:00 More renaming. - - - - - 1741c6cf by Hassan Al-Awwadi at 2024-10-01T16:00:19+02:00 updated note - - - - - 2 changed files: - compiler/GHC/Hs/Type.hs - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1088,32 +1088,47 @@ also forbids them in types involved with `deriving`: * * ************************************************************************ -Note [Lifecycle of a FieldOcc] +Note [Lifecycle of an UpdFieldOcc] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -A field occurrence (FieldOcc) has a slightly special lifecycle because field -occurrences may be deemed /ambiguous/ during renaming. Ambiguous field -occurrences can only be resolved during typechecking (since we do type-directed -disambiguation). To accommodate the fact that we may be unable to produce a -`Name` for a `FieldOcc` during renaming, `FieldOcc` is extended with -`AmbiguousFieldOcc` during renaming. Here's the life cycle: - -* The `FieldOcc` constructor of the `FieldOcc` type always refers to an - unambiguous field occurrence. We parse field occurrences into `FieldOcc`. - -* During renaming, a FieldOcc may be ambiguous and only be resolvable - during typechecking. To construct an /ambiguous/ `FieldOcc GhcRn`, we use the - extension point for constructors, which is instanced with `AmbiguousFieldOcc`: - - (XFieldOcc . Ambiguous) :: FieldOcc GhcRn - -* During typechecking, all ambiguous field occurrences must be resolved. We - statically guarantee this by making it impossible to construct a `FieldOcc - GhcTc` with an ambiguous name: - - type instance XXFieldOcc GhcTc = DataConCantHappen - -Note that throughout this lifecycle, we preserve the `RdrName` the user -originally wrote in the extension point during renaming and typechecking. +When we have an update to a field occurance (UpdFieldOcc) of the form +rec{ label = value }, its possible that what label refers to is ambigious, +aka: that there are multiple record types with label as a field. In this case +we can't go from a RdrName in the GhcPs stage to a Name in the GhcRn stage, +because we have multiple Names we could choose from. Once we typecheck, we +also do type-directed disambiguation, so at that stage we can go directly from +a Name to an Id, modulo the disambiguation succeeding. + +To accound for this the UpdFieldOcc occurence has an instantiation for its +XXUpdFieldOcc type family: AmbiguousFieldOcc. AmbiguousFieldOcc just stores +the RdrName directly, whereas the FieldOcc (GhcPass p) field will go from +RdrName to Name to Id as the stage shifts. Note that FieldOcc also stores +the RdrName throughout its lifecycle, for exact printing purpose, after the +Parse stage this RdrName just shifts from the foLabel field to the foExt field. + +Summarised the lifecycle of a FieldOcc is like this: +* GhcPs: FieldOcc noExtField RdrName +* GhcRn: FieldOcc RdrName Name +* GhcTc: FieldOcc RdrName Id + +With its extra constructor `XFieldOcc currently being unused and disabled by +instantiation XXFieldOcc (GhcPass p) = DataConCantHappen. In most cases just +having this FieldOcc datatype is enough, but as mentioned the UpdFieldOcc case +requires a case for ambiguity. + +The lifecycle of an UpdFieldOcc is as follows +* GhcPs: + * UpdFieldOcc noExtField (FieldOcc GhcPs) + * XUpdFieldOcc DataConCantHappen +* GhcRn: + * UpdFieldOcc noExtField (FieldOCc GhcRn) + * XUpdFieldOcc AmbiguousFieldOcc +* GhcTc: + * UpdFieldOcc noExtField (FieldOCc GhcRn) + * XUpdFieldOcc DataConCantHappen + +so using DataConCantHappen we statically guarentee that when we go to a +UpdFieldOcc GhcRn to UpdFieldOcc GhcTc we either succesfully disambiguate or +error when we can't. -} -- | Ambiguous Field Occurrence @@ -1124,7 +1139,8 @@ originally wrote in the extension point during renaming and typechecking. -- originally wrote, and store the selector function after the typechecker (for -- ambiguous occurrences). -- --- Unambiguous field occurrences should be stored in the proper FieldOcc datacon of FieldOcc. +-- Unambiguous field occurrences should be stored in the proper +-- UpdFieldOcc datacon of UpdFieldOcc. -- -- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat". -- See Note [Located RdrNames] in "GHC.Hs.Expr". ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -3507,7 +3507,7 @@ instance (ExactPrint body) -- --------------------------------------------------------------------- instance (ExactPrint (LocatedA body)) - => ExactPrint (HsFieldBind (LocatedA (AmbiguousFieldOcc GhcPs)) (LocatedA body)) where + => ExactPrint (HsFieldBind (LocatedA (UpdFieldOcc GhcPs)) (LocatedA body)) where getAnnotationEntry _ = NoEntryVal setAnnotationAnchor a _ _ _ = a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69e564bf991d6188cfa021c837d4e2c747e9b38a...1741c6cf917707c4126b77ef05eb7f6d6ab173d9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69e564bf991d6188cfa021c837d4e2c747e9b38a...1741c6cf917707c4126b77ef05eb7f6d6ab173d9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 14:05:46 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 10:05:46 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 6 commits: Bump GHC version to 9.13 Message-ID: <66fc01b9d9340_22646888415421524@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC Commits: e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - e362d34f by Ben Gamari at 2024-10-01T09:59:13-04:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 4b7aba68 by Ben Gamari at 2024-10-01T09:59:13-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - fa3a9d0f by Ben Gamari at 2024-10-01T09:59:13-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - a2b02e8d by Ben Gamari at 2024-10-01T09:59:13-04:00 base: Mention incorrect Data.Enum addition in changelog - - - - - 3547f0df by Ben Gamari at 2024-10-01T10:05:15-04:00 deprecate - - - - - 12 changed files: - configure.ac - − docs/users_guide/9.12.1-notes.rst - + docs/users_guide/9.14.1-notes.rst - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - testsuite/tests/interface-stability/base-exports.stdout - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== configure.ac ===================================== @@ -13,7 +13,7 @@ dnl # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) +AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.13], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) # Version on master must be X.Y (not X.Y.Z) for ProjectVersionMunged variable # to be useful (cf #19058). However, the version must have three components # (X.Y.Z) on stable branches (e.g. ghc-9.2) to ensure that pre-releases are @@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask AC_CONFIG_MACRO_DIRS([m4]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the ===================================== docs/users_guide/9.12.1-notes.rst deleted ===================================== @@ -1,283 +0,0 @@ -.. _release-9-11-1: - -Version 9.12.1 -============== - -The significant changes to the various parts of the compiler are listed in the -following sections. See the `migration guide -`_ on the GHC Wiki -for specific guidance on migrating programs to this release. - -Language -~~~~~~~~ - -- New language extension: :extension:`OrPatterns` implements `GHC Proposal #522 - `_). -- GHC Proposal `#569 `_ - "Multiline string literals" has been implemented. - The following code is now accepted by GHC:: - - {-# LANGUAGE MultilineStrings #-} - - x :: String - x = - """ - This is a - multiline - - string - - literal - """ - - This feature is guarded behind :extension:`MultilineStrings`. - -- The ordering of variables used for visible type application has been changed in two cases. - It is supposed to be left-to-right, but due to an oversight, it was wrong: - - - in an infix application ``f :: a `op` b``, it is now ``forall a op b.`` rather than - ``forall op a b.`` - - in a linear type ``f :: a %m -> b``, it is now ``forall a m b.`` rather than - ``forall a b m.``. - - This change is backwards-incompatible, although in practice we don't expect it - to cause significant disruption. - -- The built-in ``HasField`` class, used by :extension:`OverloadedRecordDot`, now - supports representation polymorphism (implementing part of `GHC Proposal #583 - `_). - This means that code using :extension:`UnliftedDatatypes` or - :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`. - -- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension - (`#22155 `_). - -- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)`` - is used as the one and only function argument. - -- The venerable ``default`` declarations have been generalized. They can now name a class - other than ``Num`` and the class defaults can be exported. The functionality is guarded - by the new ``NamedDefaults`` language extension. See the `GHC proposal - `__ - for details. - -- GHC now takes COMPLETE pragmas into consideration when deciding whether - pattern matches in do notation are fallible. - -- As part of `GHC Proposal #281 `_ - GHC now accepts type syntax in expressions, namely function type arrow ``a -> b``, - constraint arrow ``a => b``, and ``forall`` telescopes: :: - - g = f (forall a. Show a => a -> String) - where f :: forall a -> ... - -- In accordance with `GHC Proposal #425 `_, - GHC now permits wildcard binders in type declarations: :: - - type Const a b = a -- before: the `b` had to be named even if unused on the RHS - type Const a _ = a -- now: the compiler accepts a wildcard binder `_` - -Compiler -~~~~~~~~ - -- Constructor ``PluginProv`` of type ``UnivCoProvenance``, relevant - for typing plugins, gets an extra ``DCoVarSet`` argument. - The argument is intended to contain the in-scope coercion variables - that the the proof represented by the coercion makes use of. - See ``Note [The importance of tracking UnivCo dependencies]`` - in ``GHC.Core.TyCo.Rep``, :ref:`constraint-solving-with-plugins` - and the migration guide. - -- The flag :ghc-flag:`-fprof-late` will no longer prevent top level constructors from being statically allocated. - - It used to be the case that we would add a cost centre for bindings like ``foo = Just bar``. - This turned the binding into a CAF that would allocate the constructor on first evaluation. - - However without the cost centre ``foo`` can be allocated at compile time. This reduces code-bloat and - reduces overhead for short-running applications. - - The tradeoff is that calling ``whoCreated`` on top level value definitions like ``foo`` will be less informative. - -- A new flag :ghc-flag:`-fexpose-overloaded-unfoldings` has been added providing a lightweight alternative to :ghc-flag:`-fexpose-all-unfoldings`. - -- :ghc-flag:`-Wderiving-typeable` has been added to :ghc-flag:`-Wall`. - -- SIMD support has been added to the X86 native code generator. - For the time being, only 128 bit wide vectors are supported, with most - floating-point operations implemented, together with a few integer vector - operations. Other operations still require the LLVM backend. Contributors - welcome! - -- i386 Windows support is now completely removed amid massive cleanup - of legacy code to pave way for Arm64 Windows support (`#24883 - `_). Rest - assured, this does not impact existing support for x86_64 Windows or - i386 Linux. For end users, the ``stdcall`` C calling convention is - now fully deprecated and GHC will unconditionally produce a warning - and treat it as ``ccall``. All C import/export declarations on - Windows should now use ``ccall``. - -- 32-bit macOS/iOS support has also been completely removed (`#24921 - `_). This does - not affect existing support of apple systems on x86_64/aarch64. - -- The flag :ghc-flag:`-fignore-asserts` will now also enable the - :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967 - `_). - This enables people to write their own custom assertion functions. - See :ref:`assertions`. - -- The flag :ghc-flag:`-fkeep-auto-rules` that forces GHC to keep auto generated - specialization rules was added. It was actually added ghc-9.10.1 already but - mistakenly not mentioned in the 9.10.1 changelog. - -- Fixed a bug that caused GHC to panic when using the aarch64 ncg and -fregs-graph - on certain programs. (#24941) - -- A new warning :ghc-flag:`-Wview-pattern-signatures` is introduced to notify users about - future changes in parsing of view patterns in combination with pattern signatures - -- GHC now includes a new experimental flag, :ghc-flag:`-fobject-determinism`, - which enables deterministic object code generation, with a minor trade-off in - compilation speed (typically a 1-2% regression). Note, however, that this - flag doesn't yet ensure determinism across all compilation configurations; we - anticipate these cases will be addressed in future updates (:ghc-ticket:`12935`). - -GHCi -~~~~ - -- Fix a bug where GHCi would not start alongside a local file called ``Prelude.hs`` - or ``Prelude.lhs`` (:ghc-ticket:`10920`). - - -Runtime system -~~~~~~~~~~~~~~ - -- Reduce fragmentation incurred by the nonmoving GC's segment allocator. In one application this reduced resident set size by 26%. See :ghc-ticket:`24150`. - -- Memory return logic now uses live bytes rather than live blocks to measure the size of the heap. - This primarily affects the non-moving GC, which should now be more willing to return memory to the OS. - Users who have fine-tuned the :rts-flag:`-F ⟨factor⟩`, :rts-flag:`-Fd ⟨factor⟩`, or :rts-flag:`-O ⟨size⟩` flags, - and use the non-moving GC, should see if adjustments are needed in light of this change. - -- The new runtime flag :rts-flag:`--read-tix-file=\` allows to modify whether a preexisting .tix file is read in at the beginning of a program run. - The default is currently ``--read-tix-file=yes`` but will change to ``--read-tix-file=no`` in a future version of GHC. - For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing ``--read-tix-file=yes``. - Details can be found in `GHC proposal 612 `__. - -Cmm -~~~ - -- The ``bits128``, ``bits256`` and ``bits512`` types have been removed, in - favour of ``vec128``, ``vec256`` and ``vec512``. - -- The ``[*]`` jump annotation ("all registers live") has been removed, in favour - of more specific annotations ``GP_ARG_REGS`` (all general-purpose registers - live), ``SCALAR_ARG_REGS`` (all scalar registers live), and ``V16_ARG_REGS``, - ``V32_ARG_REGS`` and ``V64_ARG_REGS`` (meaning: all scalar registers plus - all vector registers up to the given vector width in bytes). - -``base`` library -~~~~~~~~~~~~~~~~ - -- Propagate HasCallStack from `errorCallWithCallStackException` to exception backtraces, fixing a bug in the implementation of `CLC proposal 164 `. - -- Add exception type metadata to SomeException's displayException and - "Exception:" header to the default handler - (i.e. ``GHC.Conc.Sync.uncaughtExceptionHandler``): - - https://github.com/haskell/core-libraries-committee/issues/231 - https://github.com/haskell/core-libraries-committee/issues/261 - -- The `deprecation process of GHC.Pack ` has come its term. The module has now been removed from ``base``. - -``ghc-prim`` library -~~~~~~~~~~~~~~~~~~~~ - -- Usage of deprecated primops is now correctly reported (#19629). -- New primops `isMutableByteArrayWeaklyPinned#` and `isByteArrayWeaklyPinned#` - to allow users to avoid copying large arrays safely when dealing with ffi. - See the users guide for more details on the different kinds of - pinned arrays in 9.12. - - This need for this distinction originally surfaced in https://gitlab.haskell.org/ghc/ghc/-/issues/22255 - -- New fused multiply-add instructions for vectors of floating-point values, - such as ``fmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#`` and - ``fnmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#``. - These follow the same semantics as ``fmadd``/``fmsub``/``fnmadd``/``fnmsub``, - operating in parallel on vectors of floating-point values. - -- New vector shuffle instructions, such as ``shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#``. - These instructions take two input vectors and a collection of indices (which must - be compile-time literal integers), and constructs a result vector by extracting - out the values at those indices. For instance, ``shuffleFloatX4#`` on input vectors with - components ``(# 0.1#, 11.1#, 22.1#, 33.1# #)`` and ``(# 44.1#, 55.1#, 66.1#, 77.1# #)``, - and indices ``(# 4#, 3#, 6#, 1# #)``, will return a vector with components - ``(# 44.1#, 33.1#, 66.1#, 11.1# #)``. - -- New instructions for minimum/maximum, such as `minDouble#` and - `minFloatX4#`. These instructions compute the minimum/maximum of their inputs, - working component-wise for SIMD vectors. Supported argument types are vector - integer values (e.g. `Word16X8#`, `Int32X4#` etc) and both scalar and vector - floating point values (e.g. `Float#`, `DoubleX2#`, `FloatX8#` etc). - -``ghc`` library -~~~~~~~~~~~~~~~ - -``ghc-heap`` library -~~~~~~~~~~~~~~~~~~~~ - -``ghc-experimental`` library -~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -``template-haskell`` library -~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -Included libraries -~~~~~~~~~~~~~~~~~~ - -The package database provided with this distribution also contains a number of -packages other than GHC itself. See the changelogs provided with these packages -for further change information. - -.. ghc-package-list:: - - libraries/array/array.cabal: Dependency of ``ghc`` library - libraries/base/base.cabal: Core library - libraries/binary/binary.cabal: Dependency of ``ghc`` library - libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library - libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility - libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility - libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library - libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library - libraries/directory/directory.cabal: Dependency of ``ghc`` library - libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library - libraries/filepath/filepath.cabal: Dependency of ``ghc`` library - compiler/ghc.cabal: The compiler itself - libraries/ghci/ghci.cabal: The REPL interface - libraries/ghc-boot/ghc-boot.cabal: Internal compiler library - libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library - libraries/ghc-compact/ghc-compact.cabal: Core library - libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library - libraries/ghc-prim/ghc-prim.cabal: Core library - utils/haddock/haddock-api/haddock-api.cabal: Dependency of ``haddock`` executable - utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable - libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable - libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable - libraries/integer-gmp/integer-gmp.cabal: Core library - libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library - libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library - libraries/pretty/pretty.cabal: Dependency of ``ghc`` library - libraries/process/process.cabal: Dependency of ``ghc`` library - libraries/stm/stm.cabal: Dependency of ``haskeline`` library - libraries/template-haskell/template-haskell.cabal: Core library - libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library - libraries/text/text.cabal: Dependency of ``Cabal`` library - libraries/time/time.cabal: Dependency of ``ghc`` library - libraries/transformers/transformers.cabal: Dependency of ``ghc`` library - libraries/unix/unix.cabal: Dependency of ``ghc`` library - libraries/Win32/Win32.cabal: Dependency of ``ghc`` library - libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable - libraries/os-string/os-string.cabal: Dependency of ``filepath`` library - libraries/file-io/file-io.cabal: Dependency of ``directory`` library ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -0,0 +1,90 @@ +.. _release-9-14-1: + +Version 9.14.1 +============== + +The significant changes to the various parts of the compiler are listed in the +following sections. See the `migration guide +`_ on the GHC Wiki +for specific guidance on migrating programs to this release. + +Language +~~~~~~~~ + +Compiler +~~~~~~~~ + +GHCi +~~~~ + +Runtime system +~~~~~~~~~~~~~~ + +Cmm +~~~ + +``base`` library +~~~~~~~~~~~~~~~~ + +``ghc-prim`` library +~~~~~~~~~~~~~~~~~~~~ + +``ghc`` library +~~~~~~~~~~~~~~~ + +``ghc-heap`` library +~~~~~~~~~~~~~~~~~~~~ + +``ghc-experimental`` library +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +``template-haskell`` library +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Included libraries +~~~~~~~~~~~~~~~~~~ + +The package database provided with this distribution also contains a number of +packages other than GHC itself. See the changelogs provided with these packages +for further change information. + +.. ghc-package-list:: + + libraries/array/array.cabal: Dependency of ``ghc`` library + libraries/base/base.cabal: Core library + libraries/binary/binary.cabal: Dependency of ``ghc`` library + libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library + libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility + libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility + libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library + libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library + libraries/directory/directory.cabal: Dependency of ``ghc`` library + libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library + libraries/filepath/filepath.cabal: Dependency of ``ghc`` library + compiler/ghc.cabal: The compiler itself + libraries/ghci/ghci.cabal: The REPL interface + libraries/ghc-boot/ghc-boot.cabal: Internal compiler library + libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library + libraries/ghc-compact/ghc-compact.cabal: Core library + libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library + libraries/ghc-prim/ghc-prim.cabal: Core library + utils/haddock/haddock-api/haddock-api.cabal: Dependency of ``haddock`` executable + utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable + libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable + libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable + libraries/integer-gmp/integer-gmp.cabal: Core library + libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library + libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library + libraries/pretty/pretty.cabal: Dependency of ``ghc`` library + libraries/process/process.cabal: Dependency of ``ghc`` library + libraries/stm/stm.cabal: Dependency of ``haskeline`` library + libraries/template-haskell/template-haskell.cabal: Core library + libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library + libraries/text/text.cabal: Dependency of ``Cabal`` library + libraries/time/time.cabal: Dependency of ``ghc`` library + libraries/transformers/transformers.cabal: Dependency of ``ghc`` library + libraries/unix/unix.cabal: Dependency of ``ghc`` library + libraries/Win32/Win32.cabal: Dependency of ``ghc`` library + libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable + libraries/os-string/os-string.cabal: Dependency of ``filepath`` library + libraries/file-io/file-io.cabal: Dependency of ``directory`` library ===================================== libraries/base/base.cabal.in ===================================== @@ -46,8 +46,10 @@ Library , Data.Bifoldable1 , Data.Bifunctor , Data.Bitraversable + , Data.Bounded , Data.Char , Data.Complex + , Data.Enum , Data.Fixed , Data.Foldable1 , Data.Functor.Classes @@ -95,7 +97,6 @@ Library , Data.Dynamic , Data.Either , Data.Eq - , Data.Enum , Data.Foldable , Data.Function , Data.Functor ===================================== libraries/base/changelog.md ===================================== @@ -22,9 +22,11 @@ and [CLC proposal #261](https://github.com/haskell/core-libraries-committee/issues/261)) * The [deprecation process of GHC.Pack](https://gitlab.haskell.org/ghc/ghc/-/issues/21461) has come its term. The module has now been removed from `base`. * Propagate HasCallStack from `errorCallWithCallStackException` to exception backtraces, fixing a bug in the implementation of [CLC proposal #164](https://github.com/haskell/core-libraries-committee/issues/164). + * Introduce `Data.Bounded` module exporting the `Bounded` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) -## 4.20.0.0 May 2024 +## 4.20.0.0 *May 2024* * Shipped with GHC 9.10.1 + * Introduce `Data.Enum` module exporting both `Enum` and `Bounded`. Note that the export of `Bounded` will be deprecated in a future release ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) * Export `foldl'` from `Prelude` ([CLC proposal #167](https://github.com/haskell/core-libraries-committee/issues/167)) * The top-level handler for uncaught exceptions now displays the output of `displayException` rather than `show` ([CLC proposal #198](https://github.com/haskell/core-libraries-committee/issues/198)) ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs ===================================== @@ -2,21 +2,23 @@ ----------------------------------------------------------------------------- -- | --- Module : GHC.Internal.Data.Enum +-- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE -- --- Maintainer : ghc-devs at haskell.org +-- Maintainer : cvs-ghc at haskell.org -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Bounded' classes. +-- +-- @since 4.21.0.0 -- ----------------------------------------------------------------------------- -module GHC.Internal.Data.Enum +module Data.Bounded ( Bounded(..) - , Enum(..) ) where -import GHC.Internal.Enum +import GHC.Enum + ===================================== libraries/base/src/Data/Enum.hs ===================================== @@ -1,7 +1,7 @@ -{-# LANGUAGE Safe #-} +{-# LANGUAGE NoImplicitPrelude #-} +----------------------------------------------------------------------------- -- | --- -- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE @@ -10,12 +10,16 @@ -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Enum' class. +-- +-- @since 4.20.0.0 -- +----------------------------------------------------------------------------- module Data.Enum - (Bounded(..), - Enum(..) - ) where + ( Enum(..) + , {-# DEPRECATED "Bounded should be imported from Data.Bounded" #-} + Bounded(..) + ) where -import GHC.Internal.Data.Enum \ No newline at end of file +import GHC.Internal.Enum ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -117,7 +117,6 @@ Library GHC.Internal.Data.Dynamic GHC.Internal.Data.Either GHC.Internal.Data.Eq - GHC.Internal.Data.Enum GHC.Internal.Data.Foldable GHC.Internal.Data.Function GHC.Internal.Data.Functor ===================================== libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs ===================================== @@ -18,7 +18,7 @@ import GHC.Generics (Generic) import GHC.Internal.Base import GHC.Internal.Show import GHC.Internal.Generics -import GHC.Internal.Data.Enum +import GHC.Internal.Enum #endif -- | The language extensions known to GHC. ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -744,6 +744,14 @@ module Data.Bool where otherwise :: Bool (||) :: Bool -> Bool -> Bool +module Data.Bounded where + -- Safety: Safe-Inferred + type Bounded :: * -> Constraint + class Bounded a where + minBound :: a + maxBound :: a + {-# MINIMAL minBound, maxBound #-} + module Data.Char where -- Safety: Trustworthy type Char :: * @@ -947,7 +955,7 @@ module Data.Either where rights :: forall a b. [Either a b] -> [b] module Data.Enum where - -- Safety: Safe + -- Safety: Safe-Inferred type Bounded :: * -> Constraint class Bounded a where minBound :: a ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -79,7 +79,7 @@ library -- this package typically supports only single major versions build-depends: base >= 4.16 && < 4.21 - , ghc ^>= 9.12 + , ghc ^>= 9.13 , haddock-library ^>= 1.11 , xhtml ^>= 3000.2.2 , parsec ^>= 3.1.13.0 ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -139,7 +139,7 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if MIN_VERSION_ghc(9,9,0) && !MIN_VERSION_ghc(9,12,0) +#if MIN_VERSION_ghc(9,11,0) && !MIN_VERSION_ghc(9,14,0) binaryInterfaceVersion = 44 binaryInterfaceVersionCompatibility :: [Word16] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f09d35dd200e5517688aabde97db4196baa541e4...3547f0df8419d1ae5ab764b19182e545ee3f0227 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f09d35dd200e5517688aabde97db4196baa541e4...3547f0df8419d1ae5ab764b19182e545ee3f0227 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 14:16:34 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 10:16:34 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] notes updated Message-ID: <66fc0442c8ec3_2264689f8f6c229dc@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: e6cc1d4d by Hassan Al-Awwadi at 2024-10-01T16:16:01+02:00 notes updated - - - - - 1 changed file: - compiler/GHC/Hs/Type.hs Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1088,32 +1088,47 @@ also forbids them in types involved with `deriving`: * * ************************************************************************ -Note [Lifecycle of a FieldOcc] +Note [Lifecycle of an UpdFieldOcc] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -A field occurrence (FieldOcc) has a slightly special lifecycle because field -occurrences may be deemed /ambiguous/ during renaming. Ambiguous field -occurrences can only be resolved during typechecking (since we do type-directed -disambiguation). To accommodate the fact that we may be unable to produce a -`Name` for a `FieldOcc` during renaming, `FieldOcc` is extended with -`AmbiguousFieldOcc` during renaming. Here's the life cycle: - -* The `FieldOcc` constructor of the `FieldOcc` type always refers to an - unambiguous field occurrence. We parse field occurrences into `FieldOcc`. - -* During renaming, a FieldOcc may be ambiguous and only be resolvable - during typechecking. To construct an /ambiguous/ `FieldOcc GhcRn`, we use the - extension point for constructors, which is instanced with `AmbiguousFieldOcc`: - - (XFieldOcc . Ambiguous) :: FieldOcc GhcRn - -* During typechecking, all ambiguous field occurrences must be resolved. We - statically guarantee this by making it impossible to construct a `FieldOcc - GhcTc` with an ambiguous name: - - type instance XXFieldOcc GhcTc = DataConCantHappen - -Note that throughout this lifecycle, we preserve the `RdrName` the user -originally wrote in the extension point during renaming and typechecking. +When we have an update to a field occurrence (UpdFieldOcc) of the form +rec{ label = value }, its possible that what label refers to is ambiguous, +aka: that there are multiple record types with label as a field. In this case +we can't go from a RdrName in the GhcPs stage to a Name in the GhcRn stage, +because we have multiple Names we could choose from. Once we typecheck, we +also do type-directed disambiguation, so at that stage we can go directly from +a Name to an Id, modulo the disambiguation succeeding. + +To account for this the UpdFieldOcc occurrence has an instantiation for its +XXUpdFieldOcc type family: AmbiguousFieldOcc. AmbiguousFieldOcc just stores +the RdrName directly, whereas the FieldOcc (GhcPass p) field will go from +RdrName to Name to Id as the stage shifts. Note that FieldOcc also stores +the RdrName throughout its lifecycle, for exact printing purpose, after the +Parse stage this RdrName just shifts from the foLabel field to the foExt field. + +Summarised the lifecycle of a FieldOcc is like this: +* GhcPs: FieldOcc noExtField RdrName +* GhcRn: FieldOcc RdrName Name +* GhcTc: FieldOcc RdrName Id + +With its extra constructor `XFieldOcc currently being unused and disabled by +instantiation XXFieldOcc (GhcPass p) = DataConCantHappen. In most cases just +having this FieldOcc datatype is enough, but as mentioned the UpdFieldOcc case +requires a case for ambiguity. + +The lifecycle of an UpdFieldOcc is as follows +* GhcPs: + * UpdFieldOcc noExtField (FieldOcc GhcPs) + * XUpdFieldOcc DataConCantHappen +* GhcRn: + * UpdFieldOcc noExtField (FieldOCc GhcRn) + * XUpdFieldOcc AmbiguousFieldOcc +* GhcTc: + * UpdFieldOcc noExtField (FieldOCc GhcRn) + * XUpdFieldOcc DataConCantHappen + +so using DataConCantHappen we statically guarantee that when we go to a +UpdFieldOcc GhcRn to UpdFieldOcc GhcTc we either succesfully disambiguate or +error when we can't. -} -- | Ambiguous Field Occurrence @@ -1124,7 +1139,8 @@ originally wrote in the extension point during renaming and typechecking. -- originally wrote, and store the selector function after the typechecker (for -- ambiguous occurrences). -- --- Unambiguous field occurrences should be stored in the proper FieldOcc datacon of FieldOcc. +-- Unambiguous field occurrences should be stored in the proper +-- UpdFieldOcc datacon of UpdFieldOcc. -- -- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat". -- See Note [Located RdrNames] in "GHC.Hs.Expr". View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6cc1d4d231d81b46cdc77206e1a753f5fa6717f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6cc1d4d231d81b46cdc77206e1a753f5fa6717f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 14:25:42 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 01 Oct 2024 10:25:42 -0400 Subject: [Git][ghc/ghc][wip/T25281] Add -Wno-incomplete-recored-selectors to cabal build Message-ID: <66fc0666588a4_226468b185dc29762@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: b36088e3 by Simon Peyton Jones at 2024-10-01T15:24:44+01:00 Add -Wno-incomplete-recored-selectors to cabal build This change is a temporary fix, until https://github.com/haskell/cabal/issues/10402 is addressed - - - - - 1 changed file: - hadrian/src/Settings/Warnings.hs Changes: ===================================== hadrian/src/Settings/Warnings.hs ===================================== @@ -71,7 +71,12 @@ ghcWarningsArgs = do , package stm ? pure [ "-Wno-deriving-typeable" ] , package osString ? pure [ "-Wno-deriving-typeable" ] , package parsec ? pure [ "-Wno-deriving-typeable" ] - , package cabal ? pure [ "-Wno-deriving-typeable" ] + + , package cabal ? pure [ "-Wno-deriving-typeable", "-Wno-incomplete-record-selectors" ] + -- The -Wno-incomplete-record-selectors is due to + -- https://github.com/haskell/cabal/issues/10402 + -- If that ticket is fixed, bwe can remove the flag again + , package cabalSyntax ? pure [ "-Wno-deriving-typeable" ] , package time ? pure [ "-Wno-deriving-typeable" ] , package transformers ? pure [ "-Wno-unused-matches" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b36088e39ab3a970071a21c8ecea44ed1a6f1e98 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b36088e39ab3a970071a21c8ecea44ed1a6f1e98 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 14:32:11 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 01 Oct 2024 10:32:11 -0400 Subject: [Git][ghc/ghc][wip/exception-propagate] 2 commits: Exception rethrowing Message-ID: <66fc07ebeefdb_226468b18dc034978@gitlab.mail> Rodrigo Mesquita pushed to branch wip/exception-propagate at Glasgow Haskell Compiler / GHC Commits: f3e85157 by Matthew Pickering at 2024-10-01T15:32:03+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - a638506c by Rodrigo Mesquita at 2024-10-01T15:32:03+01:00 Add test for #25300 - - - - - 30 changed files: - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs - libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/concurrent/should_run/T3279.hs - + testsuite/tests/exceptions/T25300.hs - + testsuite/tests/exceptions/T25300a.stdout - testsuite/tests/exceptions/all.T - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f959142263a0fccbc0b7b9328104a60283de9e49...a638506ccbffe35424f753a617954eb5775ae8b4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f959142263a0fccbc0b7b9328104a60283de9e49...a638506ccbffe35424f753a617954eb5775ae8b4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 15:14:11 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 01 Oct 2024 11:14:11 -0400 Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 5 commits: Remove redundant CallStack from exceptions Message-ID: <66fc11c3c02fb_226468110ce8470584@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC Commits: 9e0cebe8 by Rodrigo Mesquita at 2024-10-01T16:05:02+01:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack CLC proposal#285 Fixes #25283 - - - - - cc61ea80 by Rodrigo Mesquita at 2024-10-01T16:13:12+01:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 6219a5b1 by Rodrigo Mesquita at 2024-10-01T16:13:19+01:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - 39e91345 by Rodrigo Mesquita at 2024-10-01T16:13:19+01:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - 1186c66c by Rodrigo Mesquita at 2024-10-01T16:13:20+01:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 - - - - - 30 changed files: - compiler/GHC/Utils/Panic/Plain.hs - ghc/GHCi/UI/Monad.hs - libraries/base/src/Control/Exception.hs - libraries/base/src/GHC/Exception.hs - libraries/base/src/GHC/Stack.hs - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/T15349.stderr - libraries/base/tests/T19288.stderr - libraries/base/tests/T24807.stderr - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - − libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hs-boot - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - testsuite/tests/annotations/should_fail/annfail12.stderr - testsuite/tests/arityanal/should_run/T21694a.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/571aa8f3433cbc59cd43c4d9d072c1b9a6182e6b...1186c66cbef853505c0033534dbb4177d9c2d5e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/571aa8f3433cbc59cd43c4d9d072c1b9a6182e6b...1186c66cbef853505c0033534dbb4177d9c2d5e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 15:28:22 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 01 Oct 2024 11:28:22 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 4 commits: ghc-internal: Drop GHC.Internal.Data.Enum Message-ID: <66fc1516cc26_2264681221be482893@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC Commits: 165db637 by Ben Gamari at 2024-10-01T10:07:47-04:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - bc6bf710 by Ben Gamari at 2024-10-01T11:26:48-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 4fb85e30 by Ben Gamari at 2024-10-01T11:26:48-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - aad3bb7e by Ben Gamari at 2024-10-01T11:27:15-04:00 base: Mention incorrect Data.Enum addition in changelog - - - - - 7 changed files: - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - testsuite/tests/interface-stability/base-exports.stdout Changes: ===================================== libraries/base/base.cabal.in ===================================== @@ -46,8 +46,10 @@ Library , Data.Bifoldable1 , Data.Bifunctor , Data.Bitraversable + , Data.Bounded , Data.Char , Data.Complex + , Data.Enum , Data.Fixed , Data.Foldable1 , Data.Functor.Classes @@ -95,7 +97,6 @@ Library , Data.Dynamic , Data.Either , Data.Eq - , Data.Enum , Data.Foldable , Data.Function , Data.Functor ===================================== libraries/base/changelog.md ===================================== @@ -22,9 +22,11 @@ and [CLC proposal #261](https://github.com/haskell/core-libraries-committee/issues/261)) * The [deprecation process of GHC.Pack](https://gitlab.haskell.org/ghc/ghc/-/issues/21461) has come its term. The module has now been removed from `base`. * Propagate HasCallStack from `errorCallWithCallStackException` to exception backtraces, fixing a bug in the implementation of [CLC proposal #164](https://github.com/haskell/core-libraries-committee/issues/164). + * Introduce `Data.Bounded` module exporting the `Bounded` typeclass ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) -## 4.20.0.0 May 2024 +## 4.20.0.0 *May 2024* * Shipped with GHC 9.10.1 + * Introduce `Data.Enum` module exporting both `Enum` and `Bounded`. Note that the export of `Bounded` will be deprecated in a future release ([CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208)) * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) * Export `foldl'` from `Prelude` ([CLC proposal #167](https://github.com/haskell/core-libraries-committee/issues/167)) * The top-level handler for uncaught exceptions now displays the output of `displayException` rather than `show` ([CLC proposal #198](https://github.com/haskell/core-libraries-committee/issues/198)) ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs ===================================== @@ -1,22 +1,25 @@ +{-# LANGUAGE Safe #-} {-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | --- Module : GHC.Internal.Data.Enum +-- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE -- --- Maintainer : ghc-devs at haskell.org +-- Maintainer : cvs-ghc at haskell.org -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Bounded' classes. +-- +-- @since 4.21.0.0 -- ----------------------------------------------------------------------------- -module GHC.Internal.Data.Enum +module Data.Bounded ( Bounded(..) - , Enum(..) ) where -import GHC.Internal.Enum +import GHC.Enum + ===================================== libraries/base/src/Data/Enum.hs ===================================== @@ -1,7 +1,8 @@ {-# LANGUAGE Safe #-} +{-# LANGUAGE NoImplicitPrelude #-} +----------------------------------------------------------------------------- -- | --- -- Module : Data.Enum -- Copyright : (c) The University of Glasgow, 1992-2002 -- License : see libraries/base/LICENSE @@ -10,12 +11,16 @@ -- Stability : stable -- Portability : non-portable (GHC extensions) -- --- The 'Enum' and 'Bounded' classes. +-- The 'Enum' class. +-- +-- @since 4.20.0.0 -- +----------------------------------------------------------------------------- module Data.Enum - (Bounded(..), - Enum(..) - ) where + ( Enum(..) + , {-# DEPRECATED "Bounded should be imported from Data.Bounded" #-} + Bounded(..) + ) where -import GHC.Internal.Data.Enum \ No newline at end of file +import GHC.Internal.Enum ===================================== libraries/ghc-internal/ghc-internal.cabal.in ===================================== @@ -117,7 +117,6 @@ Library GHC.Internal.Data.Dynamic GHC.Internal.Data.Either GHC.Internal.Data.Eq - GHC.Internal.Data.Enum GHC.Internal.Data.Foldable GHC.Internal.Data.Function GHC.Internal.Data.Functor ===================================== libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs ===================================== @@ -18,7 +18,7 @@ import GHC.Generics (Generic) import GHC.Internal.Base import GHC.Internal.Show import GHC.Internal.Generics -import GHC.Internal.Data.Enum +import GHC.Internal.Enum #endif -- | The language extensions known to GHC. ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -744,6 +744,14 @@ module Data.Bool where otherwise :: Bool (||) :: Bool -> Bool -> Bool +module Data.Bounded where + -- Safety: Safe-Inferred + type Bounded :: * -> Constraint + class Bounded a where + minBound :: a + maxBound :: a + {-# MINIMAL minBound, maxBound #-} + module Data.Char where -- Safety: Trustworthy type Char :: * @@ -947,7 +955,7 @@ module Data.Either where rights :: forall a b. [Either a b] -> [b] module Data.Enum where - -- Safety: Safe + -- Safety: Safe-Inferred type Bounded :: * -> Constraint class Bounded a where minBound :: a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3547f0df8419d1ae5ab764b19182e545ee3f0227...aad3bb7effca83d809753bf61e95e0b26324aa99 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3547f0df8419d1ae5ab764b19182e545ee3f0227...aad3bb7effca83d809753bf61e95e0b26324aa99 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 15:36:20 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 11:36:20 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] fixed note pointer, unneeded imports, and unmatched datacon. Message-ID: <66fc16f463176_22646812808c48368b@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 142c8c94 by Hassan Al-Awwadi at 2024-10-01T17:36:01+02:00 fixed note pointer, unneeded imports, and unmatched datacon. the datacon is actually impossible but whatever. GHC wants what it wants. - - - - - 2 changed files: - compiler/Language/Haskell/Syntax/Type.hs - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -1360,6 +1360,7 @@ type LUpdFieldOcc pass = XRec pass (UpdFieldOcc pass) -- -- We differentiate between the two since there may be additional information concerning the update field. -- In particular, in GHC, an update field occurrence *may* be ambiguous, unlike other field occurrences. +-- See Note [Lifecycle of an UpdFieldOcc] data UpdFieldOcc pass = UpdFieldOcc { ufoExt :: XCUpdFieldOcc pass, @@ -1380,8 +1381,6 @@ type LFieldOcc pass = XRec pass (FieldOcc pass) -- We store both the 'RdrName' the user originally wrote, and after -- the renamer we use the extension field to store the selector -- function. --- --- See Note [Lifecycle of a FieldOcc] data FieldOcc pass = FieldOcc { foExt :: XCFieldOcc pass ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -53,7 +53,6 @@ import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import Language.Haskell.Syntax.Basic (FieldLabelString(..)) -import Language.Haskell.Syntax.Type (UpdFieldOcc(..), FieldOcc(..)) import Control.Monad (forM, when, unless) import Control.Monad.Identity (Identity(..)) @@ -4595,8 +4594,8 @@ instance ExactPrint (FieldOcc GhcPs) where instance ExactPrint (UpdFieldOcc GhcPs) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a - exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f - + exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f + exact f@(XUpdFieldOcc impossible) = dataConCantHappen impossible -- --------------------------------------------------------------------- instance (ExactPrint a) => ExactPrint (HsScaled GhcPs a) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/142c8c9407666563f637c147bf24249bff235422 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/142c8c9407666563f637c147bf24249bff235422 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 16:25:25 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 01 Oct 2024 12:25:25 -0400 Subject: [Git][ghc/ghc][wip/T25266] Better generalisation Message-ID: <66fc227526a6a_37391a35fde05335e@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC Commits: 44d054d4 by Simon Peyton Jones at 2024-10-01T17:23:35+01:00 Better generalisation - - - - - 3 changed files: - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Solver.hs Changes: ===================================== compiler/GHC/Tc/Deriv/Infer.hs ===================================== @@ -763,8 +763,9 @@ simplifyDeriv (DS { ds_loc = loc, ds_tvs = tvs -- See [STEP DAC HOIST] -- From the simplified constraints extract a subset 'good' that will -- become the context 'min_theta' for the derived instance. - ; let residual_simple = approximateWC True solved_wanteds - head_size = pSizeClassPred clas inst_tys + ; let (simple1, simple2) = approximateWC solved_wanteds + residual_simple = simple1 `unionBags` simple2 + head_size = pSizeClassPred clas inst_tys good = mapMaybeBag get_good residual_simple -- Returns @Just p@ (where @p@ is the type of the Ct) if a Ct is ===================================== compiler/GHC/Tc/Instance/FunDeps.hs ===================================== @@ -578,11 +578,22 @@ closeWrtFunDeps preds fixed_tvs = case classifyPredType pred of EqPred NomEq t1 t2 -> [([t1],[t2]), ([t2],[t1])] -- See Note [Equality superclasses] - ClassPred cls tys -> [ instFD fd cls_tvs tys - | let (cls_tvs, cls_fds) = classTvsFds cls - , fd <- cls_fds ] + + ClassPred cls tys | not (isIPClass cls) + -- isIPClass: see Note [closeWrtFunDeps ignores implicit parameters] + -> [ instFD fd cls_tvs tys + | let (cls_tvs, cls_fds) = classTvsFds cls + , fd <- cls_fds ] _ -> [] +{- Note [closeWrtFunDeps ignores implicit parameters] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Implicit params don't really determine a type variable (that is, we might have +IP "c" Bool and IP "c" Int in different places within the same program), and +skipping this causes implicit params to monomorphise too many variables; see +Note [Inheriting implicit parameters] in GHC.Tc.Solver. Skipping causes +typecheck/should_compile/tc219 to fail. +-} {- ********************************************************************* * * ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -48,7 +48,7 @@ import GHC.Tc.Utils.TcType import GHC.Core.Predicate import GHC.Core.Type import GHC.Core.Ppr -import GHC.Core.TyCon ( TyConBinder, isTypeFamilyTyCon ) +import GHC.Core.TyCon ( TyConBinder ) import GHC.Types.Name import GHC.Types.Id @@ -58,8 +58,9 @@ import GHC.Types.Var.Set import GHC.Types.Basic import GHC.Types.Error -import GHC.Utils.Misc +import GHC.Driver.DynFlags( DynFlags, xopt ) import GHC.Utils.Panic +import GHC.Utils.Misc( filterOut ) import GHC.Utils.Outputable import GHC.Data.Bag @@ -975,7 +976,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds -- All done! ; traceTc "} simplifyInfer/produced residual implication for quantification" $ - vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates + vcat [ text "wanted_dq =" <+> ppr wanted_dq , text "psig_theta =" <+> ppr psig_theta , text "bound_theta =" <+> pprCoreBinders bound_theta_vars , text "qtvs =" <+> ppr qtvs @@ -1290,8 +1291,8 @@ decideQuantification -- See Note [Deciding quantification] decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs wanted = do { -- Step 1: find the mono_tvs - ; (candidates, co_vars, mono_tvs0) - <- decidePromotedTyVars infer_mode name_taus psigs candidates + ; (candidates, co_vars) + <- decideAndPromoteTyVars infer_mode name_taus psigs wanted -- Step 2: default any non-mono tyvars, and re-simplify -- This step may do some unification, but result candidates is zonked @@ -1308,11 +1309,11 @@ decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs wanted do { candidates <- TcM.zonkTcTypes candidates ; psig_theta <- TcM.zonkTcTypes (concatMap sig_inst_theta psigs) ; return (candidates, psig_theta) } - ; min_theta <- pickQuantifiablePreds (mkVarSet qtvs) mono_tvs0 candidates -- Take account of partial type signatures -- See Note [Constraints in partial type signatures] ; let min_psig_theta = mkMinimalBySCs id psig_theta + min_theta = pickQuantifiablePreds (mkVarSet qtvs) candidates ; theta <- if | null psigs -> return min_theta -- Case (P3) | not (all has_extra_constraints_wildcard psigs) -- Case (P2) @@ -1396,13 +1397,36 @@ Some rationale and observations g :: forall b. Show b => F b -> _ -> b g x y = let _ = (f y, show x) in x But that's a battle for another day. + +Note [Generalising top-level bindings] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + class C a b | a -> b where .. + f x = ...[W] C Int beta[1]... + +When generalising `f`, closeWrtFunDeps will promote beta[1] to beta[0]. +But we do NOT want to make a top level type + f :: C Int beta[0] => blah +The danger is that beta[0] is defaulted to Any, and that then appears +in a user error message. Even the type `blah` mentions beta[0], /and/ +there is a call that fixes beta[0] to (say) Bool, we'll end up with +[W] C Int Bool, which is insoluble. Why insoluble? If there was an + instance C Int Bool +then fundeps would have fixed beta:=Bool in the first place. + +If the binding of `f` is nested, things are different: we can +definitely see all the calls. + +TODO: this reasoning is incomplete. Shouldn't it apply to nested +bindings too, when this promotion happens so it's not because +beta is already free in the envt??? -} -decidePromotedTyVars :: InferMode - -> [(Name,TcType)] - -> [TcIdSigInst] - -> [PredType] - -> TcM ([PredType], CoVarSet, TcTyVarSet) +decideAndPromoteTyVars :: InferMode + -> [(Name,TcType)] + -> [TcIdSigInst] + -> WantedConstraints + -> TcM ([PredType], CoVarSet) -- We are about to generalise over type variables at level N -- Each must be either -- (P) promoted @@ -1420,13 +1444,9 @@ decidePromotedTyVars :: InferMode -- -- Also return CoVars that appear free in the final quantified types -- we can't quantify over these, and we must make sure they are in scope -decidePromotedTyVars infer_mode name_taus psigs candidates +decideAndPromoteTyVars infer_mode name_taus psigs wanted = do { tc_lvl <- TcM.getTcLevel - - ; let (maybe_quant_cts, no_quant_cts) = approximateWC wanted - - - ; (no_quant, maybe_quant) <- pick infer_mode candidates + ; dflags <- getDynFlags -- If possible, we quantify over partial-sig qtvs, so they are -- not mono. Need to zonk them because they are meta-tyvar TyVarTvs @@ -1437,110 +1457,112 @@ decidePromotedTyVars infer_mode name_taus psigs candidates concatMap sig_inst_theta psigs ; taus <- mapM (TcM.zonkTcType . snd) name_taus ; return (psig_qtvs, psig_theta, taus) } - ; let psig_tys = mkTyVarTys psig_qtvs ++ psig_theta - -- (b) The co_var_tvs are tvs mentioned in the types of covars or + ; let (can_quant, no_quant) = approximateWC wanted + (post_mr_quant, mr_no_quant) = applyMR dflags infer_mode (ctsPreds can_quant) + + -- The co_var_tvs are tvs mentioned in the types of covars or -- coercion holes. We can't quantify over these covars, so we -- must include the variable in their types in the mono_tvs. -- E.g. If we can't quantify over co :: k~Type, then we can't -- quantify over k either! Hence closeOverKinds -- Recall that coVarsOfTypes also returns coercion holes - co_vars = coVarsOfTypes (psig_tys ++ taus ++ candidates) + co_vars = coVarsOfTypes (psig_tys ++ taus ++ post_mr_quant) co_var_tvs = closeOverKinds co_vars - mono_tvs0 = filterVarSet (not . isQuantifiableTv tc_lvl) $ - tyCoVarsOfTypes candidates - -- We need to grab all the non-quantifiable tyvars in the - -- types so that we can grow this set to find other - -- non-quantifiable tyvars. This can happen with something like - -- f x y = ... - -- where z = x 3 - -- The body of z tries to unify the type of x (call it alpha[1]) - -- with (beta[2] -> gamma[2]). This unification fails because - -- alpha is untouchable, leaving [W] alpha[1] ~ (beta[2] -> gamma[2]). - -- We need to know not to quantify over beta or gamma, because they - -- are in the equality constraint with alpha. Actual test case: - -- typecheck/should_compile/tc213 - - mono_tvs1 = mono_tvs0 `unionVarSet` co_var_tvs - - -- mono_tvs1 is now the set of variables from an outer scope - -- (that's mono_tvs0) and the set of covars, closed over kinds. - -- Given this set of variables we know we will not quantify, - -- we want to find any other variables that are determined by this - -- set, by functional dependencies or equalities. We thus use - -- closeWrtFunDeps to find all further variables determined by this root - -- set. See Note [growThetaTyVars vs closeWrtFunDeps] - - non_ip_candidates = filterOut isIPLikePred candidates - -- implicit params don't really determine a type variable - -- (that is, we might have IP "c" Bool and IP "c" Int in different - -- places within the same program), and - -- skipping this causes implicit params to monomorphise too many - -- variables; see Note [Inheriting implicit parameters] in GHC.Tc.Solver. - -- Skipping causes typecheck/should_compile/tc219 to fail. - - mono_tvs2 = closeWrtFunDeps non_ip_candidates mono_tvs1 - -- mono_tvs2 now contains any variable determined by the "root - -- set" of monomorphic tyvars in mono_tvs1. - - constrained_tvs = filterVarSet (isQuantifiableTv tc_lvl) $ - closeWrtFunDeps non_ip_candidates (tyCoVarsOfTypes no_quant) - `minusVarSet` mono_tvs2 - -- constrained_tvs: the tyvars that we are not going to - -- quantify /solely/ because of the monomorphism restriction - -- - -- (`minusVarSet` mono_tvs2): a type variable is only - -- "constrained" (so that the MR bites) if it is not - -- free in the environment (#13785) or is determined - -- by some variable that is free in the env't - - mono_tvs = (mono_tvs2 `unionVarSet` constrained_tvs) - `delVarSetList` psig_qtvs - -- (`delVarSetList` psig_qtvs): if the user has explicitly - -- asked for quantification, then that request "wins" - -- over the MR. + -- mono_tvs0 are all the type variables we + -- can't quantify over, ignoring the MR + mono_tvs0 = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant) + `unionVarSet` tyCoVarsOfTypes (ctsPreds no_quant) + `unionVarSet` co_var_tvs + + -- Next, use closeWrtFunDeps to find any other variables that are determined + -- by mono_tvs0 + mr_no_quant, by functional dependencies or equalities. + -- Example + -- f x y = ... + -- where z = x 3 + -- The body of z tries to unify the type of x (call it alpha[1]) + -- with (beta[2] -> gamma[2]). This unification fails because + -- alpha is untouchable, leaving [W] alpha[1] ~ (beta[2] -> gamma[2]). + -- We need to know not to quantify over beta or gamma, because they + -- are in the equality constraint with alpha. Actual test case: + -- typecheck/should_compile/tc213 + -- See Note [growThetaTyVars vs closeWrtFunDeps] + mono_tvs1 = closeWrtFunDeps post_mr_quant $ + mono_tvs0 `unionVarSet` tyCoVarsOfTypes mr_no_quant + + -- Finally, delete psig_qtvs + -- If the user has explicitly asked for quantification, then that + -- request "wins" over the MR. -- -- What if a psig variable is also free in the environment -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation -- in Step 2 of Note [Deciding quantification]. + mono_tvs = mono_tvs1 `delVarSetList` psig_qtvs + + -- Check if the Monomorphism Restriction has bitten + ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $ + do { let mono_tvs_wo_mr = closeWrtFunDeps post_mr_quant mono_tvs0 + `delVarSetList` psig_qtvs + + ; diagnosticTc (not (mono_tvs `subVarSet` mono_tvs_wo_mr)) $ + TcRnMonomorphicBindings (map fst name_taus) } + -- If there is a variable in mono_tvs, but not in mono_tvs_wo_mr + -- then the MR has "bitten" and reduced polymorphism. - -- Warn about the monomorphism restriction - ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $ do - let dia = TcRnMonomorphicBindings (map fst name_taus) - diagnosticTc (constrained_tvs `intersectsVarSet` tyCoVarsOfTypes taus) dia + -- In /top-level bindings/ do not quantify over any constraints + -- that mention a promoted tyvar. See Note [Generalising top-level bindings] + ; let final_quant | isTopTcLevel tc_lvl + = filterOut (predMentions mono_tvs) post_mr_quant + | otherwise + = post_mr_quant -- Promote the mono_tvs: see Note [Promote monomorphic tyvars] ; _ <- promoteTyVarSet mono_tvs - ; traceTc "decidePromotedTyVars" $ vcat - [ text "infer_mode =" <+> ppr infer_mode + ; traceTc "decideAndPromoteTyVars" $ vcat + [ text "tc_lvl =" <+> ppr tc_lvl + , text "top =" <+> ppr (isTopTcLevel tc_lvl) + , text "infer_mode =" <+> ppr infer_mode , text "psigs =" <+> ppr psigs , text "psig_qtvs =" <+> ppr psig_qtvs , text "mono_tvs0 =" <+> ppr mono_tvs0 + , text "can_quant =" <+> ppr can_quant + , text "post_mr_quant =" <+> ppr post_mr_quant , text "no_quant =" <+> ppr no_quant - , text "maybe_quant =" <+> ppr maybe_quant + , text "mr_no_quant =" <+> ppr mr_no_quant + , text "final_quant =" <+> ppr final_quant , text "mono_tvs =" <+> ppr mono_tvs , text "co_vars =" <+> ppr co_vars ] - ; return (maybe_quant, co_vars, mono_tvs0) } + ; return (final_quant, co_vars) } + +------------------- +applyMR :: DynFlags -> InferMode -> [PredType] + -> ( [PredType] -- Quantify over these + , [PredType] ) -- But not over these +-- Split the candidates into ones we definitely +-- won't quantify, and ones that we might +applyMR _ NoRestrictions cand = (cand, []) +applyMR _ ApplyMR cand = ([], cand) +applyMR dflags EagerDefaulting cand = partition not_int_ct cand where - pick :: InferMode -> [PredType] -> TcM ([PredType], [PredType]) - -- Split the candidates into ones we definitely - -- won't quantify, and ones that we might - pick ApplyMR cand = return (cand, []) - pick NoRestrictions cand = return ([], cand) - pick EagerDefaulting cand = do { os <- xoptM LangExt.OverloadedStrings - ; return (partition (is_int_ct os) cand) } - - -- is_int_ct returns True for a constraint we should /not/ quantify + ovl_strings = xopt LangExt.OverloadedStrings dflags + + -- not_int_ct returns True for a constraint we /can/ quantify -- For EagerDefaulting, do not quantify over -- over any interactive class constraint - is_int_ct ovl_strings pred + not_int_ct pred = case classifyPredType pred of - ClassPred cls _ -> isInteractiveClass ovl_strings cls - _ -> False + ClassPred cls _ -> not (isInteractiveClass ovl_strings cls) + _ -> True + +------------------- +outerLevelTyVars :: TcLevel -> TcTyVarSet -> TcTyVarSet +-- Find just the tyvars that are bound outside tc_lvl +outerLevelTyVars tc_lvl tvs + = filterVarSet (not . isQuantifiableTv tc_lvl) tvs ------------------- defaultTyVarsAndSimplify :: TcLevel @@ -1637,77 +1659,37 @@ decideQuantifiedTyVars skol_info name_taus psigs candidates ; quantifyTyVars skol_info DefaultNonStandardTyVars dvs_plus } ------------------ +predMentions :: TcTyVarSet -> TcPredType -> Bool +predMentions qtvs pred = tyCoVarsOfType pred `intersectsVarSet` qtvs + -- | When inferring types, should we quantify over a given predicate? -- See Note [pickQuantifiablePreds] pickQuantifiablePreds :: TyVarSet -- Quantifying over these - -> TcTyVarSet -- mono_tvs0: variables mentioned a candidate - -- constraint that come from some outer level -> TcThetaType -- Proposed constraints to quantify - -> TcM TcThetaType -- A subset that we can actually quantify + -> TcThetaType -- A subset that we can actually quantify -- This function decides whether a particular constraint should be -- quantified over, given the type variables that are being quantified -pickQuantifiablePreds qtvs mono_tvs0 theta - = do { tc_lvl <- TcM.getTcLevel - ; let is_nested = not (isTopTcLevel tc_lvl) - ; return (mkMinimalBySCs id $ -- See Note [Minimize by Superclasses] - mapMaybe (pick_me is_nested) theta) } +pickQuantifiablePreds qtvs theta + = mkMinimalBySCs id $ -- See Note [Minimize by Superclasses] + mapMaybe pick_me theta where - pick_me is_nested pred - = let pred_tvs = tyCoVarsOfType pred - mentions_qtvs = pred_tvs `intersectsVarSet` qtvs - in case classifyPredType pred of - - ClassPred cls tys - | Just {} <- isCallStackPred cls tys - -- NEVER infer a CallStack constraint. Otherwise we let - -- the constraints bubble up to be solved from the outer - -- context, or be defaulted when we reach the top-level. - -- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence - -> Nothing - + pick_me pred + = case classifyPredType pred of + ClassPred cls _ | isIPClass cls -> Just pred -- See Note [Inheriting implicit parameters] - | not mentions_qtvs - -> Nothing -- Don't quantify over predicates that don't - -- mention any of the quantified type variables - - | is_nested - -> Just pred - - -- From here on, we are thinking about top-level defns only - - | pred_tvs `subVarSet` (qtvs `unionVarSet` mono_tvs0) - -- See Note [Do not quantify over constraints that determine a variable] - -> Just pred - - | otherwise - -> Nothing - EqPred eq_rel ty1 ty2 - | mentions_qtvs - , quantify_equality eq_rel ty1 ty2 + | predMentions qtvs pred , Just (cls, tys) <- boxEqPred eq_rel ty1 ty2 -- boxEqPred: See Note [Lift equality constraints when quantifying] -> Just (mkClassPred cls tys) | otherwise -> Nothing - IrredPred {} | mentions_qtvs -> Just pred - | otherwise -> Nothing - - ForAllPred {} -> Nothing - - -- See Note [Quantifying over equality constraints] - quantify_equality NomEq ty1 ty2 = quant_fun ty1 || quant_fun ty2 - quantify_equality ReprEq _ _ = True - - quant_fun ty - = case tcSplitTyConApp_maybe ty of - Just (tc, tys) | isTypeFamilyTyCon tc - -> tyCoVarsOfTypes tys `intersectsVarSet` qtvs - _ -> False + _ | predMentions qtvs pred -> Just pred + | otherwise -> Nothing ------------------ growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44d054d44765311378033d35e683038ab888ddc2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44d054d44765311378033d35e683038ab888ddc2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 16:36:24 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 01 Oct 2024 12:36:24 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fc25085329c_37391a3ced305885a@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 39a00c9e by Andreas Klebinger at 2024-10-01T12:35:52-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - a4f76409 by Andreas Klebinger at 2024-10-01T12:35:53-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 65869b04 by Sylvain Henry at 2024-10-01T12:35:56-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 66ed483e by Rodrigo Mesquita at 2024-10-01T12:35:57-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - dd49c0ff by Matthew Pickering at 2024-10-01T12:35:58-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - dd34c806 by Matthew Pickering at 2024-10-01T12:35:58-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 9f8aca27 by Matthew Pickering at 2024-10-01T12:35:59-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - 1a2729c6 by Matthew Pickering at 2024-10-01T12:35:59-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 048e98e4 by Andreas Klebinger at 2024-10-01T12:35:59-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - 19 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - m4/fptools_happy.m4 - rts/CheckVectorSupport.c - rts/posix/ticker/TimerFd.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7ddcae7304e9bbdedf4aee2ea315dc24f9024e8...048e98e4be0bc4a3babac45c5d9d64122a639cc1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7ddcae7304e9bbdedf4aee2ea315dc24f9024e8...048e98e4be0bc4a3babac45c5d9d64122a639cc1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 16:41:49 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 01 Oct 2024 12:41:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/ubuntu-22_04 Message-ID: <66fc264d54d6a_37391a73b88869265@gitlab.mail> Matthew Pickering pushed new branch wip/ubuntu-22_04 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ubuntu-22_04 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 16:47:01 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Tue, 01 Oct 2024 12:47:01 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/u22 Message-ID: <66fc27853dd07_37391a7ffc7469453@gitlab.mail> Matthew Pickering pushed new branch wip/u22 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/u22 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 17:20:05 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Tue, 01 Oct 2024 13:20:05 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] removed unused binding. Message-ID: <66fc2f45cff63_37391aaa823c804ec@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 1afadcfe by Hassan Al-Awwadi at 2024-10-01T19:19:34+02:00 removed unused binding. Its errors like these that really make me wish I could build ghc completely because an half hour long pipeline to find an error like thsi is highly annoying (and a waste of the runner) - - - - - 1 changed file: - utils/check-exact/ExactPrint.hs Changes: ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -4594,8 +4594,8 @@ instance ExactPrint (FieldOcc GhcPs) where instance ExactPrint (UpdFieldOcc GhcPs) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a - exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f - exact f@(XUpdFieldOcc impossible) = dataConCantHappen impossible + exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f + exact (XUpdFieldOcc impossible) = dataConCantHappen impossible -- --------------------------------------------------------------------- instance (ExactPrint a) => ExactPrint (HsScaled GhcPs a) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1afadcfe8d9cf7d9f024ebd56e868bf239834a8c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1afadcfe8d9cf7d9f024ebd56e868bf239834a8c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 1 23:46:43 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 01 Oct 2024 19:46:43 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fc89e3a53eb_2317f8792bd822663@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 4e446417 by Andreas Klebinger at 2024-10-01T19:46:28-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 8e96ff6d by Andreas Klebinger at 2024-10-01T19:46:29-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - df4e5c54 by Sylvain Henry at 2024-10-01T19:46:32-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 569d13b5 by Rodrigo Mesquita at 2024-10-01T19:46:33-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 6a03ec4c by Matthew Pickering at 2024-10-01T19:46:34-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - b5a3423b by Matthew Pickering at 2024-10-01T19:46:34-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - c806d61e by Matthew Pickering at 2024-10-01T19:46:35-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - 5a1f086a by Matthew Pickering at 2024-10-01T19:46:35-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - bffab14f by Andreas Klebinger at 2024-10-01T19:46:35-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - 19 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - m4/fptools_happy.m4 - rts/CheckVectorSupport.c - rts/posix/ticker/TimerFd.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/048e98e4be0bc4a3babac45c5d9d64122a639cc1...bffab14fd22d43149687212f81de19f66d770cec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/048e98e4be0bc4a3babac45c5d9d64122a639cc1...bffab14fd22d43149687212f81de19f66d770cec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 06:07:55 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 02:07:55 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fce33b60180_680d7105b2b02895b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 27126212 by Andreas Klebinger at 2024-10-02T02:07:39-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - f586a64d by Andreas Klebinger at 2024-10-02T02:07:40-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 33d87224 by Sylvain Henry at 2024-10-02T02:07:44-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - a3544729 by Rodrigo Mesquita at 2024-10-02T02:07:44-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 4d8373a2 by Matthew Pickering at 2024-10-02T02:07:45-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - ed69f747 by Matthew Pickering at 2024-10-02T02:07:45-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 9177d187 by Matthew Pickering at 2024-10-02T02:07:46-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - 3232ad02 by Matthew Pickering at 2024-10-02T02:07:46-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 517a7146 by Andreas Klebinger at 2024-10-02T02:07:46-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - 19 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - m4/fptools_happy.m4 - rts/CheckVectorSupport.c - rts/posix/ticker/TimerFd.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bffab14fd22d43149687212f81de19f66d770cec...517a7146e8bccfe9279ee37ed6f0fc243fe0f28b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bffab14fd22d43149687212f81de19f66d770cec...517a7146e8bccfe9279ee37ed6f0fc243fe0f28b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 08:37:47 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Wed, 02 Oct 2024 04:37:47 -0400 Subject: [Git][ghc/ghc][wip/T23479] 21 commits: Fix typo in Prelude doc for (>>=) Message-ID: <66fd065ba49e9_680d716efbe4509d@gitlab.mail> Serge S. Gulin pushed to branch wip/T23479 at Glasgow Haskell Compiler / GHC Commits: 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - 28b3198d by Serge S. Gulin at 2024-10-02T11:37:35+03:00 JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary)) Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/ - - - - - c9a63b0a by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Use name defined at `GHC.Builtin.Names` - - - - - 3369920a by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Apply 1 suggestion(s) to 1 file(s) Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - 3a602c9d by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Attempt to take 805 for id - - - - - c921dd45 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Attempt to add to basicKnownKeyNames Co-authored-by: Andrei Borzenkov <root at sandwitch.dev> Co-authored-by: Danil Berestov <goosedb at yandex.ru> - - - - - 02460cb2 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Naive attempt to add `StgLitArg (LitString bs)` - - - - - 2b784cf2 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 WIP add logging - - - - - feb7a942 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 WIP add logging - - - - - 94685387 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add STG debug from JS Sinker - - - - - 6b74dadd by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add eager Sinker's strings unfloater - - - - - a9e62049 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add STG debug from JS Sinker - - - - - cfc3dfd6 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add limitations to unfloat string lits - - - - - b1e7ec27 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Fix build - - - - - 00a7c409 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 String lits were removed too early, need do it at Linker instead - - - - - 91de105f by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add tracing capabilities for JS Modules - - - - - f3650b38 by Serge S. Gulin at 2024-10-02T11:37:35+03:00 Add tracing capabilities for GlobalOcc's - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/CodeGen.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Monad.hs - + compiler/GHC/StgToJS/Sinker/Collect.hs - compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs - + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs - compiler/GHC/StgToJS/Symbols.hs - compiler/GHC/StgToJS/Types.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/ForeignCall.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/285413a01582a9621cc10a4d4d9dea4a276e6598...f3650b382f006777edc1a144b5dce183d8871926 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/285413a01582a9621cc10a4d4d9dea4a276e6598...f3650b382f006777edc1a144b5dce183d8871926 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 08:49:06 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 02 Oct 2024 04:49:06 -0400 Subject: [Git][ghc/ghc][wip/T25281] 24 commits: Add entity information to HieFile #24544 Message-ID: <66fd0902f0ea7_680d7182691852790@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - 1580ec44 by Sebastian Graf at 2024-10-02T09:36:49+01:00 Desugaring, plus -Wincomplete-record-selectors This commit does several related things: * Major refactor of the handling of applications in the desugarer. Now all applications are handled in `dsApp`, `ds_app` and related functions. This dramatically simplifies the code and removes complicated cruft that had accumulated. Hooray. Fixes #25281. * Improve the handling of -Wincomplete-record-selectors. We now incorporate the result type of unsaturated record selector applications as well as consider long-distance information in getField applications. Plus, the implmentation now builds the improved `dsApp` stuff above, so it is much easier to understand. Plus, incorporates improved error message wording suggested by Adam Gundry in !12685. Fixes #24824, #24891 See the long Note [Detecting incomplete record selectors] * Add -Wincomplete-record-selectors to -Wall, as specified in GHC Proposal 516. To do this, I also had to add -Wno-incomplete-record-selectors to the build flags for Cabal in GHC's CI. See hadrian/src/Settings/Warnings.hs. We can remove this when Cabal is updated so that it doesn't trigger the warning: https://github.com/haskell/cabal/issues/10402 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/Cmm/UniqueRenamer.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b36088e39ab3a970071a21c8ecea44ed1a6f1e98...1580ec44f06f4b1330c8a8d848cef4279e2bb70c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b36088e39ab3a970071a21c8ecea44ed1a6f1e98...1580ec44f06f4b1330c8a8d848cef4279e2bb70c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 09:14:12 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 02 Oct 2024 05:14:12 -0400 Subject: [Git][ghc/ghc][wip/perf-notes-fixes] testsuite: Handle division-by-zero more gracefully Message-ID: <66fd0ee470098_680d71a1dac85815b@gitlab.mail> Matthew Pickering pushed to branch wip/perf-notes-fixes at Glasgow Haskell Compiler / GHC Commits: 73d3fab7 by Ben Gamari at 2024-10-02T10:13:35+01:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 1 changed file: - testsuite/driver/runtests.py Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -404,7 +404,10 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: return "" val0 = x.baseline.perfStat.value val1 = x.stat.value - return "{:+2.1f}%".format(100 * (val1 - val0) / val0) + if val0 == 0: + return "NaN%" + else: + return "{:+2.1f}%".format(100 * (val1 - val0) / val0) dataRows = [row(( "{}({})".format(x.stat.test, x.stat.way), shorten_metric_name(x.stat.metric), View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73d3fab7f28dbbf7e7ec1e818a72d8c024d99c3a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73d3fab7f28dbbf7e7ec1e818a72d8c024d99c3a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 10:07:49 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 06:07:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/25300 Message-ID: <66fd1b75a870_3436adf9aec180e9@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/25300 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25300 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 10:07:49 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 06:07:49 -0400 Subject: [Git][ghc/ghc][wip/exception-propagate] Exception rethrowing Message-ID: <66fd1b7578ff_3436adf9a1017912@gitlab.mail> Rodrigo Mesquita pushed to branch wip/exception-propagate at Glasgow Haskell Compiler / GHC Commits: 978abd66 by Matthew Pickering at 2024-10-02T11:06:08+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - 30 changed files: - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs - libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/concurrent/should_run/T3279.hs - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/978abd669b7bdbe816b1239eec5230cbf0855289 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/978abd669b7bdbe816b1239eec5230cbf0855289 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 10:32:53 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 06:32:53 -0400 Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] Fix exception backtraces from GHCi Message-ID: <66fd21558a08c_3436ad32b0f4261f0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC Commits: 0ece3288 by Rodrigo Mesquita at 2024-10-02T11:32:12+01:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 - - - - - 3 changed files: - ghc/GHCi/UI/Monad.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs Changes: ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -73,6 +73,7 @@ import Control.Monad import Prelude hiding ((<>)) import System.Console.Haskeline (CompletionFunc, InputT) +import Control.Exception import Control.Monad.Catch as MC import Control.Monad.Trans.Class import Control.Monad.Trans.Reader @@ -212,7 +213,9 @@ data CommandResult deriving Show cmdSuccess :: MonadThrow m => CommandResult -> m (Maybe Bool) -cmdSuccess CommandComplete{ cmdResult = Left e } = throwM e +cmdSuccess CommandComplete{ cmdResult = Left e } = + {- Don't add a backtrace from ghci/ghc to the exception from the user program! -} + throwM (NoBacktrace e) cmdSuccess CommandComplete{ cmdResult = Right r } = return r cmdSuccess CommandIncomplete = return $ Just True ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -40,6 +40,9 @@ import GHC.Fingerprint import GHC.Conc (pseq, par) import Control.Concurrent import Control.Exception +#if MIN_VERSION_base(4,20,0) +import Control.Exception.Context +#endif import Data.Binary import Data.Binary.Get import Data.Binary.Put @@ -442,7 +445,15 @@ toSerializableException :: SomeException -> SerializableException toSerializableException ex | Just UserInterrupt <- fromException ex = EUserInterrupt | Just (ec::ExitCode) <- fromException ex = (EExitCode ec) - | otherwise = EOtherException (show (ex :: SomeException)) + | otherwise = EOtherException $ +#if MIN_VERSION_base(4,20,0) + -- Exception plus backtrace as seen in `displayExceptionWithInfo` + case displayExceptionContext (someExceptionContext ex) of + "" -> displayException (ex :: SomeException) + cx -> displayException (ex :: SomeException) ++ "\n\n" ++ cx +#else + show (ex :: SomeException) +#endif fromSerializableException :: SerializableException -> SomeException fromSerializableException EUserInterrupt = toException UserInterrupt ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -252,7 +252,7 @@ sandboxIO opts io = do -- rethrow :: EvalOpts -> IO a -> IO a rethrow EvalOpts{..} io = - catch io $ \se -> do + catchNoPropagate io $ \(ExceptionWithContext cx se) -> do -- If -fbreak-on-error, we break unconditionally, -- but with care of not breaking twice if breakOnError && not breakOnException @@ -263,7 +263,7 @@ rethrow EvalOpts{..} io = Just UserInterrupt -> return () -- In any other case, we don't want to break _ -> poke exceptionFlag 0 - throwIO se + rethrowIO (ExceptionWithContext cx se) -- -- While we're waiting for the sandbox thread to return a result, if View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ece32881a3dd78d364d6c2ae325388a2c44152f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ece32881a3dd78d364d6c2ae325388a2c44152f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 10:41:39 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 06:41:39 -0400 Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 5 commits: Remove redundant CallStack from exceptions Message-ID: <66fd2363a8f35_3436ad4eef3026435@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC Commits: dce7af67 by Rodrigo Mesquita at 2024-10-02T11:34:31+01:00 Remove redundant CallStack from exceptions Before the exception backtraces proposal was implemented, ErrorCall accumulated its own callstack via HasCallStack constraints, but ExceptionContext is now accumulated automatically. The original ErrorCall mechanism is now redundant and we get a duplicate CallStack Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall CLC proposal#285 Fixes #25283 - - - - - 0f108aa3 by Rodrigo Mesquita at 2024-10-02T11:35:37+01:00 Freeze call stack in error throwing functions CLC proposal#285 - - - - - 819a4208 by Rodrigo Mesquita at 2024-10-02T11:41:17+01:00 De-duplicate displayContext and displayExceptionContext The former was unused except for one module where it was essentially re-defining displayExceptionContext. Moreover, this commit extends the fix from bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too, which was missing. - - - - - c5db7e20 by Rodrigo Mesquita at 2024-10-02T11:41:17+01:00 Re-export NoBacktrace from Control.Exception This was originally proposed and accepted in section "2.7 Capturing Backtraces on Exceptions" of the CLC proposal for exception backtraces. However, the implementation missed this re-export, which this commit now fixes. - - - - - e807846d by Rodrigo Mesquita at 2024-10-02T11:41:17+01:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 - - - - - 30 changed files: - compiler/GHC/Utils/Panic/Plain.hs - ghc/GHCi/UI/Monad.hs - libraries/Cabal - libraries/base/src/Control/Exception.hs - libraries/base/src/GHC/Exception.hs - libraries/base/src/GHC/Stack.hs - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/T15349.stderr - libraries/base/tests/T19288.stderr - libraries/base/tests/T24807.stderr - libraries/base/tests/all.T - libraries/base/tests/assert.stderr - − libraries/base/tests/topHandler04.hs - − libraries/base/tests/topHandler04.stderr - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs - libraries/ghc-internal/src/GHC/Internal/Stack.hs-boot - − libraries/ghc-internal/src/GHC/Internal/Stack/CCS.hs-boot - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - testsuite/tests/annotations/should_fail/annfail12.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ece32881a3dd78d364d6c2ae325388a2c44152f...e807846d49e0c9a8ae69d93ad4d0eca882b4fba8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ece32881a3dd78d364d6c2ae325388a2c44152f...e807846d49e0c9a8ae69d93ad4d0eca882b4fba8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 10:50:19 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 06:50:19 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/bump-cabal Message-ID: <66fd256bdbc98_3436ad5d7cf82679e@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/bump-cabal at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/bump-cabal You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 11:22:29 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Wed, 02 Oct 2024 07:22:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/cabal-3.14 Message-ID: <66fd2cf55b2e2_3436ad901d703237e@gitlab.mail> Zubin pushed new branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/cabal-3.14 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 11:32:18 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 02 Oct 2024 07:32:18 -0400 Subject: [Git][ghc/ghc][wip/perf-notes-fixes] testsuite: Handle division-by-zero more gracefully Message-ID: <66fd2f4233314_3436ad9da4a44258e@gitlab.mail> Matthew Pickering pushed to branch wip/perf-notes-fixes at Glasgow Haskell Compiler / GHC Commits: 5629e247 by Ben Gamari at 2024-10-02T12:31:58+01:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 2 changed files: - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py Changes: ===================================== testsuite/driver/perf_notes.py ===================================== @@ -665,7 +665,10 @@ def check_stats_change(actual: PerfStat, display(' Upper bound ' + full_name + ' ' + actual.metric + ':', upperBound, '') display(' Actual ' + full_name + ' ' + actual.metric + ':', actual.value, '') if actual.value != expected_val: - actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) + if expected_val == 0: + actual_dev = 100 + else: + actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) display(' Deviation ' + full_name + ' ' + actual.metric + ':', actual_dev, '%') return (change, result) ===================================== testsuite/driver/runtests.py ===================================== @@ -404,7 +404,12 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: return "" val0 = x.baseline.perfStat.value val1 = x.stat.value - return "{:+2.1f}%".format(100 * (val1 - val0) / val0) + if val0 == 0 and val1 == 0: + return "0.0%" + elif val0 == 0: + return "NaN%" + else: + return "{:+2.1f}%".format(100 * (val1 - val0) / val0) dataRows = [row(( "{}({})".format(x.stat.test, x.stat.way), shorten_metric_name(x.stat.metric), @@ -425,6 +430,7 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: x.stat.value / x.baseline.perfStat.value for x in metrics if x.baseline is not None + if x.baseline.perfStat.value != 0 ] minimum = 0.0 maximum = 0.0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5629e247cfd10c26224d0e55d7a95f82dfcf0f03 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5629e247cfd10c26224d0e55d7a95f82dfcf0f03 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 12:12:43 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 02 Oct 2024 08:12:43 -0400 Subject: [Git][ghc/ghc][wip/perf-notes-fixes] testsuite: Handle division-by-zero more gracefully Message-ID: <66fd38bb17459_3ef6c0115a5832457@gitlab.mail> Matthew Pickering pushed to branch wip/perf-notes-fixes at Glasgow Haskell Compiler / GHC Commits: de619142 by Ben Gamari at 2024-10-02T13:12:34+01:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 2 changed files: - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py Changes: ===================================== testsuite/driver/perf_notes.py ===================================== @@ -665,7 +665,10 @@ def check_stats_change(actual: PerfStat, display(' Upper bound ' + full_name + ' ' + actual.metric + ':', upperBound, '') display(' Actual ' + full_name + ' ' + actual.metric + ':', actual.value, '') if actual.value != expected_val: - actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) + if expected_val == 0: + actual_dev = 100.0 + else: + actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) display(' Deviation ' + full_name + ' ' + actual.metric + ':', actual_dev, '%') return (change, result) ===================================== testsuite/driver/runtests.py ===================================== @@ -404,7 +404,12 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: return "" val0 = x.baseline.perfStat.value val1 = x.stat.value - return "{:+2.1f}%".format(100 * (val1 - val0) / val0) + if val0 == 0 and val1 == 0: + return "0.0%" + elif val0 == 0: + return "NaN%" + else: + return "{:+2.1f}%".format(100 * (val1 - val0) / val0) dataRows = [row(( "{}({})".format(x.stat.test, x.stat.way), shorten_metric_name(x.stat.metric), @@ -425,6 +430,7 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: x.stat.value / x.baseline.perfStat.value for x in metrics if x.baseline is not None + if x.baseline.perfStat.value != 0 ] minimum = 0.0 maximum = 0.0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de619142bd8fd8f71d40641e6d7572866e09adab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de619142bd8fd8f71d40641e6d7572866e09adab You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 12:43:40 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Wed, 02 Oct 2024 08:43:40 -0400 Subject: [Git][ghc/ghc][ghc-9.12] haddock: Allow building with GHC 9.12 Message-ID: <66fd3ffc8b21c_3ef6c0398e6054376@gitlab.mail> Zubin pushed to branch ghc-9.12 at Glasgow Haskell Compiler / GHC Commits: 362afd63 by Zubin Duggal at 2024-10-02T18:12:52+05:30 haddock: Allow building with GHC 9.12 Also bump `binaryInterfaceVersion` to 45 to detect binary version changes. - - - - - 1 changed file: - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -139,8 +139,8 @@ binaryInterfaceMagic = 0xD0Cface -- (2) set `binaryInterfaceVersionCompatibility` to [binaryInterfaceVersion] -- binaryInterfaceVersion :: Word16 -#if MIN_VERSION_ghc(9,9,0) && !MIN_VERSION_ghc(9,12,0) -binaryInterfaceVersion = 44 +#if MIN_VERSION_ghc(9,12,0) && !MIN_VERSION_ghc(9,13,0) +binaryInterfaceVersion = 45 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 12:47:58 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Wed, 02 Oct 2024 08:47:58 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/haddock-binary-interface-version Message-ID: <66fd40fe667b1_11b43cbc4a8953aa@gitlab.mail> Zubin pushed new branch wip/haddock-binary-interface-version at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/haddock-binary-interface-version You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 12:50:30 2024 From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher)) Date: Wed, 02 Oct 2024 08:50:30 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/sv/T25246-a Message-ID: <66fd419656888_11b43cc0134984df@gitlab.mail> Sjoerd Visscher pushed new branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/sv/T25246-a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 13:01:08 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 02 Oct 2024 09:01:08 -0400 Subject: [Git][ghc/ghc][wip/T25281] 2 commits: Switch off -Wincomplete-record-selectors Message-ID: <66fd44148ad36_11b43c20aa30102484@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 79a3add1 by Simon Peyton Jones at 2024-10-02T14:00:12+01:00 Switch off -Wincomplete-record-selectors ... because GHC uses quite a lot of them! ToDo: fix the code so it doesn't. - - - - - 9c4956e8 by Simon Peyton Jones at 2024-10-02T14:00:19+01:00 Fix incomplete record selections Refactor code to avoid incomplete record selectors (More to come.) - - - - - 25 changed files: - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Simplify/Env.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Subst.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Meta.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Utils/Panic.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - hadrian/src/Settings/Warnings.hs Changes: ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -150,14 +150,14 @@ pprAbbrevDecls platform haveDebugLine = pprDwarfInfo :: IsDoc doc => Platform -> Bool -> DwarfInfo -> doc pprDwarfInfo platform haveSrc d = case d of - DwarfCompileUnit {} -> hasChildren - DwarfSubprogram {} -> hasChildren - DwarfBlock {} -> hasChildren - DwarfSrcNote {} -> noChildren + DwarfCompileUnit {dwChildren = kids} -> hasChildren kids + DwarfSubprogram {dwChildren = kids} -> hasChildren kids + DwarfBlock {dwChildren = kids} -> hasChildren kids + DwarfSrcNote {} -> noChildren where - hasChildren = + hasChildren kids = pprDwarfInfoOpen platform haveSrc d $$ - vcat (map (pprDwarfInfo platform haveSrc) (dwChildren d)) $$ + vcat (map (pprDwarfInfo platform haveSrc) kids) $$ pprDwarfInfoClose noChildren = pprDwarfInfoOpen platform haveSrc d {-# SPECIALIZE pprDwarfInfo :: Platform -> Bool -> DwarfInfo -> SDoc #-} ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs ===================================== @@ -219,11 +219,10 @@ pprStatsSpills pprStatsSpills stats = let - finals = [ s | s at RegAllocStatsColored{} <- stats] + finals = [srms | RegAllocStatsColored{ raSRMs = srms } <- stats] -- sum up how many stores\/loads\/reg-reg-moves were left in the code - total = foldl' addSRM (0, 0, 0) - $ map raSRMs finals + total = foldl' addSRM (0, 0, 0) finals in ( text "-- spills-added-total" $$ text "-- (stores, loads, reg_reg_moves_remaining)" @@ -237,8 +236,7 @@ pprStatsLifetimes pprStatsLifetimes stats = let info = foldl' plusSpillCostInfo zeroSpillCostInfo - [ raSpillCosts s - | s at RegAllocStatsStart{} <- stats ] + [ sc | RegAllocStatsStart{ raSpillCosts = sc } <- stats ] lifeBins = binLifetimeCount $ lifeMapFromSpillCostInfo info @@ -287,7 +285,7 @@ pprStatsLifeConflict pprStatsLifeConflict stats graph = let lifeMap = lifeMapFromSpillCostInfo $ foldl' plusSpillCostInfo zeroSpillCostInfo - $ [ raSpillCosts s | s at RegAllocStatsStart{} <- stats ] + $ [ sc | RegAllocStatsStart{ raSpillCosts = sc } <- stats ] scatter = map (\r -> let lifetime = case lookupUFM lifeMap r of Just (_, l) -> l ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -1722,7 +1722,7 @@ mkFunResCo role id res_co = mkFunCoNoFTF role mult arg_co res_co where arg_co = mkReflCo role (varType id) - mult = multToCo (varMult id) + mult = multToCo (idMult id) -- mkCoCast (c :: s1 ~?r t1) (g :: (s1 ~?r t1) ~#R (s2 ~?r t2)) :: s2 ~?r t2 -- The first coercion might be lifted or unlifted; thus the ~? above ===================================== compiler/GHC/Core/FVs.hs ===================================== @@ -702,7 +702,7 @@ freeVars = go | isLocalVar v = (aFreeVar v `unionFVs` ty_fvs `unionFVs` mult_vars, AnnVar v) | otherwise = (emptyDVarSet, AnnVar v) where - mult_vars = tyCoVarsOfTypeDSet (varMult v) + mult_vars = tyCoVarsOfTypeDSet (idMult v) ty_fvs = dVarTypeTyCoVars v -- See Note [The FVAnn invariant] ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -1525,7 +1525,7 @@ lintAltBinders rhs_ue case_bndr scrut_ty con_ty ((var_w, bndr):bndrs) checkCaseLinearity :: UsageEnv -> Var -> Mult -> Var -> LintM UsageEnv checkCaseLinearity ue case_bndr var_w bndr = do ensureSubUsage lhs rhs err_msg - lintLinearBinder (ppr bndr) (case_bndr_w `mkMultMul` var_w) (varMult bndr) + lintLinearBinder (ppr bndr) (case_bndr_w `mkMultMul` var_w) (idMult bndr) return $ deleteUE ue bndr where lhs = bndr_usage `addUsage` (var_w `scaleUsage` case_bndr_usage) @@ -1538,7 +1538,7 @@ checkCaseLinearity ue case_bndr var_w bndr = do lhs_formula = ppr bndr_usage <+> text "+" <+> parens (ppr case_bndr_usage <+> text "*" <+> ppr var_w) rhs_formula = ppr case_bndr_w <+> text "*" <+> ppr var_w - case_bndr_w = varMult case_bndr + case_bndr_w = idMult case_bndr case_bndr_usage = lookupUE ue case_bndr bndr_usage = lookupUE ue bndr @@ -1625,7 +1625,7 @@ lintCaseExpr scrut var alt_ty alts = ; (scrut_ty, scrut_ue) <- markAllJoinsBad $ lintCoreExpr scrut -- See Note [Join points are less general than the paper] -- in GHC.Core - ; let scrut_mult = varMult var + ; let scrut_mult = idMult var ; alt_ty <- addLoc (CaseTy scrut) $ lintValueType alt_ty ===================================== compiler/GHC/Core/Opt/CprAnal.hs ===================================== @@ -339,7 +339,7 @@ cprTransform env id args | isLocalId id = assertPpr (isDataStructure id) (ppr id) topCprType -- See Note [CPR for DataCon wrappers] - | isDataConWrapId id, let rhs = uf_tmpl (realIdUnfolding id) + | Just rhs <- dataConWrapUnfolding_maybe id = fst $ cprAnalApp env rhs args -- DataCon worker | Just con <- isDataConWorkId_maybe id ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1015,7 +1015,7 @@ dmdTransform env var sd = -- pprTraceWith "dmdTransform:DataCon" (\ty -> ppr con $$ ppr sd $$ ppr ty) $ dmdTransformDataConSig (dataConRepStrictness con) sd -- See Note [DmdAnal for DataCon wrappers] - | isDataConWrapId var, let rhs = uf_tmpl (realIdUnfolding var) + | Just rhs <- dataConWrapUnfolding_maybe var , WithDmdType dmd_ty _rhs' <- dmdAnal env sd rhs = dmd_ty -- Dictionary component selectors ===================================== compiler/GHC/Core/Opt/Simplify/Env.hs ===================================== @@ -1307,4 +1307,4 @@ substIdType (SimplEnv { seInScope = in_scope, seTvSubst = tv_env, seCvSubst = cv no_free_vars = noFreeVarsOfType old_ty && noFreeVarsOfType old_w subst = Subst in_scope emptyIdSubstEnv tv_env cv_env old_ty = idType id - old_w = varMult id + old_w = idMult id ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -2819,8 +2819,9 @@ mkCase3 _mode scrut bndr alts_ty alts isExitJoinId :: Var -> Bool isExitJoinId id = isJoinId id - && isOneOcc (idOccInfo id) - && occ_in_lam (idOccInfo id) == IsInsideLam + && case idOccInfo id of + OneOcc { occ_in_lam = IsInsideLam } -> True + _ -> False {- Note [Dead binders] ===================================== compiler/GHC/Core/Subst.hs ===================================== @@ -482,7 +482,7 @@ substIdType subst@(Subst _ _ tv_env cv_env) id -- in a Note in the id's type itself where old_ty = idType id - old_w = varMult id + old_w = idMult id ------------------ -- | Substitute into some 'IdInfo' with regard to the supplied new 'Id'. ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -180,7 +180,7 @@ mkLamType v body_ty = mkForAllTy (Bndr v coreTyLamForAllTyFlag) body_ty | otherwise - = mkFunctionType (varMult v) (varType v) body_ty + = mkFunctionType (idMult v) (idType v) body_ty mkLamTypes vs ty = foldr mkLamType ty vs ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -652,10 +652,9 @@ pprTicks pp_no_debug pp_when_debug then pp_when_debug else pp_no_debug -instance Outputable (XRec a RdrName) => Outputable (RecordPatSynField a) where +instance Outputable (XRec (GhcPass p) RdrName) => Outputable (RecordPatSynField (GhcPass p)) where ppr (RecordPatSynField { recordPatSynField = v }) = ppr v - {- ************************************************************************ * * ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1529,6 +1529,11 @@ matchGroupArity (MG { mg_alts = alts }) hsLMatchPats :: LMatch (GhcPass id) body -> [LPat (GhcPass id)] hsLMatchPats (L _ (Match { m_pats = L _ pats })) = pats +isInfixMatch :: Match (GhcPass p) body -> Bool +isInfixMatch match = case m_ctxt match of + FunRhs {mc_fixity = Infix} -> True + _ -> False + -- We keep the type checker happy by providing EpAnnComments. They -- can only be used if they follow a `where` keyword with no binds, -- but in that case the comment is attached to the following parsed ===================================== compiler/GHC/Hs/Pat.hs ===================================== @@ -39,7 +39,6 @@ module GHC.Hs.Pat ( RecFieldsDotDot(..), hsRecFields, hsRecFieldSel, hsRecFieldId, hsRecFieldsArgs, hsRecUpdFieldId, hsRecUpdFieldOcc, hsRecUpdFieldRdr, - mkPrefixConPat, mkCharLitPat, mkNilPat, isSimplePat, isPatSyn, @@ -85,7 +84,9 @@ import GHC.Core.Type import GHC.Types.SrcLoc import GHC.Data.Bag -- collect ev vars from pats import GHC.Types.Name + import Data.Data +import qualified Data.List( map ) import qualified Data.List.NonEmpty as NE @@ -338,6 +339,16 @@ data ConPatTc cpt_wrap :: HsWrapper } + +hsRecFields :: HsRecFields (GhcPass p) arg -> [XCFieldOcc (GhcPass p)] +hsRecFields rbinds = Data.List.map (hsRecFieldSel . unLoc) (rec_flds rbinds) + +hsRecFieldsArgs :: HsRecFields (GhcPass p) arg -> [arg] +hsRecFieldsArgs rbinds = Data.List.map (hfbRHS . unLoc) (rec_flds rbinds) + +hsRecFieldSel :: HsRecField (GhcPass p) arg -> XCFieldOcc (GhcPass p) +hsRecFieldSel = fieldOccExt . unLoc . hfbLHS + hsRecFieldId :: HsRecField GhcTc arg -> Id hsRecFieldId = hsRecFieldSel ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -60,7 +60,7 @@ module GHC.Hs.Type ( HsConDetails(..), noTypeArgs, - FieldOcc(..), LFieldOcc, mkFieldOcc, + FieldOcc(..), LFieldOcc, mkFieldOcc, fieldOccExt, AmbiguousFieldOcc(..), LAmbiguousFieldOcc, mkAmbiguousFieldOcc, ambiguousFieldOccRdrName, ambiguousFieldOccLRdrName, selectorAmbiguousFieldOcc, @@ -305,10 +305,14 @@ type instance XXHsTyPat (GhcPass _) = DataConCantHappen type instance XHsSig (GhcPass _) = NoExtField type instance XXHsSigType (GhcPass _) = DataConCantHappen -hsSigWcType :: forall p. UnXRec p => LHsSigWcType p -> LHsType p -hsSigWcType = sig_body . unXRec @p . hswc_body -dropWildCards :: LHsSigWcType pass -> LHsSigType pass +hsPatSigType :: HsPatSigType (GhcPass p) -> LHsType (GhcPass p) +hsPatSigType (HsPS { hsps_body = ty }) = ty + +hsSigWcType :: LHsSigWcType (GhcPass p) -> LHsType (GhcPass p) +hsSigWcType = sig_body . unLoc . hswc_body + +dropWildCards :: LHsSigWcType (GhcPass p) -> LHsSigType (GhcPass p) -- Drop the wildcard part of a LHsSigWcType dropWildCards sig_ty = hswc_body sig_ty @@ -1099,6 +1103,8 @@ type instance XXFieldOcc (GhcPass _) = DataConCantHappen mkFieldOcc :: LocatedN RdrName -> FieldOcc GhcPs mkFieldOcc rdr = FieldOcc noExtField rdr +fieldOccExt :: FieldOcc (GhcPass p) -> XCFieldOcc (GhcPass p) +fieldOccExt (FieldOcc { foExt = ext }) = ext type instance XUnambiguous GhcPs = NoExtField type instance XUnambiguous GhcRn = Name @@ -1270,14 +1276,16 @@ instance (Outputable tyarg, Outputable arg, Outputable rec) ppr (RecCon rec) = text "RecCon:" <+> ppr rec ppr (InfixCon l r) = text "InfixCon:" <+> ppr [l, r] -instance Outputable (XRec pass RdrName) => Outputable (FieldOcc pass) where +instance Outputable (FieldOcc (GhcPass pass)) where ppr = ppr . foLabel -instance (UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (FieldOcc pass) where - pprInfixOcc = pprInfixOcc . unXRec @pass . foLabel - pprPrefixOcc = pprPrefixOcc . unXRec @pass . foLabel +instance (OutputableBndr (XRec (GhcPass p) RdrName)) + => OutputableBndr (FieldOcc (GhcPass pass)) where + pprInfixOcc = pprInfixOcc . unLoc . foLabel + pprPrefixOcc = pprPrefixOcc . unLoc . foLabel -instance (UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) where +instance (OutputableBndr (XRec (GhcPass p) RdrName)) + => OutputableBndr (GenLocated SrcSpan (FieldOcc (GhcPass p))) where pprInfixOcc = pprInfixOcc . unLoc pprPrefixOcc = pprPrefixOcc . unLoc ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -859,9 +859,9 @@ mkPatSynBind name details lpat dir anns = PatSynBind noExtField psb -- |If any of the matches in the 'FunBind' are infix, the 'FunBind' is -- considered infix. -isInfixFunBind :: forall id1 id2. UnXRec id2 => HsBindLR id1 id2 -> Bool +isInfixFunBind :: HsBindLR (GhcPass p1) (GhcPass p2) -> Bool isInfixFunBind (FunBind { fun_matches = MG _ matches }) - = any (isInfixMatch . unXRec @id2) (unXRec @id2 matches) + = any (isInfixMatch . unLoc) (unLoc matches) isInfixFunBind _ = False -- |Return the 'SrcSpan' encompassing the contents of any enclosed binds @@ -1861,5 +1861,5 @@ rec_field_expl_impl rec_flds (RecFieldsDotDot { .. }) where (explicit_binds, implicit_binds) = splitAt unRecFieldsDotDot rec_flds implicit_field_binders (L _ (HsFieldBind { hfbLHS = L _ fld, hfbRHS = rhs })) = ImplicitFieldBinders - { implFlBndr_field = foExt fld + { implFlBndr_field = fieldOccExt fld , implFlBndr_binders = collectPatBinders CollNoDictBinders rhs } ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -610,7 +610,7 @@ tcPolyCheck prag_fn ; (wrap_gen, (wrap_res, matches')) <- tcSkolemiseCompleteSig sig $ \invis_pat_tys rho_ty -> - let mono_id = mkLocalId mono_name (varMult poly_id) rho_ty in + let mono_id = mkLocalId mono_name (idMult poly_id) rho_ty in tcExtendBinderStack [TcIdBndr mono_id NotTopLevel] $ -- Why mono_id in the BinderStack? -- See Note [Relevant bindings and the binder stack] ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -71,7 +71,7 @@ module GHC.Types.Id ( isPrimOpId, isPrimOpId_maybe, isFCallId, isFCallId_maybe, isDataConWorkId, isDataConWorkId_maybe, - isDataConWrapId, isDataConWrapId_maybe, + isDataConWrapId, isDataConWrapId_maybe, dataConWrapUnfolding_maybe, isDataConId, isDataConId_maybe, idDataCon, isConLikeId, isWorkerLikeId, isDeadEndId, idIsFrom, @@ -129,10 +129,6 @@ module GHC.Types.Id ( import GHC.Prelude -import GHC.Core ( CoreRule, isStableUnfolding, evaldUnfolding - , isCompulsoryUnfolding, Unfolding( NoUnfolding ) - , IdUnfoldingFun, isEvaldUnfolding, hasSomeUnfolding, noUnfolding ) - import GHC.Types.Id.Info import GHC.Types.Basic @@ -140,11 +136,12 @@ import GHC.Types.Basic import GHC.Types.Var( Id, CoVar, JoinId, InId, InVar, OutId, OutVar, - idInfo, idDetails, setIdDetails, globaliseId, + idInfo, idDetails, setIdDetails, globaliseId, idMult, isId, isLocalId, isGlobalId, isExportedId, setIdMult, updateIdTypeAndMult, updateIdTypeButNotMult, updateIdTypeAndMultM) import qualified GHC.Types.Var as Var +import GHC.Core import GHC.Core.Type import GHC.Core.Predicate( isCoVarType ) import GHC.Core.DataCon @@ -210,9 +207,6 @@ idUnique = Var.varUnique idType :: Id -> Kind idType = Var.varType -idMult :: Id -> Mult -idMult = Var.varMult - idScaledType :: Id -> Scaled Type idScaledType id = Scaled (idMult id) (idType id) @@ -250,7 +244,7 @@ localiseId id | assert (isId id) $ isLocalId id && isInternalName name = id | otherwise - = Var.mkLocalVar (idDetails id) (localiseName name) (Var.varMult id) (idType id) (idInfo id) + = Var.mkLocalVar (idDetails id) (localiseName name) (Var.idMult id) (idType id) (idInfo id) where name = idName id @@ -544,6 +538,14 @@ isDataConWrapId_maybe id = case Var.idDetails id of DataConWrapId con -> Just con _ -> Nothing +dataConWrapUnfolding_maybe :: Id -> Maybe CoreExpr +dataConWrapUnfolding_maybe id + | DataConWrapId {} <- idDetails id + , CoreUnfolding { uf_tmpl = unf } <- realIdUnfolding id + = Just unf + | otherwise + = Nothing + isDataConId_maybe :: Id -> Maybe DataCon isDataConId_maybe id = case Var.idDetails id of DataConWorkId con -> Just con ===================================== compiler/GHC/Types/Meta.hs ===================================== @@ -16,6 +16,8 @@ import GHC.Prelude import GHC.Serialized ( Serialized ) import GHC.Hs +import GHC.Utils.Outputable +import GHC.Utils.Panic -- | The supported metaprogramming result types @@ -28,11 +30,42 @@ data MetaRequest -- | data constructors not exported to ensure correct result type data MetaResult - = MetaResE { unMetaResE :: LHsExpr GhcPs } - | MetaResP { unMetaResP :: LPat GhcPs } - | MetaResT { unMetaResT :: LHsType GhcPs } - | MetaResD { unMetaResD :: [LHsDecl GhcPs] } - | MetaResAW { unMetaResAW :: Serialized } + = MetaResE (LHsExpr GhcPs) + | MetaResP (LPat GhcPs) + | MetaResT (LHsType GhcPs) + | MetaResD [LHsDecl GhcPs] + | MetaResAW Serialized + +instance Outputable MetaResult where + ppr (MetaResE e) = text "MetaResE" <> braces (ppr e) + ppr (MetaResP p) = text "MetaResP" <> braces (ppr p) + ppr (MetaResT t) = text "MetaResT" <> braces (ppr t) + ppr (MetaResD d) = text "MetaResD" <> braces (ppr d) + ppr (MetaResAW aw) = text "MetaResAW" <> braces (ppr aw) + +-- These unMetaResE ext panics will triger if the MetaHook doesn't +-- take an expression to an expression, pattern to pattern etc. +-- +-- ToDo: surely this could be expressed in the type system? +unMetaResE :: MetaResult -> LHsExpr GhcPs +unMetaResE (MetaResE e) = e +unMetaResE mr = pprPanic "unMetaResE" (ppr mr) + +unMetaResP :: MetaResult -> LPat GhcPs +unMetaResP (MetaResP p) = p +unMetaResP mr = pprPanic "unMetaResP" (ppr mr) + +unMetaResT :: MetaResult -> LHsType GhcPs +unMetaResT (MetaResT t) = t +unMetaResT mr = pprPanic "unMetaResT" (ppr mr) + +unMetaResD :: MetaResult -> [LHsDecl GhcPs] +unMetaResD (MetaResD d) = d +unMetaResD mr = pprPanic "unMetaResD" (ppr mr) + +unMetaResAW :: MetaResult -> Serialized +unMetaResAW (MetaResAW aw) = aw +unMetaResAW mr = pprPanic "unMetaResAW" (ppr mr) type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -45,7 +45,7 @@ module GHC.Types.Var ( -- ** Taking 'Var's apart varName, varUnique, varType, - varMult, varMultMaybe, + varMultMaybe, idMult, -- ** Modifying 'Var's setVarName, setVarUnique, setVarType, @@ -417,6 +417,10 @@ varMultMaybe :: Id -> Maybe Mult varMultMaybe (Id { varMult = mult }) = Just mult varMultMaybe _ = Nothing +idMult :: HasDebugCallStack => Id -> Mult +idMult (Id { varMult = mult }) = mult +idMult non_id = pprPanic "idMult" (ppr non_id) + setVarUnique :: Var -> Unique -> Var setVarUnique var uniq = var { realUnique = uniq, ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -23,10 +23,12 @@ module GHC.Utils.Panic , handleGhcException -- * Command error throwing patterns + , panic , pprPanic , panicDoc , sorryDoc , pgmErrorDoc + -- ** Assertions , assertPprPanic , assertPpr ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -1103,11 +1103,6 @@ annotations -} -isInfixMatch :: Match id body -> Bool -isInfixMatch match = case m_ctxt match of - FunRhs {mc_fixity = Infix} -> True - _ -> False - -- | Guarded Right-Hand Sides -- -- GRHSs are used both for pattern bindings and for Matches ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -28,8 +28,7 @@ module Language.Haskell.Syntax.Pat ( HsRecFields(..), XHsRecFields, HsFieldBind(..), LHsFieldBind, HsRecField, LHsRecField, HsRecUpdField, LHsRecUpdField, - RecFieldsDotDot(..), - hsRecFields, hsRecFieldSel, hsRecFieldsArgs, + RecFieldsDotDot(..) ) where import {-# SOURCE #-} Language.Haskell.Syntax.Expr (SyntaxExpr, LHsExpr, HsUntypedSplice) @@ -394,12 +393,3 @@ data HsFieldBind lhs rhs = HsFieldBind { -- hfbLHS = Unambiguous "x" $sel:x:MkS :: AmbiguousFieldOcc Id -- -- See also Note [Disambiguating record updates] in GHC.Rename.Pat. - -hsRecFields :: forall p arg.UnXRec p => HsRecFields p arg -> [XCFieldOcc p] -hsRecFields rbinds = Data.List.map (hsRecFieldSel . unXRec @p) (rec_flds rbinds) - -hsRecFieldsArgs :: forall p arg. UnXRec p => HsRecFields p arg -> [arg] -hsRecFieldsArgs rbinds = Data.List.map (hfbRHS . unXRec @p) (rec_flds rbinds) - -hsRecFieldSel :: forall p arg. UnXRec p => HsRecField p arg -> XCFieldOcc p -hsRecFieldSel = foExt . unXRec @p . hfbLHS ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -59,8 +59,7 @@ module Language.Haskell.Syntax.Type ( mapHsOuterImplicit, hsQTvExplicit, - isHsKindedTyVar, - hsPatSigType, + isHsKindedTyVar ) where import {-# SOURCE #-} Language.Haskell.Syntax.Expr ( HsUntypedSplice ) @@ -73,6 +72,7 @@ import GHC.Types.Name.Reader ( RdrName ) import GHC.Hs.Doc (LHsDoc) import GHC.Data.FastString (FastString) +import GHC.Utils.Panic( panic ) import Data.Data hiding ( Fixity, Prefix, Infix ) import Data.Void @@ -355,7 +355,8 @@ data LHsQTyVars pass -- See Note [HsType binders] | XLHsQTyVars !(XXLHsQTyVars pass) hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr (HsBndrVis pass) pass] -hsQTvExplicit = hsq_explicit +hsQTvExplicit (HsQTvs { hsq_explicit = explicit_tvs }) = explicit_tvs +hsQTvExplicit (XLHsQTyVars {}) = panic "hsQTvExplicit" ------------------------------------------------ -- HsOuterTyVarBndrs @@ -471,9 +472,6 @@ data HsSigType pass } | XHsSigType !(XXHsSigType pass) -hsPatSigType :: HsPatSigType pass -> LHsType pass -hsPatSigType = hsps_body - {- Note [forall-or-nothing rule] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== hadrian/src/Settings/Warnings.hs ===================================== @@ -50,6 +50,7 @@ ghcWarningsArgs = do , package ghc ? pure [ "-Wcpp-undef" , "-Wincomplete-uni-patterns" , "-Wincomplete-record-updates" + , "-Wno-incomplete-record-selectors" ] , package ghcPrim ? pure [ "-Wno-trustworthy-safe" ] , package haddockLibrary ? pure [ "-Wno-unused-imports" ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1580ec44f06f4b1330c8a8d848cef4279e2bb70c...9c4956e817b98a40960adc0a2dd57c4442662401 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1580ec44f06f4b1330c8a8d848cef4279e2bb70c...9c4956e817b98a40960adc0a2dd57c4442662401 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 13:48:50 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Wed, 02 Oct 2024 09:48:50 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/experimental-version Message-ID: <66fd4f4294537_1d048abcfc096690@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/experimental-version at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/experimental-version You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 14:29:51 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 02 Oct 2024 10:29:51 -0400 Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] Fix exception backtraces from GHCi Message-ID: <66fd58df3e765_1d048a37ab04101760@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC Commits: fe6c5f62 by Rodrigo Mesquita at 2024-10-02T15:29:38+01:00 Fix exception backtraces from GHCi When running the program with `runhaskell`/`runghc` the backtrace should match the backtrace one would get by compiling and running the program. But currently, an exception thrown in a program interpreted with `runhaskell` will: * Not include the original exception backtrace at all * Include the backtrace from the internal GHCi/ghc rethrowing of the original exception This commit fixes this divergence by not annotating the ghc(i) backtrace (with NoBacktrace) and making sure that the backtrace of the original exception is serialized across the boundary and rethrown with the appropriate context. Fixes #25116 - - - - - 3 changed files: - ghc/GHCi/UI/Monad.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs Changes: ===================================== ghc/GHCi/UI/Monad.hs ===================================== @@ -212,7 +212,9 @@ data CommandResult deriving Show cmdSuccess :: MonadThrow m => CommandResult -> m (Maybe Bool) -cmdSuccess CommandComplete{ cmdResult = Left e } = throwM e +cmdSuccess CommandComplete{ cmdResult = Left e } = + {- Don't add a backtrace from ghci/ghc to the exception from the user program! -} + throwM (NoBacktrace e) cmdSuccess CommandComplete{ cmdResult = Right r } = return r cmdSuccess CommandIncomplete = return $ Just True ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -40,6 +40,9 @@ import GHC.Fingerprint import GHC.Conc (pseq, par) import Control.Concurrent import Control.Exception +#if MIN_VERSION_base(4,20,0) +import Control.Exception.Context +#endif import Data.Binary import Data.Binary.Get import Data.Binary.Put @@ -442,7 +445,15 @@ toSerializableException :: SomeException -> SerializableException toSerializableException ex | Just UserInterrupt <- fromException ex = EUserInterrupt | Just (ec::ExitCode) <- fromException ex = (EExitCode ec) - | otherwise = EOtherException (show (ex :: SomeException)) + | otherwise = EOtherException $ +#if MIN_VERSION_base(4,20,0) + -- Exception plus backtrace as seen in `displayExceptionWithInfo` + case displayExceptionContext (someExceptionContext ex) of + "" -> displayException (ex :: SomeException) + cx -> displayException (ex :: SomeException) ++ "\n\n" ++ cx +#else + show (ex :: SomeException) +#endif fromSerializableException :: SerializableException -> SomeException fromSerializableException EUserInterrupt = toException UserInterrupt ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -252,7 +252,7 @@ sandboxIO opts io = do -- rethrow :: EvalOpts -> IO a -> IO a rethrow EvalOpts{..} io = - catch io $ \se -> do + catchNoPropagate io $ \(ExceptionWithContext cx se) -> do -- If -fbreak-on-error, we break unconditionally, -- but with care of not breaking twice if breakOnError && not breakOnException @@ -263,7 +263,7 @@ rethrow EvalOpts{..} io = Just UserInterrupt -> return () -- In any other case, we don't want to break _ -> poke exceptionFlag 0 - throwIO se + rethrowIO (ExceptionWithContext cx se) -- -- While we're waiting for the sandbox thread to return a result, if View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe6c5f626f06b6f72a61f8b0086fecb6cbdf02c0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe6c5f626f06b6f72a61f8b0086fecb6cbdf02c0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 15:08:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 11:08:53 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fd6205e463a_13b5ec2045cc97523@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 7ddcf715 by Andreas Klebinger at 2024-10-02T11:08:11-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - c2f7a4a3 by Andreas Klebinger at 2024-10-02T11:08:12-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 34952896 by Sylvain Henry at 2024-10-02T11:08:24-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - e6ce5221 by Rodrigo Mesquita at 2024-10-02T11:08:25-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 15bfb31b by Matthew Pickering at 2024-10-02T11:08:25-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 24c08a36 by Matthew Pickering at 2024-10-02T11:08:26-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - d0d0fe33 by ARATA Mizuki at 2024-10-02T11:08:31-04:00 Use bundled llc/opt on Windows (#22438) - - - - - 33b851fa by Matthew Pickering at 2024-10-02T11:08:31-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - 21660150 by Matthew Pickering at 2024-10-02T11:08:31-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - ccbe4cb3 by Andreas Klebinger at 2024-10-02T11:08:32-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - cb0a03cf by Ben Gamari at 2024-10-02T11:08:32-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 43431c81 by Ben Gamari at 2024-10-02T11:08:32-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 23 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - m4/fp_settings.m4 - m4/fp_setup_windows_toolchain.m4 - m4/fptools_happy.m4 - rts/CheckVectorSupport.c - rts/posix/ticker/TimerFd.c - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/517a7146e8bccfe9279ee37ed6f0fc243fe0f28b...43431c818ec1bf88810a4f6a1d25aaeceb725ee9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/517a7146e8bccfe9279ee37ed6f0fc243fe0f28b...43431c818ec1bf88810a4f6a1d25aaeceb725ee9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 16:37:56 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 02 Oct 2024 12:37:56 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/js-memory Message-ID: <66fd76e4c9db8_2f5ec43268b01449@gitlab.mail> Matthew Pickering pushed new branch wip/js-memory at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/js-memory You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 18:04:15 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 02 Oct 2024 14:04:15 -0400 Subject: [Git][ghc/ghc][wip/js-memory] javascript: Read fields of ObjectBlock lazily Message-ID: <66fd8b1fdfe24_2f5ec46b3c80222a2@gitlab.mail> Matthew Pickering pushed to branch wip/js-memory at Glasgow Haskell Compiler / GHC Commits: 3ffc2f79 by Matthew Pickering at 2024-10-02T19:04:04+01:00 javascript: Read fields of ObjectBlock lazily When linking a module with a large dependency footprint too much of the object files were forced during linking. This lead to a large amount of memory taken up by thunks which would never be forced On the PartialDownsweep test this halves the memory required (from 25G to 13G). Towards #25324 - - - - - 2 changed files: - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Types.hs Changes: ===================================== compiler/GHC/StgToJS/Object.hs ===================================== @@ -255,23 +255,23 @@ instance Outputable ExportedFun where -- index putObjBlock :: WriteBinHandle -> ObjBlock -> IO () putObjBlock bh (ObjBlock _syms b c d e f g) = do - put_ bh b - put_ bh c + lazyPut bh b + lazyPut bh c lazyPut bh d - put_ bh e - put_ bh f - put_ bh g + lazyPut bh e + lazyPut bh f + lazyPut bh g -- | Read an ObjBlock and associate it to the given symbols (that must have been -- read from the index) getObjBlock :: [FastString] -> ReadBinHandle -> IO ObjBlock getObjBlock syms bh = do - b <- get bh - c <- get bh + b <- lazyGet bh + c <- lazyGet bh d <- lazyGet bh - e <- get bh - f <- get bh - g <- get bh + e <- lazyGet bh + f <- lazyGet bh + g <- lazyGet bh pure $ ObjBlock { oiSymbols = syms , oiClInfo = b ===================================== compiler/GHC/StgToJS/Types.hs ===================================== @@ -312,13 +312,13 @@ data LinkableUnit = LinkableUnit -- | one toplevel block in the object file data ObjBlock = ObjBlock - { oiSymbols :: ![FastString] -- ^ toplevel symbols (stored in index) - , oiClInfo :: ![ClosureInfo] -- ^ closure information of all closures in block - , oiStatic :: ![StaticInfo] -- ^ static closure data + { oiSymbols :: [FastString] -- ^ toplevel symbols (stored in index) + , oiClInfo :: [ClosureInfo] -- ^ closure information of all closures in block + , oiStatic :: [StaticInfo] -- ^ static closure data , oiStat :: Sat.JStat -- ^ the code - , oiRaw :: !BS.ByteString -- ^ raw JS code - , oiFExports :: ![ExpFun] - , oiFImports :: ![ForeignJSRef] + , oiRaw :: BS.ByteString -- ^ raw JS code + , oiFExports :: [ExpFun] + , oiFImports :: [ForeignJSRef] } data ExpFun = ExpFun View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3ffc2f792408d64a6e37280521b895f264694ccd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3ffc2f792408d64a6e37280521b895f264694ccd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 2 23:18:56 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 02 Oct 2024 19:18:56 -0400 Subject: [Git][ghc/ghc][wip/T25281] Remove more incomplete record selectors Message-ID: <66fdd4e07dc80_2b378f26d52c4844@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 893bfd1e by Simon Peyton Jones at 2024-10-03T00:13:55+01:00 Remove more incomplete record selectors - - - - - 7 changed files: - compiler/GHC/Core/Rules.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Match/Constructor.hs - compiler/GHC/HsToCore/Quote.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs Changes: ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -30,7 +30,8 @@ module GHC.Core.Rules ( rulesOfBinds, getRules, pprRulesForUser, -- * Making rules - mkRule, mkSpecRule, roughTopNames + mkRule, mkSpecRule, roughTopNames, + ruleIsOrphan ) where @@ -484,6 +485,10 @@ ruleIsVisible _ BuiltinRule{} = True ruleIsVisible vis_orphs Rule { ru_orphan = orph, ru_origin = origin } = notOrphan orph || origin `elemModuleSet` vis_orphs +ruleIsOrphan :: CoreRule -> Bool +ruleIsOrphan (BuiltinRule {}) = False +ruleIsOrphan (Rule { ru_orphan = orph }) = isOrphan orph + {- Note [Where rules are found] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The rules for an Id come from two places: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -907,7 +907,7 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl)) dsWarnOrphanRule :: CoreRule -> DsM () dsWarnOrphanRule rule - = when (isOrphan (ru_orphan rule)) $ + = when (ruleIsOrphan rule) $ diagnosticDs (DsOrphanRule rule) {- Note [SPECIALISE on INLINE functions] ===================================== compiler/GHC/HsToCore/Match/Constructor.hs ===================================== @@ -182,7 +182,7 @@ matchOneConLike vars ty mult (eqn1 :| eqns) -- All eqns for a single construct -- Divide into sub-groups; see Note [Record patterns] ; let groups :: NonEmpty (NonEmpty (ConArgPats, EquationInfoNE)) groups = NE.groupBy1 compatible_pats - $ fmap (\eqn -> (pat_args (firstPat eqn), eqn)) (eqn1 :| eqns) + $ fmap (\eqn -> (con_pat_args (firstPat eqn), eqn)) (eqn1 :| eqns) ; match_results <- mapM (match_group arg_vars) groups @@ -191,6 +191,10 @@ matchOneConLike vars ty mult (eqn1 :| eqns) -- All eqns for a single construct alt_wrapper = wrapper1, alt_result = foldr1 combineMatchResults match_results } } where + con_pat_args :: Pat GhcTc -> HsConPatDetails GhcTc + con_pat_args (ConPat { pat_args = args }) = args + con_pat_args p = pprPanic "matchOneConLike" (ppr p) -- All patterns are ConPats + ConPat { pat_con = L _ con1 , pat_args = args1 , pat_con_ext = ConPatTc ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -2158,7 +2158,8 @@ repP (ConPat NoExtField dc details) = do { con_str <- lookupLOcc dc ; case details of PrefixCon tyargs ps -> do { qs <- repLPs ps - ; let unwrapTyArg (HsConPatTyArg _ t) = unLoc (hstp_body t) + ; let unwrapTyArg (HsConPatTyArg _ (t :: HsTyPat GhcRn)) + = unLoc (hstp_body t) ; ts <- repListM typeTyConName (repTy . unwrapTyArg) tyargs ; repPcon con_str ts qs } RecCon rec -> do { fps <- repListM fieldPatTyConName rep_fld (rec_flds rec) ===================================== utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs ===================================== @@ -244,7 +244,7 @@ isSimpleSig } ) ) - | Map.null argDocs = Just (map unLoc lnames, unLoc (dropWildCards t)) + | Map.null argDocs = Just (map unLoc lnames, unLoc (dropWildCardsI t)) isSimpleSig _ = Nothing isExportModule :: ExportItem DocNameI -> Maybe Module @@ -327,7 +327,7 @@ ppDecl decl pats (doc, fnArgsDoc) instances subdocs _fxts = case unLoc decl of TyClD _ d at DataDecl{} -> ppDataDecl pats instances subdocs (Just doc) d unicode TyClD _ d at SynDecl{} -> ppTySyn (doc, fnArgsDoc) d unicode TyClD _ d at ClassDecl{} -> ppClassDecl instances doc subdocs d unicode - SigD _ (TypeSig _ lnames ty) -> ppFunSig Nothing (doc, fnArgsDoc) (map unLoc lnames) (dropWildCards ty) unicode + SigD _ (TypeSig _ lnames ty) -> ppFunSig Nothing (doc, fnArgsDoc) (map unLoc lnames) (dropWildCardsI ty) unicode SigD _ (PatSynSig _ lnames ty) -> ppLPatSig (doc, fnArgsDoc) (map unLoc lnames) ty unicode ForD _ d -> ppFor (doc, fnArgsDoc) d unicode InstD _ _ -> empty ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs ===================================== @@ -82,7 +82,7 @@ ppDecl summ links (L loc decl) pats (mbDoc, fnArgsDoc) instances fixities subdoc (locA loc) (mbDoc, fnArgsDoc) lnames - (dropWildCards lty) + (dropWildCardsI lty) fixities splice unicode @@ -1146,7 +1146,7 @@ ppInstanceSigs ppInstanceSigs links splice unicode qual sigs = do TypeSig _ lnames typ <- sigs let names = map unLoc lnames - L _ rtyp = dropWildCards typ + L _ rtyp = dropWildCardsI typ -- Instance methods signatures are synified and thus don't have a useful -- SrcSpan value. Use the methods name location instead. let lname = ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -149,6 +149,10 @@ getConNamesI ConDeclGADT{con_names = names} = names hsSigTypeI :: LHsSigType DocNameI -> LHsType DocNameI hsSigTypeI = sig_body . unLoc +dropWildCardsI :: LHsSigWcType DocNameI -> LHsSigType DocNameI +-- Drop the wildcard part of a LHsSigWcType +dropWildCardsI sig_ty = hswc_body sig_ty + mkEmptySigType :: LHsType GhcRn -> LHsSigType GhcRn -- Dubious, because the implicit binders are empty even -- though the type might have free variables View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/893bfd1ee37c40c00529c361f5394c7e81a5322f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/893bfd1ee37c40c00529c361f5394c7e81a5322f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:19:25 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:19:25 -0400 Subject: [Git][ghc/ghc][master] SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fdff2d866e4_2718665e27e85271a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 8 changed files: - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-optimisation.rst - + testsuite/tests/simplCore/should_compile/T25197.hs - + testsuite/tests/simplCore/should_compile/T25197.stderr - + testsuite/tests/simplCore/should_compile/T25197_TH.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -20,7 +20,8 @@ ToDo [Oct 2013] module GHC.Core.Opt.SpecConstr( specConstrProgram, - SpecConstrAnnotation(..) + SpecConstrAnnotation(..), + SpecFailWarning(..) ) where import GHC.Prelude @@ -51,6 +52,7 @@ import GHC.Core.Make ( mkImpossibleExpr ) import GHC.Unit.Module import GHC.Unit.Module.ModGuts +import GHC.Types.Error (MessageClass(..), Severity(..), DiagnosticReason(WarningWithoutFlag), ResolvedDiagnosticReason (..)) import GHC.Types.Literal ( litIsLifted ) import GHC.Types.Id import GHC.Types.Id.Info ( IdDetails(..) ) @@ -526,9 +528,11 @@ sc_force to True when calling specLoop. This flag does four things: (see argToPat; #4448) (FS4) Only specialise on recursive types a finite number of times (see sc_recursive; #5550; Note [Limit recursive specialisation]) -(FS5) Lift the restriction on the maximum number of arguments which - the optimisation will specialise. - (see `too_many_worker_args` in `callsToNewPats`; #14003) +(FS5) Use a different restriction on the maximum number of arguments which + the optimisation will specialise. We tried removing the limit on worker + args for forced specs (#14003) but this caused issues when specializing + code for large data structures (#25197). + This is handled by `too_many_worker_args` in `callsToNewPats` The flag holds only for specialising a single binding group, and NOT for nested bindings. (So really it should be passed around explicitly @@ -782,16 +786,25 @@ specConstrProgram :: ModGuts -> CoreM ModGuts specConstrProgram guts = do { env0 <- initScEnv guts ; us <- getUniqueSupplyM - ; let (_usg, binds') = initUs_ us $ + ; let (_usg, binds', warnings) = initUs_ us $ scTopBinds env0 (mg_binds guts) + ; when (not (null warnings)) $ msg specConstr_warn_class (warn_msg warnings) + ; return (guts { mg_binds = binds' }) } -scTopBinds :: ScEnv -> [InBind] -> UniqSM (ScUsage, [OutBind]) -scTopBinds _env [] = return (nullUsage, []) -scTopBinds env (b:bs) = do { (usg, b', bs') <- scBind TopLevel env b $ + where + specConstr_warn_class = MCDiagnostic SevWarning (ResolvedDiagnosticReason WarningWithoutFlag) Nothing + warn_msg :: SpecFailWarnings -> SDoc + warn_msg warnings = text "SpecConstr encountered one or more function(s) with a SPEC argument that resulted in too many arguments," $$ + text "which resulted in no specialization being generated for these functions:" $$ + nest 2 (vcat (map ppr warnings)) $$ + (text "If this is expected you might want to increase -fmax-forced-spec-args to force specialization anyway.") +scTopBinds :: ScEnv -> [InBind] -> UniqSM (ScUsage, [OutBind], [SpecFailWarning]) +scTopBinds _env [] = return (nullUsage, [], []) +scTopBinds env (b:bs) = do { (usg, b', bs', warnings) <- scBind TopLevel env b $ (\env -> scTopBinds env bs) - ; return (usg, b' ++ bs') } + ; return (usg, b' ++ bs', warnings) } {- ************************************************************************ @@ -905,6 +918,12 @@ data SpecConstrOpts = SpecConstrOpts -- ^ The threshold at which a worker-wrapper transformation used as part of -- this pass will no longer happen, measured in the number of arguments. + , sc_max_forced_args :: !Int + -- ^ The threshold at which a worker-wrapper transformation used as part of + -- this pass will no longer happen even if a SPEC arg was used to force + -- specialization. Measured in the number of arguments. + -- See Note [Forcing specialisation] + , sc_debug :: !Bool -- ^ Whether to print debug information @@ -975,6 +994,7 @@ instance Outputable Value where initScOpts :: DynFlags -> Module -> SpecConstrOpts initScOpts dflags this_mod = SpecConstrOpts { sc_max_args = maxWorkerArgs dflags, + sc_max_forced_args = maxForcedSpecArgs dflags, sc_debug = hasPprDebug dflags, sc_uf_opts = unfoldingOpts dflags, sc_module = this_mod, @@ -1388,29 +1408,29 @@ creates specialised versions of functions. -} scBind :: TopLevelFlag -> ScEnv -> InBind - -> (ScEnv -> UniqSM (ScUsage, a)) -- Specialise the scope of the binding - -> UniqSM (ScUsage, [OutBind], a) + -> (ScEnv -> UniqSM (ScUsage, a, [SpecFailWarning])) -- Specialise the scope of the binding + -> UniqSM (ScUsage, [OutBind], a, [SpecFailWarning]) scBind top_lvl env (NonRec bndr rhs) do_body | isTyVar bndr -- Type-lets may be created by doBeta - = do { (final_usage, body') <- do_body (extendScSubst env bndr rhs) - ; return (final_usage, [], body') } + = do { (final_usage, body', warnings) <- do_body (extendScSubst env bndr rhs) + ; return (final_usage, [], body', warnings) } | not (isTopLevel top_lvl) -- Nested non-recursive value binding -- See Note [Specialising local let bindings] = do { let (body_env, bndr') = extendBndr env bndr -- Not necessary at top level; but here we are nested - ; rhs_info <- scRecRhs env (bndr',rhs) + ; (rhs_info, rhs_ws) <- scRecRhs env (bndr',rhs) ; let body_env2 = extendHowBound body_env [bndr'] RecFun rhs' = ri_new_rhs rhs_info body_env3 = extendValEnv body_env2 bndr' (isValue (sc_vals env) rhs') - ; (body_usg, body') <- do_body body_env3 + ; (body_usg, body', warnings_body) <- do_body body_env3 -- Now make specialised copies of the binding, -- based on calls in body_usg - ; (spec_usg, specs) <- specNonRec env (scu_calls body_usg) rhs_info + ; (spec_usg, specs, warnings_bnd) <- specNonRec env (scu_calls body_usg) rhs_info -- NB: For non-recursive bindings we inherit sc_force flag from -- the parent function (see Note [Forcing specialisation]) @@ -1419,7 +1439,7 @@ scBind top_lvl env (NonRec bndr rhs) do_body bind_usage = (body_usg `delCallsFor` [bndr']) `combineUsage` spec_usg -- Note [spec_usg includes rhs_usg] - ; return (bind_usage, spec_bnds, body') + ; return (bind_usage, spec_bnds, body', mconcat [warnings_bnd, warnings_body, rhs_ws]) } | otherwise -- Top-level, non-recursive value binding @@ -1431,15 +1451,15 @@ scBind top_lvl env (NonRec bndr rhs) do_body -- -- I tried always specialising non-recursive top-level bindings too, -- but found some regressions (see !8135). So I backed off. - = do { (rhs_usage, rhs') <- scExpr env rhs + = do { (rhs_usage, rhs', ws_rhs) <- scExpr env rhs -- At top level, we've already put all binders into scope; see initScEnv -- Hence no need to call `extendBndr`. But we still want to -- extend the `ValueEnv` to record the value of this binder. ; let body_env = extendValEnv env bndr (isValue (sc_vals env) rhs') - ; (body_usage, body') <- do_body body_env + ; (body_usage, body', body_warnings) <- do_body body_env - ; return (rhs_usage `combineUsage` body_usage, [NonRec bndr rhs'], body') } + ; return (rhs_usage `combineUsage` body_usage, [NonRec bndr rhs'], body', body_warnings ++ ws_rhs) } scBind top_lvl env (Rec prs) do_body | isTopLevel top_lvl @@ -1450,19 +1470,20 @@ scBind top_lvl env (Rec prs) do_body -- ToDo: I'm honestly not sure of the rationale of this size-testing, nor -- why it only applies at top level. But that's the way it has been -- for a while. See #21456. - do { (body_usg, body') <- do_body rhs_env2 - ; (rhs_usgs, rhss') <- mapAndUnzipM (scExpr env) rhss + do { (body_usg, body', warnings_body) <- do_body rhs_env2 + ; (rhs_usgs, rhss', rhs_ws) <- mapAndUnzip3M (scExpr env) rhss ; let all_usg = (combineUsages rhs_usgs `combineUsage` body_usg) `delCallsFor` bndrs' bind' = Rec (bndrs' `zip` rhss') - ; return (all_usg, [bind'], body') } + ; return (all_usg, [bind'], body', warnings_body ++ concat rhs_ws) } | otherwise - = do { rhs_infos <- mapM (scRecRhs rhs_env2) (bndrs' `zip` rhss) - ; (body_usg, body') <- do_body rhs_env2 + = do { (rhs_infos, rhs_wss) <- mapAndUnzipM (scRecRhs rhs_env2) (bndrs' `zip` rhss) + ; let rhs_ws = mconcat rhs_wss + ; (body_usg, body', warnings_body) <- do_body rhs_env2 - ; (spec_usg, specs) <- specRec (scForce rhs_env2 force_spec) - (scu_calls body_usg) rhs_infos + ; (spec_usg, specs, spec_ws) <- specRec (scForce rhs_env2 force_spec) + (scu_calls body_usg) rhs_infos -- Do not unconditionally generate specialisations from rhs_usgs -- Instead use them only if we find an unspecialised call -- See Note [Seeding recursive groups] @@ -1473,7 +1494,7 @@ scBind top_lvl env (Rec prs) do_body -- zipWithEqual: length of returned [SpecInfo] -- should be the same as incoming [RhsInfo] - ; return (all_usg, [bind'], body') } + ; return (all_usg, [bind'], body', mconcat [warnings_body,rhs_ws,spec_ws]) } where (bndrs,rhss) = unzip prs force_spec = any (forceSpecBndr env) bndrs -- Note [Forcing specialisation] @@ -1501,59 +1522,63 @@ recursive function, but that's not essential and might even be harmful. I'm not sure. -} +withWarnings :: SpecFailWarnings -> (ScUsage, CoreExpr, SpecFailWarnings) -> (ScUsage, CoreExpr, SpecFailWarnings) +withWarnings ws (use,expr,ws2) = (use,expr,ws ++ ws2) + ------------------------ -scExpr, scExpr' :: ScEnv -> CoreExpr -> UniqSM (ScUsage, CoreExpr) +scExpr, scExpr' :: ScEnv -> CoreExpr -> UniqSM (ScUsage, CoreExpr, SpecFailWarnings) -- The unique supply is needed when we invent -- a new name for the specialised function and its args scExpr env e = scExpr' env e scExpr' env (Var v) = case scSubstId env v of - Var v' -> return (mkVarUsage env v' [], Var v') + Var v' -> return (mkVarUsage env v' [], Var v', []) e' -> scExpr (zapScSubst env) e' scExpr' env (Type t) = let !(MkSolo ty') = scSubstTy env t - in return (nullUsage, Type ty') -scExpr' env (Coercion c) = return (nullUsage, Coercion (scSubstCo env c)) -scExpr' _ e@(Lit {}) = return (nullUsage, e) -scExpr' env (Tick t e) = do (usg, e') <- scExpr env e - return (usg, Tick (scTickish env t) e') -scExpr' env (Cast e co) = do (usg, e') <- scExpr env e - return (usg, mkCast e' (scSubstCo env co)) + in return (nullUsage, Type ty', []) +scExpr' env (Coercion c) = return (nullUsage, Coercion (scSubstCo env c), []) +scExpr' _ e@(Lit {}) = return (nullUsage, e, []) +scExpr' env (Tick t e) = do (usg, e', ws) <- scExpr env e + return (usg, Tick (scTickish env t) e', ws) +scExpr' env (Cast e co) = do (usg, e', ws) <- scExpr env e + return (usg, mkCast e' (scSubstCo env co), ws) -- Important to use mkCast here -- See Note [SpecConstr call patterns] scExpr' env e@(App _ _) = scApp env (collectArgs e) scExpr' env (Lam b e) = do let (env', b') = extendBndr env b - (usg, e') <- scExpr env' e - return (usg, Lam b' e') + (usg, e', ws) <- scExpr env' e + return (usg, Lam b' e', ws) scExpr' env (Let bind body) - = do { (final_usage, binds', body') <- scBind NotTopLevel env bind $ + = do { (final_usage, binds', body', ws) <- scBind NotTopLevel env bind $ (\env -> scExpr env body) - ; return (final_usage, mkLets binds' body') } + ; return (final_usage, mkLets binds' body', ws) } scExpr' env (Case scrut b ty alts) - = do { (scrut_usg, scrut') <- scExpr env scrut + = do { (scrut_usg, scrut', ws) <- scExpr env scrut ; case isValue (sc_vals env) scrut' of Just (ConVal args_are_work_free con args) - | args_are_work_free -> sc_con_app con args scrut' + | args_are_work_free -> sc_con_app con args scrut' ws -- Don't duplicate work!! #7865 -- See Note [ConVal work-free-ness] (1) - _other -> sc_vanilla scrut_usg scrut' + _other -> sc_vanilla scrut_usg scrut' ws } where - sc_con_app con args scrut' -- Known constructor; simplify + sc_con_app con args scrut' ws -- Known constructor; simplify = do { let Alt _ bs rhs = findAlt con alts `orElse` Alt DEFAULT [] (mkImpossibleExpr ty "SpecConstr") alt_env' = extendScSubstList env ((b,scrut') : bs `zip` trimConArgs con args) - ; scExpr alt_env' rhs } + ; (use',expr',ws_new) <- scExpr alt_env' rhs + ; return (use',expr',ws ++ ws_new) } - sc_vanilla scrut_usg scrut' -- Normal case + sc_vanilla scrut_usg scrut' ws -- Normal case = do { let (alt_env,b') = extendBndrWith RecArg env b -- Record RecArg for the components - ; (alt_usgs, alt_occs, alts') <- mapAndUnzip3M (sc_alt alt_env scrut' b') alts + ; (alt_usgs, alt_occs, alts', ws_alts) <- mapAndUnzip4M (sc_alt alt_env scrut' b') alts ; let scrut_occ = foldr combineOcc NoOcc alt_occs scrut_usg' = setScrutOcc env scrut_usg scrut' scrut_occ @@ -1563,21 +1588,21 @@ scExpr' env (Case scrut b ty alts) ; let !(MkSolo ty') = scSubstTy env ty ; return (foldr combineUsage scrut_usg' alt_usgs, - Case scrut' b' ty' alts') } + Case scrut' b' ty' alts', ws ++ concat ws_alts) } single_alt = isSingleton alts sc_alt env scrut' b' (Alt con bs rhs) = do { let (env1, bs1) = extendBndrsWith RecArg env bs (env2, bs2) = extendCaseBndrs env1 scrut' b' con bs1 - ; (usg, rhs') <- scExpr env2 rhs + ; (usg, rhs', ws) <- scExpr env2 rhs ; let (usg', b_occ:arg_occs) = lookupOccs usg (b':bs2) scrut_occ = case con of DataAlt dc -- See Note [Do not specialise evals] | not (single_alt && all deadArgOcc arg_occs) -> ScrutOcc (unitUFM dc arg_occs) _ -> UnkOcc - ; return (usg', b_occ `combineOcc` scrut_occ, Alt con bs2 rhs') } + ; return (usg', b_occ `combineOcc` scrut_occ, Alt con bs2 rhs', ws) } -- | Substitute the free variables captured by a breakpoint. @@ -1626,19 +1651,20 @@ follows. still worth specialising on x. Hence the /single-alternative/ guard. -} -scApp :: ScEnv -> (InExpr, [InExpr]) -> UniqSM (ScUsage, CoreExpr) +scApp :: ScEnv -> (InExpr, [InExpr]) -> UniqSM (ScUsage, CoreExpr, SpecFailWarnings) scApp env (Var fn, args) -- Function is a variable = assert (not (null args)) $ do { args_w_usgs <- mapM (scExpr env) args - ; let (arg_usgs, args') = unzip args_w_usgs + ; let (arg_usgs, args', arg_ws) = unzip3 args_w_usgs arg_usg = combineUsages arg_usgs + arg_w = concat arg_ws ; case scSubstId env fn of - fn'@(Lam {}) -> scExpr (zapScSubst env) (doBeta fn' args') + fn'@(Lam {}) -> withWarnings arg_w <$> scExpr (zapScSubst env) (doBeta fn' args') -- Do beta-reduction and try again Var fn' -> return (arg_usg' `combineUsage` mkVarUsage env fn' args', - mkApps (Var fn') args') + mkApps (Var fn') args', arg_w ) where -- arg_usg': see Note [Specialising on dictionaries] arg_usg' | Just cls <- isClassOpId_maybe fn' @@ -1647,7 +1673,7 @@ scApp env (Var fn, args) -- Function is a variable | otherwise = arg_usg - other_fn' -> return (arg_usg, mkApps other_fn' args') } + other_fn' -> return (arg_usg, mkApps other_fn' args', arg_w) } -- NB: doing this ignores any usage info from the substituted -- function, but I don't think that matters. If it does -- we can fix it. @@ -1661,9 +1687,9 @@ scApp env (Var fn, args) -- Function is a variable -- which it may, we can get -- (let f = ...f... in f) arg1 arg2 scApp env (other_fn, args) - = do { (fn_usg, fn') <- scExpr env other_fn - ; (arg_usgs, args') <- mapAndUnzipM (scExpr env) args - ; return (combineUsages arg_usgs `combineUsage` fn_usg, mkApps fn' args') } + = do { (fn_usg, fn', fn_ws) <- scExpr env other_fn + ; (arg_usgs, args', arg_ws) <- mapAndUnzip3M (scExpr env) args + ; return (combineUsages arg_usgs `combineUsage` fn_usg, mkApps fn' args', combineSpecWarning fn_ws (concat arg_ws)) } ---------------------- mkVarUsage :: ScEnv -> Id -> [CoreExpr] -> ScUsage @@ -1679,16 +1705,16 @@ mkVarUsage env fn args | otherwise = evalScrutOcc ---------------------- -scRecRhs :: ScEnv -> (OutId, InExpr) -> UniqSM RhsInfo +scRecRhs :: ScEnv -> (OutId, InExpr) -> UniqSM (RhsInfo, SpecFailWarnings) scRecRhs env (bndr,rhs) = do { let (arg_bndrs,body) = collectBinders rhs (body_env, arg_bndrs') = extendBndrsWith RecArg env arg_bndrs - ; (body_usg, body') <- scExpr body_env body + ; (body_usg, body', body_ws) <- scExpr body_env body ; let (rhs_usg, arg_occs) = lookupOccs body_usg arg_bndrs' ; return (RI { ri_rhs_usg = rhs_usg , ri_fn = bndr, ri_new_rhs = mkLams arg_bndrs' body' , ri_lam_bndrs = arg_bndrs, ri_lam_body = body - , ri_arg_occs = arg_occs }) } + , ri_arg_occs = arg_occs }, body_ws) } -- The arg_occs says how the visible, -- lambda-bound binders of the RHS are used -- (including the TyVar binders) @@ -1757,7 +1783,7 @@ initSpecInfo (RI { ri_rhs_usg = rhs_usg }) specNonRec :: ScEnv -> CallEnv -- Calls in body -> RhsInfo -- Structure info usage info for un-specialised RHS - -> UniqSM (ScUsage, SpecInfo) -- Usage from RHSs (specialised and not) + -> UniqSM (ScUsage, SpecInfo, [SpecFailWarning]) -- Usage from RHSs (specialised and not) -- plus details of specialisations specNonRec env body_calls rhs_info @@ -1767,11 +1793,12 @@ specNonRec env body_calls rhs_info specRec :: ScEnv -> CallEnv -- Calls in body -> [RhsInfo] -- Structure info and usage info for un-specialised RHSs - -> UniqSM (ScUsage, [SpecInfo]) -- Usage from all RHSs (specialised and not) + -> UniqSM (ScUsage, [SpecInfo], SpecFailWarnings) + -- Usage from all RHSs (specialised and not) -- plus details of specialisations specRec env body_calls rhs_infos - = go 1 body_calls nullUsage (map initSpecInfo rhs_infos) + = go 1 body_calls nullUsage (map initSpecInfo rhs_infos) [] -- body_calls: see Note [Seeding recursive groups] -- NB: 'go' always calls 'specialise' once, which in turn unleashes -- si_mb_unspec if there are any boring calls in body_calls, @@ -1786,23 +1813,25 @@ specRec env body_calls rhs_infos -- Two accumulating parameters: -> ScUsage -- Usage from earlier specialisations -> [SpecInfo] -- Details of specialisations so far - -> UniqSM (ScUsage, [SpecInfo]) - go n_iter seed_calls usg_so_far spec_infos + -> SpecFailWarnings -- Warnings so far + -> UniqSM (ScUsage, [SpecInfo], SpecFailWarnings) + go n_iter seed_calls usg_so_far spec_infos ws_so_far = -- pprTrace "specRec3" (vcat [ text "bndrs" <+> ppr (map ri_fn rhs_infos) -- , text "iteration" <+> int n_iter -- , text "spec_infos" <+> ppr (map (map os_pat . si_specs) spec_infos) -- ]) $ do { specs_w_usg <- zipWithM (specialise env seed_calls) rhs_infos spec_infos - ; let (extra_usg_s, all_spec_infos) = unzip specs_w_usg + + ; let (extra_usg_s, all_spec_infos, extra_ws ) = unzip3 specs_w_usg extra_usg = combineUsages extra_usg_s all_usg = usg_so_far `combineUsage` extra_usg new_calls = scu_calls extra_usg - ; go_again n_iter new_calls all_usg all_spec_infos } + ; go_again n_iter new_calls all_usg all_spec_infos (ws_so_far ++ concat extra_ws) } -- go_again deals with termination - go_again n_iter seed_calls usg_so_far spec_infos + go_again n_iter seed_calls usg_so_far spec_infos ws_so_far | isEmptyVarEnv seed_calls - = return (usg_so_far, spec_infos) + = return (usg_so_far, spec_infos, ws_so_far) -- Limit recursive specialisation -- See Note [Limit recursive specialisation] @@ -1816,10 +1845,10 @@ specRec env body_calls rhs_infos -- for the unspecialised function, since it may now be called -- pprTrace "specRec2" (ppr (map (map os_pat . si_specs) spec_infos)) $ let rhs_usgs = combineUsages (mapMaybe si_mb_unspec spec_infos) - in return (usg_so_far `combineUsage` rhs_usgs, spec_infos) + in return (usg_so_far `combineUsage` rhs_usgs, spec_infos, ws_so_far) | otherwise - = go (n_iter + 1) seed_calls usg_so_far spec_infos + = go (n_iter + 1) seed_calls usg_so_far spec_infos ws_so_far -- See Note [Limit recursive specialisation] the_limit = case sc_count opts of @@ -1832,7 +1861,7 @@ specialise -> CallEnv -- Info on newly-discovered calls to this function -> RhsInfo -> SpecInfo -- Original RHS plus patterns dealt with - -> UniqSM (ScUsage, SpecInfo) -- New specialised versions and their usage + -> UniqSM (ScUsage, SpecInfo, [SpecFailWarning]) -- New specialised versions and their usage -- See Note [spec_usg includes rhs_usg] @@ -1850,7 +1879,7 @@ specialise env bind_calls (RI { ri_fn = fn, ri_lam_bndrs = arg_bndrs | isDeadEndId fn -- Note [Do not specialise diverging functions] -- /and/ do not generate specialisation seeds from its RHS = -- pprTrace "specialise bot" (ppr fn) $ - return (nullUsage, spec_info) + return (nullUsage, spec_info, []) | not (isNeverActive (idInlineActivation fn)) -- See Note [Transfer activation] @@ -1861,7 +1890,7 @@ specialise env bind_calls (RI { ri_fn = fn, ri_lam_bndrs = arg_bndrs , not (null arg_bndrs) -- Only specialise functions , Just all_calls <- lookupVarEnv bind_calls fn -- Some calls to it = -- pprTrace "specialise entry {" (ppr fn <+> ppr all_calls) $ - do { (boring_call, pats_discarded, new_pats) + do { (boring_call, pats_discarded, new_pats, warnings) <- callsToNewPats env fn spec_info arg_occs all_calls ; let n_pats = length new_pats @@ -1876,7 +1905,7 @@ specialise env bind_calls (RI { ri_fn = fn, ri_lam_bndrs = arg_bndrs -- , text "new_pats" <+> ppr new_pats]) ; let spec_env = decreaseSpecCount env n_pats - ; (spec_usgs, new_specs) <- mapAndUnzipM (spec_one spec_env fn arg_bndrs body) + ; (spec_usgs, new_specs, new_wss) <- mapAndUnzip3M (spec_one spec_env fn arg_bndrs body) (new_pats `zip` [spec_count..]) -- See Note [Specialise original body] @@ -1900,15 +1929,16 @@ specialise env bind_calls (RI { ri_fn = fn, ri_lam_bndrs = arg_bndrs ; return (new_usg, SI { si_specs = new_specs ++ specs , si_n_specs = spec_count + n_pats - , si_mb_unspec = mb_unspec' }) } + , si_mb_unspec = mb_unspec' } + ,warnings ++ concat new_wss) } | otherwise -- No calls, inactive, or not a function -- Behave as if there was a single, boring call = -- pprTrace "specialise inactive" (ppr fn $$ ppr mb_unspec) $ case mb_unspec of -- Behave as if there was a single, boring call - Just rhs_usg -> return (rhs_usg, spec_info { si_mb_unspec = Nothing }) + Just rhs_usg -> return (rhs_usg, spec_info { si_mb_unspec = Nothing }, []) -- See Note [spec_usg includes rhs_usg] - Nothing -> return (nullUsage, spec_info) + Nothing -> return (nullUsage, spec_info, []) --------------------- @@ -1917,7 +1947,7 @@ spec_one :: ScEnv -> [InVar] -- Lambda-binders of RHS; should match patterns -> InExpr -- Body of the original function -> (CallPat, Int) - -> UniqSM (ScUsage, OneSpec) -- Rule and binding + -> UniqSM (ScUsage, OneSpec, SpecFailWarnings) -- Rule and binding, warnings if any -- spec_one creates a specialised copy of the function, together -- with a rule for using it. I'm very proud of how short this @@ -1969,7 +1999,7 @@ spec_one env fn arg_bndrs body (call_pat, rule_number) -- Specialise the body -- ; pprTraceM "body_subst_for" $ ppr (spec_occ) $$ ppr (sc_subst body_env) - ; (spec_usg, spec_body) <- scExpr body_env body + ; (spec_usg, spec_body, body_warnings) <- scExpr body_env body -- And build the results ; (qvars', pats') <- generaliseDictPats qvars pats @@ -2018,7 +2048,7 @@ spec_one env fn arg_bndrs body (call_pat, rule_number) -- ] ; return (spec_usg, OS { os_pat = call_pat, os_rule = rule , os_id = spec_id - , os_rhs = spec_rhs }) } + , os_rhs = spec_rhs }, body_warnings) } generaliseDictPats :: [Var] -> [CoreExpr] -- Quantified vars and pats -> UniqSM ([Var], [CoreExpr]) -- New quantified vars and pats @@ -2402,12 +2432,26 @@ instance Outputable CallPat where , text "cp_args =" <+> ppr args , text "cp_strict_args = " <> ppr strict ]) +newtype SpecFailWarning = SpecFailForcedArgCount { spec_failed_fun_name :: Name } + +type SpecFailWarnings = [SpecFailWarning] + +instance Outputable SpecFailWarning where + ppr (SpecFailForcedArgCount name) = ppr name <+> pprDefinedAt name + +combineSpecWarning :: SpecFailWarnings -> SpecFailWarnings -> SpecFailWarnings +combineSpecWarning = (++) + +data ArgCountResult = WorkerSmallEnough | WorkerTooLarge | WorkerTooLargeForced Name + callsToNewPats :: ScEnv -> Id -> SpecInfo -> [ArgOcc] -> [Call] -> UniqSM ( Bool -- At least one boring call , Bool -- Patterns were discarded - , [CallPat] ) -- Patterns to specialise + , [CallPat] -- Patterns to specialise + , [SpecFailWarning] -- Things that didn't specialise we want to warn the user about) + ) -- Result has no duplicate patterns, -- nor ones mentioned in si_specs (hence "new" patterns) -- Bool indicates that there was at least one boring pattern @@ -2433,12 +2477,18 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls non_dups = subsumePats in_scope new_pats -- Remove ones that have too many worker variables - small_pats = filterOut too_many_worker_args non_dups + (small_pats, arg_count_warnings) = partitionByWorkerSize too_many_worker_args non_dups - too_many_worker_args _ - | sc_force env = False -- See (FS5) of Note [Forcing specialisation] + -- too_many_worker_args :: CallPat -> Either SpecFailWarning Bool too_many_worker_args (CP { cp_qvars = vars, cp_args = args }) - = not (isWorkerSmallEnough (sc_max_args $ sc_opts env) (valArgCount args) vars) + | sc_force env + -- See (FS5) of Note [Forcing specialisation] + = if (isWorkerSmallEnough (sc_max_forced_args $ sc_opts env) (valArgCount args) vars) + then WorkerSmallEnough + else WorkerTooLargeForced (idName fn) + | (isWorkerSmallEnough (sc_max_args $ sc_opts env) (valArgCount args) vars) + = WorkerSmallEnough + | otherwise = WorkerTooLarge -- We are about to construct w/w pair in 'spec_one'. -- Omit specialisation leading to high arity workers. -- See Note [Limit w/w arity] in GHC.Core.Opt.WorkWrap.Utils @@ -2454,10 +2504,21 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls -- , text "done_specs:" <+> ppr (map os_pat done_specs) -- , text "trimmed_pats:" <+> ppr trimmed_pats ]) - ; return (have_boring_call, pats_were_discarded, trimmed_pats) } + ; return (have_boring_call, pats_were_discarded, trimmed_pats, arg_count_warnings) } -- If any of the calls does not give rise to a specialisation, either -- because it is boring, or because there are too many specialisations, -- return a flag to say so, so that we know to keep the original function. + where + partitionByWorkerSize worker_size pats = go pats [] [] + where + go [] small warnings = (small, warnings) + go (p:ps) small warnings + | WorkerSmallEnough <- worker_size p + = go ps (p:small) warnings + | WorkerTooLarge <- worker_size p + = go ps small warnings + | WorkerTooLargeForced name <- worker_size p + = go ps small (SpecFailForcedArgCount name : warnings) trim_pats :: ScEnv -> Id -> SpecInfo -> [CallPat] -> (Bool, [CallPat]) ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -395,6 +395,7 @@ data DynFlags = DynFlags { unfoldingOpts :: !UnfoldingOpts, maxWorkerArgs :: Int, + maxForcedSpecArgs :: Int, ghciHistSize :: Int, @@ -677,6 +678,8 @@ defaultDynFlags mySettings = unfoldingOpts = defaultUnfoldingOpts, maxWorkerArgs = 10, + maxForcedSpecArgs = 333, + -- 333 is fairly arbitrary, see Note [Forcing specialisation]:FS5 ghciHistSize = 50, -- keep a log of length 50 by default ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1822,6 +1822,8 @@ dynamic_flags_deps = [ , make_ord_flag defFlag "fmax-worker-args" (intSuffix (\n d -> d {maxWorkerArgs = n})) + , make_ord_flag defFlag "fmax-forced-spec-args" + (intSuffix (\n d -> d {maxForcedSpecArgs = n})) , make_ord_flag defGhciFlag "fghci-hist-size" (intSuffix (\n d -> d {ghciHistSize = n})) , make_ord_flag defGhcFlag "fmax-inline-alloc-size" ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -870,6 +870,21 @@ as such you shouldn't need to set any of them explicitly. A flag value arguments of the resulting worker exceeds both that of the original function and this setting. +.. ghc-flag:: -fmax-forced-spec-args=⟨n⟩ + :shortdesc: *default: 333.* Maximum number of value arguments for forced SpecConstr specializations. + :type: dynamic + :category: + + :default: 512 + + When using ``SPEC`` from ``GHC.Types`` to force SpecConstr to fire on a function + sometimes this can result in functions taking a ridicolously large number of arguments + resulting a very large compile time hits for minor performance benefits. + + Since this is usually unintended we prevent SpecConstr from firing and generate + a warning if the number of arguments in the resulting function would exceed + the value given by ``-fmax-forced-spec-args``. + .. ghc-flag:: -fno-opt-coercion :shortdesc: Turn off the coercion optimiser :type: dynamic ===================================== testsuite/tests/simplCore/should_compile/T25197.hs ===================================== @@ -0,0 +1,30 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T25197 where + +import T25197_TH +import GHC.Exts + +{- +This test applies a large statically known data structure to a function with +a SPEC argument, forcing the function to be specialised for the argument. +However when the complete structure of the argument is not statically known, +or as here the leaves of the structures are primitive literals for which we do +not specialize this results in a specialized function that can take hundreds of +arguments. + +Typically this is not intended, therefore we use a limit on the number of +arguments for specializations. As at some point this sort of specialization +comes with a heavy compile time cost. However we allow users to specify this +limit just in case they really depend on this sort of specialization. +-} + +foo :: [a] -> Int +foo = go SPEC + where + go :: SPEC -> [a] -> Int + go s [] = s `seq` 0 + go s (_:xs) = 1 + go s xs + +main :: IO () +main = print $ foo $(gen 1000) ===================================== testsuite/tests/simplCore/should_compile/T25197.stderr ===================================== @@ -0,0 +1,6 @@ +T25197.hs: warning: + SpecConstr encountered one or more function(s) with a SPEC argument that resulted in too many arguments, + which resulted in no specialization being generated for these functions: + $wgo Defined at T25197.hs:26:5 + If this is expected you might want to increase -fmax-forced-spec-args to force specialization anyway. + ===================================== testsuite/tests/simplCore/should_compile/T25197_TH.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T25197_TH where + +import Language.Haskell.TH.Syntax + +gen :: Int -> Q Exp +gen 0 = [| [] |] +gen n = [| $(lift (show n)) : $(gen (n-1)) |] ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -530,3 +530,4 @@ test('T24625', [ grep_errmsg(r'case lazy') ], compile, ['-O -fno-ignore-asserts test('T24725a', [ grep_errmsg(r'testedRule')], compile, ['-O -ddump-rule-firings']) test('T25033', normal, compile, ['-O']) test('T25160', normal, compile, ['-O -ddump-rules']) +test('T25197', [req_th, extra_files(["T25197_TH.hs"]), only_ways(['optasm'])], multimod_compile, ['T25197', '-O2 -v0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da20cac16d0982c982f9d6779dc8174e5184fe15 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da20cac16d0982c982f9d6779dc8174e5184fe15 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:20:13 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:20:13 -0400 Subject: [Git][ghc/ghc][master] ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps Message-ID: <66fdff5ceb55b_2718669462e056448@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - 6 changed files: - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - testsuite/tests/interface-stability/ghc-experimental-exports.stdout - + testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 Changes: ===================================== libraries/base/src/GHC/Exts.hs ===================================== @@ -14,6 +14,9 @@ -- -- Note: no other @base@ module should import this module. +-- See Note [Where do we export PrimOps] for details about how to expose primops +-- to users. + module GHC.Exts (-- ** Pointer types Ptr(..), ===================================== libraries/ghc-experimental/ghc-experimental.cabal.in ===================================== @@ -29,6 +29,7 @@ library exposed-modules: Data.Sum.Experimental Data.Tuple.Experimental + GHC.PrimOps GHC.Profiling.Eras GHC.TypeLits.Experimental GHC.TypeNats.Experimental ===================================== libraries/ghc-experimental/src/GHC/PrimOps.hs ===================================== @@ -0,0 +1,33 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE Unsafe #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# OPTIONS_HADDOCK print-explicit-runtime-reps #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.PrimOps +-- Copyright : Andreas Klebinger 2024 +-- License : see libraries/ghc-experimental/LICENSE +-- +-- Maintainer : ghc-devs at haskell.org +-- Stability : internal +-- Portability : non-portable (GHC Extensions) +-- +-- GHC Extensions: This is the Approved Way to get at GHC-specific extensions +-- without relying on the ghc-internal package. +----------------------------------------------------------------------------- + +-- See Note [Where do we export PrimOps] for the purpose of this module. + +module GHC.PrimOps + ( + module GHC.Internal.Exts, + ) where + +import GHC.Internal.Exts + ===================================== libraries/ghc-internal/src/GHC/Internal/Exts.hs ===================================== @@ -18,11 +18,43 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- GHC Extensions: this is the Approved Way to get at GHC-specific extensions. +-- GHC Extensions: This is a unstable way to get at GHC-specific extensions. +-- If possible prefer using GHC.PrimOps from ghc-experimental +-- or GHC.Exts from base. -- --- Note: no other base module should import this module. +-- Note: no other ghc-internal module should import this module. ----------------------------------------------------------------------------- +{- Note [Where do we export PrimOps] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Built in primops are automatically exported via the magical module +GHC.Prim (See Note [GHC.Prim]). +However we don't want users to use GHC.Prim directly. Among other reasons that +would prevent us from giving those primops a regular haskell or cmm +implementation in the future. + +So instead we provide a hirarchy of Modules through which we expose PrimOps. +* ghc-internal:GHC.Exts.Internal re-exports GHC.Prim along with some other + builtin functionality. It gives zero stability guarantee and is mostly inteded + for ghc internal use. +* ghc-experimental:GHC.PrimOps contains a more stable subset of GHC.Exts.Internal. + This module does not offer any more stability *guarantees* than ghc-internal, + but we try to keep things slightly more stable there and be backwards compatible + if it's easy to do. For example an export from ghc-experimental is likely to get + deprecated before being removed. While exports from ghc-internal could be removed + without advanced notice between ghc versions! +* base:GHC.Exts: Contains all kinds of re-exports from ghc-internal:GHC.Exts.Internal + which have been grandfathered into this module from pre ghc-9.10. + Starting with 9.10.1 only definitions with a fairly high level of expected + stability should be exposed through GHC.Exts and changing the API provided by + this module now follows the CLC process. + +If there is a desire to create a module for a specific group of primitives they +should still be exported by the catch-all modules GHC.Exts.Internal and GHC.PrimOps, +with their specific module being placed under ghc-experimental:GHC.PrimOps +in the module structure. +-} + module GHC.Internal.Exts ( -- ** Pointer types ===================================== testsuite/tests/interface-stability/ghc-experimental-exports.stdout ===================================== @@ -4316,6 +4316,1839 @@ module Data.Tuple.Experimental where data Unit# = ... getSolo :: forall a. Solo a -> a +module GHC.PrimOps where + -- Safety: Unsafe + (*#) :: Int# -> Int# -> Int# + (*##) :: Double# -> Double# -> Double# + (**##) :: Double# -> Double# -> Double# + (+#) :: Int# -> Int# -> Int# + (+##) :: Double# -> Double# -> Double# + (-#) :: Int# -> Int# -> Int# + (-##) :: Double# -> Double# -> Double# + (/##) :: Double# -> Double# -> Double# + (/=#) :: Int# -> Int# -> Int# + (/=##) :: Double# -> Double# -> Int# + (<#) :: Int# -> Int# -> Int# + (<##) :: Double# -> Double# -> Int# + (<=#) :: Int# -> Int# -> Int# + (<=##) :: Double# -> Double# -> Int# + (==#) :: Int# -> Int# -> Int# + (==##) :: Double# -> Double# -> Int# + (>#) :: Int# -> Int# -> Int# + (>##) :: Double# -> Double# -> Int# + (>=#) :: Int# -> Int# -> Int# + (>=##) :: Double# -> Double# -> Int# + type Addr# :: TYPE AddrRep + data Addr# + type Any :: forall k. k + type family Any where + type Array# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType + data Array# a + type ArrayArray# :: UnliftedType + newtype ArrayArray# = ArrayArray# (Array# ByteArray#) + type BCO :: * + data BCO + type Bool :: * + data Bool = False | True + type ByteArray# :: UnliftedType + data ByteArray# + type role CONSTRAINT nominal + type CONSTRAINT :: RuntimeRep -> * + data CONSTRAINT a + type Char :: * + data Char = C# Char# + type Char# :: TYPE WordRep + data Char# + type role Coercible representational representational + type Coercible :: forall k. k -> k -> Constraint + class Coercible a b => Coercible a b + {-# MINIMAL #-} + type Compact# :: UnliftedType + data Compact# + type Constraint :: * + type Constraint = CONSTRAINT LiftedRep + type DataToTag :: forall {lev :: Levity}. TYPE (BoxedRep lev) -> Constraint + class DataToTag a where + dataToTag# :: a -> Int# + {-# MINIMAL dataToTag# #-} + type DictBox :: Constraint -> * + data DictBox a = a => MkDictBox + type Double :: * + data Double = D# Double# + type Double# :: TYPE DoubleRep + data Double# + type DoubleBox :: TYPE DoubleRep -> * + data DoubleBox a = MkDoubleBox a + type DoubleX2# :: TYPE (VecRep Vec2 DoubleElemRep) + data DoubleX2# + type DoubleX4# :: TYPE (VecRep Vec4 DoubleElemRep) + data DoubleX4# + type DoubleX8# :: TYPE (VecRep Vec8 DoubleElemRep) + data DoubleX8# + type Down :: * -> * + newtype Down a = Down {getDown :: a} + type role FUN nominal representational representational + type FUN :: forall (n :: Multiplicity) -> forall {q :: RuntimeRep} {r :: RuntimeRep}. TYPE q -> TYPE r -> * + data FUN n a b + type Float :: * + data Float = F# Float# + type Float# :: TYPE FloatRep + data Float# + type FloatBox :: TYPE FloatRep -> * + data FloatBox a = MkFloatBox a + type FloatX16# :: TYPE (VecRep Vec16 FloatElemRep) + data FloatX16# + type FloatX4# :: TYPE (VecRep Vec4 FloatElemRep) + data FloatX4# + type FloatX8# :: TYPE (VecRep Vec8 FloatElemRep) + data FloatX8# + type role FunPtr phantom + type FunPtr :: * -> * + data FunPtr a = FunPtr Addr# + type role IOPort# nominal representational + type IOPort# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data IOPort# a b + type Int :: * + data Int = I# Int# + type Int# :: TYPE IntRep + data Int# + type Int16# :: TYPE Int16Rep + data Int16# + type Int16X16# :: TYPE (VecRep Vec16 Int16ElemRep) + data Int16X16# + type Int16X32# :: TYPE (VecRep Vec32 Int16ElemRep) + data Int16X32# + type Int16X8# :: TYPE (VecRep Vec8 Int16ElemRep) + data Int16X8# + type Int32# :: TYPE Int32Rep + data Int32# + type Int32X16# :: TYPE (VecRep Vec16 Int32ElemRep) + data Int32X16# + type Int32X4# :: TYPE (VecRep Vec4 Int32ElemRep) + data Int32X4# + type Int32X8# :: TYPE (VecRep Vec8 Int32ElemRep) + data Int32X8# + type Int64# :: TYPE Int64Rep + data Int64# + type Int64X2# :: TYPE (VecRep Vec2 Int64ElemRep) + data Int64X2# + type Int64X4# :: TYPE (VecRep Vec4 Int64ElemRep) + data Int64X4# + type Int64X8# :: TYPE (VecRep Vec8 Int64ElemRep) + data Int64X8# + type Int8# :: TYPE Int8Rep + data Int8# + type Int8X16# :: TYPE (VecRep Vec16 Int8ElemRep) + data Int8X16# + type Int8X32# :: TYPE (VecRep Vec32 Int8ElemRep) + data Int8X32# + type Int8X64# :: TYPE (VecRep Vec64 Int8ElemRep) + data Int8X64# + type IntBox :: TYPE IntRep -> * + data IntBox a = MkIntBox a + type IsList :: * -> Constraint + class IsList l where + type Item :: * -> * + type family Item l + fromList :: [Item l] -> l + fromListN :: Int -> [Item l] -> l + toList :: l -> [Item l] + {-# MINIMAL fromList, toList #-} + type IsString :: * -> Constraint + class IsString a where + fromString :: GHC.Internal.Base.String -> a + {-# MINIMAL fromString #-} + KindRepApp :: GHC.Types.KindRep -> GHC.Types.KindRep -> GHC.Types.KindRep + KindRepFun :: GHC.Types.KindRep -> GHC.Types.KindRep -> GHC.Types.KindRep + KindRepTYPE :: RuntimeRep -> GHC.Types.KindRep + KindRepTyConApp :: GHC.Types.TyCon -> [GHC.Types.KindRep] -> GHC.Types.KindRep + KindRepTypeLitD :: GHC.Types.TypeLitSort -> [Char] -> GHC.Types.KindRep + KindRepTypeLitS :: GHC.Types.TypeLitSort -> Addr# -> GHC.Types.KindRep + KindRepVar :: GHC.Types.KindBndr -> GHC.Types.KindRep + type Levity :: * + data Levity = Lifted | Unlifted + type LiftedRep :: RuntimeRep + type LiftedRep = BoxedRep Lifted :: RuntimeRep + type List :: * -> * + data List a = ... + type role MVar# nominal representational + type MVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data MVar# a b + type MultMul :: Multiplicity -> Multiplicity -> Multiplicity + type family MultMul a b where + forall (x :: Multiplicity). MultMul One x = x + forall (x :: Multiplicity). MultMul x One = x + forall (x :: Multiplicity). MultMul Many x = Many + forall (x :: Multiplicity). MultMul x Many = Many + type Multiplicity :: * + data Multiplicity = One | Many + type role MutVar# nominal representational + type MutVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data MutVar# a b + type role MutableArray# nominal representational + type MutableArray# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data MutableArray# a b + type role MutableArrayArray# nominal + type MutableArrayArray# :: * -> UnliftedType + newtype MutableArrayArray# s = MutableArrayArray# (MutableArray# s ByteArray#) + type role MutableByteArray# nominal + type MutableByteArray# :: * -> UnliftedType + data MutableByteArray# a + type Ordering :: * + data Ordering = LT | EQ | GT + type PromptTag# :: * -> UnliftedType + data PromptTag# a + type role Proxy# phantom + type Proxy# :: forall k. k -> ZeroBitType + data Proxy# a + type role Ptr phantom + type Ptr :: * -> * + data Ptr a = Ptr Addr# + type RealWorld :: * + data RealWorld + type RuntimeRep :: * + data RuntimeRep = VecRep VecCount VecElem | TupleRep [RuntimeRep] | SumRep [RuntimeRep] | BoxedRep Levity | IntRep | Int8Rep | Int16Rep | Int32Rep | Int64Rep | WordRep | Word8Rep | Word16Rep | Word32Rep | Word64Rep | AddrRep | FloatRep | DoubleRep + type SPEC :: * + data SPEC = SPEC | SPEC2 + type SmallArray# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType + data SmallArray# a + type role SmallMutableArray# nominal representational + type SmallMutableArray# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data SmallMutableArray# a b + type SpecConstrAnnotation :: * + data SpecConstrAnnotation = NoSpecConstr | ForceSpecConstr + type role StableName# phantom + type StableName# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType + data StableName# a + type StablePtr# :: forall {l :: Levity}. TYPE (BoxedRep l) -> TYPE AddrRep + data StablePtr# a + type StackSnapshot# :: UnliftedType + data StackSnapshot# + type role State# nominal + type State# :: * -> ZeroBitType + data State# a + type Symbol :: * + data Symbol + type role TVar# nominal representational + type TVar# :: forall {l :: Levity}. * -> TYPE (BoxedRep l) -> UnliftedType + data TVar# a b + type role TYPE nominal + type TYPE :: RuntimeRep -> * + data TYPE a + type ThreadId# :: UnliftedType + data ThreadId# + TrNameD :: [Char] -> GHC.Types.TrName + TrNameS :: Addr# -> GHC.Types.TrName + TypeLitChar :: GHC.Types.TypeLitSort + TypeLitNat :: GHC.Types.TypeLitSort + TypeLitSymbol :: GHC.Types.TypeLitSort + type UnliftedRep :: RuntimeRep + type UnliftedRep = BoxedRep Unlifted :: RuntimeRep + type UnliftedType :: * + type UnliftedType = TYPE UnliftedRep + type VecCount :: * + data VecCount = Vec2 | Vec4 | Vec8 | Vec16 | Vec32 | Vec64 + type VecElem :: * + data VecElem = Int8ElemRep | Int16ElemRep | Int32ElemRep | Int64ElemRep | Word8ElemRep | Word16ElemRep | Word32ElemRep | Word64ElemRep | FloatElemRep | DoubleElemRep + type Void# :: ZeroBitType + type Void# = (# #) :: ZeroBitType + type Weak# :: forall {l :: Levity}. TYPE (BoxedRep l) -> UnliftedType + data Weak# a + type WithDict :: Constraint -> * -> Constraint + class WithDict cls meth where + withDict :: forall {rr :: RuntimeRep} (r :: TYPE rr). meth -> (cls => r) -> r + {-# MINIMAL withDict #-} + type Word :: * + data Word = W# Word# + type Word# :: TYPE WordRep + data Word# + type Word16# :: TYPE Word16Rep + data Word16# + type Word16X16# :: TYPE (VecRep Vec16 Word16ElemRep) + data Word16X16# + type Word16X32# :: TYPE (VecRep Vec32 Word16ElemRep) + data Word16X32# + type Word16X8# :: TYPE (VecRep Vec8 Word16ElemRep) + data Word16X8# + type Word32# :: TYPE Word32Rep + data Word32# + type Word32X16# :: TYPE (VecRep Vec16 Word32ElemRep) + data Word32X16# + type Word32X4# :: TYPE (VecRep Vec4 Word32ElemRep) + data Word32X4# + type Word32X8# :: TYPE (VecRep Vec8 Word32ElemRep) + data Word32X8# + type Word64# :: TYPE Word64Rep + data Word64# + type Word64X2# :: TYPE (VecRep Vec2 Word64ElemRep) + data Word64X2# + type Word64X4# :: TYPE (VecRep Vec4 Word64ElemRep) + data Word64X4# + type Word64X8# :: TYPE (VecRep Vec8 Word64ElemRep) + data Word64X8# + type Word8# :: TYPE Word8Rep + data Word8# + type Word8X16# :: TYPE (VecRep Vec16 Word8ElemRep) + data Word8X16# + type Word8X32# :: TYPE (VecRep Vec32 Word8ElemRep) + data Word8X32# + type Word8X64# :: TYPE (VecRep Vec64 Word8ElemRep) + data Word8X64# + type WordBox :: TYPE WordRep -> * + data WordBox a = MkWordBox a + type ZeroBitRep :: RuntimeRep + type ZeroBitRep = TupleRep '[] :: RuntimeRep + type ZeroBitType :: * + type ZeroBitType = TYPE ZeroBitRep + acosDouble# :: Double# -> Double# + acosFloat# :: Float# -> Float# + acoshDouble# :: Double# -> Double# + acoshFloat# :: Float# -> Float# + addCFinalizerToWeak# :: forall {k :: Levity} (b :: TYPE (BoxedRep k)). Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) + addIntC# :: Int# -> Int# -> (# Int#, Int# #) + addWordC# :: Word# -> Word# -> (# Word#, Int# #) + addr2Int# :: Addr# -> Int# + addrToAny# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Addr# -> (# a #) + and# :: Word# -> Word# -> Word# + and64# :: Word64# -> Word64# -> Word64# + andI# :: Int# -> Int# -> Int# + andWord16# :: Word16# -> Word16# -> Word16# + andWord32# :: Word32# -> Word32# -> Word32# + andWord8# :: Word8# -> Word8# -> Word8# + anyToAddr# :: forall a. a -> State# RealWorld -> (# State# RealWorld, Addr# #) + asinDouble# :: Double# -> Double# + asinFloat# :: Float# -> Float# + asinhDouble# :: Double# -> Double# + asinhFloat# :: Float# -> Float# + atanDouble# :: Double# -> Double# + atanFloat# :: Float# -> Float# + atanhDouble# :: Double# -> Double# + atanhFloat# :: Float# -> Float# + atomicCasAddrAddr# :: forall d. Addr# -> Addr# -> Addr# -> State# d -> (# State# d, Addr# #) + atomicCasWord16Addr# :: forall d. Addr# -> Word16# -> Word16# -> State# d -> (# State# d, Word16# #) + atomicCasWord32Addr# :: forall d. Addr# -> Word32# -> Word32# -> State# d -> (# State# d, Word32# #) + atomicCasWord64Addr# :: forall d. Addr# -> Word64# -> Word64# -> State# d -> (# State# d, Word64# #) + atomicCasWord8Addr# :: forall d. Addr# -> Word8# -> Word8# -> State# d -> (# State# d, Word8# #) + atomicCasWordAddr# :: forall d. Addr# -> Word# -> Word# -> State# d -> (# State# d, Word# #) + atomicExchangeAddrAddr# :: forall d. Addr# -> Addr# -> State# d -> (# State# d, Addr# #) + atomicExchangeWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + atomicModifyMutVar# :: forall s a b c. MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #) + atomicModifyMutVar2# :: forall d a c. MutVar# d a -> (a -> c) -> State# d -> (# State# d, a, c #) + atomicModifyMutVar_# :: forall d a. MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) + atomicReadIntArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) + atomicReadWordAddr# :: forall d. Addr# -> State# d -> (# State# d, Word# #) + atomicSwapMutVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutVar# d a -> a -> State# d -> (# State# d, a #) + atomicWriteIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + atomicWriteWordAddr# :: forall d. Addr# -> Word# -> State# d -> State# d + atomically# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] + bitReverse# :: Word# -> Word# + bitReverse16# :: Word# -> Word# + bitReverse32# :: Word# -> Word# + bitReverse64# :: Word64# -> Word64# + bitReverse8# :: Word# -> Word# + breakpoint :: forall a. a -> a + breakpointCond :: forall a. Bool -> a -> a + broadcastDoubleX2# :: Double# -> DoubleX2# + broadcastDoubleX4# :: Double# -> DoubleX4# + broadcastDoubleX8# :: Double# -> DoubleX8# + broadcastFloatX16# :: Float# -> FloatX16# + broadcastFloatX4# :: Float# -> FloatX4# + broadcastFloatX8# :: Float# -> FloatX8# + broadcastInt16X16# :: Int16# -> Int16X16# + broadcastInt16X32# :: Int16# -> Int16X32# + broadcastInt16X8# :: Int16# -> Int16X8# + broadcastInt32X16# :: Int32# -> Int32X16# + broadcastInt32X4# :: Int32# -> Int32X4# + broadcastInt32X8# :: Int32# -> Int32X8# + broadcastInt64X2# :: Int64# -> Int64X2# + broadcastInt64X4# :: Int64# -> Int64X4# + broadcastInt64X8# :: Int64# -> Int64X8# + broadcastInt8X16# :: Int8# -> Int8X16# + broadcastInt8X32# :: Int8# -> Int8X32# + broadcastInt8X64# :: Int8# -> Int8X64# + broadcastWord16X16# :: Word16# -> Word16X16# + broadcastWord16X32# :: Word16# -> Word16X32# + broadcastWord16X8# :: Word16# -> Word16X8# + broadcastWord32X16# :: Word32# -> Word32X16# + broadcastWord32X4# :: Word32# -> Word32X4# + broadcastWord32X8# :: Word32# -> Word32X8# + broadcastWord64X2# :: Word64# -> Word64X2# + broadcastWord64X4# :: Word64# -> Word64X4# + broadcastWord64X8# :: Word64# -> Word64X8# + broadcastWord8X16# :: Word8# -> Word8X16# + broadcastWord8X32# :: Word8# -> Word8X32# + broadcastWord8X64# :: Word8# -> Word8X64# + build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + byteArrayContents# :: ByteArray# -> Addr# + byteSwap# :: Word# -> Word# + byteSwap16# :: Word# -> Word# + byteSwap32# :: Word# -> Word# + byteSwap64# :: Word64# -> Word64# + casArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) + casInt16Array# :: forall d. MutableByteArray# d -> Int# -> Int16# -> Int16# -> State# d -> (# State# d, Int16# #) + casInt32Array# :: forall d. MutableByteArray# d -> Int# -> Int32# -> Int32# -> State# d -> (# State# d, Int32# #) + casInt64Array# :: forall d. MutableByteArray# d -> Int# -> Int64# -> Int64# -> State# d -> (# State# d, Int64# #) + casInt8Array# :: forall d. MutableByteArray# d -> Int# -> Int8# -> Int8# -> State# d -> (# State# d, Int8# #) + casIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> (# State# d, Int# #) + casMutVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutVar# d a -> a -> a -> State# d -> (# State# d, Int#, a #) + casSmallArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> a -> State# d -> (# State# d, Int#, a #) + castDoubleToWord64# :: Double# -> Word64# + castFloatToWord32# :: Float# -> Word32# + castWord32ToFloat# :: Word32# -> Float# + castWord64ToDouble# :: Word64# -> Double# + catch# :: forall {q :: RuntimeRep} {k :: Levity} (a :: TYPE q) (b :: TYPE (BoxedRep k)). (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + catchRetry# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + catchSTM# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + chr# :: Int# -> Char# + clearCCS# :: forall d a. (State# d -> (# State# d, a #)) -> State# d -> (# State# d, a #) + cloneArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Array# a -> Int# -> Int# -> Array# a + cloneMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) + cloneSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). SmallArray# a -> Int# -> Int# -> SmallArray# a + cloneSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) + closureSize# :: forall a. a -> Int# + clz# :: Word# -> Word# + clz16# :: Word# -> Word# + clz32# :: Word# -> Word# + clz64# :: Word64# -> Word# + clz8# :: Word# -> Word# + coerce :: forall {k :: RuntimeRep} (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b + compactAdd# :: forall a. Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) + compactAddWithSharing# :: forall a. Compact# -> a -> State# RealWorld -> (# State# RealWorld, a #) + compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) + compactContains# :: forall a. Compact# -> a -> State# RealWorld -> (# State# RealWorld, Int# #) + compactContainsAny# :: forall a. a -> State# RealWorld -> (# State# RealWorld, Int# #) + compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) + compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) + compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) + compactNew# :: Word# -> State# RealWorld -> (# State# RealWorld, Compact# #) + compactResize# :: Compact# -> Word# -> State# RealWorld -> State# RealWorld + compactSize# :: Compact# -> State# RealWorld -> (# State# RealWorld, Word# #) + compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# + considerAccessible :: Bool + control0# :: forall {r :: RuntimeRep} a (b :: TYPE r). PromptTag# a -> (((State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, b #) + copyAddrToAddr# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld + copyAddrToAddrNonOverlapping# :: Addr# -> Addr# -> Int# -> State# RealWorld -> State# RealWorld + copyAddrToByteArray# :: forall d. Addr# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + copyArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Array# a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d + copyArrayArray# :: forall s. ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s + copyByteArray# :: forall d. ByteArray# -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + copyByteArrayToAddr# :: forall d. ByteArray# -> Int# -> Addr# -> Int# -> State# d -> State# d + copyMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> MutableArray# d a -> Int# -> Int# -> State# d -> State# d + copyMutableArrayArray# :: forall s. MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s + copyMutableByteArray# :: forall d. MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + copyMutableByteArrayNonOverlapping# :: forall d. MutableByteArray# d -> Int# -> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + copyMutableByteArrayToAddr# :: forall d. MutableByteArray# d -> Int# -> Addr# -> Int# -> State# d -> State# d + copySmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. SmallArray# a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d + copySmallMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> SmallMutableArray# d a -> Int# -> Int# -> State# d -> State# d + cosDouble# :: Double# -> Double# + cosFloat# :: Float# -> Float# + coshDouble# :: Double# -> Double# + coshFloat# :: Float# -> Float# + cstringLength# :: Addr# -> Int# + ctz# :: Word# -> Word# + ctz16# :: Word# -> Word# + ctz32# :: Word# -> Word# + ctz64# :: Word64# -> Word# + ctz8# :: Word# -> Word# + currentCallStack :: GHC.Types.IO [GHC.Internal.Base.String] + deRefStablePtr# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) + deRefWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #) + decodeDouble_2Int# :: Double# -> (# Int#, Word#, Word#, Int# #) + decodeDouble_Int64# :: Double# -> (# Int64#, Int# #) + decodeFloat_Int# :: Float# -> (# Int#, Int# #) + delay# :: forall d. Int# -> State# d -> State# d + divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + divideFloat# :: Float# -> Float# -> Float# + divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + double2Float# :: Double# -> Float# + double2Int# :: Double# -> Int# + eqAddr# :: Addr# -> Addr# -> Int# + eqChar# :: Char# -> Char# -> Int# + eqFloat# :: Float# -> Float# -> Int# + eqInt16# :: Int16# -> Int16# -> Int# + eqInt32# :: Int32# -> Int32# -> Int# + eqInt64# :: Int64# -> Int64# -> Int# + eqInt8# :: Int8# -> Int8# -> Int# + eqStableName# :: forall {k :: Levity} {l :: Levity} (a :: TYPE (BoxedRep k)) (b :: TYPE (BoxedRep l)). StableName# a -> StableName# b -> Int# + eqStablePtr# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). StablePtr# a -> StablePtr# a -> Int# + eqWord# :: Word# -> Word# -> Int# + eqWord16# :: Word16# -> Word16# -> Int# + eqWord32# :: Word32# -> Word32# -> Int# + eqWord64# :: Word64# -> Word64# -> Int# + eqWord8# :: Word8# -> Word8# -> Int# + expDouble# :: Double# -> Double# + expFloat# :: Float# -> Float# + expm1Double# :: Double# -> Double# + expm1Float# :: Float# -> Float# + fabsDouble# :: Double# -> Double# + fabsFloat# :: Float# -> Float# + fetchAddIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchAddWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + fetchAndIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchAndWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + fetchNandIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchNandWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + fetchOrIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchOrWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + fetchSubIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchSubWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) + fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) + finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) + float2Double# :: Float# -> Double# + float2Int# :: Float# -> Int# + fmaddDouble# :: Double# -> Double# -> Double# -> Double# + fmaddDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2# + fmaddDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4# + fmaddDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8# + fmaddFloat# :: Float# -> Float# -> Float# -> Float# + fmaddFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16# + fmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4# + fmaddFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8# + fmsubDouble# :: Double# -> Double# -> Double# -> Double# + fmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2# + fmsubDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4# + fmsubDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8# + fmsubFloat# :: Float# -> Float# -> Float# -> Float# + fmsubFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16# + fmsubFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4# + fmsubFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8# + fnmaddDouble# :: Double# -> Double# -> Double# -> Double# + fnmaddDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2# + fnmaddDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4# + fnmaddDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8# + fnmaddFloat# :: Float# -> Float# -> Float# -> Float# + fnmaddFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16# + fnmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4# + fnmaddFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8# + fnmsubDouble# :: Double# -> Double# -> Double# -> Double# + fnmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2# + fnmsubDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# -> DoubleX4# + fnmsubDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# -> DoubleX8# + fnmsubFloat# :: Float# -> Float# -> Float# -> Float# + fnmsubFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# -> FloatX16# + fnmsubFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4# + fnmsubFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# -> FloatX8# + fork# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) + forkOn# :: forall {q :: RuntimeRep} (a :: TYPE q). Int# -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, ThreadId# #) + freezeArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, Array# a #) + freezeSmallArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> Int# -> State# d -> (# State# d, SmallArray# a #) + geAddr# :: Addr# -> Addr# -> Int# + geChar# :: Char# -> Char# -> Int# + geFloat# :: Float# -> Float# -> Int# + geInt16# :: Int16# -> Int16# -> Int# + geInt32# :: Int32# -> Int32# -> Int# + geInt64# :: Int64# -> Int64# -> Int# + geInt8# :: Int8# -> Int8# -> Int# + geWord# :: Word# -> Word# -> Int# + geWord16# :: Word16# -> Word16# -> Int# + geWord32# :: Word32# -> Word32# -> Int# + geWord64# :: Word64# -> Word64# -> Int# + geWord8# :: Word8# -> Word8# -> Int# + getApStackVal# :: forall a b. a -> Int# -> (# Int#, b #) + getCCSOf# :: forall a d. a -> State# d -> (# State# d, Addr# #) + getCurrentCCS# :: forall a d. a -> State# d -> (# State# d, Addr# #) + getMaskingState# :: State# RealWorld -> (# State# RealWorld, Int# #) + getSizeofMutableByteArray# :: forall d. MutableByteArray# d -> State# d -> (# State# d, Int# #) + getSizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, Int# #) + getSpark# :: forall d a. State# d -> (# State# d, Int#, a #) + getThreadAllocationCounter# :: State# RealWorld -> (# State# RealWorld, Int64# #) + groupWith :: forall b a. GHC.Classes.Ord b => (a -> b) -> [a] -> [[a]] + gtAddr# :: Addr# -> Addr# -> Int# + gtChar# :: Char# -> Char# -> Int# + gtFloat# :: Float# -> Float# -> Int# + gtInt16# :: Int16# -> Int16# -> Int# + gtInt32# :: Int32# -> Int32# -> Int# + gtInt64# :: Int64# -> Int64# -> Int# + gtInt8# :: Int8# -> Int8# -> Int# + gtWord# :: Word# -> Word# -> Int# + gtWord16# :: Word16# -> Word16# -> Int# + gtWord32# :: Word32# -> Word32# -> Int# + gtWord64# :: Word64# -> Word64# -> Int# + gtWord8# :: Word8# -> Word8# -> Int# + iShiftL# :: Int# -> Int# -> Int# + iShiftRA# :: Int# -> Int# -> Int# + iShiftRL# :: Int# -> Int# -> Int# + indexAddrArray# :: ByteArray# -> Int# -> Addr# + indexAddrOffAddr# :: Addr# -> Int# -> Addr# + indexArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Array# a -> Int# -> (# a #) + indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# + indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# + indexCharArray# :: ByteArray# -> Int# -> Char# + indexCharOffAddr# :: Addr# -> Int# -> Char# + indexDoubleArray# :: ByteArray# -> Int# -> Double# + indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# + indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# + indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# + indexDoubleOffAddr# :: Addr# -> Int# -> Double# + indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# + indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# + indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# + indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# + indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# + indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# + indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# + indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# + indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# + indexFloatArray# :: ByteArray# -> Int# -> Float# + indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# + indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# + indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# + indexFloatOffAddr# :: Addr# -> Int# -> Float# + indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# + indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# + indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# + indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# + indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# + indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# + indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# + indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# + indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# + indexInt16Array# :: ByteArray# -> Int# -> Int16# + indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# + indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# + indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# + indexInt16OffAddr# :: Addr# -> Int# -> Int16# + indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# + indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# + indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# + indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# + indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# + indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# + indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# + indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# + indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# + indexInt32Array# :: ByteArray# -> Int# -> Int32# + indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# + indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# + indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# + indexInt32OffAddr# :: Addr# -> Int# -> Int32# + indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# + indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# + indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# + indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# + indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# + indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# + indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# + indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# + indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# + indexInt64Array# :: ByteArray# -> Int# -> Int64# + indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# + indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# + indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# + indexInt64OffAddr# :: Addr# -> Int# -> Int64# + indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# + indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# + indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# + indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# + indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# + indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# + indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# + indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# + indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# + indexInt8Array# :: ByteArray# -> Int# -> Int8# + indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# + indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# + indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# + indexInt8OffAddr# :: Addr# -> Int# -> Int8# + indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# + indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# + indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# + indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# + indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# + indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# + indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# + indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# + indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# + indexIntArray# :: ByteArray# -> Int# -> Int# + indexIntOffAddr# :: Addr# -> Int# -> Int# + indexSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). SmallArray# a -> Int# -> (# a #) + indexStablePtrArray# :: forall a. ByteArray# -> Int# -> StablePtr# a + indexStablePtrOffAddr# :: forall a. Addr# -> Int# -> StablePtr# a + indexWideCharArray# :: ByteArray# -> Int# -> Char# + indexWideCharOffAddr# :: Addr# -> Int# -> Char# + indexWord16Array# :: ByteArray# -> Int# -> Word16# + indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# + indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# + indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# + indexWord16OffAddr# :: Addr# -> Int# -> Word16# + indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# + indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# + indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# + indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# + indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# + indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# + indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# + indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# + indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# + indexWord32Array# :: ByteArray# -> Int# -> Word32# + indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# + indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# + indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# + indexWord32OffAddr# :: Addr# -> Int# -> Word32# + indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# + indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# + indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# + indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# + indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# + indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# + indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# + indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# + indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# + indexWord64Array# :: ByteArray# -> Int# -> Word64# + indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# + indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# + indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# + indexWord64OffAddr# :: Addr# -> Int# -> Word64# + indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# + indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# + indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# + indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# + indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# + indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# + indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# + indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# + indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# + indexWord8Array# :: ByteArray# -> Int# -> Word8# + indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# + indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# + indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# + indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# + indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# + indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# + indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# + indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64# + indexWord8ArrayAsStablePtr# :: forall a. ByteArray# -> Int# -> StablePtr# a + indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# + indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# + indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# + indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# + indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64# + indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# + indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# + indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# + indexWord8OffAddr# :: Addr# -> Int# -> Word8# + indexWord8OffAddrAsAddr# :: Addr# -> Int# -> Addr# + indexWord8OffAddrAsChar# :: Addr# -> Int# -> Char# + indexWord8OffAddrAsDouble# :: Addr# -> Int# -> Double# + indexWord8OffAddrAsFloat# :: Addr# -> Int# -> Float# + indexWord8OffAddrAsInt# :: Addr# -> Int# -> Int# + indexWord8OffAddrAsInt16# :: Addr# -> Int# -> Int16# + indexWord8OffAddrAsInt32# :: Addr# -> Int# -> Int32# + indexWord8OffAddrAsInt64# :: Addr# -> Int# -> Int64# + indexWord8OffAddrAsStablePtr# :: forall a. Addr# -> Int# -> StablePtr# a + indexWord8OffAddrAsWideChar# :: Addr# -> Int# -> Char# + indexWord8OffAddrAsWord# :: Addr# -> Int# -> Word# + indexWord8OffAddrAsWord16# :: Addr# -> Int# -> Word16# + indexWord8OffAddrAsWord32# :: Addr# -> Int# -> Word32# + indexWord8OffAddrAsWord64# :: Addr# -> Int# -> Word64# + indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# + indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# + indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# + indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# + indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# + indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# + indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# + indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# + indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# + indexWordArray# :: ByteArray# -> Int# -> Word# + indexWordOffAddr# :: Addr# -> Int# -> Word# + inline :: forall a. a -> a + insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# + insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# + insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# + insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# + insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# + insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# + insertInt16X16# :: Int16X16# -> Int16# -> Int# -> Int16X16# + insertInt16X32# :: Int16X32# -> Int16# -> Int# -> Int16X32# + insertInt16X8# :: Int16X8# -> Int16# -> Int# -> Int16X8# + insertInt32X16# :: Int32X16# -> Int32# -> Int# -> Int32X16# + insertInt32X4# :: Int32X4# -> Int32# -> Int# -> Int32X4# + insertInt32X8# :: Int32X8# -> Int32# -> Int# -> Int32X8# + insertInt64X2# :: Int64X2# -> Int64# -> Int# -> Int64X2# + insertInt64X4# :: Int64X4# -> Int64# -> Int# -> Int64X4# + insertInt64X8# :: Int64X8# -> Int64# -> Int# -> Int64X8# + insertInt8X16# :: Int8X16# -> Int8# -> Int# -> Int8X16# + insertInt8X32# :: Int8X32# -> Int8# -> Int# -> Int8X32# + insertInt8X64# :: Int8X64# -> Int8# -> Int# -> Int8X64# + insertWord16X16# :: Word16X16# -> Word16# -> Int# -> Word16X16# + insertWord16X32# :: Word16X32# -> Word16# -> Int# -> Word16X32# + insertWord16X8# :: Word16X8# -> Word16# -> Int# -> Word16X8# + insertWord32X16# :: Word32X16# -> Word32# -> Int# -> Word32X16# + insertWord32X4# :: Word32X4# -> Word32# -> Int# -> Word32X4# + insertWord32X8# :: Word32X8# -> Word32# -> Int# -> Word32X8# + insertWord64X2# :: Word64X2# -> Word64# -> Int# -> Word64X2# + insertWord64X4# :: Word64X4# -> Word64# -> Int# -> Word64X4# + insertWord64X8# :: Word64X8# -> Word64# -> Int# -> Word64X8# + insertWord8X16# :: Word8X16# -> Word8# -> Int# -> Word8X16# + insertWord8X32# :: Word8X32# -> Word8# -> Int# -> Word8X32# + insertWord8X64# :: Word8X64# -> Word8# -> Int# -> Word8X64# + int16ToInt# :: Int16# -> Int# + int16ToWord16# :: Int16# -> Word16# + int2Addr# :: Int# -> Addr# + int2Double# :: Int# -> Double# + int2Float# :: Int# -> Float# + int2Word# :: Int# -> Word# + int32ToInt# :: Int32# -> Int# + int32ToWord32# :: Int32# -> Word32# + int64ToInt# :: Int64# -> Int# + int64ToWord64# :: Int64# -> Word64# + int8ToInt# :: Int8# -> Int# + int8ToWord8# :: Int8# -> Word8# + intToInt16# :: Int# -> Int16# + intToInt32# :: Int# -> Int32# + intToInt64# :: Int# -> Int64# + intToInt8# :: Int# -> Int8# + isByteArrayPinned# :: ByteArray# -> Int# + isByteArrayWeaklyPinned# :: ByteArray# -> Int# + isCurrentThreadBound# :: State# RealWorld -> (# State# RealWorld, Int# #) + isEmptyMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int# #) + isMutableByteArrayPinned# :: forall d. MutableByteArray# d -> Int# + isMutableByteArrayWeaklyPinned# :: forall d. MutableByteArray# d -> Int# + isTrue# :: Int# -> Bool + keepAlive# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE (BoxedRep l)) d (b :: TYPE r). a -> State# d -> (State# d -> b) -> b + killThread# :: forall a. ThreadId# -> a -> State# RealWorld -> State# RealWorld + labelThread# :: ThreadId# -> ByteArray# -> State# RealWorld -> State# RealWorld + lazy :: forall a. a -> a + leAddr# :: Addr# -> Addr# -> Int# + leChar# :: Char# -> Char# -> Int# + leFloat# :: Float# -> Float# -> Int# + leInt16# :: Int16# -> Int16# -> Int# + leInt32# :: Int32# -> Int32# -> Int# + leInt64# :: Int64# -> Int64# -> Int# + leInt8# :: Int8# -> Int8# -> Int# + leWord# :: Word# -> Word# -> Int# + leWord16# :: Word16# -> Word16# -> Int# + leWord32# :: Word32# -> Word32# -> Int# + leWord64# :: Word64# -> Word64# -> Int# + leWord8# :: Word8# -> Word8# -> Int# + leftSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b + listThreads# :: State# RealWorld -> (# State# RealWorld, Array# ThreadId# #) + log1pDouble# :: Double# -> Double# + log1pFloat# :: Float# -> Float# + logDouble# :: Double# -> Double# + logFloat# :: Float# -> Float# + ltAddr# :: Addr# -> Addr# -> Int# + ltChar# :: Char# -> Char# -> Int# + ltFloat# :: Float# -> Float# -> Int# + ltInt16# :: Int16# -> Int16# -> Int# + ltInt32# :: Int32# -> Int32# -> Int# + ltInt64# :: Int64# -> Int64# -> Int# + ltInt8# :: Int8# -> Int8# -> Int# + ltWord# :: Word# -> Word# -> Int# + ltWord16# :: Word16# -> Word16# -> Int# + ltWord32# :: Word32# -> Word32# -> Int# + ltWord64# :: Word64# -> Word64# -> Int# + ltWord8# :: Word8# -> Word8# -> Int# + makeStableName# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StableName# a #) + makeStablePtr# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) + maskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + maskUninterruptible# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + maxDouble# :: Double# -> Double# -> Double# + maxDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + maxDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + maxDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + maxFloat# :: Float# -> Float# -> Float# + maxFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + maxFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + maxFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + maxInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + maxInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + maxInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + maxInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + maxInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + maxInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + maxInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + maxInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + maxInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + maxInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + maxInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + maxInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + maxTupleSize :: Int + maxWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + maxWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + maxWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + maxWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + maxWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + maxWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + maxWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + maxWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + maxWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + maxWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + maxWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + maxWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + minDouble# :: Double# -> Double# -> Double# + minDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + minDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + minDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + minFloat# :: Float# -> Float# -> Float# + minFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + minFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + minInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + minInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + minInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + minInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + minInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + minInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + minInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + minInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + minInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + minInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + minInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + minInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + minWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + minWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + minWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + minWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + minWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + minWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + minWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + minWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + minWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + minWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + minWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + minusAddr# :: Addr# -> Addr# -> Int# + minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + minusFloat# :: Float# -> Float# -> Float# + minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + minusWord# :: Word# -> Word# -> Word# + minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + mkApUpd0# :: forall a. BCO -> (# a #) + mkWeak# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)) c. a -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) + mkWeakNoFinalizer# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> State# RealWorld -> (# State# RealWorld, Weak# b #) + mulIntMayOflo# :: Int# -> Int# -> Int# + mutableByteArrayContents# :: forall d. MutableByteArray# d -> Addr# + myThreadId# :: State# RealWorld -> (# State# RealWorld, ThreadId# #) + narrow16Int# :: Int# -> Int# + narrow16Word# :: Word# -> Word# + narrow32Int# :: Int# -> Int# + narrow32Word# :: Word# -> Word# + narrow8Int# :: Int# -> Int# + narrow8Word# :: Word# -> Word# + neAddr# :: Addr# -> Addr# -> Int# + neChar# :: Char# -> Char# -> Int# + neFloat# :: Float# -> Float# -> Int# + neInt16# :: Int16# -> Int16# -> Int# + neInt32# :: Int32# -> Int32# -> Int# + neInt64# :: Int64# -> Int64# -> Int# + neInt8# :: Int8# -> Int8# -> Int# + neWord# :: Word# -> Word# -> Int# + neWord16# :: Word16# -> Word16# -> Int# + neWord32# :: Word32# -> Word32# -> Int# + neWord64# :: Word64# -> Word64# -> Int# + neWord8# :: Word8# -> Word8# -> Int# + negateDouble# :: Double# -> Double# + negateDoubleX2# :: DoubleX2# -> DoubleX2# + negateDoubleX4# :: DoubleX4# -> DoubleX4# + negateDoubleX8# :: DoubleX8# -> DoubleX8# + negateFloat# :: Float# -> Float# + negateFloatX16# :: FloatX16# -> FloatX16# + negateFloatX4# :: FloatX4# -> FloatX4# + negateFloatX8# :: FloatX8# -> FloatX8# + negateInt# :: Int# -> Int# + negateInt16# :: Int16# -> Int16# + negateInt16X16# :: Int16X16# -> Int16X16# + negateInt16X32# :: Int16X32# -> Int16X32# + negateInt16X8# :: Int16X8# -> Int16X8# + negateInt32# :: Int32# -> Int32# + negateInt32X16# :: Int32X16# -> Int32X16# + negateInt32X4# :: Int32X4# -> Int32X4# + negateInt32X8# :: Int32X8# -> Int32X8# + negateInt64# :: Int64# -> Int64# + negateInt64X2# :: Int64X2# -> Int64X2# + negateInt64X4# :: Int64X4# -> Int64X4# + negateInt64X8# :: Int64X8# -> Int64X8# + negateInt8# :: Int8# -> Int8# + negateInt8X16# :: Int8X16# -> Int8X16# + negateInt8X32# :: Int8X32# -> Int8X32# + negateInt8X64# :: Int8X64# -> Int8X64# + newAlignedPinnedByteArray# :: forall d. Int# -> Int# -> State# d -> (# State# d, MutableByteArray# d #) + newArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, MutableArray# d a #) + newArrayArray# :: forall s. Int# -> State# s -> (# State# s, MutableArrayArray# s #) + newBCO# :: forall a d. ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# d -> (# State# d, BCO #) + newByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) + newIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, IOPort# d a #) + newMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). State# d -> (# State# d, MVar# d a #) + newMutVar# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. a -> State# d -> (# State# d, MutVar# d a #) + newPinnedByteArray# :: forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) + newPromptTag# :: forall a. State# RealWorld -> (# State# RealWorld, PromptTag# a #) + newSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Int# -> a -> State# d -> (# State# d, SmallMutableArray# d a #) + newTVar# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. a -> State# d -> (# State# d, TVar# d a #) + noDuplicate# :: forall d. State# d -> State# d + noinline :: forall a. a -> a + not# :: Word# -> Word# + not64# :: Word64# -> Word64# + notI# :: Int# -> Int# + notWord16# :: Word16# -> Word16# + notWord32# :: Word32# -> Word32# + notWord8# :: Word8# -> Word8# + nullAddr# :: Addr# + numSparks# :: forall d. State# d -> (# State# d, Int# #) + oneShot :: forall {q :: RuntimeRep} {r :: RuntimeRep} (a :: TYPE q) (b :: TYPE r). (a -> b) -> a -> b + or# :: Word# -> Word# -> Word# + or64# :: Word64# -> Word64# -> Word64# + orI# :: Int# -> Int# -> Int# + orWord16# :: Word16# -> Word16# -> Word16# + orWord32# :: Word32# -> Word32# -> Word32# + orWord8# :: Word8# -> Word8# -> Word8# + ord# :: Char# -> Int# + packDoubleX2# :: (# Double#, Double# #) -> DoubleX2# + packDoubleX4# :: (# Double#, Double#, Double#, Double# #) -> DoubleX4# + packDoubleX8# :: (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) -> DoubleX8# + packFloatX16# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX16# + packFloatX4# :: (# Float#, Float#, Float#, Float# #) -> FloatX4# + packFloatX8# :: (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) -> FloatX8# + packInt16X16# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X16# + packInt16X32# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X32# + packInt16X8# :: (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) -> Int16X8# + packInt32X16# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X16# + packInt32X4# :: (# Int32#, Int32#, Int32#, Int32# #) -> Int32X4# + packInt32X8# :: (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) -> Int32X8# + packInt64X2# :: (# Int64#, Int64# #) -> Int64X2# + packInt64X4# :: (# Int64#, Int64#, Int64#, Int64# #) -> Int64X4# + packInt64X8# :: (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) -> Int64X8# + packInt8X16# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X16# + packInt8X32# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X32# + packInt8X64# :: (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) -> Int8X64# + packWord16X16# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X16# + packWord16X32# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X32# + packWord16X8# :: (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) -> Word16X8# + packWord32X16# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X16# + packWord32X4# :: (# Word32#, Word32#, Word32#, Word32# #) -> Word32X4# + packWord32X8# :: (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) -> Word32X8# + packWord64X2# :: (# Word64#, Word64# #) -> Word64X2# + packWord64X4# :: (# Word64#, Word64#, Word64#, Word64# #) -> Word64X4# + packWord64X8# :: (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) -> Word64X8# + packWord8X16# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X16# + packWord8X32# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X32# + packWord8X64# :: (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) -> Word8X64# + par# :: forall a. a -> Int# + pdep# :: Word# -> Word# -> Word# + pdep16# :: Word# -> Word# -> Word# + pdep32# :: Word# -> Word# -> Word# + pdep64# :: Word64# -> Word64# -> Word64# + pdep8# :: Word# -> Word# -> Word# + pext# :: Word# -> Word# -> Word# + pext16# :: Word# -> Word# -> Word# + pext32# :: Word# -> Word# -> Word# + pext64# :: Word64# -> Word64# -> Word64# + pext8# :: Word# -> Word# -> Word# + plusAddr# :: Addr# -> Int# -> Addr# + plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + plusFloat# :: Float# -> Float# -> Float# + plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + plusInt16# :: Int16# -> Int16# -> Int16# + plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + plusInt32# :: Int32# -> Int32# -> Int32# + plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + plusInt64# :: Int64# -> Int64# -> Int64# + plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + plusInt8# :: Int8# -> Int8# -> Int8# + plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + plusWord# :: Word# -> Word# -> Word# + plusWord16# :: Word16# -> Word16# -> Word16# + plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + plusWord2# :: Word# -> Word# -> (# Word#, Word# #) + plusWord32# :: Word32# -> Word32# -> Word32# + plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + plusWord64# :: Word64# -> Word64# -> Word64# + plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + plusWord8# :: Word8# -> Word8# -> Word8# + plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + popCnt# :: Word# -> Word# + popCnt16# :: Word# -> Word# + popCnt32# :: Word# -> Word# + popCnt64# :: Word64# -> Word# + popCnt8# :: Word# -> Word# + powerFloat# :: Float# -> Float# -> Float# + prefetchAddr0# :: forall d. Addr# -> Int# -> State# d -> State# d + prefetchAddr1# :: forall d. Addr# -> Int# -> State# d -> State# d + prefetchAddr2# :: forall d. Addr# -> Int# -> State# d -> State# d + prefetchAddr3# :: forall d. Addr# -> Int# -> State# d -> State# d + prefetchByteArray0# :: forall d. ByteArray# -> Int# -> State# d -> State# d + prefetchByteArray1# :: forall d. ByteArray# -> Int# -> State# d -> State# d + prefetchByteArray2# :: forall d. ByteArray# -> Int# -> State# d -> State# d + prefetchByteArray3# :: forall d. ByteArray# -> Int# -> State# d -> State# d + prefetchMutableByteArray0# :: forall d. MutableByteArray# d -> Int# -> State# d -> State# d + prefetchMutableByteArray1# :: forall d. MutableByteArray# d -> Int# -> State# d -> State# d + prefetchMutableByteArray2# :: forall d. MutableByteArray# d -> Int# -> State# d -> State# d + prefetchMutableByteArray3# :: forall d. MutableByteArray# d -> Int# -> State# d -> State# d + prefetchValue0# :: forall a d. a -> State# d -> State# d + prefetchValue1# :: forall a d. a -> State# d -> State# d + prefetchValue2# :: forall a d. a -> State# d -> State# d + prefetchValue3# :: forall a d. a -> State# d -> State# d + prompt# :: forall a. PromptTag# a -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + proxy# :: forall {k} (a :: k). Proxy# a + putMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> a -> State# d -> State# d + quotInt# :: Int# -> Int# -> Int# + quotInt16# :: Int16# -> Int16# -> Int16# + quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + quotInt32# :: Int32# -> Int32# -> Int32# + quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + quotInt64# :: Int64# -> Int64# -> Int64# + quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + quotInt8# :: Int8# -> Int8# -> Int8# + quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + quotRemInt# :: Int# -> Int# -> (# Int#, Int# #) + quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #) + quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #) + quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #) + quotRemWord# :: Word# -> Word# -> (# Word#, Word# #) + quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #) + quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#, Word# #) + quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #) + quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #) + quotWord# :: Word# -> Word# -> Word# + quotWord16# :: Word16# -> Word16# -> Word16# + quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + quotWord32# :: Word32# -> Word32# -> Word32# + quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + quotWord64# :: Word64# -> Word64# -> Word64# + quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + quotWord8# :: Word8# -> Word8# -> Word8# + quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + raise# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE (BoxedRep l)) (b :: TYPE r). a -> b + raiseDivZero# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b + raiseIO# :: forall {l :: Levity} {r :: RuntimeRep} (a :: TYPE (BoxedRep l)) (b :: TYPE r). a -> State# RealWorld -> (# State# RealWorld, b #) + raiseOverflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b + raiseUnderflow# :: forall {r :: RuntimeRep} (b :: TYPE r). (# #) -> b + readAddrArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) + readAddrOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Addr# #) + readArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> State# d -> (# State# d, a #) + readArrayArrayArray# :: forall s. MutableArrayArray# s -> Int# -> State# s -> (# State# s, ArrayArray# #) + readByteArrayArray# :: forall s. MutableArrayArray# s -> Int# -> State# s -> (# State# s, ByteArray# #) + readCharArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) + readCharOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #) + readDoubleArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) + readDoubleArrayAsDoubleX2# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) + readDoubleArrayAsDoubleX4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) + readDoubleArrayAsDoubleX8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) + readDoubleOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Double# #) + readDoubleOffAddrAsDoubleX2# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) + readDoubleOffAddrAsDoubleX4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) + readDoubleOffAddrAsDoubleX8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) + readDoubleX2Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX2# #) + readDoubleX2OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX2# #) + readDoubleX4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX4# #) + readDoubleX4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX4# #) + readDoubleX8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, DoubleX8# #) + readDoubleX8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, DoubleX8# #) + readFloatArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) + readFloatArrayAsFloatX16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) + readFloatArrayAsFloatX4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) + readFloatArrayAsFloatX8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) + readFloatOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Float# #) + readFloatOffAddrAsFloatX16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) + readFloatOffAddrAsFloatX4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) + readFloatOffAddrAsFloatX8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) + readFloatX16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX16# #) + readFloatX16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX16# #) + readFloatX4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX4# #) + readFloatX4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX4# #) + readFloatX8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, FloatX8# #) + readFloatX8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, FloatX8# #) + readIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). IOPort# d a -> State# d -> (# State# d, a #) + readInt16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) + readInt16ArrayAsInt16X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) + readInt16ArrayAsInt16X32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) + readInt16ArrayAsInt16X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) + readInt16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16# #) + readInt16OffAddrAsInt16X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) + readInt16OffAddrAsInt16X32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) + readInt16OffAddrAsInt16X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) + readInt16X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X16# #) + readInt16X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X16# #) + readInt16X32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X32# #) + readInt16X32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X32# #) + readInt16X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16X8# #) + readInt16X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16X8# #) + readInt32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) + readInt32ArrayAsInt32X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) + readInt32ArrayAsInt32X4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) + readInt32ArrayAsInt32X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) + readInt32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32# #) + readInt32OffAddrAsInt32X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) + readInt32OffAddrAsInt32X4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) + readInt32OffAddrAsInt32X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) + readInt32X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X16# #) + readInt32X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X16# #) + readInt32X4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X4# #) + readInt32X4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X4# #) + readInt32X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32X8# #) + readInt32X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32X8# #) + readInt64Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) + readInt64ArrayAsInt64X2# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) + readInt64ArrayAsInt64X4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) + readInt64ArrayAsInt64X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) + readInt64OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64# #) + readInt64OffAddrAsInt64X2# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) + readInt64OffAddrAsInt64X4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) + readInt64OffAddrAsInt64X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) + readInt64X2Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X2# #) + readInt64X2OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X2# #) + readInt64X4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X4# #) + readInt64X4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X4# #) + readInt64X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64X8# #) + readInt64X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64X8# #) + readInt8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8# #) + readInt8ArrayAsInt8X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) + readInt8ArrayAsInt8X32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) + readInt8ArrayAsInt8X64# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) + readInt8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8# #) + readInt8OffAddrAsInt8X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) + readInt8OffAddrAsInt8X32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) + readInt8OffAddrAsInt8X64# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) + readInt8X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X16# #) + readInt8X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X16# #) + readInt8X32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X32# #) + readInt8X32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X32# #) + readInt8X64Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int8X64# #) + readInt8X64OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int8X64# #) + readIntArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) + readIntOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int# #) + readMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) + readMutVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutVar# d a -> State# d -> (# State# d, a #) + readMutableArrayArrayArray# :: forall s. MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableArrayArray# s #) + readMutableByteArrayArray# :: forall s. MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) + readSmallArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> (# State# d, a #) + readStablePtrArray# :: forall d a. MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) + readStablePtrOffAddr# :: forall d a. Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) + readTVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) + readTVarIO# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). TVar# d a -> State# d -> (# State# d, a #) + readWideCharArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) + readWideCharOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #) + readWord16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) + readWord16ArrayAsWord16X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) + readWord16ArrayAsWord16X32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) + readWord16ArrayAsWord16X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) + readWord16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16# #) + readWord16OffAddrAsWord16X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) + readWord16OffAddrAsWord16X32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) + readWord16OffAddrAsWord16X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) + readWord16X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X16# #) + readWord16X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X16# #) + readWord16X32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X32# #) + readWord16X32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X32# #) + readWord16X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16X8# #) + readWord16X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16X8# #) + readWord32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) + readWord32ArrayAsWord32X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) + readWord32ArrayAsWord32X4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) + readWord32ArrayAsWord32X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) + readWord32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32# #) + readWord32OffAddrAsWord32X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) + readWord32OffAddrAsWord32X4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) + readWord32OffAddrAsWord32X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) + readWord32X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X16# #) + readWord32X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X16# #) + readWord32X4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X4# #) + readWord32X4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X4# #) + readWord32X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32X8# #) + readWord32X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32X8# #) + readWord64Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) + readWord64ArrayAsWord64X2# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) + readWord64ArrayAsWord64X4# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) + readWord64ArrayAsWord64X8# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) + readWord64OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64# #) + readWord64OffAddrAsWord64X2# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) + readWord64OffAddrAsWord64X4# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) + readWord64OffAddrAsWord64X8# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) + readWord64X2Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X2# #) + readWord64X2OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X2# #) + readWord64X4Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X4# #) + readWord64X4OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X4# #) + readWord64X8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64X8# #) + readWord64X8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64X8# #) + readWord8Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8# #) + readWord8ArrayAsAddr# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) + readWord8ArrayAsChar# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) + readWord8ArrayAsDouble# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) + readWord8ArrayAsFloat# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) + readWord8ArrayAsInt# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int# #) + readWord8ArrayAsInt16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int16# #) + readWord8ArrayAsInt32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int32# #) + readWord8ArrayAsInt64# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Int64# #) + readWord8ArrayAsStablePtr# :: forall d a. MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) + readWord8ArrayAsWideChar# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) + readWord8ArrayAsWord# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) + readWord8ArrayAsWord16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word16# #) + readWord8ArrayAsWord32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word32# #) + readWord8ArrayAsWord64# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word64# #) + readWord8ArrayAsWord8X16# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) + readWord8ArrayAsWord8X32# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) + readWord8ArrayAsWord8X64# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) + readWord8OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8# #) + readWord8OffAddrAsAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Addr# #) + readWord8OffAddrAsChar# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #) + readWord8OffAddrAsDouble# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Double# #) + readWord8OffAddrAsFloat# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Float# #) + readWord8OffAddrAsInt# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int# #) + readWord8OffAddrAsInt16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int16# #) + readWord8OffAddrAsInt32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int32# #) + readWord8OffAddrAsInt64# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Int64# #) + readWord8OffAddrAsStablePtr# :: forall d a. Addr# -> Int# -> State# d -> (# State# d, StablePtr# a #) + readWord8OffAddrAsWideChar# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Char# #) + readWord8OffAddrAsWord# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word# #) + readWord8OffAddrAsWord16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word16# #) + readWord8OffAddrAsWord32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word32# #) + readWord8OffAddrAsWord64# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word64# #) + readWord8OffAddrAsWord8X16# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) + readWord8OffAddrAsWord8X32# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) + readWord8OffAddrAsWord8X64# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) + readWord8X16Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X16# #) + readWord8X16OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X16# #) + readWord8X32Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X32# #) + readWord8X32OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X32# #) + readWord8X64Array# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word8X64# #) + readWord8X64OffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word8X64# #) + readWordArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) + readWordOffAddr# :: forall d. Addr# -> Int# -> State# d -> (# State# d, Word# #) + realWorld# :: State# RealWorld + reallyUnsafePtrEquality :: forall a. a -> a -> Int# + reallyUnsafePtrEquality# :: forall {l :: Levity} {k :: Levity} (a :: TYPE (BoxedRep l)) (b :: TYPE (BoxedRep k)). a -> b -> Int# + remAddr# :: Addr# -> Int# -> Int# + remInt# :: Int# -> Int# -> Int# + remInt16# :: Int16# -> Int16# -> Int16# + remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + remInt32# :: Int32# -> Int32# -> Int32# + remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + remInt64# :: Int64# -> Int64# -> Int64# + remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + remInt8# :: Int8# -> Int8# -> Int8# + remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + remWord# :: Word# -> Word# -> Word# + remWord16# :: Word16# -> Word16# -> Word16# + remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + remWord32# :: Word32# -> Word32# -> Word32# + remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + remWord64# :: Word64# -> Word64# -> Word64# + remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + remWord8# :: Word8# -> Word8# -> Word8# + remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + resizeMutableByteArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> (# State# d, MutableByteArray# d #) + resizeSmallMutableArray# :: forall s a. SmallMutableArray# s a -> Int# -> a -> State# s -> (# State# s, SmallMutableArray# s a #) + retry# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). State# RealWorld -> (# State# RealWorld, a #) + rightSection :: forall {q :: RuntimeRep} {r :: RuntimeRep} {s :: RuntimeRep} (a :: TYPE q) (b :: TYPE r) (c :: TYPE s). (a -> b -> c) -> b -> a -> c + runRW# :: forall (r :: RuntimeRep) (o :: TYPE r). (State# RealWorld -> o) -> o + sameArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int# + sameArrayArray# :: ArrayArray# -> ArrayArray# -> Int# + sameByteArray# :: ByteArray# -> ByteArray# -> Int# + sameIOPort# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). IOPort# s a -> IOPort# s a -> Int# + sameMVar# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). MVar# s a -> MVar# s a -> Int# + sameMutVar# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). MutVar# s a -> MutVar# s a -> Int# + sameMutableArray# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). MutableArray# s a -> MutableArray# s a -> Int# + sameMutableArrayArray# :: forall s. MutableArrayArray# s -> MutableArrayArray# s -> Int# + sameMutableByteArray# :: forall s. MutableByteArray# s -> MutableByteArray# s -> Int# + samePromptTag# :: forall a. PromptTag# a -> PromptTag# a -> Int# + sameSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). SmallArray# a -> SmallArray# a -> Int# + sameSmallMutableArray# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). SmallMutableArray# s a -> SmallMutableArray# s a -> Int# + sameTVar# :: forall {l :: Levity} s (a :: TYPE (BoxedRep l)). TVar# s a -> TVar# s a -> Int# + seq :: forall {r :: RuntimeRep} a (b :: TYPE r). a -> b -> b + seq# :: forall a s. a -> State# s -> (# State# s, a #) + setAddrRange# :: Addr# -> Int# -> Int# -> State# RealWorld -> State# RealWorld + setByteArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> Int# -> State# d -> State# d + setThreadAllocationCounter# :: Int64# -> State# RealWorld -> State# RealWorld + shiftL# :: Word# -> Int# -> Word# + shiftRL# :: Word# -> Int# -> Word# + shrinkMutableByteArray# :: forall d. MutableByteArray# d -> Int# -> State# d -> State# d + shrinkSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> State# d -> State# d + shuffleDoubleX2# :: DoubleX2# -> DoubleX2# -> (# Int#, Int# #) -> DoubleX2# + shuffleDoubleX4# :: DoubleX4# -> DoubleX4# -> (# Int#, Int#, Int#, Int# #) -> DoubleX4# + shuffleDoubleX8# :: DoubleX8# -> DoubleX8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> DoubleX8# + shuffleFloatX16# :: FloatX16# -> FloatX16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> FloatX16# + shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# + shuffleFloatX8# :: FloatX8# -> FloatX8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> FloatX8# + shuffleInt16X16# :: Int16X16# -> Int16X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X16# + shuffleInt16X32# :: Int16X32# -> Int16X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X32# + shuffleInt16X8# :: Int16X8# -> Int16X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int16X8# + shuffleInt32X16# :: Int32X16# -> Int32X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X16# + shuffleInt32X4# :: Int32X4# -> Int32X4# -> (# Int#, Int#, Int#, Int# #) -> Int32X4# + shuffleInt32X8# :: Int32X8# -> Int32X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int32X8# + shuffleInt64X2# :: Int64X2# -> Int64X2# -> (# Int#, Int# #) -> Int64X2# + shuffleInt64X4# :: Int64X4# -> Int64X4# -> (# Int#, Int#, Int#, Int# #) -> Int64X4# + shuffleInt64X8# :: Int64X8# -> Int64X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int64X8# + shuffleInt8X16# :: Int8X16# -> Int8X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X16# + shuffleInt8X32# :: Int8X32# -> Int8X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X32# + shuffleInt8X64# :: Int8X64# -> Int8X64# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Int8X64# + shuffleWord16X16# :: Word16X16# -> Word16X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X16# + shuffleWord16X32# :: Word16X32# -> Word16X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X32# + shuffleWord16X8# :: Word16X8# -> Word16X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word16X8# + shuffleWord32X16# :: Word32X16# -> Word32X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word32X16# + shuffleWord32X4# :: Word32X4# -> Word32X4# -> (# Int#, Int#, Int#, Int# #) -> Word32X4# + shuffleWord32X8# :: Word32X8# -> Word32X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word32X8# + shuffleWord64X2# :: Word64X2# -> Word64X2# -> (# Int#, Int# #) -> Word64X2# + shuffleWord64X4# :: Word64X4# -> Word64X4# -> (# Int#, Int#, Int#, Int# #) -> Word64X4# + shuffleWord64X8# :: Word64X8# -> Word64X8# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word64X8# + shuffleWord8X16# :: Word8X16# -> Word8X16# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X16# + shuffleWord8X32# :: Word8X32# -> Word8X32# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X32# + shuffleWord8X64# :: Word8X64# -> Word8X64# -> (# Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int#, Int# #) -> Word8X64# + sinDouble# :: Double# -> Double# + sinFloat# :: Float# -> Float# + sinhDouble# :: Double# -> Double# + sinhFloat# :: Float# -> Float# + sizeofArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). Array# a -> Int# + sizeofArrayArray# :: ArrayArray# -> Int# + sizeofByteArray# :: ByteArray# -> Int# + sizeofMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# + sizeofMutableArrayArray# :: forall s. MutableArrayArray# s -> Int# + sizeofMutableByteArray# :: forall d. MutableByteArray# d -> Int# + sizeofSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). SmallArray# a -> Int# + sizeofSmallMutableArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# + sortWith :: forall b a. GHC.Classes.Ord b => (a -> b) -> [a] -> [a] + spark# :: forall a d. a -> State# d -> (# State# d, a #) + sqrtDouble# :: Double# -> Double# + sqrtFloat# :: Float# -> Float# + stableNameToInt# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)). StableName# a -> Int# + subInt16# :: Int16# -> Int16# -> Int16# + subInt32# :: Int32# -> Int32# -> Int32# + subInt64# :: Int64# -> Int64# -> Int64# + subInt8# :: Int8# -> Int8# -> Int8# + subIntC# :: Int# -> Int# -> (# Int#, Int# #) + subWord16# :: Word16# -> Word16# -> Word16# + subWord32# :: Word32# -> Word32# -> Word32# + subWord64# :: Word64# -> Word64# -> Word64# + subWord8# :: Word8# -> Word8# -> Word8# + subWordC# :: Word# -> Word# -> (# Word#, Int# #) + tagToEnum# :: forall a. Int# -> a + takeMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> State# d -> (# State# d, a #) + tanDouble# :: Double# -> Double# + tanFloat# :: Float# -> Float# + tanhDouble# :: Double# -> Double# + tanhFloat# :: Float# -> Float# + thawArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Array# a -> Int# -> Int# -> State# d -> (# State# d, MutableArray# d a #) + thawSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. SmallArray# a -> Int# -> Int# -> State# d -> (# State# d, SmallMutableArray# d a #) + the :: forall a. GHC.Classes.Eq a => [a] -> a + threadLabel# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, ByteArray# #) + threadStatus# :: ThreadId# -> State# RealWorld -> (# State# RealWorld, Int#, Int#, Int# #) + timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# + timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# + timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# + timesFloat# :: Float# -> Float# -> Float# + timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# + timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# + timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# + timesInt16# :: Int16# -> Int16# -> Int16# + timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# + timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# + timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# + timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #) + timesInt32# :: Int32# -> Int32# -> Int32# + timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# + timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# + timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# + timesInt64# :: Int64# -> Int64# -> Int64# + timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# + timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# + timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# + timesInt8# :: Int8# -> Int8# -> Int8# + timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# + timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# + timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# + timesWord# :: Word# -> Word# -> Word# + timesWord16# :: Word16# -> Word16# -> Word16# + timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# + timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# + timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# + timesWord2# :: Word# -> Word# -> (# Word#, Word# #) + timesWord32# :: Word32# -> Word32# -> Word32# + timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# + timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# + timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# + timesWord64# :: Word64# -> Word64# -> Word64# + timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# + timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# + timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# + timesWord8# :: Word8# -> Word8# -> Word8# + timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# + timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# + timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# + touch# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. a -> State# d -> State# d + traceBinaryEvent# :: forall d. Addr# -> Int# -> State# d -> State# d + traceEvent :: GHC.Internal.Base.String -> GHC.Types.IO () + traceEvent# :: forall d. Addr# -> State# d -> State# d + traceMarker# :: forall d. Addr# -> State# d -> State# d + tryPutMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> a -> State# d -> (# State# d, Int# #) + tryReadMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) + tryTakeMVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MVar# d a -> State# d -> (# State# d, Int#, a #) + uncheckedIShiftL# :: Int# -> Int# -> Int# + uncheckedIShiftL64# :: Int64# -> Int# -> Int64# + uncheckedIShiftRA# :: Int# -> Int# -> Int# + uncheckedIShiftRA64# :: Int64# -> Int# -> Int64# + uncheckedIShiftRL# :: Int# -> Int# -> Int# + uncheckedIShiftRL64# :: Int64# -> Int# -> Int64# + uncheckedShiftL# :: Word# -> Int# -> Word# + uncheckedShiftL64# :: Word64# -> Int# -> Word64# + uncheckedShiftLInt16# :: Int16# -> Int# -> Int16# + uncheckedShiftLInt32# :: Int32# -> Int# -> Int32# + uncheckedShiftLInt8# :: Int8# -> Int# -> Int8# + uncheckedShiftLWord16# :: Word16# -> Int# -> Word16# + uncheckedShiftLWord32# :: Word32# -> Int# -> Word32# + uncheckedShiftLWord8# :: Word8# -> Int# -> Word8# + uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16# + uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32# + uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8# + uncheckedShiftRL# :: Word# -> Int# -> Word# + uncheckedShiftRL64# :: Word64# -> Int# -> Word64# + uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16# + uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32# + uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8# + uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16# + uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32# + uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8# + unmaskAsyncExceptions# :: forall {q :: RuntimeRep} (a :: TYPE q). (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) + unpackAppendCString# :: Addr# -> [Char] -> [Char] + unpackCString# :: Addr# -> [Char] + unpackCStringUtf8# :: Addr# -> [Char] + unpackClosure# :: forall a b. a -> (# Addr#, ByteArray#, Array# b #) + unpackDoubleX2# :: DoubleX2# -> (# Double#, Double# #) + unpackDoubleX4# :: DoubleX4# -> (# Double#, Double#, Double#, Double# #) + unpackDoubleX8# :: DoubleX8# -> (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #) + unpackFloatX16# :: FloatX16# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) + unpackFloatX4# :: FloatX4# -> (# Float#, Float#, Float#, Float# #) + unpackFloatX8# :: FloatX8# -> (# Float#, Float#, Float#, Float#, Float#, Float#, Float#, Float# #) + unpackFoldrCString# :: forall a. Addr# -> (Char -> a -> a) -> a -> a + unpackInt16X16# :: Int16X16# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) + unpackInt16X32# :: Int16X32# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) + unpackInt16X8# :: Int16X8# -> (# Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16#, Int16# #) + unpackInt32X16# :: Int32X16# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) + unpackInt32X4# :: Int32X4# -> (# Int32#, Int32#, Int32#, Int32# #) + unpackInt32X8# :: Int32X8# -> (# Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32#, Int32# #) + unpackInt64X2# :: Int64X2# -> (# Int64#, Int64# #) + unpackInt64X4# :: Int64X4# -> (# Int64#, Int64#, Int64#, Int64# #) + unpackInt64X8# :: Int64X8# -> (# Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64#, Int64# #) + unpackInt8X16# :: Int8X16# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) + unpackInt8X32# :: Int8X32# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) + unpackInt8X64# :: Int8X64# -> (# Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8#, Int8# #) + unpackNBytes# :: Addr# -> Int# -> [Char] + unpackWord16X16# :: Word16X16# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) + unpackWord16X32# :: Word16X32# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) + unpackWord16X8# :: Word16X8# -> (# Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16#, Word16# #) + unpackWord32X16# :: Word32X16# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) + unpackWord32X4# :: Word32X4# -> (# Word32#, Word32#, Word32#, Word32# #) + unpackWord32X8# :: Word32X8# -> (# Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32#, Word32# #) + unpackWord64X2# :: Word64X2# -> (# Word64#, Word64# #) + unpackWord64X4# :: Word64X4# -> (# Word64#, Word64#, Word64#, Word64# #) + unpackWord64X8# :: Word64X8# -> (# Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64#, Word64# #) + unpackWord8X16# :: Word8X16# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) + unpackWord8X32# :: Word8X32# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) + unpackWord8X64# :: Word8X64# -> (# Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8#, Word8# #) + unsafeCoerce# :: forall (q :: RuntimeRep) (r :: RuntimeRep) (a :: TYPE q) (b :: TYPE r). a -> b + unsafeFreezeArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> State# d -> (# State# d, Array# a #) + unsafeFreezeArrayArray# :: forall s. MutableArrayArray# s -> State# s -> (# State# s, ArrayArray# #) + unsafeFreezeByteArray# :: forall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) + unsafeFreezeSmallArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> State# d -> (# State# d, SmallArray# a #) + unsafePtrEquality# :: forall (a :: UnliftedType) (b :: UnliftedType). a -> b -> Int# + unsafeThawArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. Array# a -> State# d -> (# State# d, MutableArray# d a #) + unsafeThawByteArray# :: forall d. ByteArray# -> State# d -> (# State# d, MutableByteArray# d #) + unsafeThawSmallArray# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) d. SmallArray# a -> State# d -> (# State# d, SmallMutableArray# d a #) + void# :: (# #) + waitRead# :: forall d. Int# -> State# d -> State# d + waitWrite# :: forall d. Int# -> State# d -> State# d + word16ToInt16# :: Word16# -> Int16# + word16ToWord# :: Word16# -> Word# + word2Double# :: Word# -> Double# + word2Float# :: Word# -> Float# + word2Int# :: Word# -> Int# + word32ToInt32# :: Word32# -> Int32# + word32ToWord# :: Word32# -> Word# + word64ToInt64# :: Word64# -> Int64# + word64ToWord# :: Word64# -> Word# + word8ToInt8# :: Word8# -> Int8# + word8ToWord# :: Word8# -> Word# + wordToWord16# :: Word# -> Word16# + wordToWord32# :: Word# -> Word32# + wordToWord64# :: Word# -> Word64# + wordToWord8# :: Word# -> Word8# + writeAddrArray# :: forall d. MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d + writeAddrOffAddr# :: forall d. Addr# -> Int# -> Addr# -> State# d -> State# d + writeArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutableArray# d a -> Int# -> a -> State# d -> State# d + writeArrayArrayArray# :: forall s. MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s + writeByteArrayArray# :: forall s. MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s + writeCharArray# :: forall d. MutableByteArray# d -> Int# -> Char# -> State# d -> State# d + writeCharOffAddr# :: forall d. Addr# -> Int# -> Char# -> State# d -> State# d + writeDoubleArray# :: forall d. MutableByteArray# d -> Int# -> Double# -> State# d -> State# d + writeDoubleArrayAsDoubleX2# :: forall d. MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d + writeDoubleArrayAsDoubleX4# :: forall d. MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d + writeDoubleArrayAsDoubleX8# :: forall d. MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d + writeDoubleOffAddr# :: forall d. Addr# -> Int# -> Double# -> State# d -> State# d + writeDoubleOffAddrAsDoubleX2# :: forall d. Addr# -> Int# -> DoubleX2# -> State# d -> State# d + writeDoubleOffAddrAsDoubleX4# :: forall d. Addr# -> Int# -> DoubleX4# -> State# d -> State# d + writeDoubleOffAddrAsDoubleX8# :: forall d. Addr# -> Int# -> DoubleX8# -> State# d -> State# d + writeDoubleX2Array# :: forall d. MutableByteArray# d -> Int# -> DoubleX2# -> State# d -> State# d + writeDoubleX2OffAddr# :: forall d. Addr# -> Int# -> DoubleX2# -> State# d -> State# d + writeDoubleX4Array# :: forall d. MutableByteArray# d -> Int# -> DoubleX4# -> State# d -> State# d + writeDoubleX4OffAddr# :: forall d. Addr# -> Int# -> DoubleX4# -> State# d -> State# d + writeDoubleX8Array# :: forall d. MutableByteArray# d -> Int# -> DoubleX8# -> State# d -> State# d + writeDoubleX8OffAddr# :: forall d. Addr# -> Int# -> DoubleX8# -> State# d -> State# d + writeFloatArray# :: forall d. MutableByteArray# d -> Int# -> Float# -> State# d -> State# d + writeFloatArrayAsFloatX16# :: forall d. MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d + writeFloatArrayAsFloatX4# :: forall d. MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d + writeFloatArrayAsFloatX8# :: forall d. MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d + writeFloatOffAddr# :: forall d. Addr# -> Int# -> Float# -> State# d -> State# d + writeFloatOffAddrAsFloatX16# :: forall d. Addr# -> Int# -> FloatX16# -> State# d -> State# d + writeFloatOffAddrAsFloatX4# :: forall d. Addr# -> Int# -> FloatX4# -> State# d -> State# d + writeFloatOffAddrAsFloatX8# :: forall d. Addr# -> Int# -> FloatX8# -> State# d -> State# d + writeFloatX16Array# :: forall d. MutableByteArray# d -> Int# -> FloatX16# -> State# d -> State# d + writeFloatX16OffAddr# :: forall d. Addr# -> Int# -> FloatX16# -> State# d -> State# d + writeFloatX4Array# :: forall d. MutableByteArray# d -> Int# -> FloatX4# -> State# d -> State# d + writeFloatX4OffAddr# :: forall d. Addr# -> Int# -> FloatX4# -> State# d -> State# d + writeFloatX8Array# :: forall d. MutableByteArray# d -> Int# -> FloatX8# -> State# d -> State# d + writeFloatX8OffAddr# :: forall d. Addr# -> Int# -> FloatX8# -> State# d -> State# d + writeIOPort# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). IOPort# d a -> a -> State# d -> (# State# d, Int# #) + writeInt16Array# :: forall d. MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d + writeInt16ArrayAsInt16X16# :: forall d. MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d + writeInt16ArrayAsInt16X32# :: forall d. MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d + writeInt16ArrayAsInt16X8# :: forall d. MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d + writeInt16OffAddr# :: forall d. Addr# -> Int# -> Int16# -> State# d -> State# d + writeInt16OffAddrAsInt16X16# :: forall d. Addr# -> Int# -> Int16X16# -> State# d -> State# d + writeInt16OffAddrAsInt16X32# :: forall d. Addr# -> Int# -> Int16X32# -> State# d -> State# d + writeInt16OffAddrAsInt16X8# :: forall d. Addr# -> Int# -> Int16X8# -> State# d -> State# d + writeInt16X16Array# :: forall d. MutableByteArray# d -> Int# -> Int16X16# -> State# d -> State# d + writeInt16X16OffAddr# :: forall d. Addr# -> Int# -> Int16X16# -> State# d -> State# d + writeInt16X32Array# :: forall d. MutableByteArray# d -> Int# -> Int16X32# -> State# d -> State# d + writeInt16X32OffAddr# :: forall d. Addr# -> Int# -> Int16X32# -> State# d -> State# d + writeInt16X8Array# :: forall d. MutableByteArray# d -> Int# -> Int16X8# -> State# d -> State# d + writeInt16X8OffAddr# :: forall d. Addr# -> Int# -> Int16X8# -> State# d -> State# d + writeInt32Array# :: forall d. MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d + writeInt32ArrayAsInt32X16# :: forall d. MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d + writeInt32ArrayAsInt32X4# :: forall d. MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d + writeInt32ArrayAsInt32X8# :: forall d. MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d + writeInt32OffAddr# :: forall d. Addr# -> Int# -> Int32# -> State# d -> State# d + writeInt32OffAddrAsInt32X16# :: forall d. Addr# -> Int# -> Int32X16# -> State# d -> State# d + writeInt32OffAddrAsInt32X4# :: forall d. Addr# -> Int# -> Int32X4# -> State# d -> State# d + writeInt32OffAddrAsInt32X8# :: forall d. Addr# -> Int# -> Int32X8# -> State# d -> State# d + writeInt32X16Array# :: forall d. MutableByteArray# d -> Int# -> Int32X16# -> State# d -> State# d + writeInt32X16OffAddr# :: forall d. Addr# -> Int# -> Int32X16# -> State# d -> State# d + writeInt32X4Array# :: forall d. MutableByteArray# d -> Int# -> Int32X4# -> State# d -> State# d + writeInt32X4OffAddr# :: forall d. Addr# -> Int# -> Int32X4# -> State# d -> State# d + writeInt32X8Array# :: forall d. MutableByteArray# d -> Int# -> Int32X8# -> State# d -> State# d + writeInt32X8OffAddr# :: forall d. Addr# -> Int# -> Int32X8# -> State# d -> State# d + writeInt64Array# :: forall d. MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d + writeInt64ArrayAsInt64X2# :: forall d. MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d + writeInt64ArrayAsInt64X4# :: forall d. MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d + writeInt64ArrayAsInt64X8# :: forall d. MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d + writeInt64OffAddr# :: forall d. Addr# -> Int# -> Int64# -> State# d -> State# d + writeInt64OffAddrAsInt64X2# :: forall d. Addr# -> Int# -> Int64X2# -> State# d -> State# d + writeInt64OffAddrAsInt64X4# :: forall d. Addr# -> Int# -> Int64X4# -> State# d -> State# d + writeInt64OffAddrAsInt64X8# :: forall d. Addr# -> Int# -> Int64X8# -> State# d -> State# d + writeInt64X2Array# :: forall d. MutableByteArray# d -> Int# -> Int64X2# -> State# d -> State# d + writeInt64X2OffAddr# :: forall d. Addr# -> Int# -> Int64X2# -> State# d -> State# d + writeInt64X4Array# :: forall d. MutableByteArray# d -> Int# -> Int64X4# -> State# d -> State# d + writeInt64X4OffAddr# :: forall d. Addr# -> Int# -> Int64X4# -> State# d -> State# d + writeInt64X8Array# :: forall d. MutableByteArray# d -> Int# -> Int64X8# -> State# d -> State# d + writeInt64X8OffAddr# :: forall d. Addr# -> Int# -> Int64X8# -> State# d -> State# d + writeInt8Array# :: forall d. MutableByteArray# d -> Int# -> Int8# -> State# d -> State# d + writeInt8ArrayAsInt8X16# :: forall d. MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d + writeInt8ArrayAsInt8X32# :: forall d. MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d + writeInt8ArrayAsInt8X64# :: forall d. MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d + writeInt8OffAddr# :: forall d. Addr# -> Int# -> Int8# -> State# d -> State# d + writeInt8OffAddrAsInt8X16# :: forall d. Addr# -> Int# -> Int8X16# -> State# d -> State# d + writeInt8OffAddrAsInt8X32# :: forall d. Addr# -> Int# -> Int8X32# -> State# d -> State# d + writeInt8OffAddrAsInt8X64# :: forall d. Addr# -> Int# -> Int8X64# -> State# d -> State# d + writeInt8X16Array# :: forall d. MutableByteArray# d -> Int# -> Int8X16# -> State# d -> State# d + writeInt8X16OffAddr# :: forall d. Addr# -> Int# -> Int8X16# -> State# d -> State# d + writeInt8X32Array# :: forall d. MutableByteArray# d -> Int# -> Int8X32# -> State# d -> State# d + writeInt8X32OffAddr# :: forall d. Addr# -> Int# -> Int8X32# -> State# d -> State# d + writeInt8X64Array# :: forall d. MutableByteArray# d -> Int# -> Int8X64# -> State# d -> State# d + writeInt8X64OffAddr# :: forall d. Addr# -> Int# -> Int8X64# -> State# d -> State# d + writeIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + writeIntOffAddr# :: forall d. Addr# -> Int# -> Int# -> State# d -> State# d + writeMutVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). MutVar# d a -> a -> State# d -> State# d + writeMutableArrayArrayArray# :: forall s. MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s + writeMutableByteArrayArray# :: forall s. MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s + writeSmallArray# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). SmallMutableArray# d a -> Int# -> a -> State# d -> State# d + writeStablePtrArray# :: forall d a. MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d + writeStablePtrOffAddr# :: forall a d. Addr# -> Int# -> StablePtr# a -> State# d -> State# d + writeTVar# :: forall {l :: Levity} d (a :: TYPE (BoxedRep l)). TVar# d a -> a -> State# d -> State# d + writeWideCharArray# :: forall d. MutableByteArray# d -> Int# -> Char# -> State# d -> State# d + writeWideCharOffAddr# :: forall d. Addr# -> Int# -> Char# -> State# d -> State# d + writeWord16Array# :: forall d. MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d + writeWord16ArrayAsWord16X16# :: forall d. MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d + writeWord16ArrayAsWord16X32# :: forall d. MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d + writeWord16ArrayAsWord16X8# :: forall d. MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d + writeWord16OffAddr# :: forall d. Addr# -> Int# -> Word16# -> State# d -> State# d + writeWord16OffAddrAsWord16X16# :: forall d. Addr# -> Int# -> Word16X16# -> State# d -> State# d + writeWord16OffAddrAsWord16X32# :: forall d. Addr# -> Int# -> Word16X32# -> State# d -> State# d + writeWord16OffAddrAsWord16X8# :: forall d. Addr# -> Int# -> Word16X8# -> State# d -> State# d + writeWord16X16Array# :: forall d. MutableByteArray# d -> Int# -> Word16X16# -> State# d -> State# d + writeWord16X16OffAddr# :: forall d. Addr# -> Int# -> Word16X16# -> State# d -> State# d + writeWord16X32Array# :: forall d. MutableByteArray# d -> Int# -> Word16X32# -> State# d -> State# d + writeWord16X32OffAddr# :: forall d. Addr# -> Int# -> Word16X32# -> State# d -> State# d + writeWord16X8Array# :: forall d. MutableByteArray# d -> Int# -> Word16X8# -> State# d -> State# d + writeWord16X8OffAddr# :: forall d. Addr# -> Int# -> Word16X8# -> State# d -> State# d + writeWord32Array# :: forall d. MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d + writeWord32ArrayAsWord32X16# :: forall d. MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d + writeWord32ArrayAsWord32X4# :: forall d. MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d + writeWord32ArrayAsWord32X8# :: forall d. MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d + writeWord32OffAddr# :: forall d. Addr# -> Int# -> Word32# -> State# d -> State# d + writeWord32OffAddrAsWord32X16# :: forall d. Addr# -> Int# -> Word32X16# -> State# d -> State# d + writeWord32OffAddrAsWord32X4# :: forall d. Addr# -> Int# -> Word32X4# -> State# d -> State# d + writeWord32OffAddrAsWord32X8# :: forall d. Addr# -> Int# -> Word32X8# -> State# d -> State# d + writeWord32X16Array# :: forall d. MutableByteArray# d -> Int# -> Word32X16# -> State# d -> State# d + writeWord32X16OffAddr# :: forall d. Addr# -> Int# -> Word32X16# -> State# d -> State# d + writeWord32X4Array# :: forall d. MutableByteArray# d -> Int# -> Word32X4# -> State# d -> State# d + writeWord32X4OffAddr# :: forall d. Addr# -> Int# -> Word32X4# -> State# d -> State# d + writeWord32X8Array# :: forall d. MutableByteArray# d -> Int# -> Word32X8# -> State# d -> State# d + writeWord32X8OffAddr# :: forall d. Addr# -> Int# -> Word32X8# -> State# d -> State# d + writeWord64Array# :: forall d. MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d + writeWord64ArrayAsWord64X2# :: forall d. MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d + writeWord64ArrayAsWord64X4# :: forall d. MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d + writeWord64ArrayAsWord64X8# :: forall d. MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d + writeWord64OffAddr# :: forall d. Addr# -> Int# -> Word64# -> State# d -> State# d + writeWord64OffAddrAsWord64X2# :: forall d. Addr# -> Int# -> Word64X2# -> State# d -> State# d + writeWord64OffAddrAsWord64X4# :: forall d. Addr# -> Int# -> Word64X4# -> State# d -> State# d + writeWord64OffAddrAsWord64X8# :: forall d. Addr# -> Int# -> Word64X8# -> State# d -> State# d + writeWord64X2Array# :: forall d. MutableByteArray# d -> Int# -> Word64X2# -> State# d -> State# d + writeWord64X2OffAddr# :: forall d. Addr# -> Int# -> Word64X2# -> State# d -> State# d + writeWord64X4Array# :: forall d. MutableByteArray# d -> Int# -> Word64X4# -> State# d -> State# d + writeWord64X4OffAddr# :: forall d. Addr# -> Int# -> Word64X4# -> State# d -> State# d + writeWord64X8Array# :: forall d. MutableByteArray# d -> Int# -> Word64X8# -> State# d -> State# d + writeWord64X8OffAddr# :: forall d. Addr# -> Int# -> Word64X8# -> State# d -> State# d + writeWord8Array# :: forall d. MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d + writeWord8ArrayAsAddr# :: forall d. MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d + writeWord8ArrayAsChar# :: forall d. MutableByteArray# d -> Int# -> Char# -> State# d -> State# d + writeWord8ArrayAsDouble# :: forall d. MutableByteArray# d -> Int# -> Double# -> State# d -> State# d + writeWord8ArrayAsFloat# :: forall d. MutableByteArray# d -> Int# -> Float# -> State# d -> State# d + writeWord8ArrayAsInt# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> State# d + writeWord8ArrayAsInt16# :: forall d. MutableByteArray# d -> Int# -> Int16# -> State# d -> State# d + writeWord8ArrayAsInt32# :: forall d. MutableByteArray# d -> Int# -> Int32# -> State# d -> State# d + writeWord8ArrayAsInt64# :: forall d. MutableByteArray# d -> Int# -> Int64# -> State# d -> State# d + writeWord8ArrayAsStablePtr# :: forall d a. MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d + writeWord8ArrayAsWideChar# :: forall d. MutableByteArray# d -> Int# -> Char# -> State# d -> State# d + writeWord8ArrayAsWord# :: forall d. MutableByteArray# d -> Int# -> Word# -> State# d -> State# d + writeWord8ArrayAsWord16# :: forall d. MutableByteArray# d -> Int# -> Word16# -> State# d -> State# d + writeWord8ArrayAsWord32# :: forall d. MutableByteArray# d -> Int# -> Word32# -> State# d -> State# d + writeWord8ArrayAsWord64# :: forall d. MutableByteArray# d -> Int# -> Word64# -> State# d -> State# d + writeWord8ArrayAsWord8X16# :: forall d. MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d + writeWord8ArrayAsWord8X32# :: forall d. MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d + writeWord8ArrayAsWord8X64# :: forall d. MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d + writeWord8OffAddr# :: forall d. Addr# -> Int# -> Word8# -> State# d -> State# d + writeWord8OffAddrAsAddr# :: forall d. Addr# -> Int# -> Addr# -> State# d -> State# d + writeWord8OffAddrAsChar# :: forall d. Addr# -> Int# -> Char# -> State# d -> State# d + writeWord8OffAddrAsDouble# :: forall d. Addr# -> Int# -> Double# -> State# d -> State# d + writeWord8OffAddrAsFloat# :: forall d. Addr# -> Int# -> Float# -> State# d -> State# d + writeWord8OffAddrAsInt# :: forall d. Addr# -> Int# -> Int# -> State# d -> State# d + writeWord8OffAddrAsInt16# :: forall d. Addr# -> Int# -> Int16# -> State# d -> State# d + writeWord8OffAddrAsInt32# :: forall d. Addr# -> Int# -> Int32# -> State# d -> State# d + writeWord8OffAddrAsInt64# :: forall d. Addr# -> Int# -> Int64# -> State# d -> State# d + writeWord8OffAddrAsStablePtr# :: forall a d. Addr# -> Int# -> StablePtr# a -> State# d -> State# d + writeWord8OffAddrAsWideChar# :: forall d. Addr# -> Int# -> Char# -> State# d -> State# d + writeWord8OffAddrAsWord# :: forall d. Addr# -> Int# -> Word# -> State# d -> State# d + writeWord8OffAddrAsWord16# :: forall d. Addr# -> Int# -> Word16# -> State# d -> State# d + writeWord8OffAddrAsWord32# :: forall d. Addr# -> Int# -> Word32# -> State# d -> State# d + writeWord8OffAddrAsWord64# :: forall d. Addr# -> Int# -> Word64# -> State# d -> State# d + writeWord8OffAddrAsWord8X16# :: forall d. Addr# -> Int# -> Word8X16# -> State# d -> State# d + writeWord8OffAddrAsWord8X32# :: forall d. Addr# -> Int# -> Word8X32# -> State# d -> State# d + writeWord8OffAddrAsWord8X64# :: forall d. Addr# -> Int# -> Word8X64# -> State# d -> State# d + writeWord8X16Array# :: forall d. MutableByteArray# d -> Int# -> Word8X16# -> State# d -> State# d + writeWord8X16OffAddr# :: forall d. Addr# -> Int# -> Word8X16# -> State# d -> State# d + writeWord8X32Array# :: forall d. MutableByteArray# d -> Int# -> Word8X32# -> State# d -> State# d + writeWord8X32OffAddr# :: forall d. Addr# -> Int# -> Word8X32# -> State# d -> State# d + writeWord8X64Array# :: forall d. MutableByteArray# d -> Int# -> Word8X64# -> State# d -> State# d + writeWord8X64OffAddr# :: forall d. Addr# -> Int# -> Word8X64# -> State# d -> State# d + writeWordArray# :: forall d. MutableByteArray# d -> Int# -> Word# -> State# d -> State# d + writeWordOffAddr# :: forall d. Addr# -> Int# -> Word# -> State# d -> State# d + xor# :: Word# -> Word# -> Word# + xor64# :: Word64# -> Word64# -> Word64# + xorI# :: Int# -> Int# -> Int# + xorWord16# :: Word16# -> Word16# -> Word16# + xorWord32# :: Word32# -> Word32# -> Word32# + xorWord8# :: Word8# -> Word8# -> Word8# + yield# :: State# RealWorld -> State# RealWorld + type (~) :: forall k. k -> k -> Constraint + class (a ~ b) => (~) a b + {-# MINIMAL #-} + type (~~) :: forall k0 k1. k0 -> k1 -> Constraint + class (a ~~ b) => (~~) a b + {-# MINIMAL #-} + module GHC.Profiling.Eras where -- Safety: Trustworthy getUserEra :: GHC.Types.IO GHC.Types.Word @@ -8657,6 +10490,92 @@ module Prelude.Experimental where -- Instances: +instance GHC.Internal.Base.Alternative GHC.Types.IO -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Alternative [] -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Applicative GHC.Internal.Data.Ord.Down -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Internal.Base.Applicative GHC.Types.IO -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Applicative [] -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Applicative GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Applicative GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Applicative Solo -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Applicative ((,) a) -- Defined in ‘GHC.Internal.Base’ +instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => GHC.Internal.Base.Applicative ((,,) a b) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Applicative ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Functor GHC.Internal.Data.Ord.Down -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Internal.Base.Functor GHC.Types.IO -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Functor [] -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Functor GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Functor GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Functor Solo -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Functor ((,) a) -- Defined in ‘GHC.Internal.Base’ +instance forall a b. GHC.Internal.Base.Functor ((,,) a b) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c. GHC.Internal.Base.Functor ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d. GHC.Internal.Base.Functor ((,,,,) a b c d) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d e. GHC.Internal.Base.Functor ((,,,,,) a b c d e) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d e f. GHC.Internal.Base.Functor ((,,,,,,) a b c d e f) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monad GHC.Internal.Data.Ord.Down -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Internal.Base.Monad GHC.Types.IO -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monad [] -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monad GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monad GHC.Internal.Base.NonEmpty -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monad Solo -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monad ((,) a) -- Defined in ‘GHC.Internal.Base’ +instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => GHC.Internal.Base.Monad ((,,) a b) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monad ((,,,) a b c) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.MonadPlus GHC.Types.IO -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.MonadPlus [] -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.MonadPlus GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (GHC.Types.IO a) -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Monoid [a] -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Monoid (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monoid GHC.Types.Ordering -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Monoid a => GHC.Internal.Base.Monoid (Solo a) -- Defined in ‘GHC.Internal.Base’ +instance forall a b. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b) => GHC.Internal.Base.Monoid (a, b) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c) => GHC.Internal.Base.Monoid (a, b, c) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d) => GHC.Internal.Base.Monoid (a, b, c, d) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d e. (GHC.Internal.Base.Monoid a, GHC.Internal.Base.Monoid b, GHC.Internal.Base.Monoid c, GHC.Internal.Base.Monoid d, GHC.Internal.Base.Monoid e) => GHC.Internal.Base.Monoid (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Monoid () -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Types.IO a) -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup [a] -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Semigroup GHC.Types.Ordering -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Base.Semigroup a => GHC.Internal.Base.Semigroup (Solo a) -- Defined in ‘GHC.Internal.Base’ +instance forall a b. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Semigroup b) => GHC.Internal.Base.Semigroup (a, b) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Semigroup b, GHC.Internal.Base.Semigroup c) => GHC.Internal.Base.Semigroup (a, b, c) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Semigroup b, GHC.Internal.Base.Semigroup c, GHC.Internal.Base.Semigroup d) => GHC.Internal.Base.Semigroup (a, b, c, d) -- Defined in ‘GHC.Internal.Base’ +instance forall a b c d e. (GHC.Internal.Base.Semigroup a, GHC.Internal.Base.Semigroup b, GHC.Internal.Base.Semigroup c, GHC.Internal.Base.Semigroup d, GHC.Internal.Base.Semigroup e) => GHC.Internal.Base.Semigroup (a, b, c, d, e) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Semigroup () -- Defined in ‘GHC.Internal.Base’ +instance GHC.Internal.Base.Semigroup GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’ +instance forall a. GHC.Internal.Bits.Bits a => GHC.Internal.Bits.Bits (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Bits.FiniteBits a => GHC.Internal.Bits.FiniteBits (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Internal.Data.Data.Data GHC.Internal.Exts.SpecConstrAnnotation -- Defined in ‘GHC.Internal.Exts’ +instance forall a k (b :: k). GHC.Internal.Data.String.IsString a => GHC.Internal.Data.String.IsString (GHC.Internal.Data.Functor.Const.Const a b) -- Defined in ‘GHC.Internal.Data.String’ +instance forall a. GHC.Internal.Data.String.IsString a => GHC.Internal.Data.String.IsString (GHC.Internal.Data.Functor.Identity.Identity a) -- Defined in ‘GHC.Internal.Data.String’ +instance forall a. (a ~ GHC.Types.Char) => GHC.Internal.Data.String.IsString [a] -- Defined in ‘GHC.Internal.Data.String’ +instance forall a. GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. (GHC.Internal.Enum.Enum a, GHC.Internal.Enum.Bounded a, GHC.Classes.Eq a) => GHC.Internal.Enum.Enum (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Foreign.Storable.Storable a => GHC.Internal.Foreign.Storable.Storable (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Internal.IsList.IsList GHC.Internal.Stack.Types.CallStack -- Defined in ‘GHC.Internal.IsList’ +instance forall a. GHC.Internal.IsList.IsList [a] -- Defined in ‘GHC.Internal.IsList’ +instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.IsList’ +instance GHC.Internal.IsList.IsList GHC.Internal.Data.Version.Version -- Defined in ‘GHC.Internal.IsList’ +instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Functor.ZipList.ZipList a) -- Defined in ‘GHC.Internal.IsList’ +instance forall a. GHC.Internal.Ix.Ix a => GHC.Internal.Ix.Ix (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Num.Num a => GHC.Internal.Num.Num (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Read.Read a => GHC.Internal.Read.Read (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Real.Real a => GHC.Internal.Real.Real (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Real.RealFrac a => GHC.Internal.Real.RealFrac (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Show.Show a => GHC.Internal.Show.Show (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.FunPtr a) -- Defined in ‘GHC.Internal.Ptr’ +instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.Internal.Ptr’ +instance GHC.Internal.Show.Show GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’ instance GHC.Classes.Eq GHC.Types.Bool -- Defined in ‘GHC.Classes’ instance GHC.Classes.Eq GHC.Types.Char -- Defined in ‘GHC.Classes’ instance GHC.Classes.Eq GHC.Types.Double -- Defined in ‘GHC.Classes’ @@ -8684,6 +10603,13 @@ instance forall a b c d e f g h i. (GHC.Classes.Eq a, GHC.Classes.Eq b, GHC.Clas instance GHC.Classes.Eq GHC.Types.TyCon -- Defined in ‘GHC.Classes’ instance GHC.Classes.Eq () -- Defined in ‘GHC.Classes’ instance GHC.Classes.Eq GHC.Types.Word -- Defined in ‘GHC.Classes’ +instance forall a. GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance GHC.Classes.Eq GHC.Internal.Exts.SpecConstrAnnotation -- Defined in ‘GHC.Internal.Exts’ +instance forall a. GHC.Classes.Eq (GHC.Internal.Ptr.FunPtr a) -- Defined in ‘GHC.Internal.Ptr’ +instance forall a. GHC.Classes.Eq (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.Internal.Ptr’ +instance forall a. GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Classes.Eq GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’ +instance GHC.Classes.Eq GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’ instance GHC.Classes.Ord GHC.Types.Bool -- Defined in ‘GHC.Classes’ instance GHC.Classes.Ord GHC.Types.Char -- Defined in ‘GHC.Classes’ instance GHC.Classes.Ord GHC.Types.Double -- Defined in ‘GHC.Classes’ @@ -8709,3 +10635,8 @@ instance forall a b c d e f g h i. (GHC.Classes.Ord a, GHC.Classes.Ord b, GHC.Cl instance GHC.Classes.Ord GHC.Types.TyCon -- Defined in ‘GHC.Classes’ instance GHC.Classes.Ord () -- Defined in ‘GHC.Classes’ instance GHC.Classes.Ord GHC.Types.Word -- Defined in ‘GHC.Classes’ +instance forall a. GHC.Classes.Ord a => GHC.Classes.Ord (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’ +instance forall a. GHC.Classes.Ord (GHC.Internal.Ptr.FunPtr a) -- Defined in ‘GHC.Internal.Ptr’ +instance forall a. GHC.Classes.Ord (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.Internal.Ptr’ +instance forall a. GHC.Classes.Ord a => GHC.Classes.Ord (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’ +instance GHC.Classes.Ord GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’ ===================================== testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32 ===================================== The diff for this file was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39497eeda74fc7f1e7ea89292de395b16f69cee2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39497eeda74fc7f1e7ea89292de395b16f69cee2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:21:42 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:21:42 -0400 Subject: [Git][ghc/ghc][master] RTS: cleanup timerfd file descriptors after a fork (#25280) Message-ID: <66fdffb5f01db_271866988f786511b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 3 changed files: - rts/posix/ticker/TimerFd.c - + testsuite/tests/rts/T25280.hs - testsuite/tests/rts/all.T Changes: ===================================== rts/posix/ticker/TimerFd.c ===================================== @@ -192,6 +192,14 @@ initTicker (Time interval, TickProc handle_tick) it.it_value.tv_nsec = TimeToNS(itimer_interval) % 1000000000; it.it_interval = it.it_value; + if (timerfd != -1) { + // don't leak the old file descriptors after a fork (#25280) + close(timerfd); + close(pipefds[0]); + close(pipefds[1]); + timerfd = -1; + } + timerfd = timerfd_create(CLOCK_MONOTONIC, TFD_CLOEXEC); if (timerfd == -1) { barf("timerfd_create: %s", strerror(errno)); ===================================== testsuite/tests/rts/T25280.hs ===================================== @@ -0,0 +1,24 @@ +module Main where + +import Control.Concurrent +import qualified System.Posix.Process as SPP +import System.Directory +import Control.Monad +import System.Exit + +main = do + fds <- listDirectory "/proc/self/fd" + go 0 5 fds + +go :: Int -> Int -> [FilePath] -> IO () +go i n fds + | i == n = return () + | otherwise = do + fds' <- listDirectory "/proc/self/fd" + when (fds /= fds') $ do + putStrLn "File descriptors changed after fork:" + putStrLn $ "Before:" ++ show fds + putStrLn $ "After: " ++ show fds' + exitFailure + pid <- SPP.forkProcess $ go (i+1) n fds + void (SPP.getProcessStatus True True pid) ===================================== testsuite/tests/rts/all.T ===================================== @@ -618,3 +618,4 @@ test('IOManager', [js_skip, when(arch('wasm32'), skip), when(opsys('mingw32'), s test('T24142', [req_target_smp], compile_and_run, ['-threaded -with-rtsopts "-N2"']) test('T25232', [unless(have_profiling(), skip), only_ways(['normal','nonmoving','nonmoving_prof','nonmoving_thr_prof']), extra_ways(['nonmoving', 'nonmoving_prof'] + (['nonmoving_thr_prof'] if have_threaded() else []))], compile_and_run, ['']) +test('T25280', [unless(opsys('linux'),skip),req_process,js_skip], compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9dc26907e13eeb73514ff3f70323b40b40ef8ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9dc26907e13eeb73514ff3f70323b40b40ef8ac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:22:17 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:22:17 -0400 Subject: [Git][ghc/ghc][master] determinism: Deterministic MonadGetUnique LlvmM Message-ID: <66fdffd954d7_271866e0608c6674a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 2 changed files: - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs Changes: ===================================== compiler/GHC/CmmToLlvm.hs ===================================== @@ -85,25 +85,23 @@ llvmCodeGen logger cfg h dus cmm_stream llvm_ver = fromMaybe supportedLlvmVersionLowerBound mb_ver -- run code generation - a <- runLlvm logger cfg llvm_ver bufh $ - llvmCodeGen' cfg dus cmm_stream + (a, _) <- runLlvm logger cfg llvm_ver bufh dus $ + llvmCodeGen' cfg cmm_stream bFlush bufh return a llvmCodeGen' :: LlvmCgConfig - -> DUniqSupply -- ^ The deterministic uniq supply to run the CgStream. - -- See Note [Deterministic Uniques in the CG] -> CgStream RawCmmGroup a -> LlvmM a -llvmCodeGen' cfg dus cmm_stream +llvmCodeGen' cfg cmm_stream = do -- Preamble renderLlvm (llvmHeader cfg) (llvmHeader cfg) ghcInternalFunctions cmmMetaLlvmPrelude -- Procedures - (a, _) <- runUDSMT dus $ Stream.consume cmm_stream (hoistUDSMT liftIO) (liftUDSMT . llvmGroupLlvmGens) + a <- Stream.consume cmm_stream (GHC.CmmToLlvm.Base.liftUDSMT) (llvmGroupLlvmGens) -- Declare aliases for forward references decls <- generateExternDecls ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -23,7 +23,7 @@ module GHC.CmmToLlvm.Base ( ghcInternalFunctions, getPlatform, getConfig, getMetaUniqueId, - setUniqMeta, getUniqMeta, liftIO, + setUniqMeta, getUniqMeta, liftIO, liftUDSMT, cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, @@ -57,7 +57,6 @@ import GHC.Types.Unique.FM import GHC.Types.Unique import GHC.Utils.BufHandle ( BufHandle ) import GHC.Types.Unique.Set -import GHC.Types.Unique.Supply import qualified GHC.Types.Unique.DSM as DSM import GHC.Utils.Logger @@ -68,6 +67,7 @@ import Data.Maybe (fromJust, mapMaybe) import Data.List (find, isPrefixOf) import qualified Data.List.NonEmpty as NE import Data.Ord (comparing) +import qualified Control.Monad.IO.Class as IO -- ---------------------------------------------------------------------------- -- * Some Data Types @@ -296,14 +296,13 @@ data LlvmEnv = LlvmEnv type LlvmEnvMap = UniqFM Unique LlvmType -- | The Llvm monad. Wraps @LlvmEnv@ state as well as the @IO@ monad -newtype LlvmM a = LlvmM { runLlvmM :: LlvmEnv -> IO (a, LlvmEnv) } +newtype LlvmM a = LlvmM { runLlvmM :: LlvmEnv -> DSM.UniqDSMT IO (a, LlvmEnv) } deriving stock (Functor) - deriving (Applicative, Monad) via StateT LlvmEnv IO + deriving (Applicative, Monad) via StateT LlvmEnv (DSM.UniqDSMT IO) instance HasLogger LlvmM where getLogger = LlvmM $ \env -> return (envLogger env, env) - -- | Get target platform getPlatform :: LlvmM Platform getPlatform = llvmCgPlatform <$> getConfig @@ -312,23 +311,30 @@ getConfig :: LlvmM LlvmCgConfig getConfig = LlvmM $ \env -> return (envConfig env, env) --- TODO(#25274): If you want Llvm code to be deterministic, this instance should use a --- deterministic unique supply to produce uniques, rather than using 'uniqFromTag'. +-- This instance uses a deterministic unique supply from UniqDSMT, so new +-- uniques within LlvmM will be sampled deterministically. instance DSM.MonadGetUnique LlvmM where getUniqueM = do tag <- getEnv envTag - liftIO $! uniqFromTag tag + liftUDSMT $! do + uq <- DSM.getUniqueM + return (newTagUnique uq tag) -- | Lifting of IO actions. Not exported, as we want to encapsulate IO. liftIO :: IO a -> LlvmM a -liftIO m = LlvmM $ \env -> do x <- m +liftIO m = LlvmM $ \env -> do x <- IO.liftIO m return (x, env) +-- | Lifting of UniqDSMT actions. Gives access to the deterministic unique supply being threaded through by LlvmM. +liftUDSMT :: DSM.UniqDSMT IO a -> LlvmM a +liftUDSMT m = LlvmM $ \env -> do x <- m + return (x, env) + -- | Get initial Llvm environment. -runLlvm :: Logger -> LlvmCgConfig -> LlvmVersion -> BufHandle -> LlvmM a -> IO a -runLlvm logger cfg ver out m = do - (a, _) <- runLlvmM m env - return a +runLlvm :: Logger -> LlvmCgConfig -> LlvmVersion -> BufHandle -> DSM.DUniqSupply -> LlvmM a -> IO (a, DSM.DUniqSupply) +runLlvm logger cfg ver out us m = do + ((a, _), us') <- DSM.runUDSMT us $ runLlvmM m env + return (a, us') where env = LlvmEnv { envFunMap = emptyUFM , envVarMap = emptyUFM , envStackRegs = [] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64e876bc0a5dd5d59b47ee3969b52a3bcecb37e6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64e876bc0a5dd5d59b47ee3969b52a3bcecb37e6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:22:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:22:50 -0400 Subject: [Git][ghc/ghc][master] Bump LLVM upper bound to allow LLVM 19 Message-ID: <66fdfffae15af_271866fef8a869840@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 2 changed files: - .gitlab-ci.yml - configure.ac Changes: ===================================== .gitlab-ci.yml ===================================== @@ -2,7 +2,7 @@ variables: GIT_SSL_NO_VERIFY: "1" # Commit of ghc/ci-images repository from which to pull Docker images - DOCKER_REV: 486541129a8e7bf77c2cf7cd76ca998f690d5685 + DOCKER_REV: 6efac743853f9c2172777e934d7aea44434415ec # Sequential version number of all cached things. # Bump to invalidate GitLab CI cache. ===================================== configure.ac ===================================== @@ -528,7 +528,7 @@ AC_SUBST(InstallNameToolCmd) # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. LlvmMinVersion=13 # inclusive -LlvmMaxVersion=19 # not inclusive +LlvmMaxVersion=20 # not inclusive AC_SUBST([LlvmMinVersion]) AC_SUBST([LlvmMaxVersion]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36bbb167f354a2fbc6c4842755f2b1e374e3580e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/36bbb167f354a2fbc6c4842755f2b1e374e3580e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:23:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:23:50 -0400 Subject: [Git][ghc/ghc][master] configure: Allow happy-2.0.2 Message-ID: <66fe003677a4e_271866684f9877524@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 1 changed file: - m4/fptools_happy.m4 Changes: ===================================== m4/fptools_happy.m4 ===================================== @@ -24,10 +24,15 @@ changequote([, ])dnl ]) if test ! -f compiler/GHC/Parser.hs || test ! -f compiler/GHC/Cmm/Parser.hs then + failure_msg="Happy version == 1.20.* || >= 2.0.2 && < 2.1 is required to compile GHC" FP_COMPARE_VERSIONS([$fptools_cv_happy_version],[-lt],[1.20.0], - [AC_MSG_ERROR([Happy version 1.20 or later is required to compile GHC.])])[] + [AC_MSG_ERROR([$failure_msg])])[] FP_COMPARE_VERSIONS([$fptools_cv_happy_version],[-ge],[1.21.0], - [AC_MSG_ERROR([Happy version 1.20 or earlier is required to compile GHC.])])[] + FP_COMPARE_VERSIONS([$fptools_cv_happy_version], [-le], [2.0.1], + [AC_MSG_ERROR([$failure_msg])])[])[] + FP_COMPARE_VERSIONS([$fptools_cv_happy_version],[-ge],[2.1.0], + [AC_MSG_ERROR([$failure_msg])])[] + fi HappyVersion=$fptools_cv_happy_version; AC_SUBST(HappyVersion) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0029ca91c845dd4530eb2c4606ad5bd59775cec2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0029ca91c845dd4530eb2c4606ad5bd59775cec2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:24:24 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:24:24 -0400 Subject: [Git][ghc/ghc][master] Use bundled llc/opt on Windows (#22438) Message-ID: <66fe0058c4a64_271866fcaddc8227b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - 2 changed files: - m4/fp_settings.m4 - m4/fp_setup_windows_toolchain.m4 Changes: ===================================== m4/fp_settings.m4 ===================================== @@ -85,6 +85,11 @@ AC_DEFUN([FP_SETTINGS], SettingsWindresCommand="$WindresCmd" fi + # LLVM backend tools + SettingsLlcCommand="$LlcCmd" + SettingsOptCommand="$OptCmd" + SettingsLlvmAsCommand="$LlvmAsCmd" + if test "$EnableDistroToolchain" = "YES"; then # If the user specified --enable-distro-toolchain then we just use the # executable names, not paths. @@ -96,6 +101,9 @@ AC_DEFUN([FP_SETTINGS], SettingsMergeObjectsCommand="$(basename $SettingsMergeObjectsCommand)" SettingsArCommand="$(basename $SettingsArCommand)" SettingsWindresCommand="$(basename $SettingsWindresCommand)" + SettingsLlcCommand="$(basename $SettingsLlcCommand)" + SettingsOptCommand="$(basename $SettingsOptCommand)" + SettingsLlvmAsCommand="$(basename $SettingsLlvmAsCommand)" fi if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"; then @@ -120,15 +128,11 @@ AC_DEFUN([FP_SETTINGS], SUBST_TOOLDIR([SettingsArCommand]) SUBST_TOOLDIR([SettingsRanlibCommand]) SUBST_TOOLDIR([SettingsWindresCommand]) + SUBST_TOOLDIR([SettingsLlcCommand]) + SUBST_TOOLDIR([SettingsOptCommand]) + SUBST_TOOLDIR([SettingsLlvmAsCommand]) fi - # LLVM backend tools - SettingsLlcCommand="$LlcCmd" - - SettingsOptCommand="$OptCmd" - - SettingsLlvmAsCommand="$LlvmAsCmd" - # Mac-only tools if test -z "$OtoolCmd"; then OtoolCmd="otool" ===================================== m4/fp_setup_windows_toolchain.m4 ===================================== @@ -131,6 +131,9 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[ OBJDUMP="${mingwbin}llvm-objdump.exe" DLLTOOL="${mingwbin}llvm-dlltool.exe" WindresCmd="${mingwbin}llvm-windres.exe" + LLC="${mingwbin}llc.exe" + OPT="${mingwbin}opt.exe" + LLVMAS="${mingwbin}clang.exe" # N.B. LLD does not support -r MergeObjsCmd="" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92976985625ffba551f1e1422f5e3a0cbf7beb89 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92976985625ffba551f1e1422f5e3a0cbf7beb89 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:24:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:24:53 -0400 Subject: [Git][ghc/ghc][master] 3 commits: Fix registerArch for riscv64 Message-ID: <66fe00753c3df_271866e0bd98825b9@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - 5 changed files: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/Platform/Reg/Class.hs - rts/CheckVectorSupport.c Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -1109,6 +1109,8 @@ getRegister' config plat expr = MO_F_Mul w -> floatOp w (\d x y -> unitOL $ annExpr expr (MUL d x y)) MO_F_Quot w -> floatOp w (\d x y -> unitOL $ annExpr expr (DIV d x y)) -- Floating point comparison + MO_F_Min w -> floatOp w (\d x y -> unitOL $ annExpr expr (FMIN d x y)) + MO_F_Max w -> floatOp w (\d x y -> unitOL $ annExpr expr (FMAX d x y)) MO_F_Eq w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y EQ)) MO_F_Ne w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y NE)) MO_F_Ge w -> floatCond w (\d x y -> unitOL $ annExpr expr (CSET d x y FGE)) @@ -2208,6 +2210,8 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = FENCE {} -> 1 FCVT {} -> 1 FABS {} -> 1 + FMIN {} -> 1 + FMAX {} -> 1 FMA {} -> 1 -- estimate the subsituted size for jumps to lables -- jumps to registers have size 1 ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -107,6 +107,8 @@ regUsageOfInstr platform instr = case instr of FENCE _ _ -> usage ([], []) FCVT _variant dst src -> usage (regOp src, regOp dst) FABS dst src -> usage (regOp src, regOp dst) + FMIN dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) + FMAX dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) FMA _ dst src1 src2 src3 -> usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst) _ -> panic $ "regUsageOfInstr: " ++ instrCon instr @@ -203,6 +205,8 @@ patchRegsOfInstr instr env = case instr of FENCE o1 o2 -> FENCE o1 o2 FCVT variant o1 o2 -> FCVT variant (patchOp o1) (patchOp o2) FABS o1 o2 -> FABS (patchOp o1) (patchOp o2) + FMIN o1 o2 o3 -> FMIN (patchOp o1) (patchOp o2) (patchOp o3) + FMAX o1 o2 o3 -> FMAX (patchOp o1) (patchOp o2) (patchOp o3) FMA s o1 o2 o3 o4 -> FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4) _ -> panic $ "patchRegsOfInstr: " ++ instrCon instr @@ -603,6 +607,13 @@ data Instr FCVT FcvtVariant Operand Operand | -- | Floating point ABSolute value FABS Operand Operand + + | -- | Min + -- dest = min(r1) + FMIN Operand Operand Operand + | -- | Max + FMAX Operand Operand Operand + | -- | Floating-point fused multiply-add instructions -- -- - fmadd : d = r1 * r2 + r3 @@ -658,6 +669,8 @@ instrCon i = FENCE {} -> "FENCE" FCVT {} -> "FCVT" FABS {} -> "FABS" + FMIN {} -> "FMIN" + FMAX {} -> "FMAX" FMA variant _ _ _ _ -> case variant of FMAdd -> "FMADD" ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -666,6 +666,10 @@ pprInstr platform instr = case instr of $ line (pprOp platform o1 <> text "->" <> pprOp platform o2) FABS o1 o2 | isSingleOp o2 -> op2 (text "\tfabs.s") o1 o2 FABS o1 o2 | isDoubleOp o2 -> op2 (text "\tfabs.d") o1 o2 + FMIN o1 o2 o3 | isSingleOp o1 -> op3 (text "\tfmin.s") o1 o2 o3 + | isDoubleOp o2 -> op3 (text "\tfmin.d") o1 o2 o3 + FMAX o1 o2 o3 | isSingleOp o1 -> op3 (text "\tfmax.s") o1 o2 o3 + | isDoubleOp o2 -> op3 (text "\tfmax.d") o1 o2 o3 FMA variant d r1 r2 r3 -> let fma = case variant of FMAdd -> text "\tfmadd" <> dot <> floatPrecission d ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -49,5 +49,8 @@ registerArch arch = ArchPPC -> Unified ArchPPC_64 {} -> Unified ArchAArch64 -> Unified - ArchRISCV64 -> Separate + -- Support for vector registers not yet implemented for RISC-V + -- see panic in `getFreeRegs`. + --ArchRISCV64 -> Separate + ArchRISCV64 -> NoVectors _ -> NoVectors ===================================== rts/CheckVectorSupport.c ===================================== @@ -65,12 +65,16 @@ int checkVectorSupport(void) { */ #elif defined(__riscv) - unsigned long vlenb; - asm volatile ("csrr %0, vlenb" : "=r" (vlenb)); +// csrr instruction nott allowed in user-mode qemu emulation of riscv +// Backend doesn't yet support vector registers, so hard-coded to no vector support +// for now. +// +// unsigned long vlenb; +// asm volatile ("csrr %0, vlenb" : "=r" (vlenb)); // VLENB gives the length in bytes - supports_V16 = vlenb >= 16; - supports_V32 = vlenb >= 32; - supports_V64 = vlenb >= 64; + supports_V16 = 0; + supports_V32 = 0; + supports_V64 = 0; #else // On other platforms, we conservatively return no vector support. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92976985625ffba551f1e1422f5e3a0cbf7beb89...115a30e9142b4481de3ba735396e9d0417d46445 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92976985625ffba551f1e1422f5e3a0cbf7beb89...115a30e9142b4481de3ba735396e9d0417d46445 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:25:38 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:25:38 -0400 Subject: [Git][ghc/ghc][master] 2 commits: testsuite/perf: Report better error message on malformed note Message-ID: <66fe00a2686c8_2718668292f4872be@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 2 changed files: - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py Changes: ===================================== testsuite/driver/perf_notes.py ===================================== @@ -165,6 +165,9 @@ class RelativeMetricAcceptanceWindow(MetricAcceptanceWindow): def parse_perf_stat(stat_str: str) -> PerfStat: field_vals = stat_str.strip('\t').split('\t') + if len(field_vals) != 5: + raise ValueError(f'Invalid stat line: {field_vals}') + stat = PerfStat(*field_vals) # type: ignore if stat.test_env.startswith('"') and stat.test_env.endswith('"'): # Due to a bug, in historical data sometimes the test_env @@ -183,11 +186,14 @@ def get_perf_stats(commit: Union[GitRef, GitHash]=GitRef('HEAD'), except subprocess.CalledProcessError: return [] - return \ - [ parse_perf_stat(stat_str) - for stat_str in log.strip('\n').split('\n') - if stat_str != '' - ] + try: + return \ + [ parse_perf_stat(stat_str) + for stat_str in log.strip('\n').split('\n') + if stat_str != '' + ] + except ValueError as e: + raise ValueError(f'Invalid stat line for commit {commit}') # Check if a str is in a 40 character git commit hash. _commit_hash_re = re.compile('[0-9a-f]' * 40) @@ -659,7 +665,10 @@ def check_stats_change(actual: PerfStat, display(' Upper bound ' + full_name + ' ' + actual.metric + ':', upperBound, '') display(' Actual ' + full_name + ' ' + actual.metric + ':', actual.value, '') if actual.value != expected_val: - actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) + if expected_val == 0: + actual_dev = 100.0 + else: + actual_dev = round(((float(actual.value) * 100)/ int(expected_val)) - 100, 1) display(' Deviation ' + full_name + ' ' + actual.metric + ':', actual_dev, '%') return (change, result) ===================================== testsuite/driver/runtests.py ===================================== @@ -404,7 +404,12 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: return "" val0 = x.baseline.perfStat.value val1 = x.stat.value - return "{:+2.1f}%".format(100 * (val1 - val0) / val0) + if val0 == 0 and val1 == 0: + return "0.0%" + elif val0 == 0: + return "NaN%" + else: + return "{:+2.1f}%".format(100 * (val1 - val0) / val0) dataRows = [row(( "{}({})".format(x.stat.test, x.stat.way), shorten_metric_name(x.stat.metric), @@ -425,6 +430,7 @@ def tabulate_metrics(metrics: List[PerfMetric]) -> None: x.stat.value / x.baseline.perfStat.value for x in metrics if x.baseline is not None + if x.baseline.perfStat.value != 0 ] minimum = 0.0 maximum = 0.0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/115a30e9142b4481de3ba735396e9d0417d46445...513775082b89deae3f83896031caf0e89a7ed333 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/115a30e9142b4481de3ba735396e9d0417d46445...513775082b89deae3f83896031caf0e89a7ed333 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 02:55:29 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 02 Oct 2024 22:55:29 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 15 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fe07a1ae52d_27186619e11b8977cc@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 97f1c516 by Matthew Pickering at 2024-10-02T22:55:02-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - b2439f4e by Zubin Duggal at 2024-10-02T22:55:02-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - cbb32e33 by Andreas Klebinger at 2024-10-02T22:55:02-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 27 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/src/GHC/Internal/Exts.hs - m4/fp_settings.m4 - m4/fp_setup_windows_toolchain.m4 - m4/fptools_happy.m4 - rts/CheckVectorSupport.c - rts/posix/ticker/TimerFd.c - testsuite/driver/perf_notes.py - testsuite/driver/runtests.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43431c818ec1bf88810a4f6a1d25aaeceb725ee9...cbb32e33f2e3dd8f735eb85afc5f7667640eec47 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43431c818ec1bf88810a4f6a1d25aaeceb725ee9...cbb32e33f2e3dd8f735eb85afc5f7667640eec47 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 07:41:09 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 03 Oct 2024 03:41:09 -0400 Subject: [Git][ghc/ghc][wip/T25281] wibble Message-ID: <66fe4a95af5d7_27186628730dc1176d0@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 4c203e57 by Simon Peyton Jones at 2024-10-03T08:40:57+01:00 wibble - - - - - 1 changed file: - compiler/GHC/Utils/Panic.hs Changes: ===================================== compiler/GHC/Utils/Panic.hs ===================================== @@ -23,7 +23,6 @@ module GHC.Utils.Panic , handleGhcException -- * Command error throwing patterns - , panic , pprPanic , panicDoc , sorryDoc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4c203e57475eba57b9a16c5cb6c430dece48dd28 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4c203e57475eba57b9a16c5cb6c430dece48dd28 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 08:48:28 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 03 Oct 2024 04:48:28 -0400 Subject: [Git][ghc/ghc][wip/js-memory] javascript: Read fields of ObjectBlock lazily Message-ID: <66fe5a5c8da81_1e2e9d278774608a0@gitlab.mail> Matthew Pickering pushed to branch wip/js-memory at Glasgow Haskell Compiler / GHC Commits: 78d27ee2 by Matthew Pickering at 2024-10-03T09:47:47+01:00 javascript: Read fields of ObjectBlock lazily When linking a module with a large dependency footprint too much of the object files were forced during linking. This lead to a large amount of memory taken up by thunks which would never be forced On the PartialDownsweep test this halves the memory required (from 25G to 13G). Towards #25324 ------------------------- Metric Increase: size_hello_obj ------------------------- - - - - - 2 changed files: - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Types.hs Changes: ===================================== compiler/GHC/StgToJS/Object.hs ===================================== @@ -255,23 +255,23 @@ instance Outputable ExportedFun where -- index putObjBlock :: WriteBinHandle -> ObjBlock -> IO () putObjBlock bh (ObjBlock _syms b c d e f g) = do - put_ bh b - put_ bh c + lazyPut bh b + lazyPut bh c lazyPut bh d - put_ bh e - put_ bh f - put_ bh g + lazyPut bh e + lazyPut bh f + lazyPut bh g -- | Read an ObjBlock and associate it to the given symbols (that must have been -- read from the index) getObjBlock :: [FastString] -> ReadBinHandle -> IO ObjBlock getObjBlock syms bh = do - b <- get bh - c <- get bh + b <- lazyGet bh + c <- lazyGet bh d <- lazyGet bh - e <- get bh - f <- get bh - g <- get bh + e <- lazyGet bh + f <- lazyGet bh + g <- lazyGet bh pure $ ObjBlock { oiSymbols = syms , oiClInfo = b ===================================== compiler/GHC/StgToJS/Types.hs ===================================== @@ -312,13 +312,13 @@ data LinkableUnit = LinkableUnit -- | one toplevel block in the object file data ObjBlock = ObjBlock - { oiSymbols :: ![FastString] -- ^ toplevel symbols (stored in index) - , oiClInfo :: ![ClosureInfo] -- ^ closure information of all closures in block - , oiStatic :: ![StaticInfo] -- ^ static closure data + { oiSymbols :: [FastString] -- ^ toplevel symbols (stored in index) + , oiClInfo :: [ClosureInfo] -- ^ closure information of all closures in block + , oiStatic :: [StaticInfo] -- ^ static closure data , oiStat :: Sat.JStat -- ^ the code - , oiRaw :: !BS.ByteString -- ^ raw JS code - , oiFExports :: ![ExpFun] - , oiFImports :: ![ForeignJSRef] + , oiRaw :: BS.ByteString -- ^ raw JS code + , oiFExports :: [ExpFun] + , oiFImports :: [ForeignJSRef] } data ExpFun = ExpFun View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78d27ee2f4df35ea320c35355ddf67fee52d7073 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78d27ee2f4df35ea320c35355ddf67fee52d7073 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 09:55:47 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 03 Oct 2024 05:55:47 -0400 Subject: [Git][ghc/ghc][master] ci: Add nightly & release ubuntu-22.04 jobs Message-ID: <66fe6a2346024_3ffcbee5c6874088@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 5 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1144,6 +1144,8 @@ ghcup-metadata-nightly: artifacts: false - job: nightly-x86_64-linux-centos7-validate artifacts: false + - job: nightly-x86_64-linux-ubuntu22_04-validate + artifacts: false - job: nightly-x86_64-linux-ubuntu20_04-validate artifacts: false - job: nightly-x86_64-linux-ubuntu18_04-validate ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -112,6 +112,7 @@ data LinuxDistro | Debian9 | Fedora33 | Fedora38 + | Ubuntu2204 | Ubuntu2004 | Ubuntu1804 | Centos7 @@ -308,6 +309,7 @@ distroName Fedora33 = "fedora33" distroName Fedora38 = "fedora38" distroName Ubuntu1804 = "ubuntu18_04" distroName Ubuntu2004 = "ubuntu20_04" +distroName Ubuntu2204 = "ubuntu22_04" distroName Centos7 = "centos7" distroName Alpine312 = "alpine3_12" distroName Alpine318 = "alpine3_18" @@ -1060,6 +1062,7 @@ ubuntu_x86 :: [JobGroup Job] ubuntu_x86 = [ disableValidate (standardBuilds Amd64 (Linux Ubuntu1804)) , disableValidate (standardBuilds Amd64 (Linux Ubuntu2004)) + , disableValidate (standardBuilds Amd64 (Linux Ubuntu2204)) ] rhel_x86 :: [JobGroup Job] ===================================== .gitlab/jobs.yaml ===================================== @@ -2745,6 +2745,69 @@ "XZ_OPT": "-9" } }, + "nightly-x86_64-linux-ubuntu22_04-validate": { + "after_script": [ + ".gitlab/ci.sh save_cache", + ".gitlab/ci.sh save_test_output", + ".gitlab/ci.sh clean", + "cat ci_timings" + ], + "allow_failure": false, + "artifacts": { + "expire_in": "8 weeks", + "paths": [ + "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz", + "junit.xml", + "unexpected-test-output.tar.gz" + ], + "reports": { + "junit": "junit.xml" + }, + "when": "always" + }, + "cache": { + "key": "x86_64-linux-ubuntu22_04-$CACHE_REV", + "paths": [ + "cabal-cache", + "toolchain" + ] + }, + "dependencies": [], + "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV", + "needs": [ + { + "artifacts": false, + "job": "hadrian-ghc-in-ghci" + } + ], + "rules": [ + { + "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)", + "when": "on_success" + } + ], + "script": [ + "sudo chown ghc:ghc -R .", + ".gitlab/ci.sh setup", + ".gitlab/ci.sh configure", + ".gitlab/ci.sh build_hadrian", + ".gitlab/ci.sh test_hadrian" + ], + "stage": "full-build", + "tags": [ + "x86_64-linux" + ], + "variables": { + "BIGNUM_BACKEND": "gmp", + "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate", + "BUILD_FLAVOUR": "validate", + "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "RUNTEST_ARGS": "", + "TEST_ENV": "x86_64-linux-ubuntu22_04-validate", + "XZ_OPT": "-9" + } + }, "nightly-x86_64-windows-int_native-validate": { "after_script": [ "bash .gitlab/ci.sh save_cache", @@ -4452,6 +4515,71 @@ "XZ_OPT": "-9" } }, + "release-x86_64-linux-ubuntu22_04-release": { + "after_script": [ + ".gitlab/ci.sh save_cache", + ".gitlab/ci.sh save_test_output", + ".gitlab/ci.sh clean", + "cat ci_timings" + ], + "allow_failure": false, + "artifacts": { + "expire_in": "1 year", + "paths": [ + "ghc-x86_64-linux-ubuntu22_04-release.tar.xz", + "junit.xml", + "unexpected-test-output.tar.gz" + ], + "reports": { + "junit": "junit.xml" + }, + "when": "always" + }, + "cache": { + "key": "x86_64-linux-ubuntu22_04-$CACHE_REV", + "paths": [ + "cabal-cache", + "toolchain" + ] + }, + "dependencies": [], + "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV", + "needs": [ + { + "artifacts": false, + "job": "hadrian-ghc-in-ghci" + } + ], + "rules": [ + { + "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)", + "when": "on_success" + } + ], + "script": [ + "sudo chown ghc:ghc -R .", + ".gitlab/ci.sh setup", + ".gitlab/ci.sh configure", + ".gitlab/ci.sh build_hadrian", + ".gitlab/ci.sh test_hadrian" + ], + "stage": "full-build", + "tags": [ + "x86_64-linux" + ], + "variables": { + "BIGNUM_BACKEND": "gmp", + "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-release", + "BUILD_FLAVOUR": "release", + "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "HADRIAN_ARGS": "--hash-unit-ids", + "IGNORE_PERF_FAILURES": "all", + "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "RUNTEST_ARGS": "", + "TEST_ENV": "x86_64-linux-ubuntu22_04-release", + "XZ_OPT": "-9" + } + }, "release-x86_64-windows-int_native-release": { "after_script": [ "bash .gitlab/ci.sh save_cache", ===================================== .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py ===================================== @@ -19,6 +19,7 @@ def job_triple(job_name): 'release-x86_64-windows-release': 'x86_64-unknown-mingw32', 'release-x86_64-windows-int_native-release': 'x86_64-unknown-mingw32-int_native', 'release-x86_64-linux-rocky8-release': 'x86_64-rocky8-linux', + 'release-x86_64-linux-ubuntu22_04-release': 'x86_64-ubuntu22_04-linux', 'release-x86_64-linux-ubuntu20_04-release': 'x86_64-ubuntu20_04-linux', 'release-x86_64-linux-ubuntu18_04-release': 'x86_64-ubuntu18_04-linux', 'release-x86_64-linux-fedora38-release': 'x86_64-fedora38-linux', ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -191,6 +191,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): # Here are all the bindists we can distribute ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) + ubuntu2204 = mk(ubuntu("22_04")) rocky8 = mk(rocky("8")) centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) @@ -222,7 +223,10 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): , "unknown_versioning": deb11 } , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004 , "( >= 16 && < 18 )": deb9 - , "( >= 18 && < 19 )": ubuntu1804 } + , "( >= 18 && < 19 )": ubuntu1804 + , "( >= 19 && < 21 )": ubuntu2004 + , "( >= 21 )": ubuntu2204 + } , "Linux_Mint" : { "< 20": ubuntu1804 , ">= 20": ubuntu2004 , "unknown_versioning": ubuntu2004 } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/504900755e3297c000a3bcf4f20eaae1f10298f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/504900755e3297c000a3bcf4f20eaae1f10298f4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 09:56:30 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 03 Oct 2024 05:56:30 -0400 Subject: [Git][ghc/ghc][master] haddock: Bump binary interface version to 46. Message-ID: <66fe6a4e181b4_3ffcbe324a9c76940@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 1 changed file: - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -140,7 +140,7 @@ binaryInterfaceMagic = 0xD0Cface -- binaryInterfaceVersion :: Word16 #if MIN_VERSION_ghc(9,11,0) && !MIN_VERSION_ghc(9,14,0) -binaryInterfaceVersion = 44 +binaryInterfaceVersion = 46 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9cf1cef5ba7ae709bda16859f53900de3a262992 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9cf1cef5ba7ae709bda16859f53900de3a262992 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 09:57:05 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 03 Oct 2024 05:57:05 -0400 Subject: [Git][ghc/ghc][master] Change versionig of ghc-experimental to follow ghc versions. Message-ID: <66fe6a71be685_3ffcbe42bd0081553@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 1 changed file: - libraries/ghc-experimental/ghc-experimental.cabal.in Changes: ===================================== libraries/ghc-experimental/ghc-experimental.cabal.in ===================================== @@ -4,7 +4,9 @@ cabal-version: 3.0 -- Make sure you are editing ghc-experimental.cabal.in, not ghc-experimental.cabal name: ghc-experimental -version: 0.1.0.0 +-- The project is ghc's version plus ghc-experimental's version suffix. +-- For example, for ghc=9.10.1, ghc-experimental's version will be 9.1001.0. +version: @ProjectVersionForLib at .0 synopsis: Experimental features of GHC's standard library description: This package is where experimental GHC standard library interfaces start View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2293c0b7d709df7be04f596e72c97fd2435c4134 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2293c0b7d709df7be04f596e72c97fd2435c4134 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:19:00 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Thu, 03 Oct 2024 06:19:00 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/9.12-submodule-bumps Message-ID: <66fe6f944f504_3ea6b2bedc060166@gitlab.mail> Zubin pushed new branch wip/9.12-submodule-bumps at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12-submodule-bumps You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:33:20 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 06:33:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/25330 Message-ID: <66fe72f0675b2_3ea6b22c0218717ac@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/25330 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25330 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:33:50 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Thu, 03 Oct 2024 06:33:50 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] test update Message-ID: <66fe730e9068e_3ea6b22c7dc4760de@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 60268659 by Hassan Al-Awwadi at 2024-10-03T12:32:47+02:00 test update - - - - - 1 changed file: - testsuite/tests/parser/should_compile/T14189.stderr Changes: ===================================== testsuite/tests/parser/should_compile/T14189.stderr ===================================== @@ -165,7 +165,8 @@ (EpaComments [])) (FieldOcc - {Name: T14189.f} + (Unqual + {OccName: f}) (L (EpAnn (EpaSpan { T14189.hs:6:33 }) @@ -173,8 +174,7 @@ []) (EpaComments [])) - (Unqual - {OccName: f}))))] + {Name: T14189.f})))] (L (EpAnn (EpaSpan { T14189.hs:6:38-40 }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60268659980e83ff7bb7a2b6393c54ac80c8ddfe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60268659980e83ff7bb7a2b6393c54ac80c8ddfe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:35:19 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Thu, 03 Oct 2024 06:35:19 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] 30 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fe736774fc9_3ea6b224f78476729@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - ea2e0ae4 by Jade at 2024-10-03T12:34:55+02:00 Refactor FieldOcc vs AmbiguousFieldOcc with TTG Improves the design of FieldOcc vs AmbiguousFieldOcc, and removes a dependency on `RdrName` from the Language.Haskell.* namespace (#21592). The design: * The FieldOcc constructor of FieldOcc always refers to an unambiguous field occurrence. * During renaming, a FieldOcc may be ambiguous and only be resolvable during Typechecking * Therefore, we extend (with TTG) `FieldOcc GhcRn` with a constructor `AmbiguousFieldOcc` that constructs a definitely ambiguous `FieldOcc`. * During typechecking, all ambiguous field occurrences must be resolved, so the `AmbiguousFieldOcc` constructor no longer exists See Note [Lifecycle of a FieldOcc] Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - a8e9116b by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 Wrangled until everything compiled. There are two issues: - FieldOcc used to only have one constructor and always be unambigious, this is no longer the case. Calls to foLabel are thus partial now. Don't know how much we care about this, since the partial calls are mostly inside functions that used to operate on the operate on the unambigious FieldOcc - Lots of functions that take in a FieldOcc, or a HsExpr (with the HsRecSel constructor) now have a new case. It was not always clear to me what the correct implementation was for these. I have filled them in as far as I could and left one undefined... - - - - - d041e170 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 fixed ambiguity regression - - - - - b64d807a by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 Apply 2 suggestion(s) to 2 file(s) Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - e231f43b by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 eleminated outdated comments and use dataConCantHappen - - - - - 0b6984ec by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 Moved HsRecSel to the XConstructors. FieldOcc types kept in Language.Haskell though because they are also used by HsRecUpdField in L.H.S.Pat.hs - - - - - 07df8f81 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 hopefully fixes the assert error* and clears up some whitespace *in GHC.Rename.HsType. I'm not certain but I also don't know what else it could be... - - - - - 0d63c50f by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 attempt 2 at fixing the asssert error if I could manage to get the full build working on my machine I'd test it locally but alas, I wil have to make the gitlab runners do the work... - - - - - 6625da61 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 rename stuff - - - - - 4450f854 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 cleaned remnant AmbiguousFieldOcc -> UpdFieldOcc - - - - - e2af9434 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 More renaming. - - - - - d6dffb4c by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 notes updated - - - - - f48f60f2 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 fixed note pointer, unneeded imports, and unmatched datacon. the datacon is actually impossible but whatever. GHC wants what it wants. - - - - - ca800046 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 removed unused binding. Its errors like these that really make me wish I could build ghc completely because an half hour long pipeline to find an error like thsi is highly annoying (and a waste of the runner) - - - - - 7c04d0b7 by Hassan Al-Awwadi at 2024-10-03T12:34:55+02:00 test update - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Platform/Reg/Class.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60268659980e83ff7bb7a2b6393c54ac80c8ddfe...7c04d0b73cfc27f0096dcbc69ea4cee811cbc155 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60268659980e83ff7bb7a2b6393c54ac80c8ddfe...7c04d0b73cfc27f0096dcbc69ea4cee811cbc155 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:48:05 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 06:48:05 -0400 Subject: [Git][ghc/ghc][wip/exception-propagate] 17 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fe7665f15f1_3ea6b24e185880599@gitlab.mail> Rodrigo Mesquita pushed to branch wip/exception-propagate at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 31ecbd72 by Matthew Pickering at 2024-10-03T11:47:53+01:00 Fix toException method for ExceptionWithContext Fixes #25235 - - - - - 608279bf by Matthew Pickering at 2024-10-03T11:47:54+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/src/GHC/Exts.hs - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/978abd669b7bdbe816b1239eec5230cbf0855289...608279bf335668abd561832837211c5c0c1260c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/978abd669b7bdbe816b1239eec5230cbf0855289...608279bf335668abd561832837211c5c0c1260c4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 10:52:46 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Thu, 03 Oct 2024 06:52:46 -0400 Subject: [Git][ghc/ghc][wip/9.12-submodule-bumps] Deleted 1 commit: Bump hpc submodule to master Message-ID: <66fe777ebcfb3_3ea6b254295081052@gitlab.mail> Zubin pushed to branch wip/9.12-submodule-bumps at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: 5c95b906 by Zubin Duggal at 2024-10-03T15:46:22+05:30 Bump hpc submodule to master We need a release: https://gitlab.haskell.org/hpc/hpc-bin/-/issues/19 - - - - - 1 changed file: - utils/hpc Changes: ===================================== utils/hpc ===================================== @@ -1 +1 @@ -Subproject commit d1780eb21c1e5a1227fff80c8d325d5142f04255 +Subproject commit 8c807459bf0fa35224fb51a719e6febf8f55e5f2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c95b9064f0fb73fa2f8e0b7733738e06db5139b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c95b9064f0fb73fa2f8e0b7733738e06db5139b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 11:12:02 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 03 Oct 2024 07:12:02 -0400 Subject: [Git][ghc/ghc][wip/T25281] More record selector safety Message-ID: <66fe7c0249beb_8e3b0fa438905f@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: bcf3053e by Simon Peyton Jones at 2024-10-03T12:10:17+01:00 More record selector safety - - - - - 3 changed files: - compiler/GHC/Iface/Load.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -70,6 +70,7 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Logger +import GHC.Utils.Fingerprint( Fingerprint ) import GHC.Settings.Constants @@ -1186,13 +1187,15 @@ pprExport avail@(AvailTC n _) = pp_export names = braces (hsep (map ppr names)) pprUsage :: Usage -> SDoc -pprUsage usage at UsagePackageModule{} - = pprUsageImport usage usg_mod -pprUsage usage at UsageHomeModule{} - = pprUsageImport usage (\u -> mkModule (usg_unit_id u) (usg_mod_name u)) $$ +pprUsage UsagePackageModule{ usg_mod = mod, usg_mod_hash = hash, usg_safe = safe } + = pprUsageImport mod hash safe +pprUsage UsageHomeModule{ usg_unit_id = unit_id, usg_mod_name = mod_name + , usg_mod_hash = hash, usg_safe = safe + , usg_exports = exports, usg_entities = entities } + = pprUsageImport (mkModule unit_id mod_name) hash safe $$ nest 2 ( - maybe Outputable.empty (\v -> text "exports: " <> ppr v) (usg_exports usage) $$ - vcat [ ppr n <+> ppr v | (n,v) <- usg_entities usage ] + maybe Outputable.empty (\v -> text "exports: " <> ppr v) exports $$ + vcat [ ppr n <+> ppr v | (n,v) <- entities ] ) pprUsage usage at UsageFile{} = hsep [text "addDependentFile", @@ -1205,13 +1208,13 @@ pprUsage usage at UsageHomeModuleInterface{} , ppr (usg_unit_id usage) , ppr (usg_iface_hash usage)] -pprUsageImport :: Outputable a => Usage -> (Usage -> a) -> SDoc -pprUsageImport usage usg_mod' - = hsep [text "import", safe, ppr (usg_mod' usage), - ppr (usg_mod_hash usage)] +pprUsageImport :: Outputable mod => mod -> Fingerprint -> IsSafeImport -> SDoc +pprUsageImport mod hash safe + = hsep [ text "import", pp_safe, ppr mod + , ppr hash ] where - safe | usg_safe usage = text "safe" - | otherwise = text " -/ " + pp_safe | safe = text "safe" + | otherwise = text " -/ " pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -316,17 +316,12 @@ lHsQTyVarsToTypes tvs = restrictTo :: [Name] -> LHsDecl GhcRn -> LHsDecl GhcRn restrictTo names (L loc decl) = L loc $ case decl of TyClD x d - | isDataDecl d -> - TyClD x (d{tcdDataDefn = restrictDataDefn names (tcdDataDefn d)}) + | DataDecl { tcdDataDefn = dd } <- d + -> TyClD x (d {tcdDataDefn = restrictDataDefn names dd}) TyClD x d - | isClassDecl d -> - TyClD - x - ( d - { tcdSigs = restrictDecls names (tcdSigs d) - , tcdATs = restrictATs names (tcdATs d) - } - ) + | ClassDecl { tcdSigs = sigs, tcdATs = ats } <- d + -> TyClD x (d { tcdSigs = restrictDecls names sigs + , tcdATs = restrictATs names ats } ) _ -> decl restrictDataDefn :: [Name] -> HsDataDefn GhcRn -> HsDataDefn GhcRn @@ -561,13 +556,12 @@ instance Parent (ConDecl GhcRn) where instance Parent (TyClDecl GhcRn) where children d - | isDataDecl d = - map unLoc $ - concatMap (toList . getConNames . unLoc) $ - (dd_cons . tcdDataDefn) d - | isClassDecl d = - map (unLoc . fdLName . unLoc) (tcdATs d) - ++ [unLoc n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns] + | DataDecl { tcdDataDefn = dd } <- d + = map unLoc $ + concatMap (toList . getConNames . unLoc) (dd_cons dd) + | ClassDecl{ tcdSigs = sigs, tcdATs = ats } <- d + = map (unLoc . fdLName . unLoc) ats + ++ [unLoc n | L _ (TypeSig _ ns _) <- sigs, n <- ns] | otherwise = [] -- | A parent and its children @@ -581,9 +575,9 @@ familyConDecl d = zip (toList $ unLoc <$> getConNames d) (repeat $ children d) -- child to its grand-children, recursively. families :: TyClDecl GhcRn -> [(Name, [Name])] families d - | isDataDecl d = family d : concatMap (familyConDecl . unLoc) (dd_cons (tcdDataDefn d)) - | isClassDecl d = [family d] - | otherwise = [] + | DataDecl {} <- d = family d : concatMap (familyConDecl . unLoc) (dd_cons (tcdDataDefn d)) + | ClassDecl {} <- d = [family d] + | otherwise = [] -- | A mapping from child to parent parentMap :: TyClDecl GhcRn -> [(Name, Name)] ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -945,6 +945,7 @@ type instance XXFamilyDecl DocNameI = DataConCantHappen type instance XXTyClDecl DocNameI = DataConCantHappen type instance XHsWC DocNameI _ = NoExtField +type instance XXHsWildCardBndrs DocNameI _ = DataConCantHappen type instance XHsOuterExplicit DocNameI _ = NoExtField type instance XHsOuterImplicit DocNameI = NoExtField @@ -954,6 +955,8 @@ type instance XHsSig DocNameI = NoExtField type instance XXHsSigType DocNameI = DataConCantHappen type instance XHsQTvs DocNameI = NoExtField +type instance XXLHsQTyVars DocNameI = DataConCantHappen + type instance XConDeclField DocNameI = NoExtField type instance XXConDeclField DocNameI = DataConCantHappen View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcf3053e9197451aae7d55f61cb0ad0931339017 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcf3053e9197451aae7d55f61cb0ad0931339017 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 11:32:05 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 03 Oct 2024 07:32:05 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/only_job Message-ID: <66fe80b595c57_8e3b02368249478d@gitlab.mail> Matthew Pickering pushed new branch wip/only_job at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/only_job You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 11:37:37 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 07:37:37 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/base_expose_weakly Message-ID: <66fe82017232f_8e3b033a8ec994d9@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/base_expose_weakly at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/base_expose_weakly You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 11:39:26 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 03 Oct 2024 07:39:26 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/i386-label Message-ID: <66fe826e6141d_8e3b06b3460101484@gitlab.mail> Matthew Pickering pushed new branch wip/i386-label at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/i386-label You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 11:57:12 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 07:57:12 -0400 Subject: [Git][ghc/ghc][wip/clc275] 71 commits: ci: Run abi-test on test-abi label Message-ID: <66fe86985e77e_8e3b07829e0106780@gitlab.mail> Andreas Klebinger pushed to branch wip/clc275 at Glasgow Haskell Compiler / GHC Commits: 2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30 ci: Run abi-test on test-abi label - - - - - ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 testsuite: Add a test for object determinism Extends the abi_test with an object determinism check Also includes a standalone test to be run by developers manually when debugging issues with determinism. - - - - - d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Sampling uniques in the CG To achieve object determinism, the passes processing Cmm and the rest of the code generation pipeline musn't create new uniques which are non-deterministic. This commit changes occurrences of non-deterministic unique sampling within these code generation passes by a deterministic unique sampling strategy by propagating and threading through a deterministic incrementing counter in them. The threading is done implicitly with `UniqDSM` and `UniqDSMT`. Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded through all passes to guarantee uniques in different passes are unique amongst them altogether. Specifically, the same `DUniqSupply` must be threaded through the CG Streaming pipeline, starting with Driver.Main calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and `codeOutput` in sequence. To thread resources through the `Stream` abstraction, we use the `UniqDSMT` transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will thread the `DUniqSupply` through every pass applied to the `Stream`, for every element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in code generation which that carries through the deterministic unique supply. See Note [Deterministic Uniques in the CG] - - - - - 3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Cmm unique renaming pass To achieve object determinism, we need to prevent the non-deterministic uniques from leaking into the object code. We can do this by deterministically renaming the non-external uniques in the Cmm groups that are yielded right after StgToCmm. The key to deterministic renaming is observing that the order of declarations, instructions, and data in the Cmm groups are already deterministic (modulo other determinism bugs), regardless of the uniques. We traverse the Cmm AST in this deterministic order and rename the uniques, incrementally, in the order they are found, thus making them deterministic. This renaming is guarded by -fobject-determinism which is disabled by default for now. This is one of the key passes for object determinism. Read about the overview of object determinism and a more detailed explanation of this pass in: * Note [Object determinism] * Note [Renaming uniques deterministically] Significantly closes the gap to #12935 - - - - - 8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: DCmmGroup vs CmmGroup Part of our strategy in producing deterministic objects, namely, renaming all Cmm uniques in order, depend on the object code produced having a deterministic order (say, A_closure always comes before B_closure). However, the use of LabelMaps in the Cmm representation invalidated this requirement because the LabelMaps elements would already be in a non-deterministic order (due to the original uniques), and the renaming in sequence wouldn't work because of that non-deterministic order. Therefore, we now start off with lists in CmmGroup (which preserve the original order), and convert them into LabelMaps (for performance in the code generator) after the uniques of the list elements have been renamed. See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935. Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Don't print unique in pprFullName This unique was leaking as part of the profiling description in info tables when profiling was enabled, despite not providing information relevant to the profile. - - - - - 340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: UDFM for distinct-constructor-tables In order to produce deterministic objects when compiling with -distinct-constructor-tables, we also have to update the data constructor map to be backed by a deterministic unique map (UDFM) rather than a non-deterministic one (UniqMap). - - - - - 282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: InfoTableMap uniques in generateCgIPEStub Fixes object determinism when using -finfo-table-map Make sure to also deterministically rename the IPE map (as per Note [Renaming uniques deterministically]), and to use a deterministic unique supply when creating new labels for the IPE information to guarantee deterministic objects when IPE information is requested. Note that the Cmm group produced in generateCgIPEStub must /not/ be renamed because renaming uniques is not idempotent, and the references to the previously renamed code in the IPE Cmm group would be renamed twice and become invalid references to non-existent symbols. We do need to det-rename the InfoTableMap that is created in the conversion from Core to Stg. This is not a problem since that map won't refer any already renamed names (since it was created before the renaming). - - - - - 7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30 ci: Allow abi-test to fail. We are not fully deterministic yet, see #12935 for work that remains to be done. - - - - - a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00 Add Given injectivity for built-in type families Ticket #24845 asks (reasonably enough) that if we have [G] a+b ~ 0 then we also know [G] a ~ 0, b ~ 0 and similar injectivity-like facts for other built-in type families. The status quo was that we never generate evidence for injectivity among Givens -- but it is quite reasonnable to do so. All we need is to have /evidence/ for the new constraints This MR implements that goal. I also took the opportunity to * Address #24978: refactoring UnivCo * Fix #25248, which was a consequences of the previous formulation of UnivCo As a result this MR touches a lot of code. The big things are: * Coercion constructor UnivCo now takes a [Coercion] as argument to express the coercions on which the UnivCo depends. A nice consequence is that UnivCoProvenance now has no free variables, simpler in a number of places. * Coercion constructors AxiomInstCo and AxiomRuleCo are combined into AxiomCo. The new AxiomCo, carries a (slightly oddly named) CoAxiomRule, which itself is a sum type of the various forms of built-in axiom. See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom A merit of this is that we can separate the case of open and closed type families, and eliminate the redundant `BranchIndex` in the former case. * Much better representation for data BuiltInSynFamily, which means we no longer need to enumerate built-in axioms as well as built-in tycons. * There is a massive refactor in GHC.Builtin.Types.Literals, which contains all the built-in axioms for type-level operations (arithmetic, append, cons etc). A big change is that instead of redundantly having (a) a hand-written matcher, and (b) a template-based "proves" function, which were hard to keep in sync, the two are derive from one set of human-supplied info. See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends. * Significant changes in GHC.Tc.Solver.Equality to account for the new opportunity for Given/Given equalities. Smaller things * Improve pretty-printing to avoid parens around atomic coercions. * Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`. Looks like a bug, Richard agrees. * coercionLKind and coercionRKind are hot functions. I refactored the implementation (which I had to change anyway) to increase sharing. See Note [coercionKind performance] in GHC.Core.Coercion * I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan names * I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid calling tyConsOfType. I forget exactly why I did this, but it's definitely better now. * I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc - - - - - dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00 Resolve ambiguous method-bound type variables in vanilla defaults and GND When defining an instance of a class with a "vanilla" default, such as in the following example (from #14266): ```hs class A t where f :: forall x m. Monoid x => t m -> m f = <blah> instance A [] ``` We have to reckon with the fact that the type of `x` (bound by the type signature for the `f` method) is ambiguous. If we don't deal with the ambiguity somehow, then when we generate the following code: ```hs instance A [] where f = $dmf @[] -- NB: the type of `x` is still ambiguous ``` Then the generated code will not typecheck. (Issue #25148 is a more recent example of the same problem.) To fix this, we bind the type variables from the method's original type signature using `TypeAbstractions` and instantiate `$dmf` with them using `TypeApplications`: ```hs instance A [] where f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous ``` Note that we only do this for vanilla defaults and not for generic defaults (i.e., defaults using `DefaultSignatures`). For the full details, see `Note [Default methods in instances] (Wrinkle: Ambiguous types from vanilla method type signatures)`. The same problem arose in the code generated by `GeneralizedNewtypeDeriving`, as we also fix it here using the same technique. This time, we can take advantage of the fact that `GeneralizedNewtypeDeriving`-generated code _already_ brings method-bound type variables into scope via `TypeAbstractions` (after !13190), so it is very straightforward to visibly apply the type variables on the right-hand sides of equations. See `Note [GND and ambiguity]`. Fixes #14266. Fixes #25148. - - - - - 0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00 Document primitive string literals and desugaring of string literals Fixes #17474 and #17974 Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00 rts: Fix segfault when using non-moving GC with profiling `nonMovingCollect()` swaps out the `static_flag` value used as a sentinel for `gct->scavenged_static_objects`, but the subsequent call `resetStaticObjectForProfiling()` sees the old value of `static_flag` used as the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()` before calling `nonMovingCollect()` as otherwise it looks for the incorrect sentinel value Fixes #25232 and #23958 Also teach the testsuite driver about nonmoving profiling ways and stop disabling metric collection when nonmoving GC is enabled. - - - - - e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00 Fix interaction between fork and kqueue (#24672) A kqueue file descriptor isn't inherited by a child created with fork. As such we mustn't try to close this file descriptor as we would close a random one, e.g. the one used by timerfd. Fix #24672 - - - - - 6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00 Improve GHC.Tc.Solver.defaultEquality This MR improves GHC.Tc.Solver.defaultEquality to solve #25251. The main change is to use checkTyEqRhs to check the equality, so that we do promotion properly. But within that we needed a small enhancement to LC_Promote. See Note [Defaulting equalites] (DE4) and (DE5) The tricky case is (alas) hard to trigger, so I have not added a regression test. - - - - - 97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00 JS: fix h$withCStringOnHeap helper (#25288) strlen returns the length of the string without the \0 terminating byte, hence CString weren't properly allocated on the heap (ending \0 byte was missing). - - - - - 5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00 base: Propagate `error` CallStack to thrown exception Previously `errorCallWithCallStackException` failed to propagate its `CallStack` argument, which represents the call-chain of the preceding `error` call, to the exception that it returned. Consequently, the call-stack of `error` calls were quite useless. Unfortunately, this is the second time that I have fixed this but it seems the first must have been lost in rebasing. Fixes a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164> Fixes #24807. - - - - - c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00 driver: Fix -working-dir for foreign files -working-dir definitely needs more serious testing, there are some easy ways to test this. * Modify Cabal to call ghc using -working-dir rather than changing directory. * Modify the testsuite to run ghc using `-working-dir` rather than running GHC with cwd = temporary directory. However this will have to wait until after 9.12. Fixes #25150 - - - - - 88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: reuse predError, succError, toEnumError Reuse predError, succError, and toEnumError when deriving Enum instances to avoid generating different error strings per instance. E.g. before this patch for every instance for a type FOO we would generate a string: "pred{FOO}: tried to take `pred' of first tag in enumeration"# - - - - - e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: generate better code (#16364) Generate better code for Enum.toEnum: check both the lower and the upper bounds at once with an unsigned comparison. Initially I've used a type ascription with a call to 'fromIntegral', hence the slight refactoring of nlAscribe. Using 'fromIntegral' was problematic (too low in the module hierarchy) so 'enumIntToWord' was introduced instead. Combined with the previous commit, T21839c ghc/alloc decrease by 5% Metric Decrease: T21839c - - - - - 383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00 Core: add absorb rules for binary or/and (#16351) Rules: x or (x and y) ==> x x and (x or y) ==> x - - - - - 783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Don't compile `asBox` with -fprof-late The `asBox` function is intended to store exactly the closure which the user passes to it. Placing a cost centre on asBox introduces a thunk, which violates this expectation and can change the result of using asBox when profiling is enabled. See #25212 for more details and ample opportunity to discuss if this is a bug or not. - - - - - 0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Fix normalisation of .prof files Fix 1: If a cost centre contained CAF then the normalisation was corrupted, now only check if CAF is at the start of a line. Fix 2: "no location info" contain a space, which messed up the next normalisation logic which assumed that columns didn't have spaced in. - - - - - 9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00 testsuite: Fix normalisation of prof_files removing newlines These normalisation steps were collapsing lines together, which made subsequent normalisation steps fail. ``` foo x y z CAF x y z qux x y z ``` was getting normalised to ``` foo x y z qux x y z ``` which means that subsequent line based filters would not work correctly. - - - - - 2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00 packaging: Enable late-ccs for release flavour This enables late cost centres when building profiled libraries and subsequently greatly improves the resolution of cost centre stacks when profiling. This patch also introduces the `grep_prof` test modifier which is used to apply a further filter to the .prof file before they are compared. Fixes #21732 ------------------------- Metric Increase: libdir ------------------------- - - - - - bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00 Replace manual string lexing (#25158) Metric Increase: MultilineStringsPerf This commit replaces the manual string lexing logic with native Alex lexing syntax. This aligns the lexer much closer to the Haskell Report, making it easier to see how the implementation and spec relate. This slightly increases memory usage when compiling multiline strings because we now have two distinct phases: lexing the multiline string with Alex and post-processing the string afterwards. Before, these were done at the same time, but separating them allows us to push as much logic into normal Alex lexing as possible. Since multiline strings are a new feature, this regression shouldn't be too noticeable. We can optimize this over time. - - - - - 16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import This behaviour is problematic for the principle reason that `import Prelude` may not refer to the `base` package, and in which case importing an entirely unrelated module causing your implicit prelude to leave the scope is extremely surprising. See the added test for this example. Discussion on #17045. The secondary reason for reverting this patch is that "base" can't be a wired in package any more (see #24903), so we have to remove special logic which singles out base from the compiler. The rule for implicit shadowing is now simply: * If you write import Prelude (..) then you don't get an implicit prelude import * If you write import "foobar" Prelude (..) for all pkgs foobar, you get an implicit import of prelude. If you want to write a package import of Prelude, then you can enable `NoImplicitPrelude` for the module in question to recover the behaviour of ghc-9.2-9.10. Fixes #17045 - - - - - 57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE The COMPILING_BASE_PACKAGE macro is concerned with issues defining symbols and using symbols in the same compilation unit. However, these symbols now exist in ghc-internal rather than base, so we should rename the macro accordingly. The code is guards is likely never used as we never produce windows DLLs but it is simpler to just perform the renaming for now. These days there is little doubt that this macro defined in this ad-hoc manner would be permitted to exist, but these days are not those days. Fixes #25221 - - - - - 70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Preload ghc-internal rather than base This occurence of baseUnitId was missed when moving the bulk of internal definitions into `ghc-internal`. We need to remove this preloading of `base` now because `base` should not be wired in. Towards #24903 - - - - - 12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Remove Data.List compat warning There is currently a warning implemented in -Wcompat which warns you when importing Data.List in a non-qualified manner. ``` A.hs:3:8: warning: [-Wcompat-unqualified-imports] To ensure compatibility with future core libraries changes imports to Data.List should be either qualified or have an explicit import list. | 3 | import Data.List | ^^^^^^^^^ Ok, one module loaded. ``` GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244 CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E This warning was implemented as part of the migration to making Data.List monomorphic again (and to be used like Data.Set, Data.Map etc). That doesn't seem like it happened, and I imagine that the current CLC would require a new proposal anyway in order to do that now. It's not clear in any case what "future core libraries changes" we are waiting to happen before this warning can be removed. Given the first phase of the proposal has lasted 5 years it doesn't seem that anyone is motivated to carry the proposal to completion. It does seem a bit unnecessary to include a warning in the compiler about "future changes to the module" when there's no timeline or volunteer to implement these changes. The removal of this warning was discussed again at: https://github.com/haskell/core-libraries-committee/issues/269 During the discussion there was no new enthusiasm to move onto the next stages of the proposal so we are removing the warning to unblock the reinstallable "base" project (#24903) Fixes #24904 - - - - - d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Move Control.Monad.Zip into ghc-internal mzip is wired in and therefore needs to be in ghc-internal. Fixes #25222 Towards #24903 - - - - - d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00 Unwire the base package This patch just removes all the functions related to wiring-in the base package and the `-this-unit-id=base` flag from the cabal file. After this commit "base" becomes just like any other package and the door is opened to moving base into an external repo and releasing base on a separate schedule to the rest of ghc. Closes #24903 - - - - - 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 6f009439 by Ben Gamari at 2024-10-03T13:37:57+02:00 base: Add `HasCallStack` constraint to `ioError` As proposed in core-libraries-committee#275. - - - - - 23 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/85b92a493143ca704a2d381896fd71e3da532567...6f009439346dc50681cc22eadbbce557a5b41a5f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/85b92a493143ca704a2d381896fd71e3da532567...6f009439346dc50681cc22eadbbce557a5b41a5f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 12:49:38 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 08:49:38 -0400 Subject: [Git][ghc/ghc][wip/romes/25330] Deprecation for WarnCompatUnqualifiedImports Message-ID: <66fe92e2719f4_8e3b0c6863012158b@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25330 at Glasgow Haskell Compiler / GHC Commits: 2e78a0ce by Rodrigo Mesquita at 2024-10-03T13:49:26+01:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 2 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1370,8 +1370,7 @@ minusWeverythingOpts = [ toEnum 0 .. ] -- code future compatible to fix issues before they even generate warnings. minusWcompatOpts :: [WarningFlag] minusWcompatOpts - = [ Opt_WarnCompatUnqualifiedImports - , Opt_WarnImplicitRhsQuantification + = [ Opt_WarnImplicitRhsQuantification , Opt_WarnDeprecatedTypeAbstractions ] ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2328,7 +2328,8 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnPartialFields -> warnSpec x Opt_WarnPrepositiveQualifiedModule -> warnSpec x Opt_WarnUnusedPackages -> warnSpec x - Opt_WarnCompatUnqualifiedImports -> warnSpec x + Opt_WarnCompatUnqualifiedImports -> + depWarnSpec x "This warning no longer does anything; see GHC #24904" Opt_WarnInvalidHaddock -> warnSpec x Opt_WarnOperatorWhitespaceExtConflict -> warnSpec x Opt_WarnOperatorWhitespace -> warnSpec x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e78a0cecd6cf471561728ade2f7bc3b1fbbd426 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e78a0cecd6cf471561728ade2f7bc3b1fbbd426 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:01:02 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 09:01:02 -0400 Subject: [Git][ghc/ghc][wip/fllvm-error] driver: bail out when -fllvm is passed to GHC not configured with LLVM Message-ID: <66fe958e579d0_1a6c8bc43d81003c9@gitlab.mail> Rodrigo Mesquita pushed to branch wip/fllvm-error at Glasgow Haskell Compiler / GHC Commits: 4628f7d2 by Cheng Shao at 2024-10-03T14:00:37+01:00 driver: bail out when -fllvm is passed to GHC not configured with LLVM This patch makes GHC bail out with an proper error message when it's not configured with LLVM but users attempt to pass -fllvm, see #25011 and added comment for details. Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 4 changed files: - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Types/Error/Codes.hs Changes: ===================================== compiler/GHC/Driver/Errors/Ppr.hs ===================================== @@ -35,6 +35,7 @@ import GHC.HsToCore.Errors.Types (DsMessage) import GHC.Iface.Errors.Types import GHC.Tc.Errors.Ppr () -- instance Diagnostic TcRnMessage import GHC.Iface.Errors.Ppr () -- instance Diagnostic IfaceMessage +import GHC.CmmToLlvm.Version (llvmVersionStr, supportedLlvmVersionLowerBound, supportedLlvmVersionUpperBound) -- -- Suggestions @@ -268,6 +269,14 @@ instance Diagnostic DriverMessage where mkSimpleDecorated $ vcat [ text "Unexpected backpack instantiation in dependency graph while constructing Makefile:" , nest 2 $ ppr node ] + DriverNoConfiguredLLVMToolchain -> + mkSimpleDecorated $ + text "GHC was not configured with a supported LLVM toolchain" $$ + text ("Make sure you have installed LLVM between [" + ++ llvmVersionStr supportedLlvmVersionLowerBound + ++ " and " + ++ llvmVersionStr supportedLlvmVersionUpperBound + ++ ") and reinstall GHC to make -fllvm work") diagnosticReason = \case DriverUnknownMessage m @@ -337,6 +346,8 @@ instance Diagnostic DriverMessage where -> ErrorWithoutFlag DriverInstantiationNodeInDependencyGeneration {} -> ErrorWithoutFlag + DriverNoConfiguredLLVMToolchain + -> ErrorWithoutFlag diagnosticHints = \case DriverUnknownMessage m @@ -408,5 +419,7 @@ instance Diagnostic DriverMessage where -> noHints DriverInstantiationNodeInDependencyGeneration {} -> noHints + DriverNoConfiguredLLVMToolchain + -> noHints diagnosticCode = constructorCode ===================================== compiler/GHC/Driver/Errors/Types.hs ===================================== @@ -402,6 +402,14 @@ data DriverMessage where Backpack 'InstantiationNode's. -} DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage + {-| DriverNoConfiguredLLVMToolchain is an error that occurs if there is no + LLVM toolchain configured but -fllvm is passed as an option to the compiler. + + Test cases: None. + + -} + DriverNoConfiguredLLVMToolchain :: DriverMessage + deriving instance Generic DriverMessage data DriverMessageOpts = ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -19,7 +19,6 @@ import GHC.Settings import GHC.SysTools.Process import GHC.Driver.Session - import GHC.Utils.Exception as Exception import GHC.Utils.Error import GHC.Utils.Outputable @@ -28,10 +27,16 @@ import GHC.Utils.Logger import GHC.Utils.TmpFs import GHC.Utils.Panic +import Control.Monad import Data.List (tails, isPrefixOf) import Data.Maybe (fromMaybe) import System.IO import System.Process +import GHC.Driver.Config.Diagnostic +import GHC.Driver.Errors +import GHC.Driver.Errors.Types (GhcMessage(..), DriverMessage (DriverNoConfiguredLLVMToolchain)) +import GHC.Driver.CmdLine (warnsToMessages) +import GHC.Types.SrcLoc (noLoc) {- ************************************************************************ @@ -277,12 +282,26 @@ runEmscripten logger dflags args = traceSystoolCommand logger "emcc" $ do figureLlvmVersion :: Logger -> DynFlags -> IO (Maybe LlvmVersion) figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do let (pgm,opts) = pgm_lc dflags + diag_opts = initDiagOpts dflags args = filter notNull (map showOpt opts) -- we grab the args even though they should be useless just in -- case the user is using a customised 'llc' that requires some -- of the options they've specified. llc doesn't care what other -- options are specified when '-version' is used. args' = args ++ ["-version"] + -- Since !12001, when GHC is not configured with llc/opt with + -- supported version range, configure script will leave llc/opt + -- commands as blank in settings. In this case, we should bail out + -- with a proper error, see #25011. + -- + -- Note that this does not make the -Wunsupported-llvm-version + -- warning logic redundant! Power users might want to use + -- -pgmlc/-pgmlo to override llc/opt locations to test LLVM outside + -- officially supported version range, and the driver will produce + -- the warning and carry on code generation. + when (null pgm) $ + printOrThrowDiagnostics logger (initPrintConfig dflags) diag_opts + (GhcDriverMessage <$> warnsToMessages diag_opts [noLoc DriverNoConfiguredLLVMToolchain]) catchIO (do (pin, pout, perr, p) <- runInteractiveProcess pgm args' Nothing Nothing @@ -360,4 +379,3 @@ runWindres logger dflags args = traceSystoolCommand logger "windres" $ do opts = map Option (getOpts dflags opt_windres) mb_env <- getGccEnv cc_args runSomethingFiltered logger id "Windres" windres (opts ++ args) Nothing mb_env - ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -324,6 +324,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "DriverDeprecatedFlag" = 53692 GhcDiagnosticCode "DriverModuleGraphCycle" = 92213 GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284 + GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain" = 66599 -- Constraint solver diagnostic codes GhcDiagnosticCode "BadTelescope" = 97739 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4628f7d20e0e4cbe010d891d95f17596815c4334 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4628f7d20e0e4cbe010d891d95f17596815c4334 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:11:01 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 09:11:01 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/hadrian_progress Message-ID: <66fe97e520919_1a6c8b2c75e01025b7@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/hadrian_progress at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/hadrian_progress You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:14:53 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 09:14:53 -0400 Subject: [Git][ghc/ghc][wip/andreask/hadrian_progress] Adjust progress message for hadrian to include cwd. Message-ID: <66fe98cd22f18_1a6c8b37e330104320@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/hadrian_progress at Glasgow Haskell Compiler / GHC Commits: 0080bed0 by Andreas Klebinger at 2024-10-03T14:55:34+02:00 Adjust progress message for hadrian to include cwd. Fixes #25335 - - - - - 3 changed files: - hadrian/hadrian.cabal - hadrian/src/Main.hs - + hadrian/src/Progress.hs Changes: ===================================== hadrian/hadrian.cabal ===================================== @@ -74,6 +74,7 @@ executable hadrian , Oracles.ModuleFiles , Oracles.TestSettings , Packages + , Progress , Rules , Rules.BinaryDist , Rules.CabalReinstall ===================================== hadrian/src/Main.hs ===================================== @@ -27,6 +27,7 @@ import qualified Rules.Selftest import qualified Rules.SourceDist import qualified Rules.Test import qualified UserSettings +import qualified Progress main :: IO () main = do @@ -56,7 +57,7 @@ main = do options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = buildRoot -/- Base.shakeFilesDir - , shakeProgress = progressSimple + , shakeProgress = Progress.hadrianProgress (cwd -/- "hadrian > " <> buildRoot <> ":") , shakeRebuild = rebuild , shakeTimings = False , shakeColor = shakeColor ===================================== hadrian/src/Progress.hs ===================================== @@ -0,0 +1,14 @@ +module Progress (hadrianProgress) where + +import Development.Shake + +-- | A simple method for displaying progress messages, suitable for using as 'Development.Shake.shakeProgress'. +-- This is the shakeProgress function hadrian uses. It writes the current progress to the titlebar every five seconds +-- using 'progressTitlebar', and calls any @shake-progress@ program on the @$PATH@ using 'progressProgram'. +-- +-- Unlike the default shake progress bar it includes a prefix for the status bar. +hadrianProgress :: String -> IO Progress -> IO () +hadrianProgress prefix p = do + program <- progressProgram + progressDisplay 5 (\status -> let s = prefix <> status in progressTitlebar s >> program s) p + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0080bed0bc6ee4f2f0714c214bee42131f023f11 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0080bed0bc6ee4f2f0714c214bee42131f023f11 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:19:36 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 09:19:36 -0400 Subject: [Git][ghc/ghc][wip/andreask/base_expose_weakly] Expose is[Mutable]ByteArrayWeaklyPinned# from GHC.Exts Message-ID: <66fe99e8635b_1a6c8b3068d01046de@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/base_expose_weakly at Glasgow Haskell Compiler / GHC Commits: 325b1f6b by Andreas Klebinger at 2024-10-03T15:00:26+02:00 Expose is[Mutable]ByteArrayWeaklyPinned# from GHC.Exts - - - - - 4 changed files: - libraries/base/src/GHC/Exts.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/325b1f6b4ce59a58b4b6e46552c32b4d8023c4c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/325b1f6b4ce59a58b4b6e46552c32b4d8023c4c3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:20:39 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 09:20:39 -0400 Subject: [Git][ghc/ghc][wip/romes/25330] Deprecation for WarnCompatUnqualifiedImports Message-ID: <66fe9a27620e5_1a6c8b37e3301049a4@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25330 at Glasgow Haskell Compiler / GHC Commits: b3ad4d55 by Rodrigo Mesquita at 2024-10-03T14:20:08+01:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 29 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-warnings.rst - libraries/base/tests/T9586.hs - libraries/base/tests/list001.hs - testsuite/tests/ghci/scripts/T14828.script - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci036.script - testsuite/tests/module/Mod137_A.hs - testsuite/tests/module/Mod138_A.hs - testsuite/tests/module/Mod141_A.hs - testsuite/tests/module/mod154.hs - testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs - testsuite/tests/perf/compiler/T16875.hs - testsuite/tests/rename/prog001/rn037.hs - testsuite/tests/rename/should_compile/T17244A.hs - testsuite/tests/rename/should_compile/T17244B.hs - testsuite/tests/rename/should_compile/T17244B.stderr - testsuite/tests/rename/should_compile/T17244C.hs - testsuite/tests/rename/should_compile/T17244C.stderr - testsuite/tests/rename/should_compile/T4478.hs - testsuite/tests/rename/should_compile/T7167.hs - testsuite/tests/rename/should_compile/rn025.hs - testsuite/tests/rename/should_compile/rn027.hs - testsuite/tests/rename/should_compile/rn031.hs - testsuite/tests/rename/should_compile/rn060.hs - testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs - testsuite/tests/warnings/should_compile/T11077.hs Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1370,8 +1370,7 @@ minusWeverythingOpts = [ toEnum 0 .. ] -- code future compatible to fix issues before they even generate warnings. minusWcompatOpts :: [WarningFlag] minusWcompatOpts - = [ Opt_WarnCompatUnqualifiedImports - , Opt_WarnImplicitRhsQuantification + = [ Opt_WarnImplicitRhsQuantification , Opt_WarnDeprecatedTypeAbstractions ] ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2328,7 +2328,8 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnPartialFields -> warnSpec x Opt_WarnPrepositiveQualifiedModule -> warnSpec x Opt_WarnUnusedPackages -> warnSpec x - Opt_WarnCompatUnqualifiedImports -> warnSpec x + Opt_WarnCompatUnqualifiedImports -> + depWarnSpec x "This warning no longer does anything; see GHC #24904" Opt_WarnInvalidHaddock -> warnSpec x Opt_WarnOperatorWhitespaceExtConflict -> warnSpec x Opt_WarnOperatorWhitespace -> warnSpec x ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -169,7 +169,6 @@ as ``-Wno-...`` for every individual warning in the group. .. hlist:: :columns: 3 - * :ghc-flag:`-Wcompat-unqualified-imports` * :ghc-flag:`-Wimplicit-rhs-quantification` * :ghc-flag:`-Wdeprecated-type-abstractions` @@ -296,25 +295,16 @@ of ``-W(no-)*``. recognised. .. ghc-flag:: -Wcompat-unqualified-imports - :shortdesc: Report unqualified imports of core libraries which are expected - to cause compatibility problems in future releases. + :shortdesc: *(deprecated)* + Report unqualified imports of core libraries which are expected + to cause compatibility problems in future releases. :type: dynamic :reverse: -Wno-compat-unqualified-imports :category: :since: 8.10 - Warns on unqualified imports of core library modules which are subject to - change in future GHC releases. Currently the following modules are covered - by this warning: - - - ``Data.List`` due to the future addition of ``Data.List.singleton`` and - specialisation of exports to the ``[]`` type. See the - `mailing list `_ - for details. - - This warning can be addressed by either adding an explicit import list or - using a ``qualified`` import. + This warning is deprecated. It no longer has any effect .. ghc-flag:: -Wprepositive-qualified-module :shortdesc: Report imports with a leading/prepositive "qualified" ===================================== libraries/base/tests/T9586.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module XPrelude (module X) where import Control.Monad as X ===================================== libraries/base/tests/list001.hs ===================================== @@ -1,5 +1,4 @@ {-# LANGUAGE CPP #-} -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Main where import Data.List ===================================== testsuite/tests/ghci/scripts/T14828.script ===================================== @@ -14,7 +14,6 @@ :p mempty :p mappend -:set -Wno-compat-unqualified-imports :m + Data.List :p foldl' ===================================== testsuite/tests/ghci/scripts/ghci024.stdout ===================================== @@ -16,9 +16,9 @@ other dynamic, non-language, flag settings: -fprefer-byte-code -fbreak-points warning settings: - -Wcompat-unqualified-imports -Wimplicit-rhs-quantification -Wdeprecated-type-abstractions + -Wcompat-unqualified-imports ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: GHC2021 ===================================== testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 ===================================== @@ -15,9 +15,9 @@ other dynamic, non-language, flag settings: -fprefer-byte-code -fbreak-points warning settings: - -Wcompat-unqualified-imports -Wimplicit-rhs-quantification -Wdeprecated-type-abstractions + -Wcompat-unqualified-imports ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: GHC2021 ===================================== testsuite/tests/ghci/scripts/ghci036.script ===================================== @@ -1,4 +1,3 @@ -:set -Wno-compat-unqualified-imports import Data.List (nub) :t nubBy import Data.List (nubBy) ===================================== testsuite/tests/module/Mod137_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod137_A (module Data.Char) where import Data.Char ===================================== testsuite/tests/module/Mod138_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod138_A (module Data.Char) where import qualified Data.Char ===================================== testsuite/tests/module/Mod141_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod141_A (partition, module Data.List) where import Data.List hiding (partition) ===================================== testsuite/tests/module/mod154.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Default export list isn't the same as (module M) -- This should succeed, exporting only the local 'sort', -- and not being confused by the 'sort' from 'List'. ===================================== testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} {-# LANGUAGE OverloadedLists, TypeFamilies, RebindableSyntax #-} import Prelude ===================================== testsuite/tests/perf/compiler/T16875.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module T16875 where import Control.Applicative ===================================== testsuite/tests/rename/prog001/rn037.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that you can hide a constructor module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/T17244A.hs ===================================== @@ -2,7 +2,8 @@ module T17244A (hello) where --- This should warn with -Wcompat-unqualified-imports. +-- This used to warn with -Wcompat-unqualified-imports. +-- Now it shows the flag is deprecated. import Data.List hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244B.hs ===================================== @@ -2,7 +2,8 @@ module T17244B (hello) where --- This should not warn with -Wcompat-unqualified-imports. +-- This wouldn't warn with -Wcompat-unqualified-imports. +-- The flag is deprecated now. import qualified Data.List as List hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244B.stderr ===================================== @@ -0,0 +1,3 @@ +T17244B.hs:1:17: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wcompat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + ===================================== testsuite/tests/rename/should_compile/T17244C.hs ===================================== @@ -2,7 +2,8 @@ module T17244C (hello) where --- This should not warn with -Wcompat-unqualified-imports. +-- This would not warn with -Wcompat-unqualified-imports. +-- The flag is deprecated now. import Data.List (sum) hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244C.stderr ===================================== @@ -0,0 +1,3 @@ +T17244C.hs:1:17: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wcompat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + ===================================== testsuite/tests/rename/should_compile/T4478.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- We don't want to warn about duplicate exports for things exported -- by both "module" exports module T4478 (module Prelude, module Data.List) where ===================================== testsuite/tests/rename/should_compile/T7167.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} {-# OPTIONS_GHC -fwarn-dodgy-imports #-} module T7167 where ===================================== testsuite/tests/rename/should_compile/rn025.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Re-exporting a module whose contents is partially hidden. module ShouldCompile ( module Data.List ) where ===================================== testsuite/tests/rename/should_compile/rn027.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that an imported module may still have -- !!! a local alias without having used 'qualified'. module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/rn031.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that an imported module may still have -- !!! a local alias without having used 'qualified'. module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/rn060.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module Foo (module Data.List) where import Data.List ===================================== testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs ===================================== @@ -47,7 +47,7 @@ import Data.Functor import Data.IORef import Data.Int import Data.Ix -import Data.List () -- -Wno-compat-unqualified-imports +import Data.List import Data.Maybe import Data.Monoid import Data.Ord ===================================== testsuite/tests/warnings/should_compile/T11077.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module T11077 (module X, foo) where import Data.List as X foo = undefined View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3ad4d555500dca5f942d66b4009dc4aafba8bfd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3ad4d555500dca5f942d66b4009dc4aafba8bfd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:22:25 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 09:22:25 -0400 Subject: [Git][ghc/ghc][wip/romes/25330] Deprecation for WarnCompatUnqualifiedImports Message-ID: <66fe9a918dc11_1a6c8b37fe241053ea@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25330 at Glasgow Haskell Compiler / GHC Commits: 69fae256 by Rodrigo Mesquita at 2024-10-03T14:22:14+01:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 30 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-warnings.rst - libraries/base/tests/T9586.hs - libraries/base/tests/list001.hs - testsuite/tests/ghci/scripts/T14828.script - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci036.script - testsuite/tests/module/Mod137_A.hs - testsuite/tests/module/Mod138_A.hs - testsuite/tests/module/Mod141_A.hs - testsuite/tests/module/mod154.hs - testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs - testsuite/tests/perf/compiler/T16875.hs - testsuite/tests/rename/prog001/rn037.hs - testsuite/tests/rename/should_compile/T17244A.hs - + testsuite/tests/rename/should_compile/T17244A.stderr - testsuite/tests/rename/should_compile/T17244B.hs - testsuite/tests/rename/should_compile/T17244B.stderr - testsuite/tests/rename/should_compile/T17244C.hs - testsuite/tests/rename/should_compile/T17244C.stderr - testsuite/tests/rename/should_compile/T4478.hs - testsuite/tests/rename/should_compile/T7167.hs - testsuite/tests/rename/should_compile/rn025.hs - testsuite/tests/rename/should_compile/rn027.hs - testsuite/tests/rename/should_compile/rn031.hs - testsuite/tests/rename/should_compile/rn060.hs - testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs - testsuite/tests/warnings/should_compile/T11077.hs Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -1370,8 +1370,7 @@ minusWeverythingOpts = [ toEnum 0 .. ] -- code future compatible to fix issues before they even generate warnings. minusWcompatOpts :: [WarningFlag] minusWcompatOpts - = [ Opt_WarnCompatUnqualifiedImports - , Opt_WarnImplicitRhsQuantification + = [ Opt_WarnImplicitRhsQuantification , Opt_WarnDeprecatedTypeAbstractions ] ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2328,7 +2328,8 @@ wWarningFlagsDeps = [minBound..maxBound] >>= \x -> case x of Opt_WarnPartialFields -> warnSpec x Opt_WarnPrepositiveQualifiedModule -> warnSpec x Opt_WarnUnusedPackages -> warnSpec x - Opt_WarnCompatUnqualifiedImports -> warnSpec x + Opt_WarnCompatUnqualifiedImports -> + depWarnSpec x "This warning no longer does anything; see GHC #24904" Opt_WarnInvalidHaddock -> warnSpec x Opt_WarnOperatorWhitespaceExtConflict -> warnSpec x Opt_WarnOperatorWhitespace -> warnSpec x ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -169,7 +169,6 @@ as ``-Wno-...`` for every individual warning in the group. .. hlist:: :columns: 3 - * :ghc-flag:`-Wcompat-unqualified-imports` * :ghc-flag:`-Wimplicit-rhs-quantification` * :ghc-flag:`-Wdeprecated-type-abstractions` @@ -296,25 +295,16 @@ of ``-W(no-)*``. recognised. .. ghc-flag:: -Wcompat-unqualified-imports - :shortdesc: Report unqualified imports of core libraries which are expected - to cause compatibility problems in future releases. + :shortdesc: *(deprecated)* + Report unqualified imports of core libraries which are expected + to cause compatibility problems in future releases. :type: dynamic :reverse: -Wno-compat-unqualified-imports :category: :since: 8.10 - Warns on unqualified imports of core library modules which are subject to - change in future GHC releases. Currently the following modules are covered - by this warning: - - - ``Data.List`` due to the future addition of ``Data.List.singleton`` and - specialisation of exports to the ``[]`` type. See the - `mailing list `_ - for details. - - This warning can be addressed by either adding an explicit import list or - using a ``qualified`` import. + This warning is deprecated. It no longer has any effect since GHC 9.12. .. ghc-flag:: -Wprepositive-qualified-module :shortdesc: Report imports with a leading/prepositive "qualified" ===================================== libraries/base/tests/T9586.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module XPrelude (module X) where import Control.Monad as X ===================================== libraries/base/tests/list001.hs ===================================== @@ -1,5 +1,4 @@ {-# LANGUAGE CPP #-} -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Main where import Data.List ===================================== testsuite/tests/ghci/scripts/T14828.script ===================================== @@ -14,7 +14,6 @@ :p mempty :p mappend -:set -Wno-compat-unqualified-imports :m + Data.List :p foldl' ===================================== testsuite/tests/ghci/scripts/ghci024.stdout ===================================== @@ -16,9 +16,9 @@ other dynamic, non-language, flag settings: -fprefer-byte-code -fbreak-points warning settings: - -Wcompat-unqualified-imports -Wimplicit-rhs-quantification -Wdeprecated-type-abstractions + -Wcompat-unqualified-imports ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: GHC2021 ===================================== testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 ===================================== @@ -15,9 +15,9 @@ other dynamic, non-language, flag settings: -fprefer-byte-code -fbreak-points warning settings: - -Wcompat-unqualified-imports -Wimplicit-rhs-quantification -Wdeprecated-type-abstractions + -Wcompat-unqualified-imports ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: GHC2021 ===================================== testsuite/tests/ghci/scripts/ghci036.script ===================================== @@ -1,4 +1,3 @@ -:set -Wno-compat-unqualified-imports import Data.List (nub) :t nubBy import Data.List (nubBy) ===================================== testsuite/tests/module/Mod137_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod137_A (module Data.Char) where import Data.Char ===================================== testsuite/tests/module/Mod138_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod138_A (module Data.Char) where import qualified Data.Char ===================================== testsuite/tests/module/Mod141_A.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module Mod141_A (partition, module Data.List) where import Data.List hiding (partition) ===================================== testsuite/tests/module/mod154.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Default export list isn't the same as (module M) -- This should succeed, exporting only the local 'sort', -- and not being confused by the 'sort' from 'List'. ===================================== testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} {-# LANGUAGE OverloadedLists, TypeFamilies, RebindableSyntax #-} import Prelude ===================================== testsuite/tests/perf/compiler/T16875.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} module T16875 where import Control.Applicative ===================================== testsuite/tests/rename/prog001/rn037.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that you can hide a constructor module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/T17244A.hs ===================================== @@ -2,7 +2,8 @@ module T17244A (hello) where --- This should warn with -Wcompat-unqualified-imports. +-- This used to warn with -Wcompat-unqualified-imports. +-- Now it shows the flag is deprecated. import Data.List hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244A.stderr ===================================== @@ -0,0 +1,6 @@ +on the commandline: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wno-error=compat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + +T17244A.hs:1:17: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wcompat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + ===================================== testsuite/tests/rename/should_compile/T17244B.hs ===================================== @@ -2,7 +2,8 @@ module T17244B (hello) where --- This should not warn with -Wcompat-unqualified-imports. +-- This wouldn't warn with -Wcompat-unqualified-imports. +-- The flag is deprecated now. import qualified Data.List as List hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244B.stderr ===================================== @@ -0,0 +1,3 @@ +T17244B.hs:1:17: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wcompat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + ===================================== testsuite/tests/rename/should_compile/T17244C.hs ===================================== @@ -2,7 +2,8 @@ module T17244C (hello) where --- This should not warn with -Wcompat-unqualified-imports. +-- This would not warn with -Wcompat-unqualified-imports. +-- The flag is deprecated now. import Data.List (sum) hello :: [Int] -> Int ===================================== testsuite/tests/rename/should_compile/T17244C.stderr ===================================== @@ -0,0 +1,3 @@ +T17244C.hs:1:17: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)] + -Wcompat-unqualified-imports is deprecated: This warning no longer does anything; see GHC #24904 + ===================================== testsuite/tests/rename/should_compile/T4478.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- We don't want to warn about duplicate exports for things exported -- by both "module" exports module T4478 (module Prelude, module Data.List) where ===================================== testsuite/tests/rename/should_compile/T7167.hs ===================================== @@ -1,4 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} {-# OPTIONS_GHC -fwarn-dodgy-imports #-} module T7167 where ===================================== testsuite/tests/rename/should_compile/rn025.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Re-exporting a module whose contents is partially hidden. module ShouldCompile ( module Data.List ) where ===================================== testsuite/tests/rename/should_compile/rn027.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that an imported module may still have -- !!! a local alias without having used 'qualified'. module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/rn031.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - -- !!! Checking that an imported module may still have -- !!! a local alias without having used 'qualified'. module ShouldCompile where ===================================== testsuite/tests/rename/should_compile/rn060.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module Foo (module Data.List) where import Data.List ===================================== testsuite/tests/safeHaskell/unsafeLibs/GoodImport03.hs ===================================== @@ -47,7 +47,7 @@ import Data.Functor import Data.IORef import Data.Int import Data.Ix -import Data.List () -- -Wno-compat-unqualified-imports +import Data.List import Data.Maybe import Data.Monoid import Data.Ord ===================================== testsuite/tests/warnings/should_compile/T11077.hs ===================================== @@ -1,5 +1,3 @@ -{-# OPTIONS_GHC -Wno-compat-unqualified-imports #-} - module T11077 (module X, foo) where import Data.List as X foo = undefined View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69fae2568ea30da25d91d8e423cef68cd18a0df5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69fae2568ea30da25d91d8e423cef68cd18a0df5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:26:32 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 09:26:32 -0400 Subject: [Git][ghc/ghc][wip/fllvm-error] 159 commits: haddock: include package info with --show-interface Message-ID: <66fe9b8844b80_1a6c8b759f0411029e@gitlab.mail> Rodrigo Mesquita pushed to branch wip/fllvm-error at Glasgow Haskell Compiler / GHC Commits: 6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00 haddock: include package info with --show-interface - - - - - 7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00 Document the (x86) SIMD macros. Fixes #25021. - - - - - 05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00 ghc-internal: Derive version from ghc's version Fixes #25005 - - - - - 73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00 base: Deprecate GHC.Desugar See https://github.com/haskell/core-libraries-committee/issues/216. This will be removed in GHC 9.14. - - - - - 821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00 compiler: Store ForeignStubs and foreign C files in interfaces This data is used alongside Core bindings to reconstruct intermediate build products when linking Template Haskell splices with bytecode. Since foreign stubs and files are generated in the pipeline, they were lost with only Core bindings stored in interfaces. The interface codec type `IfaceForeign` contains a simplified representation of `ForeignStubs` and the set of foreign sources that were manually added by the user. When the backend phase writes an interface, `mkFullIface` calls `encodeIfaceForeign` to read foreign source file contents and assemble `IfaceForeign`. After the recompilation status check of an upstream module, `initWholeCoreBindings` calls `decodeIfaceForeign` to restore `ForeignStubs` and write the contents of foreign sources to the file system as temporary files. The restored foreign inputs are then processed by `hscInteractive` in the same manner as in a regular pipeline. When linking the stub objects for splices, they are excluded from suffix adjustment for the interpreter way through a new flag in `Unlinked`. For details about these processes, please consult Note [Foreign stubs and TH bytecode linking]. Metric Decrease: T13701 - - - - - f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00 git: remove a.out and include it in .gitignore a.out is a configure script byproduct. It was mistakenly checked into the tree in !13118. This patch removes it, and include it in .gitignore to prevent a similar error in the future. - - - - - 1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00 docs: Fix code-block syntax on old sphinx version This code-block directive breaks the deb9 sphinx build. Fixes #25201 - - - - - 27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00 JS: add basic support for POSIX *at functions (#25190) openat/fstatat/unlinkat/dup are now used in the recent release of the `directory` and `file-io` packages. As such, these functions are (indirectly) used in the following tests one we'll bump the `directory` submodule (see !13122): - openFile008 - jsOptimizer - T20509 - bkpcabal02 - bkpcabal03 - bkpcabal04 - - - - - c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00 Update directory submodule to latest master The primary reason for this bump is to fix the warning from `ghc-pkg check`: ``` Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory ``` This also requires adding the `file-io` package as a boot library (which is discussed in #25145) Fixes #23594 #25145 - - - - - 4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Fix aarch64-alpine target platform description We are producing bindists where the target triple is aarch64-alpine-linux when it should be aarch64-unknown-linux This is because the bootstrapped compiler originally set the target triple to `aarch64-alpine-linux` which is when propagated forwards by setting `bootstrap_target` from the bootstrap compiler target. In order to break this chain we explicitly specify build/host/target for aarch64-alpine. This requires a new configure flag `--enable-ignore-` which just switches off a validation check that the target platform of the bootstrap compiler is the same as the build platform. It is the same, but the name is just wrong. These commits can be removed when the bootstrap compiler has the correct target triple (I looked into patching this on ci-images, but it looked hard to do correctly as the build/host platform is not in the settings file). Fixes #25200 - - - - - e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00 Bump nixpkgs commit for gen_ci script - - - - - 63a27091 by doyougnu at 2024-08-26T20:39:30-04:00 rts: win32: emit additional debugging information -- migration from haskell.nix - - - - - aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00 Only export defaults when NamedDefaults are enabled (#25206) This is a reinterpretation of GHC Proposal #409 that avoids a breaking change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal" Consider a module M that has no explicit export list: module M where default (Rational) Should it export the default (Rational)? The proposal says "yes", and there's a test case for that: default/DefaultImport04.hs However, as it turns out, this change in behavior breaks existing programs, e.g. the colour-2.3.6 package can no longer be compiled, as reported in #25206. In this patch, we make implicit exports of defaults conditional on the NamedDefaults extension. This fix is unintrusive and compliant with the existing proposal text (i.e. it does not require a proposal amendment). Should the proposal be amended, we can go for a simpler solution, such as requiring all defaults to be exported explicitly. Test case: testsuite/tests/default/T25206.hs - - - - - 3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00 simplifier: Fix space leak during demand analysis The lazy structure (a list) in a strict field in `DmdType` is not fully forced which leads to a very large thunk build-up. It seems there is likely still more work to be done here as it seems we may be trading space usage for work done. For now, this is the right choice as rather than using all the memory on my computer, compilation just takes a little bit longer. See #25196 - - - - - c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00 Add missing parenthesizeHsType in cvtp's InvisP case We need to ensure that when we convert an `InvisP` (invisible type pattern) to a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as `@(a :: k)` will parse correctly when roundtripped back through the parser. Fixes #25209. - - - - - 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. - - - - - 768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00 Add functions to check for weakly pinned arrays. This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops. These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved by the user via compaction but won't be moved by the RTS. This moves us one more stop closer to nailing down #22255. - - - - - b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00 ghc-toolchain: Don't leave stranded a.outs when testing for -g0 This happened because, when ghc-toolchain tests for -g0, it does so by compiling an empty program. This compilation creates an a.out. Since we create a temporary directory, lets place the test program compilation in it also, so that it gets cleaned up. Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74 Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203 - - - - - 83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00 Build foreign objects for TH with interpreter's way when loading from iface Fixes #25211 When linking bytecode for TH from interface core bindings with `-fprefer-byte-code`, foreign sources are loaded from the interface as well and compiled to object code in an ad-hoc manner. The results are then loaded by the interpreter, whose way may differ from the current build's target way. This patch ensures that foreign objects are compiled with the interpreter's way. - - - - - 0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00 rts: fix checkClosure error message This patch fixes an error message in checkClosure() when the closure has already been evacuated. The previous logic was meant to print the evacuated closure's type in the error message, but it was completely wrong, given info was not really an info table, but a tagged pointer that points to the closure's new address. - - - - - fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00 MO_AcquireFence: Less restrictive barrier GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)` to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which also implies stores.) - - - - - a45f1488 by Fendor at 2024-09-04T20:22:00-04:00 testsuite: Add support to capture performance metrics via 'perf' Performance metrics collected via 'perf' can be more accurate for run-time performance than GHC's rts, due to the usage of hardware counters. We allow performance tests to also record PMU events according to 'perf list'. - - - - - ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00 gitlab-ci: Add nightly job for running the testsuite with perf profiling support - - - - - 6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00 Enable perf profiling for compiler performance tests - - - - - da306610 by sheaf at 2024-09-04T20:22:41-04:00 RecordCon lookup: don't allow a TyCon This commit adds extra logic when looking up a record constructor. If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to the logic explained in Note [Pattern to type (P2T) conversion]), we emit an error saying that the data constructor is not in scope. This avoids the compiler falling over shortly thereafter, in the call to 'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc', because the record constructor would not have been a ConLike. Fixes #25056 - - - - - 9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00 Use deterministic names for temporary files When there are multiple threads they can race to create a temporary file, in some situations the thread will create ghc_1.c and in some it will create ghc_2.c. This filename ends up in the debug info for object files after compiling a C file, therefore contributes to object nondeterminism. In order to fix this we store a prefix in `TmpFs` which serves to namespace temporary files. The prefix is populated from the counter in TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked outside the thread which consumes it, in a deterministic order, so each thread always receives a TmpFs with the same prefix. This assumes that after the initial TmpFs is created, all other TmpFs are created from forking the original TmpFs. Which should have been try anyway as otherwise there would be file collisions and non-determinism. Fixes #25224 - - - - - 59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 Silence x-partial in Haddock.Backends.Xhtml This is an unfortunate consequence of two mechanisms: * GHC provides (possibly-empty) lists of names * The functions that retrieve those names are not equipped to do error reporting, and thus accept these lists at face value. They will have to be attached an effect for error reporting in a later refactoring - - - - - 8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00 hadrian: Support loading haddock in ghci There is one tricky aspect with wired-in packages where the boot package is built with `-this-unit-id ghc` but the dependency is reported as `-package-id ghc-9.6...`. This has never been fixed in GHC as the situation of loading wired-in packages into the multi-repl seems like quite a niche feature that is always just easier to workaround. - - - - - 6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00 hadrian/multi: Load all targets when ./hadrian/ghci-multi is called This seems to make a bit more sense than just loading `ghc` component (and dependencies). - - - - - 7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00 ci: Beef up determinism interface test There have recently been some determinism issues with the simplifier and documentation. We enable more things to test in the ABI test to check that we produce interface files deterministically. - - - - - 5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00 Transform some StgRhsClosure into StgRhsCon after unarisation (#25166) Before unarisation we may have code like: Test.foo :: Test.D [GblId, Unf=OtherCon []] = \u [] case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] { __DEFAULT -> Test.D [GHC.Types.True sat_sAw]; }; After unarisation we get: Test.foo :: Test.D [GblId, Unf=OtherCon []] = {} \u [] Test.D [GHC.Types.True 2#]; Notice that it's still an Updatable closure for no reason anymore. This patch transforms appropriate StgRhsClosures into StgRhsCons after unarisation, allowing these closures to be statically allocated. Now we get the expected: Test.foo :: Test.D [GblId, Unf=OtherCon []] = Test.D! [GHC.Types.True 2#]; Fix #25166 To avoid duplicating code, this patch refactors the mk(Top)StgRhs functions and put them in a GHC.Stg.Make module alongside the new mk(Top)StgRhsCon_maybe functions. - - - - - 958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00 haddock: Add missing requirements.txt for the online manual - - - - - 573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00 AArch64: Implement takeRegRegMoveInstr This has likely been forgotten. - - - - - 20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00 haddock: Configuration fix for ReadTheDocs - - - - - 03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00 JS: fake support for native adjustors (#25159) The JS backend doesn't support adjustors (I believe) and in any case if it ever supports them it will be a native support, not one via libffi. - - - - - 5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00 JS: remove redundant h$lstat It was introduced a second time by mistake in 27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190) - - - - - ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Refactor only newSysLocalDs * Change newSysLocalDs to take a scaled type * Add newSysLocalMDs that takes a type and makes a ManyTy local Lots of files touched, nothing deep. - - - - - 7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Don't introduce 'nospec' on the LHS of a RULE This patch address #25160. The main payload is: * When desugaring the LHS of a RULE, do not introduce the `nospec` call for non-canonical evidence. See GHC.Core.InstEnv Note [Coherence and specialisation: overview] The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it on the LHS of a RULE (that's what caused #25160). So now `dsHsWrapper` takes a flag to say if it's on the LHS of a RULE. See wrinkle (NC1) in `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds. But I think this flag will go away again when I have finished with my (entirely separate) speciaise-on-values patch (#24359). All this meant I had to re-understand the `nospec` stuff and coherence, and that in turn made me do some refactoring, and add a lot of new documentation The big change is that in GHC.Core.InstEnv, I changed the /type synonym/ `Canonical` into a /data type/ `CanonicalEvidence` and documented it a lot better. That in turn made me realise that CalLStacks were being treated with a bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`. - - - - - 663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00 Add defaulting of equalities This MR adds one new defaulting strategy to the top-level defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver. This resolves #25029 and #25125, which showed that users were accidentally relying on a GHC bug, which was fixed by commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4 Author: Simon Peyton Jones <simon.peytonjones at gmail.com> Date: Wed Jun 12 17:44:59 2024 +0100 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. This fix gave rise to a number of user complaints; but the improved defaulting story of this MR largely resolves them. On the way I did a bit of refactoring, of course * Completely restructure the extremely messy top-level defaulting code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much, much, much esaier to grok. - - - - - e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00 Don't name a binding pattern It's a keyword when PatternSynonyms are set. - - - - - b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00 Do not use an error thunk for an absent dictionary In worker/wrapper we were using an error thunk for an absent dictionary, but that works very badly for -XDictsStrict, or even (as #24934 showed) in some complicated cases involving strictness analysis and unfoldings. This MR just uses RubbishLit for dictionaries. Simple. No test case, sadly because our only repro case is rather complicated. - - - - - 8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00 haddock: Remove support for applehelp format in the Manual - - - - - 9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00 RTS linker: add support for hidden symbols (#25191) Add linker support for hidden symbols. We basically treat them as weak symbols. Patch upstreamed from haskell.nix Co-authored-by: Sylvain Henry <sylvain at haskus.fr> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00 Fix C warnings (#25237) GCC 14 treats the fixed warnings as errors by default. I.e. we're gaining GCC 14 compatibility with these fixes. - - - - - 05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00 JS: fix codegen of static string data Before this patch, when string literals are made trivial, we would generate `h$("foo")` instead of `h$str("foo")`. This was introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091. - - - - - 949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Re-organise cross-OS compatibility layer - - - - - 84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Remove CPP for obsolete GHC and Cabal versions - - - - - 370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00 haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file - - - - - cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00 Add ZonkAny and document it This MR fixed #24817 by adding ZonkAny, which takes a Nat argument. See Note [Any types] in GHC.Builtin.Types, especially wrinkle (Any4). - - - - - 0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00 hadrian: Make sure ffi headers are built before using a compiler When we are using ffi adjustors then we rely on `ffi.h` and `ffitarget.h` files during code generation when compiling stubs. Therefore we need to add this dependency to the build system (which this patch does). Reproducer, configure with `--enable-libffi-adjustors` and then build "_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o". Observe that this fails before this patch and works afterwards. Fixes #24864 Co-authored-by: Sylvain Henry <sylvain at haskus.fr> - - - - - 0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00 base: Deprecate BCO primops exports from GHC.Exts See https://github.com/haskell/core-libraries-committee/issues/212. These reexports will be removed in GHC 9.14. - - - - - cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00 EPA: Remove Anchor = EpaLocation synonym This just causes confusion. - - - - - 8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00 Bump submodule deepseq to 1.5.1.0 - - - - - aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00 User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250) Fixes #25250. - - - - - 1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add Native Code Generator (NCG) This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00 Adjust test timings for slower computers Increase the delays a bit to be able to run these tests on slower computers. The reference was a Lichee Pi 4a RISCV64 machine. - - - - - a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add RTS linker This architecture wasn't supported before. Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Ignore divbyzero test The architecture's behaviour differs from the test's expectations. See comment in code why this is okay. - - - - - abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Enable MulMayOflo_full test It works and thus can be tested. - - - - - 38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: LibffiAdjustor: Ensure code caches are flushed RISCV64 needs a specific code flushing sequence (involving fence.i) when new code is created/loaded. - - - - - 7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add additional linker symbols for builtins We're relying on some GCC/Clang builtins. These need to be visible to the linker (and not be stripped away.) - - - - - 92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Add GHCi support As we got a RTS linker for this architecture now, we can enable GHCi for it. - - - - - a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00 RISCV64: Set codeowners of the NCG - - - - - 8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00 Add test for C calling convention Ensure that parameters and return values are correctly processed. A dedicated test (like this) helps to get the subtleties of calling conventions easily right. The test is failing for WASM32 and marked as fragile to not forget to investigate this (#25249). - - - - - fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00 finder: Add `IsBootInterface` to finder cache keys - - - - - cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00 EPA: Sync ghc-exactprint to GHC - - - - - 1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00 DmdAnal: Fast path for `multDmdType` (#25196) This is in order to counter a regression exposed by SpecConstr. Fixes #25196. - - - - - 80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00 Bump submodule array to 0.5.8.0 - - - - - 49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00 Linker: add support for extra built-in symbols (#25155) See added Note [Extra RTS symbols] and new user guide entry. Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00 GNU/Hurd: Add getExecutablePath support GNU/Hurd exposes it as /proc/self/exe just like on Linux. - - - - - d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00 RTS: expose closure_sizeW_ (#25252) C code using the closure_sizeW macro can't be linked with the RTS linker without this patch. It fails with: ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_ Fix #25252 Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00 HsExpr: Inline `HsWrap` into `WrapExpr` This nice refactoring was suggested by Simon during review: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374 Fixes #25264. - - - - - 7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00 Pmc: Improve Desugaring of overloaded list patterns (#25257) This actually makes things simpler. Fixes #25257. - - - - - e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00 configure: Correctly report when subsections-via-symbols is disabled As noted in #24962, currently subsections-via-symbols is disabled on AArch64/Darwin due to alleged breakage. However, `configure` reports to the user that it is enabled. Fix this. - - - - - 9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00 Modified the default export implementation to match the amended spec - - - - - 35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00 FFI: don't ppr Id/Var symbols with debug info (#25255) Even if `-dpp-debug` is enabled we should still generate valid C code. So we disable debug info printing when rendering with Code style. - - - - - 9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00 Demand: Combine examples into Note (#25107) Just a leftover from !13060. Fixes #25107. - - - - - 21aaa34b by sheaf at 2024-09-21T17:48:36-04:00 Use x86_64-unknown-windows-gnu target for LLVM on Windows - - - - - 992a7624 by sheaf at 2024-09-21T17:48:36-04:00 LLVM: use -relocation-model=pic on Windows This is necessary to avoid the segfaults reported in #22487. Fixes #22487 - - - - - c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00 compiler: Use type abstractions when deriving For deriving newtype and deriving via, in order to bring type variables needed for the coercions into scope, GHC generates type signatures for derived class methods. As a simplification, drop the type signatures and instead use type abstractions to bring method type variables into scope. - - - - - f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00 driver: Ensure we run driverPlugin for staticPlugins (#25217) driverPlugins are only run when the plugin state changes. This meant they were never run for static plugins, as their state never changes. We need to keep track of whether a static plugin has been initialised to ensure we run static driver plugins at least once. This necessitates an additional field in the `StaticPlugin` constructor as this state has to be bundled with the plugin itself, as static plugins have no name/identifier we can use to otherwise reference them - - - - - 620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00 Allow unknown fd device types for setNonBlockingMode. This allows fds with a unknown device type to have blocking mode set. This happens for example for fds from the inotify subsystem. Fixes #25199. - - - - - c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00 Use Hackage version of Cabal 3.14.0.0 for Hadrian. We remove the vendored Cabal submodule. Also update the bootstrap plans Fixes #25086 - - - - - 6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00 ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh ci.sh sets up the toolchain environment, including paths for the cabal directory, the toolchain binaries etc. If we run any commands outside of ci.sh, unless we source ci.sh we will use the wrong values for these environment variables. In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was using an old index state despite `ci.sh setup` updating and setting the correct index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which is where the index was downloaded to, but we were using the default cabal directory outside ci.sh The solution is to source the correct environment `ci.sh` using `. ci.sh setup` - - - - - 9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00 ghc-toolchain: Set -fuse-ld even for ld.bfd This reflects the behaviour of the autoconf scripts. - - - - - d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00 Parser: be more careful when lexing extended literals (#25258) Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3]. A side-effect of this patch is that we now allow negative unsigned extended literals. They trigger an overflow warning later anyway. - - - - - ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00 rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog. To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID, and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new cost centres up to the one we already dumped in DUMPED_CC_ID. Fixes #24148 - - - - - c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00 EPA: Replace AnnsModule am_main with EpTokens Working towards removing `AddEpAnn` - - - - - 2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30 ci: Run abi-test on test-abi label - - - - - ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 testsuite: Add a test for object determinism Extends the abi_test with an object determinism check Also includes a standalone test to be run by developers manually when debugging issues with determinism. - - - - - d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Sampling uniques in the CG To achieve object determinism, the passes processing Cmm and the rest of the code generation pipeline musn't create new uniques which are non-deterministic. This commit changes occurrences of non-deterministic unique sampling within these code generation passes by a deterministic unique sampling strategy by propagating and threading through a deterministic incrementing counter in them. The threading is done implicitly with `UniqDSM` and `UniqDSMT`. Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded through all passes to guarantee uniques in different passes are unique amongst them altogether. Specifically, the same `DUniqSupply` must be threaded through the CG Streaming pipeline, starting with Driver.Main calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and `codeOutput` in sequence. To thread resources through the `Stream` abstraction, we use the `UniqDSMT` transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will thread the `DUniqSupply` through every pass applied to the `Stream`, for every element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in code generation which that carries through the deterministic unique supply. See Note [Deterministic Uniques in the CG] - - - - - 3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Cmm unique renaming pass To achieve object determinism, we need to prevent the non-deterministic uniques from leaking into the object code. We can do this by deterministically renaming the non-external uniques in the Cmm groups that are yielded right after StgToCmm. The key to deterministic renaming is observing that the order of declarations, instructions, and data in the Cmm groups are already deterministic (modulo other determinism bugs), regardless of the uniques. We traverse the Cmm AST in this deterministic order and rename the uniques, incrementally, in the order they are found, thus making them deterministic. This renaming is guarded by -fobject-determinism which is disabled by default for now. This is one of the key passes for object determinism. Read about the overview of object determinism and a more detailed explanation of this pass in: * Note [Object determinism] * Note [Renaming uniques deterministically] Significantly closes the gap to #12935 - - - - - 8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: DCmmGroup vs CmmGroup Part of our strategy in producing deterministic objects, namely, renaming all Cmm uniques in order, depend on the object code produced having a deterministic order (say, A_closure always comes before B_closure). However, the use of LabelMaps in the Cmm representation invalidated this requirement because the LabelMaps elements would already be in a non-deterministic order (due to the original uniques), and the renaming in sequence wouldn't work because of that non-deterministic order. Therefore, we now start off with lists in CmmGroup (which preserve the original order), and convert them into LabelMaps (for performance in the code generator) after the uniques of the list elements have been renamed. See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935. Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Don't print unique in pprFullName This unique was leaking as part of the profiling description in info tables when profiling was enabled, despite not providing information relevant to the profile. - - - - - 340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: UDFM for distinct-constructor-tables In order to produce deterministic objects when compiling with -distinct-constructor-tables, we also have to update the data constructor map to be backed by a deterministic unique map (UDFM) rather than a non-deterministic one (UniqMap). - - - - - 282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: InfoTableMap uniques in generateCgIPEStub Fixes object determinism when using -finfo-table-map Make sure to also deterministically rename the IPE map (as per Note [Renaming uniques deterministically]), and to use a deterministic unique supply when creating new labels for the IPE information to guarantee deterministic objects when IPE information is requested. Note that the Cmm group produced in generateCgIPEStub must /not/ be renamed because renaming uniques is not idempotent, and the references to the previously renamed code in the IPE Cmm group would be renamed twice and become invalid references to non-existent symbols. We do need to det-rename the InfoTableMap that is created in the conversion from Core to Stg. This is not a problem since that map won't refer any already renamed names (since it was created before the renaming). - - - - - 7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30 ci: Allow abi-test to fail. We are not fully deterministic yet, see #12935 for work that remains to be done. - - - - - a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00 Add Given injectivity for built-in type families Ticket #24845 asks (reasonably enough) that if we have [G] a+b ~ 0 then we also know [G] a ~ 0, b ~ 0 and similar injectivity-like facts for other built-in type families. The status quo was that we never generate evidence for injectivity among Givens -- but it is quite reasonnable to do so. All we need is to have /evidence/ for the new constraints This MR implements that goal. I also took the opportunity to * Address #24978: refactoring UnivCo * Fix #25248, which was a consequences of the previous formulation of UnivCo As a result this MR touches a lot of code. The big things are: * Coercion constructor UnivCo now takes a [Coercion] as argument to express the coercions on which the UnivCo depends. A nice consequence is that UnivCoProvenance now has no free variables, simpler in a number of places. * Coercion constructors AxiomInstCo and AxiomRuleCo are combined into AxiomCo. The new AxiomCo, carries a (slightly oddly named) CoAxiomRule, which itself is a sum type of the various forms of built-in axiom. See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom A merit of this is that we can separate the case of open and closed type families, and eliminate the redundant `BranchIndex` in the former case. * Much better representation for data BuiltInSynFamily, which means we no longer need to enumerate built-in axioms as well as built-in tycons. * There is a massive refactor in GHC.Builtin.Types.Literals, which contains all the built-in axioms for type-level operations (arithmetic, append, cons etc). A big change is that instead of redundantly having (a) a hand-written matcher, and (b) a template-based "proves" function, which were hard to keep in sync, the two are derive from one set of human-supplied info. See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends. * Significant changes in GHC.Tc.Solver.Equality to account for the new opportunity for Given/Given equalities. Smaller things * Improve pretty-printing to avoid parens around atomic coercions. * Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`. Looks like a bug, Richard agrees. * coercionLKind and coercionRKind are hot functions. I refactored the implementation (which I had to change anyway) to increase sharing. See Note [coercionKind performance] in GHC.Core.Coercion * I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan names * I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid calling tyConsOfType. I forget exactly why I did this, but it's definitely better now. * I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc - - - - - dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00 Resolve ambiguous method-bound type variables in vanilla defaults and GND When defining an instance of a class with a "vanilla" default, such as in the following example (from #14266): ```hs class A t where f :: forall x m. Monoid x => t m -> m f = <blah> instance A [] ``` We have to reckon with the fact that the type of `x` (bound by the type signature for the `f` method) is ambiguous. If we don't deal with the ambiguity somehow, then when we generate the following code: ```hs instance A [] where f = $dmf @[] -- NB: the type of `x` is still ambiguous ``` Then the generated code will not typecheck. (Issue #25148 is a more recent example of the same problem.) To fix this, we bind the type variables from the method's original type signature using `TypeAbstractions` and instantiate `$dmf` with them using `TypeApplications`: ```hs instance A [] where f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous ``` Note that we only do this for vanilla defaults and not for generic defaults (i.e., defaults using `DefaultSignatures`). For the full details, see `Note [Default methods in instances] (Wrinkle: Ambiguous types from vanilla method type signatures)`. The same problem arose in the code generated by `GeneralizedNewtypeDeriving`, as we also fix it here using the same technique. This time, we can take advantage of the fact that `GeneralizedNewtypeDeriving`-generated code _already_ brings method-bound type variables into scope via `TypeAbstractions` (after !13190), so it is very straightforward to visibly apply the type variables on the right-hand sides of equations. See `Note [GND and ambiguity]`. Fixes #14266. Fixes #25148. - - - - - 0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00 Document primitive string literals and desugaring of string literals Fixes #17474 and #17974 Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00 rts: Fix segfault when using non-moving GC with profiling `nonMovingCollect()` swaps out the `static_flag` value used as a sentinel for `gct->scavenged_static_objects`, but the subsequent call `resetStaticObjectForProfiling()` sees the old value of `static_flag` used as the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()` before calling `nonMovingCollect()` as otherwise it looks for the incorrect sentinel value Fixes #25232 and #23958 Also teach the testsuite driver about nonmoving profiling ways and stop disabling metric collection when nonmoving GC is enabled. - - - - - e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00 Fix interaction between fork and kqueue (#24672) A kqueue file descriptor isn't inherited by a child created with fork. As such we mustn't try to close this file descriptor as we would close a random one, e.g. the one used by timerfd. Fix #24672 - - - - - 6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00 Improve GHC.Tc.Solver.defaultEquality This MR improves GHC.Tc.Solver.defaultEquality to solve #25251. The main change is to use checkTyEqRhs to check the equality, so that we do promotion properly. But within that we needed a small enhancement to LC_Promote. See Note [Defaulting equalites] (DE4) and (DE5) The tricky case is (alas) hard to trigger, so I have not added a regression test. - - - - - 97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00 JS: fix h$withCStringOnHeap helper (#25288) strlen returns the length of the string without the \0 terminating byte, hence CString weren't properly allocated on the heap (ending \0 byte was missing). - - - - - 5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00 base: Propagate `error` CallStack to thrown exception Previously `errorCallWithCallStackException` failed to propagate its `CallStack` argument, which represents the call-chain of the preceding `error` call, to the exception that it returned. Consequently, the call-stack of `error` calls were quite useless. Unfortunately, this is the second time that I have fixed this but it seems the first must have been lost in rebasing. Fixes a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164> Fixes #24807. - - - - - c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00 driver: Fix -working-dir for foreign files -working-dir definitely needs more serious testing, there are some easy ways to test this. * Modify Cabal to call ghc using -working-dir rather than changing directory. * Modify the testsuite to run ghc using `-working-dir` rather than running GHC with cwd = temporary directory. However this will have to wait until after 9.12. Fixes #25150 - - - - - 88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: reuse predError, succError, toEnumError Reuse predError, succError, and toEnumError when deriving Enum instances to avoid generating different error strings per instance. E.g. before this patch for every instance for a type FOO we would generate a string: "pred{FOO}: tried to take `pred' of first tag in enumeration"# - - - - - e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: generate better code (#16364) Generate better code for Enum.toEnum: check both the lower and the upper bounds at once with an unsigned comparison. Initially I've used a type ascription with a call to 'fromIntegral', hence the slight refactoring of nlAscribe. Using 'fromIntegral' was problematic (too low in the module hierarchy) so 'enumIntToWord' was introduced instead. Combined with the previous commit, T21839c ghc/alloc decrease by 5% Metric Decrease: T21839c - - - - - 383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00 Core: add absorb rules for binary or/and (#16351) Rules: x or (x and y) ==> x x and (x or y) ==> x - - - - - 783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Don't compile `asBox` with -fprof-late The `asBox` function is intended to store exactly the closure which the user passes to it. Placing a cost centre on asBox introduces a thunk, which violates this expectation and can change the result of using asBox when profiling is enabled. See #25212 for more details and ample opportunity to discuss if this is a bug or not. - - - - - 0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Fix normalisation of .prof files Fix 1: If a cost centre contained CAF then the normalisation was corrupted, now only check if CAF is at the start of a line. Fix 2: "no location info" contain a space, which messed up the next normalisation logic which assumed that columns didn't have spaced in. - - - - - 9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00 testsuite: Fix normalisation of prof_files removing newlines These normalisation steps were collapsing lines together, which made subsequent normalisation steps fail. ``` foo x y z CAF x y z qux x y z ``` was getting normalised to ``` foo x y z qux x y z ``` which means that subsequent line based filters would not work correctly. - - - - - 2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00 packaging: Enable late-ccs for release flavour This enables late cost centres when building profiled libraries and subsequently greatly improves the resolution of cost centre stacks when profiling. This patch also introduces the `grep_prof` test modifier which is used to apply a further filter to the .prof file before they are compared. Fixes #21732 ------------------------- Metric Increase: libdir ------------------------- - - - - - bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00 Replace manual string lexing (#25158) Metric Increase: MultilineStringsPerf This commit replaces the manual string lexing logic with native Alex lexing syntax. This aligns the lexer much closer to the Haskell Report, making it easier to see how the implementation and spec relate. This slightly increases memory usage when compiling multiline strings because we now have two distinct phases: lexing the multiline string with Alex and post-processing the string afterwards. Before, these were done at the same time, but separating them allows us to push as much logic into normal Alex lexing as possible. Since multiline strings are a new feature, this regression shouldn't be too noticeable. We can optimize this over time. - - - - - 16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import This behaviour is problematic for the principle reason that `import Prelude` may not refer to the `base` package, and in which case importing an entirely unrelated module causing your implicit prelude to leave the scope is extremely surprising. See the added test for this example. Discussion on #17045. The secondary reason for reverting this patch is that "base" can't be a wired in package any more (see #24903), so we have to remove special logic which singles out base from the compiler. The rule for implicit shadowing is now simply: * If you write import Prelude (..) then you don't get an implicit prelude import * If you write import "foobar" Prelude (..) for all pkgs foobar, you get an implicit import of prelude. If you want to write a package import of Prelude, then you can enable `NoImplicitPrelude` for the module in question to recover the behaviour of ghc-9.2-9.10. Fixes #17045 - - - - - 57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE The COMPILING_BASE_PACKAGE macro is concerned with issues defining symbols and using symbols in the same compilation unit. However, these symbols now exist in ghc-internal rather than base, so we should rename the macro accordingly. The code is guards is likely never used as we never produce windows DLLs but it is simpler to just perform the renaming for now. These days there is little doubt that this macro defined in this ad-hoc manner would be permitted to exist, but these days are not those days. Fixes #25221 - - - - - 70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Preload ghc-internal rather than base This occurence of baseUnitId was missed when moving the bulk of internal definitions into `ghc-internal`. We need to remove this preloading of `base` now because `base` should not be wired in. Towards #24903 - - - - - 12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Remove Data.List compat warning There is currently a warning implemented in -Wcompat which warns you when importing Data.List in a non-qualified manner. ``` A.hs:3:8: warning: [-Wcompat-unqualified-imports] To ensure compatibility with future core libraries changes imports to Data.List should be either qualified or have an explicit import list. | 3 | import Data.List | ^^^^^^^^^ Ok, one module loaded. ``` GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244 CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E This warning was implemented as part of the migration to making Data.List monomorphic again (and to be used like Data.Set, Data.Map etc). That doesn't seem like it happened, and I imagine that the current CLC would require a new proposal anyway in order to do that now. It's not clear in any case what "future core libraries changes" we are waiting to happen before this warning can be removed. Given the first phase of the proposal has lasted 5 years it doesn't seem that anyone is motivated to carry the proposal to completion. It does seem a bit unnecessary to include a warning in the compiler about "future changes to the module" when there's no timeline or volunteer to implement these changes. The removal of this warning was discussed again at: https://github.com/haskell/core-libraries-committee/issues/269 During the discussion there was no new enthusiasm to move onto the next stages of the proposal so we are removing the warning to unblock the reinstallable "base" project (#24903) Fixes #24904 - - - - - d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Move Control.Monad.Zip into ghc-internal mzip is wired in and therefore needs to be in ghc-internal. Fixes #25222 Towards #24903 - - - - - d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00 Unwire the base package This patch just removes all the functions related to wiring-in the base package and the `-this-unit-id=base` flag from the cabal file. After this commit "base" becomes just like any other package and the door is opened to moving base into an external repo and releasing base on a separate schedule to the rest of ghc. Closes #24903 - - - - - 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 43247314 by Cheng Shao at 2024-10-03T14:26:02+01:00 driver: bail out when -fllvm is passed to GHC not configured with LLVM This patch makes GHC bail out with an proper error message when it's not configured with LLVM but users attempt to pass -fllvm, see #25011 and added comment for details. Fixes #25011 Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 24 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/flake.lock - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - CODEOWNERS - − a.out - compiler/CodeGen.Platform.h - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Graph.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4628f7d20e0e4cbe010d891d95f17596815c4334...43247314ceb00d6010417824accea056340ea522 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4628f7d20e0e4cbe010d891d95f17596815c4334...43247314ceb00d6010417824accea056340ea522 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:54:47 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 03 Oct 2024 09:54:47 -0400 Subject: [Git][ghc/ghc][wip/T25281] More record selector elimination Message-ID: <66fea22731b82_1a6c8b9a48a411312b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 487faf51 by Simon Peyton Jones at 2024-10-03T14:54:11+01:00 More record selector elimination - - - - - 5 changed files: - compiler/GHC/Hs/Decls.hs - compiler/Language/Haskell/Syntax/Decls.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -131,6 +131,7 @@ import GHC.Unit.Module.Warnings import GHC.Data.Maybe import Data.Data (Data) +import Data.List (concatMap) import Data.Foldable (toList) {- @@ -222,6 +223,21 @@ hsGroupTopLevelFixitySigs (HsGroup{ hs_fixds = fixds, hs_tyclds = tyclds }) = , L loc (FixSig _ sig) <- sigs ] +hsGroupInstDecls :: HsGroup (GhcPass p) -> [LInstDecl (GhcPass p)] +hsGroupInstDecls = (=<<) group_instds . hs_tyclds + +tyClGroupTyClDecls :: [TyClGroup (GhcPass p)] -> [LTyClDecl (GhcPass p)] +tyClGroupTyClDecls = Data.List.concatMap group_tyclds + +tyClGroupInstDecls :: [TyClGroup (GhcPass p)] -> [LInstDecl (GhcPass p)] +tyClGroupInstDecls = Data.List.concatMap group_instds + +tyClGroupRoleDecls :: [TyClGroup (GhcPass p)] -> [LRoleAnnotDecl (GhcPass p)] +tyClGroupRoleDecls = Data.List.concatMap group_roles + +tyClGroupKindSigs :: [TyClGroup (GhcPass p)] -> [LStandaloneKindSig (GhcPass p)] +tyClGroupKindSigs = Data.List.concatMap group_kisigs + appendGroups :: HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p) appendGroups @@ -393,6 +409,10 @@ tyClDeclLName (SynDecl { tcdLName = ln }) = ln tyClDeclLName (DataDecl { tcdLName = ln }) = ln tyClDeclLName (ClassDecl { tcdLName = ln }) = ln +tyClDeclTyVars :: TyClDecl (GhcPass p) -> LHsQTyVars (GhcPass p) +tyClDeclTyVars (FamDecl { tcdFam = FamilyDecl { fdTyVars = tvs } }) = tvs +tyClDeclTyVars d = tcdTyVars d + countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int) -- class, synonym decls, data, newtype, family decls countTyClDecls decls ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -36,12 +36,9 @@ module Language.Haskell.Syntax.Decls ( -- ** Class or type declarations TyClDecl(..), LTyClDecl, TyClGroup(..), - tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls, - tyClGroupKindSigs, isClassDecl, isDataDecl, isSynDecl, isFamilyDecl, isTypeFamilyDecl, isDataFamilyDecl, isOpenTypeFamilyInfo, isClosedTypeFamilyInfo, - tyClDeclTyVars, FamilyDecl(..), LFamilyDecl, -- ** Instance declarations @@ -86,7 +83,7 @@ module Language.Haskell.Syntax.Decls ( FamilyResultSig(..), LFamilyResultSig, InjectivityAnn(..), LInjectivityAnn, -- * Grouping - HsGroup(..), hsGroupInstDecls, + HsGroup(..) ) where -- friends: @@ -115,12 +112,10 @@ import Data.Data hiding (TyCon, Fixity, Infix) import Data.Void import Data.Maybe import Data.String -import Data.Function import Data.Eq import Data.Int import Data.Bool import Prelude (Show) -import qualified Data.List import Data.Foldable import Data.Traversable import Data.List.NonEmpty (NonEmpty (..)) @@ -240,9 +235,6 @@ data HsGroup p | XHsGroup !(XXHsGroup p) -hsGroupInstDecls :: HsGroup id -> [LInstDecl id] -hsGroupInstDecls = (=<<) group_instds . hs_tyclds - -- | Located Splice Declaration type LSpliceDecl pass = XRec pass (SpliceDecl pass) @@ -567,11 +559,6 @@ isDataFamilyDecl _other = False -- Dealing with names -tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass -tyClDeclTyVars (FamDecl { tcdFam = FamilyDecl { fdTyVars = tvs } }) = tvs -tyClDeclTyVars d = tcdTyVars d - - {- Note [CUSKs: complete user-supplied kind signatures] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We kind-check declarations differently if they have a complete, user-supplied @@ -702,19 +689,6 @@ data TyClGroup pass -- See Note [TyClGroups and dependency analysis] | XTyClGroup !(XXTyClGroup pass) -tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass] -tyClGroupTyClDecls = Data.List.concatMap group_tyclds - -tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass] -tyClGroupInstDecls = Data.List.concatMap group_instds - -tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass] -tyClGroupRoleDecls = Data.List.concatMap group_roles - -tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass] -tyClGroupKindSigs = Data.List.concatMap group_kisigs - - {- ********************************************************************* * * Data and type family declarations ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs ===================================== @@ -215,7 +215,7 @@ ppClass sDocContext decl@(ClassDecl{}) subdocs = ppSig' = flip (ppSigWithDoc sDocContext) subdocs - add_ctxt = addClassContext (tcdName decl) (tyClDeclTyVars decl) + add_ctxt = addClassContext (tcdName decl) (tyClDeclTyVarsI decl) ppTyFams :: String ppTyFams @@ -331,7 +331,7 @@ ppCtor sDocContext dat subdocs con at ConDeclH98{con_args = con_args'} = apps $ map reL $ (HsTyVar noAnn NotPromoted (reL (tcdName dat))) - : map (tyVarArg . unLoc) (hsQTvExplicit $ tyClDeclTyVars dat) + : map (tyVarArg . unLoc) (hsQTvExplicit $ tyClDeclTyVarsI dat) ppCtor sDocContext _dat ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -248,6 +248,10 @@ tyClDeclLNameI (SynDecl{tcdLName = ln}) = ln tyClDeclLNameI (DataDecl{tcdLName = ln}) = ln tyClDeclLNameI (ClassDecl{tcdLName = ln}) = ln +tyClDeclTyVarsI :: TyClDecl DocNameI -> LHsQTyVars DocNameI +tyClDeclTyVarsI (FamDecl { tcdFam = FamilyDecl { fdTyVars = tvs } }) = tvs +tyClDeclTyVarsI d = tcdTyVars d + tcdNameI :: TyClDecl DocNameI -> DocName tcdNameI = unLoc . tyClDeclLNameI ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -847,7 +847,7 @@ extractDecl prr dflags sDocContext name decl -- TODO: document fixity case (matchesMethod, matchesAssociatedType) of ([s0], _) -> - let tyvar_names = tyClDeclTyVars d + let tyvar_names = tyClDeclTyVarsI d L pos sig = addClassContext clsNm tyvar_names s0 in pure (Right $ L pos (SigD noExtField sig)) (_, [L pos fam_decl]) -> pure (Right $ L pos (TyClD noExtField (FamDecl noExtField fam_decl))) @@ -881,7 +881,7 @@ extractDecl prr dflags sDocContext name decl { tcdLName = L _ dataNm , tcdDataDefn = HsDataDefn{dd_cons = dataCons} } -> pure $ do - let ty_args = lHsQTyVarsToTypes (tyClDeclTyVars d) + let ty_args = lHsQTyVarsToTypes (tyClDeclTyVarsI d) lsig <- if isDataConName name then extractPatternSyn name dataNm ty_args (toList dataCons) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/487faf515075969df88cde8c27354f3b305533ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/487faf515075969df88cde8c27354f3b305533ac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:55:31 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 03 Oct 2024 09:55:31 -0400 Subject: [Git][ghc/ghc][wip/T25266] Wibbles to short cuts Message-ID: <66fea253d514e_1a6c8b983f3c113773@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC Commits: 5f60c70e by Simon Peyton Jones at 2024-10-03T14:55:09+01:00 Wibbles to short cuts - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Solve.hs Changes: ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -73,9 +73,6 @@ simplifyWantedsTcM wanted solveWanteds :: WantedConstraints -> TcS WantedConstraints solveWanteds wc@(WC { wc_errors = errs }) - | isEmptyWC wc -- Fast path - = return wc - | otherwise = do { cur_lvl <- TcS.getTcLevel ; traceTcS "solveWanteds {" $ vcat [ text "Level =" <+> ppr cur_lvl @@ -106,6 +103,9 @@ simplify_loop :: Int -> IntWithInf -> Bool -- else, so we do them once, at the end in solveWanteds simplify_loop n limit definitely_redo_implications wc@(WC { wc_simple = simples, wc_impl = implics }) + | isSolvedWC wc -- Fast path + = return wc + | otherwise = do { csTraceTcS $ text "simplify_loop iteration=" <> int n <+> (parens $ hsep [ text "definitely_redo =" <+> ppr definitely_redo_implications <> comma @@ -145,7 +145,7 @@ maybe_simplify_again n limit unif_happened wc@(WC { wc_simple = simples }) | unif_happened = simplify_loop n limit True wc - | superClassesMightHelp wc + | superClassesMightHelp wc -- Returns False quickly if wc is solved = -- We still have unsolved goals, and apparently no way to solve them, -- so try expanding superclasses at this level, both Given and Wanted do { pending_given <- getPendingGivenScs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f60c70edc5d7286f4f6730a019ba02d4e14d9f7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f60c70edc5d7286f4f6730a019ba02d4e14d9f7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 13:59:48 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Thu, 03 Oct 2024 09:59:48 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] Refactor FieldOcc and AmbiguousFieldOcc with TTG Message-ID: <66fea3544b838_1a6c8b97d560114120@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: f3a0573a by Hassan Al-Awwadi at 2024-10-03T15:46:10+02:00 Refactor FieldOcc and AmbiguousFieldOcc with TTG The main purpose of this commit is to rip RdrName out of FieldOcc, and to make the cases where the FieldOcc can be ambgiuous more precise. To do the first, we make FieldOccs store (LIdP p) instead of always storing Located RdrName, and moved the readername to the extension points where necessary. For the second we've renamed AmbiguousFieldOcc to UpdFieldOcc, but now instead of having Ambiguous be a constantly present constructor, it has been moved to the extension constructor XUpdFieldOcc, only present during the Renaming stage. See Note [Lifecycle of a UpdFieldOcc] for more details. co-authored by: Jade <Jade512 at proton.me> Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Pat.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3a0573ae2c6d427b0f96ff8bbd29f29bf1efa07 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3a0573ae2c6d427b0f96ff8bbd29f29bf1efa07 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 14:14:08 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Thu, 03 Oct 2024 10:14:08 -0400 Subject: [Git][ghc/ghc][wip/andreask/hadrian_progress] Adjust progress message for hadrian to include cwd. Message-ID: <66fea6b0579de_1a6c8bd38880117489@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/hadrian_progress at Glasgow Haskell Compiler / GHC Commits: 88c520c2 by Andreas Klebinger at 2024-10-03T15:54:59+02:00 Adjust progress message for hadrian to include cwd. Fixes #25335 - - - - - 3 changed files: - hadrian/hadrian.cabal - hadrian/src/Main.hs - + hadrian/src/Progress.hs Changes: ===================================== hadrian/hadrian.cabal ===================================== @@ -74,6 +74,7 @@ executable hadrian , Oracles.ModuleFiles , Oracles.TestSettings , Packages + , Progress , Rules , Rules.BinaryDist , Rules.CabalReinstall ===================================== hadrian/src/Main.hs ===================================== @@ -27,6 +27,7 @@ import qualified Rules.Selftest import qualified Rules.SourceDist import qualified Rules.Test import qualified UserSettings +import qualified Progress main :: IO () main = do @@ -56,7 +57,7 @@ main = do options = shakeOptions { shakeChange = ChangeModtimeAndDigest , shakeFiles = buildRoot -/- Base.shakeFilesDir - , shakeProgress = progressSimple + , shakeProgress = Progress.hadrianProgress cwd , shakeRebuild = rebuild , shakeTimings = False , shakeColor = shakeColor ===================================== hadrian/src/Progress.hs ===================================== @@ -0,0 +1,12 @@ +module Progress (hadrianProgress) where + +import Development.Shake + +-- | A simple method for displaying progress messages, suitable for using as 'Development.Shake.shakeProgress'. +-- This is the shakeProgress function hadrian uses. It writes the current progress to the titlebar every five seconds +-- using 'progressTitlebar', and calls any @shake-progress@ program on the @$PATH@ using 'progressProgram'. +hadrianProgress :: String -> IO Progress -> IO () +hadrianProgress cwd p = do + program <- progressProgram + progressDisplay 5 (\status -> let s = status<> "(" <> cwd <> ")" in progressTitlebar s >> program s) p + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88c520c2a2f0cf5450e02b1f21f8dc1776e5d063 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/88c520c2a2f0cf5450e02b1f21f8dc1776e5d063 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 15:30:29 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 03 Oct 2024 11:30:29 -0400 Subject: [Git][ghc/ghc][wip/backports-9.8] 2 commits: testsuite: Give the pre_cmd for mhu-perf more time Message-ID: <66feb895d6ae6_fead319c7382854a@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC Commits: 930eb181 by Matthew Craven at 2024-10-03T11:30:15-04:00 testsuite: Give the pre_cmd for mhu-perf more time (cherry picked from commit dba03aababff057c03e2d92677de02d8375cd23a) - - - - - 0c24f3e2 by Cheng Shao at 2024-10-03T11:30:15-04:00 testsuite: give pre_cmd for mhu-perf 5x time (cherry picked from commit 0820750140af2972ca254a42c0fdc537f3b7c447) - - - - - 3 changed files: - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/tests/driver/multipleHomeUnits/mhu-perf/all.T Changes: ===================================== testsuite/driver/testglobals.py ===================================== @@ -452,6 +452,7 @@ class TestOptions: self.combined_output = False # How should the timeout be adjusted on this test? + self.pre_cmd_timeout_multiplier = 1.0 self.compile_timeout_multiplier = 1.0 self.run_timeout_multiplier = 1.0 ===================================== testsuite/driver/testlib.py ===================================== @@ -549,6 +549,12 @@ def signal_exit_code( val: int ): # ----- +def pre_cmd_timeout_multiplier( val: float ): + return lambda name, opts, v=val: _pre_cmd_timeout_multiplier(name, opts, v) + +def _pre_cmd_timeout_multiplier( name, opts, v ): + opts.pre_cmd_timeout_multiplier = v + def compile_timeout_multiplier( val: float ): return lambda name, opts, v=val: _compile_timeout_multiplier(name, opts, v) @@ -1367,7 +1373,9 @@ async def do_test(name: TestName, exit_code = await runCmd('cd "{0}" && {1}'.format(opts.testdir, override_options(opts.pre_cmd)), stdout = stdout_path, stderr = stderr_path, - print_output = config.verbose >= 3) + print_output = config.verbose >= 3, + timeout_multiplier = opts.pre_cmd_timeout_multiplier, + ) # If user used expect_broken then don't record failures of pre_cmd if exit_code != 0 and opts.expect not in ['fail']: ===================================== testsuite/tests/driver/multipleHomeUnits/mhu-perf/all.T ===================================== @@ -4,7 +4,8 @@ test('mhu-perf', pre_cmd('$MAKE -s --no-print-directory mhu-perf'), js_broken(22349), when(arch('wasm32'), skip), # wasm32 doesn't like running Setup/Makefile tests - compile_timeout_multiplier(5) + pre_cmd_timeout_multiplier(5), + compile_timeout_multiplier(5), ], multiunit_compile, [['unitTop1', 'unitTop2'], '-fhide-source-paths']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6a95d279e39cf2082aeff1ce91262a361d823fb...0c24f3e2de17d486f8ab25b737190d8db3465dfd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6a95d279e39cf2082aeff1ce91262a361d823fb...0c24f3e2de17d486f8ab25b737190d8db3465dfd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 17:05:44 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 03 Oct 2024 13:05:44 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/targetSupportsRPaths Message-ID: <66fecee8c6965_fead37c077c616ad@gitlab.mail> Cheng Shao pushed new branch wip/targetSupportsRPaths at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/targetSupportsRPaths You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 17:23:16 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 03 Oct 2024 13:23:16 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.8-2 Message-ID: <66fed304b1dd7_fead39b6b6c644f@gitlab.mail> Ben Gamari pushed new branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.8-2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 18:23:19 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 03 Oct 2024 14:23:19 -0400 Subject: [Git][ghc/ghc][wip/CLC208] 22 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <66fee116f3092_2e854c1fc2b432966@gitlab.mail> Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 91b0e20b by Ben Gamari at 2024-10-03T13:41:35-04:00 ghc-internal: Drop GHC.Internal.Data.Enum This module consists only of reexports and consequently there is no reason for it to exist. - - - - - 0a282351 by Ben Gamari at 2024-10-03T13:41:35-04:00 base: Introduce Data.Bounded As proposed in [CLC#208] but unfortunately `Data.Enum` was already incorrectly introduced in the `ghc-internal` refactor. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - 6814c541 by Ben Gamari at 2024-10-03T13:41:35-04:00 base: Deprecate export of Bounded from Data.Enum This begins the process of bringing us into compliance with [CLC#208]. [CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208 - - - - - a626a773 by Ben Gamari at 2024-10-03T13:41:35-04:00 base: Mention incorrect Data.Enum addition in changelog - - - - - bf57140f by Ben Gamari at 2024-10-03T14:20:29-04:00 instance order - - - - - 8a4d135c by Ben Gamari at 2024-10-03T14:22:29-04:00 Enum - - - - - 4312b0cd by Ben Gamari at 2024-10-03T14:23:00-04:00 Enum instance ordering - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Platform/Reg/Class.hs - configure.ac - docs/users_guide/using-optimisation.rst - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Data/Enum.hs → libraries/base/src/Data/Bounded.hs - libraries/base/src/Data/Enum.hs - libraries/base/src/GHC/Exts.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - + libraries/ghc-experimental/src/GHC/PrimOps.hs - libraries/ghc-internal/ghc-internal.cabal.in - libraries/ghc-internal/src/GHC/Internal/Exts.hs - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - m4/fp_settings.m4 - m4/fp_setup_windows_toolchain.m4 - m4/fptools_happy.m4 - rts/CheckVectorSupport.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aad3bb7effca83d809753bf61e95e0b26324aa99...4312b0cd44ea988978c8b56169e727fdc7edf191 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aad3bb7effca83d809753bf61e95e0b26324aa99...4312b0cd44ea988978c8b56169e727fdc7edf191 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 18:53:52 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 03 Oct 2024 14:53:52 -0400 Subject: [Git][ghc/ghc][wip/fllvm-error] driver: bail out when -fllvm is passed to GHC not configured with LLVM Message-ID: <66fee840cbbfe_2e854c3d7070335f6@gitlab.mail> Rodrigo Mesquita pushed to branch wip/fllvm-error at Glasgow Haskell Compiler / GHC Commits: 8f95179a by Cheng Shao at 2024-10-03T19:53:33+01:00 driver: bail out when -fllvm is passed to GHC not configured with LLVM This patch makes GHC bail out with an proper error message when it's not configured with LLVM but users attempt to pass -fllvm, see #25011 and added comment for details. Fixes #25011 Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 5 changed files: - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Types/Error/Codes.hs - testsuite/tests/diagnostic-codes/codes.stdout Changes: ===================================== compiler/GHC/Driver/Errors/Ppr.hs ===================================== @@ -35,6 +35,7 @@ import GHC.HsToCore.Errors.Types (DsMessage) import GHC.Iface.Errors.Types import GHC.Tc.Errors.Ppr () -- instance Diagnostic TcRnMessage import GHC.Iface.Errors.Ppr () -- instance Diagnostic IfaceMessage +import GHC.CmmToLlvm.Version (llvmVersionStr, supportedLlvmVersionLowerBound, supportedLlvmVersionUpperBound) -- -- Suggestions @@ -268,6 +269,14 @@ instance Diagnostic DriverMessage where mkSimpleDecorated $ vcat [ text "Unexpected backpack instantiation in dependency graph while constructing Makefile:" , nest 2 $ ppr node ] + DriverNoConfiguredLLVMToolchain -> + mkSimpleDecorated $ + text "GHC was not configured with a supported LLVM toolchain" $$ + text ("Make sure you have installed LLVM between [" + ++ llvmVersionStr supportedLlvmVersionLowerBound + ++ " and " + ++ llvmVersionStr supportedLlvmVersionUpperBound + ++ ") and reinstall GHC to make -fllvm work") diagnosticReason = \case DriverUnknownMessage m @@ -337,6 +346,8 @@ instance Diagnostic DriverMessage where -> ErrorWithoutFlag DriverInstantiationNodeInDependencyGeneration {} -> ErrorWithoutFlag + DriverNoConfiguredLLVMToolchain + -> ErrorWithoutFlag diagnosticHints = \case DriverUnknownMessage m @@ -408,5 +419,7 @@ instance Diagnostic DriverMessage where -> noHints DriverInstantiationNodeInDependencyGeneration {} -> noHints + DriverNoConfiguredLLVMToolchain + -> noHints diagnosticCode = constructorCode ===================================== compiler/GHC/Driver/Errors/Types.hs ===================================== @@ -402,6 +402,14 @@ data DriverMessage where Backpack 'InstantiationNode's. -} DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage + {-| DriverNoConfiguredLLVMToolchain is an error that occurs if there is no + LLVM toolchain configured but -fllvm is passed as an option to the compiler. + + Test cases: None. + + -} + DriverNoConfiguredLLVMToolchain :: DriverMessage + deriving instance Generic DriverMessage data DriverMessageOpts = ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -19,7 +19,6 @@ import GHC.Settings import GHC.SysTools.Process import GHC.Driver.Session - import GHC.Utils.Exception as Exception import GHC.Utils.Error import GHC.Utils.Outputable @@ -28,10 +27,16 @@ import GHC.Utils.Logger import GHC.Utils.TmpFs import GHC.Utils.Panic +import Control.Monad import Data.List (tails, isPrefixOf) import Data.Maybe (fromMaybe) import System.IO import System.Process +import GHC.Driver.Config.Diagnostic +import GHC.Driver.Errors +import GHC.Driver.Errors.Types (GhcMessage(..), DriverMessage (DriverNoConfiguredLLVMToolchain)) +import GHC.Driver.CmdLine (warnsToMessages) +import GHC.Types.SrcLoc (noLoc) {- ************************************************************************ @@ -277,12 +282,26 @@ runEmscripten logger dflags args = traceSystoolCommand logger "emcc" $ do figureLlvmVersion :: Logger -> DynFlags -> IO (Maybe LlvmVersion) figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do let (pgm,opts) = pgm_lc dflags + diag_opts = initDiagOpts dflags args = filter notNull (map showOpt opts) -- we grab the args even though they should be useless just in -- case the user is using a customised 'llc' that requires some -- of the options they've specified. llc doesn't care what other -- options are specified when '-version' is used. args' = args ++ ["-version"] + -- Since !12001, when GHC is not configured with llc/opt with + -- supported version range, configure script will leave llc/opt + -- commands as blank in settings. In this case, we should bail out + -- with a proper error, see #25011. + -- + -- Note that this does not make the -Wunsupported-llvm-version + -- warning logic redundant! Power users might want to use + -- -pgmlc/-pgmlo to override llc/opt locations to test LLVM outside + -- officially supported version range, and the driver will produce + -- the warning and carry on code generation. + when (null pgm) $ + printOrThrowDiagnostics logger (initPrintConfig dflags) diag_opts + (GhcDriverMessage <$> warnsToMessages diag_opts [noLoc DriverNoConfiguredLLVMToolchain]) catchIO (do (pin, pout, perr, p) <- runInteractiveProcess pgm args' Nothing Nothing @@ -360,4 +379,3 @@ runWindres logger dflags args = traceSystoolCommand logger "windres" $ do opts = map Option (getOpts dflags opt_windres) mb_env <- getGccEnv cc_args runSomethingFiltered logger id "Windres" windres (opts ++ args) Nothing mb_env - ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -324,6 +324,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "DriverDeprecatedFlag" = 53692 GhcDiagnosticCode "DriverModuleGraphCycle" = 92213 GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284 + GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain" = 66599 -- Constraint solver diagnostic codes GhcDiagnosticCode "BadTelescope" = 97739 ===================================== testsuite/tests/diagnostic-codes/codes.stdout ===================================== @@ -42,6 +42,7 @@ [GHC-37141] is untested (constructor = DriverCannotLoadInterfaceFile) [GHC-29747] is untested (constructor = DriverMissingSafeHaskellMode) [GHC-74284] is untested (constructor = DriverInstantiationNodeInDependencyGeneration) +[GHC-66599] is untested (constructor = DriverNoConfiguredLLVMToolchain) [GHC-06200] is untested (constructor = BlockedEquality) [GHC-81325] is untested (constructor = ExpectingMoreArguments) [GHC-78125] is untested (constructor = AmbiguityPreventsSolvingCt) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f95179ae3ad12cfca19c3e30993041195082d45 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f95179ae3ad12cfca19c3e30993041195082d45 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 21:37:12 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 03 Oct 2024 17:37:12 -0400 Subject: [Git][ghc/ghc][wip/T25066] 92 commits: RTS: expose closure_sizeW_ (#25252) Message-ID: <66ff0e88e15a4_2e854c94e0e438942@gitlab.mail> Ben Gamari pushed to branch wip/T25066 at Glasgow Haskell Compiler / GHC Commits: d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00 RTS: expose closure_sizeW_ (#25252) C code using the closure_sizeW macro can't be linked with the RTS linker without this patch. It fails with: ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_ Fix #25252 Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com> Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00 HsExpr: Inline `HsWrap` into `WrapExpr` This nice refactoring was suggested by Simon during review: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374 Fixes #25264. - - - - - 7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00 Pmc: Improve Desugaring of overloaded list patterns (#25257) This actually makes things simpler. Fixes #25257. - - - - - e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00 configure: Correctly report when subsections-via-symbols is disabled As noted in #24962, currently subsections-via-symbols is disabled on AArch64/Darwin due to alleged breakage. However, `configure` reports to the user that it is enabled. Fix this. - - - - - 9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00 Modified the default export implementation to match the amended spec - - - - - 35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00 FFI: don't ppr Id/Var symbols with debug info (#25255) Even if `-dpp-debug` is enabled we should still generate valid C code. So we disable debug info printing when rendering with Code style. - - - - - 9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00 Demand: Combine examples into Note (#25107) Just a leftover from !13060. Fixes #25107. - - - - - 21aaa34b by sheaf at 2024-09-21T17:48:36-04:00 Use x86_64-unknown-windows-gnu target for LLVM on Windows - - - - - 992a7624 by sheaf at 2024-09-21T17:48:36-04:00 LLVM: use -relocation-model=pic on Windows This is necessary to avoid the segfaults reported in #22487. Fixes #22487 - - - - - c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00 compiler: Use type abstractions when deriving For deriving newtype and deriving via, in order to bring type variables needed for the coercions into scope, GHC generates type signatures for derived class methods. As a simplification, drop the type signatures and instead use type abstractions to bring method type variables into scope. - - - - - f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00 driver: Ensure we run driverPlugin for staticPlugins (#25217) driverPlugins are only run when the plugin state changes. This meant they were never run for static plugins, as their state never changes. We need to keep track of whether a static plugin has been initialised to ensure we run static driver plugins at least once. This necessitates an additional field in the `StaticPlugin` constructor as this state has to be bundled with the plugin itself, as static plugins have no name/identifier we can use to otherwise reference them - - - - - 620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00 Allow unknown fd device types for setNonBlockingMode. This allows fds with a unknown device type to have blocking mode set. This happens for example for fds from the inotify subsystem. Fixes #25199. - - - - - c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00 Use Hackage version of Cabal 3.14.0.0 for Hadrian. We remove the vendored Cabal submodule. Also update the bootstrap plans Fixes #25086 - - - - - 6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00 ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh ci.sh sets up the toolchain environment, including paths for the cabal directory, the toolchain binaries etc. If we run any commands outside of ci.sh, unless we source ci.sh we will use the wrong values for these environment variables. In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was using an old index state despite `ci.sh setup` updating and setting the correct index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which is where the index was downloaded to, but we were using the default cabal directory outside ci.sh The solution is to source the correct environment `ci.sh` using `. ci.sh setup` - - - - - 9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00 ghc-toolchain: Set -fuse-ld even for ld.bfd This reflects the behaviour of the autoconf scripts. - - - - - d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00 Parser: be more careful when lexing extended literals (#25258) Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3]. A side-effect of this patch is that we now allow negative unsigned extended literals. They trigger an overflow warning later anyway. - - - - - ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00 rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog. To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID, and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new cost centres up to the one we already dumped in DUMPED_CC_ID. Fixes #24148 - - - - - c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00 EPA: Replace AnnsModule am_main with EpTokens Working towards removing `AddEpAnn` - - - - - 2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30 ci: Run abi-test on test-abi label - - - - - ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 testsuite: Add a test for object determinism Extends the abi_test with an object determinism check Also includes a standalone test to be run by developers manually when debugging issues with determinism. - - - - - d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Sampling uniques in the CG To achieve object determinism, the passes processing Cmm and the rest of the code generation pipeline musn't create new uniques which are non-deterministic. This commit changes occurrences of non-deterministic unique sampling within these code generation passes by a deterministic unique sampling strategy by propagating and threading through a deterministic incrementing counter in them. The threading is done implicitly with `UniqDSM` and `UniqDSMT`. Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded through all passes to guarantee uniques in different passes are unique amongst them altogether. Specifically, the same `DUniqSupply` must be threaded through the CG Streaming pipeline, starting with Driver.Main calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and `codeOutput` in sequence. To thread resources through the `Stream` abstraction, we use the `UniqDSMT` transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will thread the `DUniqSupply` through every pass applied to the `Stream`, for every element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in code generation which that carries through the deterministic unique supply. See Note [Deterministic Uniques in the CG] - - - - - 3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Cmm unique renaming pass To achieve object determinism, we need to prevent the non-deterministic uniques from leaking into the object code. We can do this by deterministically renaming the non-external uniques in the Cmm groups that are yielded right after StgToCmm. The key to deterministic renaming is observing that the order of declarations, instructions, and data in the Cmm groups are already deterministic (modulo other determinism bugs), regardless of the uniques. We traverse the Cmm AST in this deterministic order and rename the uniques, incrementally, in the order they are found, thus making them deterministic. This renaming is guarded by -fobject-determinism which is disabled by default for now. This is one of the key passes for object determinism. Read about the overview of object determinism and a more detailed explanation of this pass in: * Note [Object determinism] * Note [Renaming uniques deterministically] Significantly closes the gap to #12935 - - - - - 8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: DCmmGroup vs CmmGroup Part of our strategy in producing deterministic objects, namely, renaming all Cmm uniques in order, depend on the object code produced having a deterministic order (say, A_closure always comes before B_closure). However, the use of LabelMaps in the Cmm representation invalidated this requirement because the LabelMaps elements would already be in a non-deterministic order (due to the original uniques), and the renaming in sequence wouldn't work because of that non-deterministic order. Therefore, we now start off with lists in CmmGroup (which preserve the original order), and convert them into LabelMaps (for performance in the code generator) after the uniques of the list elements have been renamed. See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935. Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: Don't print unique in pprFullName This unique was leaking as part of the profiling description in info tables when profiling was enabled, despite not providing information relevant to the profile. - - - - - 340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: UDFM for distinct-constructor-tables In order to produce deterministic objects when compiling with -distinct-constructor-tables, we also have to update the data constructor map to be backed by a deterministic unique map (UDFM) rather than a non-deterministic one (UniqMap). - - - - - 282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30 determinism: InfoTableMap uniques in generateCgIPEStub Fixes object determinism when using -finfo-table-map Make sure to also deterministically rename the IPE map (as per Note [Renaming uniques deterministically]), and to use a deterministic unique supply when creating new labels for the IPE information to guarantee deterministic objects when IPE information is requested. Note that the Cmm group produced in generateCgIPEStub must /not/ be renamed because renaming uniques is not idempotent, and the references to the previously renamed code in the IPE Cmm group would be renamed twice and become invalid references to non-existent symbols. We do need to det-rename the InfoTableMap that is created in the conversion from Core to Stg. This is not a problem since that map won't refer any already renamed names (since it was created before the renaming). - - - - - 7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30 ci: Allow abi-test to fail. We are not fully deterministic yet, see #12935 for work that remains to be done. - - - - - a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00 Add Given injectivity for built-in type families Ticket #24845 asks (reasonably enough) that if we have [G] a+b ~ 0 then we also know [G] a ~ 0, b ~ 0 and similar injectivity-like facts for other built-in type families. The status quo was that we never generate evidence for injectivity among Givens -- but it is quite reasonnable to do so. All we need is to have /evidence/ for the new constraints This MR implements that goal. I also took the opportunity to * Address #24978: refactoring UnivCo * Fix #25248, which was a consequences of the previous formulation of UnivCo As a result this MR touches a lot of code. The big things are: * Coercion constructor UnivCo now takes a [Coercion] as argument to express the coercions on which the UnivCo depends. A nice consequence is that UnivCoProvenance now has no free variables, simpler in a number of places. * Coercion constructors AxiomInstCo and AxiomRuleCo are combined into AxiomCo. The new AxiomCo, carries a (slightly oddly named) CoAxiomRule, which itself is a sum type of the various forms of built-in axiom. See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom A merit of this is that we can separate the case of open and closed type families, and eliminate the redundant `BranchIndex` in the former case. * Much better representation for data BuiltInSynFamily, which means we no longer need to enumerate built-in axioms as well as built-in tycons. * There is a massive refactor in GHC.Builtin.Types.Literals, which contains all the built-in axioms for type-level operations (arithmetic, append, cons etc). A big change is that instead of redundantly having (a) a hand-written matcher, and (b) a template-based "proves" function, which were hard to keep in sync, the two are derive from one set of human-supplied info. See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends. * Significant changes in GHC.Tc.Solver.Equality to account for the new opportunity for Given/Given equalities. Smaller things * Improve pretty-printing to avoid parens around atomic coercions. * Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`. Looks like a bug, Richard agrees. * coercionLKind and coercionRKind are hot functions. I refactored the implementation (which I had to change anyway) to increase sharing. See Note [coercionKind performance] in GHC.Core.Coercion * I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan names * I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid calling tyConsOfType. I forget exactly why I did this, but it's definitely better now. * I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc - - - - - dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00 Resolve ambiguous method-bound type variables in vanilla defaults and GND When defining an instance of a class with a "vanilla" default, such as in the following example (from #14266): ```hs class A t where f :: forall x m. Monoid x => t m -> m f = <blah> instance A [] ``` We have to reckon with the fact that the type of `x` (bound by the type signature for the `f` method) is ambiguous. If we don't deal with the ambiguity somehow, then when we generate the following code: ```hs instance A [] where f = $dmf @[] -- NB: the type of `x` is still ambiguous ``` Then the generated code will not typecheck. (Issue #25148 is a more recent example of the same problem.) To fix this, we bind the type variables from the method's original type signature using `TypeAbstractions` and instantiate `$dmf` with them using `TypeApplications`: ```hs instance A [] where f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous ``` Note that we only do this for vanilla defaults and not for generic defaults (i.e., defaults using `DefaultSignatures`). For the full details, see `Note [Default methods in instances] (Wrinkle: Ambiguous types from vanilla method type signatures)`. The same problem arose in the code generated by `GeneralizedNewtypeDeriving`, as we also fix it here using the same technique. This time, we can take advantage of the fact that `GeneralizedNewtypeDeriving`-generated code _already_ brings method-bound type variables into scope via `TypeAbstractions` (after !13190), so it is very straightforward to visibly apply the type variables on the right-hand sides of equations. See `Note [GND and ambiguity]`. Fixes #14266. Fixes #25148. - - - - - 0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00 Document primitive string literals and desugaring of string literals Fixes #17474 and #17974 Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00 rts: Fix segfault when using non-moving GC with profiling `nonMovingCollect()` swaps out the `static_flag` value used as a sentinel for `gct->scavenged_static_objects`, but the subsequent call `resetStaticObjectForProfiling()` sees the old value of `static_flag` used as the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()` before calling `nonMovingCollect()` as otherwise it looks for the incorrect sentinel value Fixes #25232 and #23958 Also teach the testsuite driver about nonmoving profiling ways and stop disabling metric collection when nonmoving GC is enabled. - - - - - e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00 Fix interaction between fork and kqueue (#24672) A kqueue file descriptor isn't inherited by a child created with fork. As such we mustn't try to close this file descriptor as we would close a random one, e.g. the one used by timerfd. Fix #24672 - - - - - 6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00 Improve GHC.Tc.Solver.defaultEquality This MR improves GHC.Tc.Solver.defaultEquality to solve #25251. The main change is to use checkTyEqRhs to check the equality, so that we do promotion properly. But within that we needed a small enhancement to LC_Promote. See Note [Defaulting equalites] (DE4) and (DE5) The tricky case is (alas) hard to trigger, so I have not added a regression test. - - - - - 97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00 JS: fix h$withCStringOnHeap helper (#25288) strlen returns the length of the string without the \0 terminating byte, hence CString weren't properly allocated on the heap (ending \0 byte was missing). - - - - - 5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00 base: Propagate `error` CallStack to thrown exception Previously `errorCallWithCallStackException` failed to propagate its `CallStack` argument, which represents the call-chain of the preceding `error` call, to the exception that it returned. Consequently, the call-stack of `error` calls were quite useless. Unfortunately, this is the second time that I have fixed this but it seems the first must have been lost in rebasing. Fixes a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164> Fixes #24807. - - - - - c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00 driver: Fix -working-dir for foreign files -working-dir definitely needs more serious testing, there are some easy ways to test this. * Modify Cabal to call ghc using -working-dir rather than changing directory. * Modify the testsuite to run ghc using `-working-dir` rather than running GHC with cwd = temporary directory. However this will have to wait until after 9.12. Fixes #25150 - - - - - 88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: reuse predError, succError, toEnumError Reuse predError, succError, and toEnumError when deriving Enum instances to avoid generating different error strings per instance. E.g. before this patch for every instance for a type FOO we would generate a string: "pred{FOO}: tried to take `pred' of first tag in enumeration"# - - - - - e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00 Enum deriving: generate better code (#16364) Generate better code for Enum.toEnum: check both the lower and the upper bounds at once with an unsigned comparison. Initially I've used a type ascription with a call to 'fromIntegral', hence the slight refactoring of nlAscribe. Using 'fromIntegral' was problematic (too low in the module hierarchy) so 'enumIntToWord' was introduced instead. Combined with the previous commit, T21839c ghc/alloc decrease by 5% Metric Decrease: T21839c - - - - - 383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00 Core: add absorb rules for binary or/and (#16351) Rules: x or (x and y) ==> x x and (x or y) ==> x - - - - - 783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Don't compile `asBox` with -fprof-late The `asBox` function is intended to store exactly the closure which the user passes to it. Placing a cost centre on asBox introduces a thunk, which violates this expectation and can change the result of using asBox when profiling is enabled. See #25212 for more details and ample opportunity to discuss if this is a bug or not. - - - - - 0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00 Fix normalisation of .prof files Fix 1: If a cost centre contained CAF then the normalisation was corrupted, now only check if CAF is at the start of a line. Fix 2: "no location info" contain a space, which messed up the next normalisation logic which assumed that columns didn't have spaced in. - - - - - 9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00 testsuite: Fix normalisation of prof_files removing newlines These normalisation steps were collapsing lines together, which made subsequent normalisation steps fail. ``` foo x y z CAF x y z qux x y z ``` was getting normalised to ``` foo x y z qux x y z ``` which means that subsequent line based filters would not work correctly. - - - - - 2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00 packaging: Enable late-ccs for release flavour This enables late cost centres when building profiled libraries and subsequently greatly improves the resolution of cost centre stacks when profiling. This patch also introduces the `grep_prof` test modifier which is used to apply a further filter to the .prof file before they are compared. Fixes #21732 ------------------------- Metric Increase: libdir ------------------------- - - - - - bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00 Replace manual string lexing (#25158) Metric Increase: MultilineStringsPerf This commit replaces the manual string lexing logic with native Alex lexing syntax. This aligns the lexer much closer to the Haskell Report, making it easier to see how the implementation and spec relate. This slightly increases memory usage when compiling multiline strings because we now have two distinct phases: lexing the multiline string with Alex and post-processing the string afterwards. Before, these were done at the same time, but separating them allows us to push as much logic into normal Alex lexing as possible. Since multiline strings are a new feature, this regression shouldn't be too noticeable. We can optimize this over time. - - - - - 16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import This behaviour is problematic for the principle reason that `import Prelude` may not refer to the `base` package, and in which case importing an entirely unrelated module causing your implicit prelude to leave the scope is extremely surprising. See the added test for this example. Discussion on #17045. The secondary reason for reverting this patch is that "base" can't be a wired in package any more (see #24903), so we have to remove special logic which singles out base from the compiler. The rule for implicit shadowing is now simply: * If you write import Prelude (..) then you don't get an implicit prelude import * If you write import "foobar" Prelude (..) for all pkgs foobar, you get an implicit import of prelude. If you want to write a package import of Prelude, then you can enable `NoImplicitPrelude` for the module in question to recover the behaviour of ghc-9.2-9.10. Fixes #17045 - - - - - 57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE The COMPILING_BASE_PACKAGE macro is concerned with issues defining symbols and using symbols in the same compilation unit. However, these symbols now exist in ghc-internal rather than base, so we should rename the macro accordingly. The code is guards is likely never used as we never produce windows DLLs but it is simpler to just perform the renaming for now. These days there is little doubt that this macro defined in this ad-hoc manner would be permitted to exist, but these days are not those days. Fixes #25221 - - - - - 70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Preload ghc-internal rather than base This occurence of baseUnitId was missed when moving the bulk of internal definitions into `ghc-internal`. We need to remove this preloading of `base` now because `base` should not be wired in. Towards #24903 - - - - - 12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Remove Data.List compat warning There is currently a warning implemented in -Wcompat which warns you when importing Data.List in a non-qualified manner. ``` A.hs:3:8: warning: [-Wcompat-unqualified-imports] To ensure compatibility with future core libraries changes imports to Data.List should be either qualified or have an explicit import list. | 3 | import Data.List | ^^^^^^^^^ Ok, one module loaded. ``` GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244 CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E This warning was implemented as part of the migration to making Data.List monomorphic again (and to be used like Data.Set, Data.Map etc). That doesn't seem like it happened, and I imagine that the current CLC would require a new proposal anyway in order to do that now. It's not clear in any case what "future core libraries changes" we are waiting to happen before this warning can be removed. Given the first phase of the proposal has lasted 5 years it doesn't seem that anyone is motivated to carry the proposal to completion. It does seem a bit unnecessary to include a warning in the compiler about "future changes to the module" when there's no timeline or volunteer to implement these changes. The removal of this warning was discussed again at: https://github.com/haskell/core-libraries-committee/issues/269 During the discussion there was no new enthusiasm to move onto the next stages of the proposal so we are removing the warning to unblock the reinstallable "base" project (#24903) Fixes #24904 - - - - - d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00 Move Control.Monad.Zip into ghc-internal mzip is wired in and therefore needs to be in ghc-internal. Fixes #25222 Towards #24903 - - - - - d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00 Unwire the base package This patch just removes all the functions related to wiring-in the base package and the `-this-unit-id=base` flag from the cabal file. After this commit "base" becomes just like any other package and the door is opened to moving base into an external repo and releasing base on a separate schedule to the rest of ghc. Closes #24903 - - - - - 1b39363b by Patrick at 2024-09-27T06:10:19-04:00 Add entity information to HieFile #24544 Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details. Work have been done: * Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`. * Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile` to store the mapping from entity name to corresponding entity infos in `GHC.Iface.Ext.Types`. * Compute `EntityInfo` for each entity name in the HieAst from `TyThing, Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`. * Add test T24544 to test the generation of `EntityInfo`. - - - - - 4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00 The X86 SIMD patch. This commit adds support for 128 bit wide SIMD vectors and vector operations to GHC's X86 native code generator. Main changes: - Introduction of vector formats (`GHC.CmmToAsm.Format`) - Introduction of 128-bit virtual register (`GHC.Platform.Reg`), and removal of unused Float virtual register. - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector` (for registers that can be used for scalar floating point values as well as vectors). - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track of which format each register is used at, so that the register allocator can know if it needs to spill the entire vector register or just the lower 64 bits. - Modify spill/load/reg-2-reg code to account for vector registers (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`). - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate the format we are storing in any given register, for instance changing `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`. - Add logic to lower vector `MachOp`s to X86 assembly (see `GHC.CmmToAsm.X86.CodeGen`) - Minor cleanups to genprimopcode, to remove the llvm_only attribute which is no longer applicable. Tests for this feature are provided in the "testsuite/tests/simd" directory. Fixes #7741 Keeping track of register formats adds a small memory overhead to the register allocator (in particular, regUsageOfInstr now allocates more to keep track of the `Format` each register is used at). This explains the following metric increases. ------------------------- Metric Increase: T12707 T13035 T13379 T3294 T4801 T5321FD T5321Fun T783 ------------------------- - - - - - 10e431ef by sheaf at 2024-09-27T06:10:57-04:00 Use xmm registers in genapply This commit updates genapply to use xmm, ymm and zmm registers, for stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively. It also updates the Cmm lexer and parser to produce Cmm vectors rather than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128, bits256 and bits512 in favour of vectors. The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86) it is okay to use a single vector register to hold multiple different types of data, and we don't know just from seeing e.g. "XMM1" how to interpret the 128 bits of data within. Fixes #25062 - - - - - 8238fb2d by sheaf at 2024-09-27T06:10:57-04:00 Add vector fused multiply-add operations This commit adds fused multiply add operations such as `fmaddDoubleX2#`. These are handled both in the X86 NCG and the LLVM backends. - - - - - 2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00 Add vector shuffle primops This adds vector shuffle primops, such as ``` shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# ``` which shuffle the components of the input two vectors into the output vector. NB: the indices must be compile time literals, to match the X86 SHUFPD instruction immediate and the LLVM shufflevector instruction. These are handled in the X86 NCG and the LLVM backend. Tested in simd009. - - - - - 0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00 Add Broadcast MachOps This adds proper MachOps for broadcast instructions, allowing us to produce better code for broadcasting a value than simply packing that value (doing many vector insertions in a row). These are lowered in the X86 NCG and LLVM backends. In the LLVM backend, it uses the previously introduced shuffle instructions. - - - - - e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00 Fix treatment of signed zero in vector negation This commit fixes the handling of signed zero in floating-point vector negation. A slight hack was introduced to work around the fact that Cmm doesn't currently have a notion of signed floating point literals (see get_float_broadcast_value_reg). This can be removed once CmmFloat can express the value -0.0. The simd006 test has been updated to use a stricter notion of equality of floating-point values, which ensure the validity of this change. - - - - - f496ff7f by sheaf at 2024-09-27T06:10:57-04:00 Add min/max primops This commit adds min/max primops, such as minDouble# :: Double# -> Double# -> Double# minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# These are supported in: - the X86, AArch64 and PowerPC NCGs, - the LLVM backend, - the WebAssembly and JavaScript backends. Fixes #25120 - - - - - 5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00 Add test for C calls & SIMD vectors - - - - - f824e1ee by sheaf at 2024-09-27T06:10:58-04:00 Add test for #25169 - - - - - d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00 Fix #25169 using Plan A from the ticket We now compile certain low-level Cmm functions in the RTS multiple times, with different levels of vector support. We then dispatch at runtime in the RTS, based on what instructions are supported. See Note [realArgRegsCover] in GHC.Cmm.CallConv. Fixes #25169 ------------------------- Metric Increase: T10421 T12425 T18730 T1969 T9198 ------------------------- - - - - - d5f8778a by sheaf at 2024-09-27T06:10:58-04:00 Fix C calls with SIMD vectors This commit fixes the code generation for C calls, to take into account the calling convention. This is particularly tricky on Windows, where all vectors are expected to be passed by reference. See Note [The Windows X64 C calling convention] in GHC.CmmToAsm.X86.CodeGen. - - - - - f64bd564 by sheaf at 2024-09-27T06:10:58-04:00 X86 CodeGen: refactor getRegister CmmLit This refactors the code dealing with loading literals into registers, removing duplication and putting all the code in a single place. It also changes which XOR instruction is used to place a zero value into a register, so that we use VPXOR for a 128-bit integer vector when AVX is supported. - - - - - ab12de6b by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall: promote arg before calling evalArgs The job of evalArgs is to ensure each argument is put into a temporary register, so that it can then be loaded directly into one of the argument registers for the C call, without the generated code clobbering any other register used for argument passing. However, if we promote arguments after calling evalArgs, there is the possibility that the code used for the promotion will clobber a register, defeating the work of evalArgs. To avoid this, we first promote arguments, and only then call evalArgs. - - - - - 8fd12429 by sheaf at 2024-09-27T06:10:58-04:00 X86 genCCall64: simplify loadArg code This commit simplifies the argument loading code by making the assumption that it is safe to directly load the argument into register, because doing so will not clobber any previous assignments. This assumption is borne from the use of 'evalArgs', which evaluates any arguments which might necessitate non-trivial code generation into separate temporary registers. - - - - - 12504a9f by sheaf at 2024-09-27T06:10:58-04:00 LLVM: propagate GlobalRegUse information This commit ensures we keep track of how any particular global register is being used in the LLVM backend. This informs the LLVM type annotations, and avoids type mismatches of the following form: argument is not of expected type '<2 x double>' call ccc <2 x double> (<2 x double>) (<4 x i32> arg) - - - - - 2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00 Link bytecode from interface-stored core bindings in oneshot mode !13042 Part of #T25090 If the flag `-fprefer-byte-code` is given when compiling a module containing TH, GHC will use Core bindings stored in interfaces to compile and link bytecode for splices. This was only implemented for `--make` mode initially, so this commit adds the same mechanism to oneshot mode (`-c`). When an interface is loaded into the EPS in `loadInterface` that has dehydrated Core bindings, an entry is added to the new field `eps_iface_bytecode`, containing an IO action that produces a bytecode `Linkable`, lazily processing the `mi_extra_decls` by calling `loadIfaceByteCode`. When Template Haskell dependencies are resolved in `getLinkDeps`, this action is looked up after loading a module's interface. If it exists, the action is evaluated and the bytecode is added to the set of `Linkable`s used for execution of the splice; otherwise it falls back on the traditional object file. Metric Decrease: MultiLayerModules T13701 - - - - - 7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00 ci: Fix variable inheritence for ghcup-metadata testing job Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine how to setup all the different jobs. On the downstream trigger this was being inherited from the default setting in .gitlab.yml file. Therefore this led to job failures as the necessary CONFIGURE_ARGS were not being passed to the configure script when installing the bindist. See docs: * https://docs.gitlab.com/ee/ci/yaml/#inherit * https://docs.gitlab.com/ee/ci/yaml/#triggerforward 1. inherit:variables:fals - This stops the global variables being inherited into the job and hence forwarded onto the downstream job. 2. trigger:forward:* - yaml_variables: true (default) pass yaml variables to downstream, this is important to pass the upstream pipeline id to downstream. - pipeline_variables: false (default) but don't pass pipeline variables (normal environment variables). Fixes #25294 - - - - - 9ffd6163 by Leo at 2024-09-27T16:26:01+05:30 Fix typo in Prelude doc for (>>=) Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude. - - - - - 5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30 Wildcard binders in type declarations (#23501) Add support for wildcard binders in type declarations: type Const a b = a -- BEFORE: the `b` had to be named -- even if unused on the RHS type Const a _ = a -- AFTER: the compiler accepts -- a wildcard binder `_` The new feature is part of GHC Proposal #425 "Invisible binders in type declarations", and more specifically its amendment #641. Just like a named binder, a wildcard binder `_` may be: * plain: _ * kinded: (_ :: k -> Type) * invisible, plain: @_ * invisible, kinded: @(_ :: k -> Type) Those new forms of binders are allowed to occur on the LHSs of data, newtype, type, class, and type/data family declarations: data D _ = ... newtype N _ = ... type T _ = ... class C _ where ... type family F _ data family DF _ (Test case: testsuite/tests/typecheck/should_compile/T23501a.hs) However, we choose to reject them in forall telescopes and type family result variable binders (the latter being part of the TypeFamilyDependencies extension): type family Fd a = _ -- disallowed (WildcardBndrInTyFamResultVar) fn :: forall _. Int -- disallowed (WildcardBndrInForallTelescope) (Test case: testsuite/tests/rename/should_fail/T23501_fail.hs) See the new Notes: * Note [Type variable binders] * Note [Wildcard binders in disallowed contexts] To accommodate the new forms of binders, HsTyVarBndr was changed as follows (demonstrated without x-fields for clarity) -- BEFORE (ignoring x-fields and locations) data HsTyVarBndr flag = UserTyVar flag Name | KindedTyVar flag Name HsKind -- AFTER (ignoring x-fields and locations) data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind data HsBndrVar = HsBndrVar Name | HsBndrWildCard data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind The rest of the patch is downstream from this change. To avoid a breaking change to the TH AST, we generate fresh names to replace wildcard binders instead of adding a dedicated representation for them (as discussed in #641). And to put a cherry on top of the cake, we now allow wildcards in kind-polymorphic type variable binders in constructor patterns, see Note [Type patterns: binders and unifiers] and the tyPatToBndr function in GHC.Tc.Gen.HsType; example: fn (MkT @(_ :: forall k. k -> Type) _ _) = ... (Test case: testsuite/tests/typecheck/should_compile/T23501b.hs) - - - - - ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30 ci: Push perf notes from wasm jobs It was observed in #25299 that we were failing to push performance numbers from the wasm jobs. In future we might want to remove this ad-hoc check but for now it's easier to add another special case. Towards #25299 - - - - - 4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30 Bump GHC version to 9.12 - - - - - e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30 Bump GHC version to 9.13 - - - - - da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 6d3e822e by Ben Gamari at 2024-10-03T17:36:53-04:00 testsuite: Normalise trailing digits from hole fits output The type variables in the holes fit output from `abstract_refinement_hole_fits` is quite sensitive to compiler configuration. Specifically, a slight change in the inlining behavior of `throw` changes type variable naming in `(>>=)` and a few others. Ideally we would make hole fits output more deterministic but in the meantime we simply normalise this difference away as it not relevant to the test's goal. - - - - - 0ea62599 by Ben Gamari at 2024-10-03T17:36:53-04:00 base: Add test for #25066 - - - - - 68535ebc by Ben Gamari at 2024-10-03T17:36:53-04:00 base: Fix #25066 As noted in #25066, the exception backtrace proposal introduced a rather subtle performance regression due to simplification producing Core which the demand analyser concludes may diverge with a precise exception. The nature of the problem is more completely described in the new Note [Hiding precise exception signature in throw]. The (rather hacky) solution we use here hides the problematic optimisation through judicious use of `noinline`. Ultimately however we will want a more principled solution (e.g. #23847). Metric Decrease: T9872d - - - - - 0c7e4fd2 by Ben Gamari at 2024-10-03T17:36:53-04:00 base: Improve documentation of Control.Exception.Backtrace - - - - - 25 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow.hs - compiler/GHC/Cmm/Dataflow/Graph.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/208d8a8c192a55a3884c4f210da20a1c0cea3448...0c7e4fd200bb56f3c8074591cb7adeba04924fff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/208d8a8c192a55a3884c4f210da20a1c0cea3448...0c7e4fd200bb56f3c8074591cb7adeba04924fff You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 21:55:11 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Thu, 03 Oct 2024 17:55:11 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/monomorphic-nonempty-unzip Message-ID: <66ff12bee50d2_2e854c97719c432b3@gitlab.mail> Bodigrim pushed new branch wip/monomorphic-nonempty-unzip at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/monomorphic-nonempty-unzip You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 22:17:00 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Thu, 03 Oct 2024 18:17:00 -0400 Subject: [Git][ghc/ghc][wip/backports-9.8] Accept performance shifts Message-ID: <66ff17dc77931_2e854cc2d73848054@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC Commits: 6bd62051 by Ben Gamari at 2024-10-03T18:16:53-04:00 Accept performance shifts MultiLayerModulesTH_Make performance regresses considerably, but bizarrely only on Darwin. Metric Increase: MultiLayerModulesTH_Make - - - - - 0 changed files: Changes: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bd62051db8abee470e4b5481a6a110c319d21cc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bd62051db8abee470e4b5481a6a110c319d21cc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 23:33:41 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 03 Oct 2024 19:33:41 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/interpreterDynamic Message-ID: <66ff29d5bb2d2_2e854c1096784559ee@gitlab.mail> Cheng Shao pushed new branch wip/interpreterDynamic at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/interpreterDynamic You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Oct 3 23:57:22 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 03 Oct 2024 19:57:22 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/remove-testsuite-debug-print Message-ID: <66ff2f62c9995_2e854c1287e806197e@gitlab.mail> Cheng Shao pushed new branch wip/remove-testsuite-debug-print at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/remove-testsuite-debug-print You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 00:00:50 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 03 Oct 2024 20:00:50 -0400 Subject: [Git][ghc/ghc][wip/interpreterDynamic] interpreterDynamic Message-ID: <66ff3032a82aa_2e854c12c5f5064927@gitlab.mail> Cheng Shao pushed to branch wip/interpreterDynamic at Glasgow Haskell Compiler / GHC Commits: bbd46547 by Cheng Shao at 2024-10-04T00:00:41+00:00 interpreterDynamic - - - - - 4 changed files: - compiler/GHC/Linker/Loader.hs - testsuite/tests/quasiquotation/Makefile - testsuite/tests/quasiquotation/all.T - testsuite/tests/th/all.T Changes: ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -566,7 +566,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do preload_statics _paths names = do b <- or <$> mapM doesFileExist names if not b then return (False, pls) - else if hostIsDynamic + else if interpreterDynamic interp then do pls1 <- dynLoadObjs interp hsc_env pls names return (True, pls1) else do mapM_ (loadObj interp) names @@ -575,7 +575,7 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do preload_static_archive _paths name = do b <- doesFileExist name if not b then return False - else do if hostIsDynamic + else do if interpreterDynamic interp then throwGhcExceptionIO $ CmdLineError dynamic_msg else loadArchive interp name ===================================== testsuite/tests/quasiquotation/Makefile ===================================== @@ -10,6 +10,6 @@ T4150: -'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -c T4150.hs T14028: - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 T14028Quote.hs - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fPIC -c T14028C.c - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fexternal-interpreter T14028 T14028C.o + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 T14028Quote.hs + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 -c T14028C.c -o T14028C.o + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) -v0 -fexternal-interpreter T14028 T14028C.o ===================================== testsuite/tests/quasiquotation/all.T ===================================== @@ -10,4 +10,4 @@ test('T14028', only_ways([config.ghc_th_way]), unless(config.have_ext_interp, skip), when(opsys('freebsd'), expect_broken(19723))], - makefile_test, ['T14028']) + makefile_test, ['T14028 ghcThWayFlags=' + config.ghc_th_way_flags]) ===================================== testsuite/tests/th/all.T ===================================== @@ -591,7 +591,7 @@ test('T23829_hasty', normal, compile_fail, ['']) test('T23829_hasty_b', normal, compile_fail, ['']) test('T23927', normal, compile_and_run, ['']) test('T23954', normal, compile_and_run, ['']) -test('T23309', [extra_files(['T23309A.hs']), req_c], multimod_compile, ['T23309', '-v0 T23309.c -optc-fPIC']) +test('T23309', [extra_files(['T23309A.hs']), req_c], multimod_compile, ['T23309', '-v0 T23309.c ' + config.ghc_th_way_flags]) test('T23378', [extra_files(['T23378A.hs']), js_skip], multimod_compile, ['T23378', '-v0']) test('T23962', normal, compile_and_run, ['']) test('T23968', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbd4654769bc545a6cc28e51c0c2caeed832ba55 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbd4654769bc545a6cc28e51c0c2caeed832ba55 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 08:52:11 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 04 Oct 2024 04:52:11 -0400 Subject: [Git][ghc/ghc][wip/T25281] Better record selectors Message-ID: <66ffacbb383ad_3a68e2438424862d3@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: 24cfa3eb by Simon Peyton Jones at 2024-10-04T09:51:31+01:00 Better record selectors esp in hole-fits code - - - - - 12 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Hole.hs-boot - compiler/GHC/Tc/Errors/Hole/FitTypes.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -59,7 +59,7 @@ module GHC.Core ( unSaturatedOk, needSaturated, boringCxtOk, boringCxtNotOk, -- ** Predicates and deconstruction on 'Unfolding' - unfoldingTemplate, expandUnfolding_maybe, + expandUnfolding_maybe, maybeUnfoldingTemplate, otherCons, isValueUnfolding, isEvaldUnfolding, isCheapUnfolding, isExpandableUnfolding, isConLikeUnfolding, isCompulsoryUnfolding, @@ -1287,7 +1287,8 @@ ruleIdName :: CoreRule -> Name ruleIdName = ru_fn isLocalRule :: CoreRule -> Bool -isLocalRule = ru_local +isLocalRule (BuiltinRule {}) = False +isLocalRule (Rule { ru_local = is_local }) = is_local -- | Set the 'Name' of the 'GHC.Types.Id.Id' at the head of the rule left hand side setRuleIdName :: Name -> CoreRule -> CoreRule @@ -1513,10 +1514,6 @@ bootUnfolding = BootUnfolding mkOtherCon :: [AltCon] -> Unfolding mkOtherCon = OtherCon --- | Retrieves the template of an unfolding: panics if none is known -unfoldingTemplate :: Unfolding -> CoreExpr -unfoldingTemplate = uf_tmpl - -- | Retrieves the template of an unfolding if possible -- maybeUnfoldingTemplate is used mainly when specialising, and we do -- want to specialise DFuns, so it's important to return a template ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -2781,8 +2781,11 @@ isValue env (Var v) -- but that doesn't take account of which branch of a -- case we are in, which is the whole point - | not (isLocalId v) && isCheapUnfolding unf - = isValue env (unfoldingTemplate unf) + | not (isLocalId v) + , isCheapUnfolding unf + , Just rhs <- maybeUnfoldingTemplate unf -- Succeds if isCheapUnfolding does + = isValue env rhs -- Can't use isEvaldUnfolding because + -- we want to consult the `env` where unf = idUnfolding v -- However we do want to consult the unfolding ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -573,7 +573,7 @@ lookupRule opts rule_env@(ISE in_scope _) is_active fn args rules = go ((r,mkTicks ticks e):ms) rs | otherwise = -- pprTrace "match failed" (ppr r $$ ppr args $$ - -- ppr [ (arg_id, unfoldingTemplate unf) + -- ppr [ (arg_id, maybeUnfoldingTemplate unf) -- | Var arg_id <- args -- , let unf = idUnfolding arg_id -- , isCheapUnfolding unf] ) ===================================== compiler/GHC/Core/SimpleOpt.hs ===================================== @@ -339,10 +339,12 @@ simple_app env (Var v) as = simple_app (soeSetInScope (soeInScope env) env') e as | let unf = idUnfolding v - , isCompulsoryUnfolding (idUnfolding v) + , isCompulsoryUnfolding unf , isAlwaysActive (idInlineActivation v) -- See Note [Unfold compulsory unfoldings in RULE LHSs] - = simple_app (soeZapSubst env) (unfoldingTemplate unf) as + , Just rhs <- maybeUnfoldingTemplate unf + -- Always succeeds if isCompulsoryUnfolding does + = simple_app (soeZapSubst env) rhs as | otherwise , let out_fn = lookupIdSubst (soe_subst env) v ===================================== compiler/GHC/CoreToIface.hs ===================================== @@ -785,9 +785,9 @@ In order to implement this sharing: * When creating the interface, check the criteria above and don't serialise the RHS if such a case. - See -* When reading an interface, look at the realIdUnfolding, and then the unfoldingTemplate. - See `tc_iface_binding` for where this happens. + +* When reading an interface, look at the realIdUnfolding, and then the + maybeUnfoldingTemplate. See `tc_iface_binding` for where this happens. There are two main reasons why the mi_extra_decls field exists rather than shoe-horning all the core bindings ===================================== compiler/GHC/Iface/Tidy.hs ===================================== @@ -530,7 +530,6 @@ collectCostCentres mod_name binds rules do_binder cs b = maybe cs (go cs) (get_unf b) - -- Unfoldings may have cost centres that in the original definion are -- optimized away, see #5889. get_unf = maybeUnfoldingTemplate . realIdUnfolding @@ -652,7 +651,14 @@ getImplicitBinds tc = cls_binds ++ getTyConImplicitBinds tc getTyConImplicitBinds :: TyCon -> [CoreBind] getTyConImplicitBinds tc - | isDataTyCon tc = map get_defn (mapMaybe dataConWrapId_maybe (tyConDataCons tc)) + | isDataTyCon tc = [ NonRec wrap_id rhs + | dc <- tyConDataCons tc + , let wrap_id = dataConWrapId dc + -- For data cons with no wrapper, this wrap_id + -- is in fact a DataConWorkId, and hence + -- dataConWrapUnfolding_maybe returns Nothing + , Just rhs <- [dataConWrapUnfolding_maybe wrap_id] ] + | otherwise = [] -- The 'otherwise' includes family TyCons of course, but also (less obviously) -- * Newtypes: see Note [Compulsory newtype unfolding] in GHC.Types.Id.Make @@ -663,9 +669,6 @@ getClassImplicitBinds cls = [ NonRec op (mkDictSelRhs cls val_index) | (op, val_index) <- classAllSelIds cls `zip` [0..] ] -get_defn :: Id -> CoreBind -get_defn id = NonRec id (unfoldingTemplate (realIdUnfolding id)) - {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -471,17 +471,17 @@ addHoleFitDocs fits = else return fits } where msg = text "GHC.Tc.Errors.Hole addHoleFitDocs" - upd mb_local_docs mods_without_docs fit@(HoleFit {hfCand = cand}) = + upd mb_local_docs mods_without_docs (TcHoleFit fit@(HoleFit {hfCand = cand})) = let name = getName cand in do { mb_docs <- if hfIsLcl fit then pure mb_local_docs else mi_docs <$> loadInterfaceForName msg name ; case mb_docs of - { Nothing -> return (Set.insert (nameOrigin name) mods_without_docs, fit) + { Nothing -> return (Set.insert (nameOrigin name) mods_without_docs, TcHoleFit fit) ; Just docs -> do { let doc = lookupUniqMap (docs_decls docs) name - ; return $ (mods_without_docs, fit {hfDoc = map hsDocString <$> doc}) }}} - upd _ mods_without_docs fit = pure (mods_without_docs, fit) + ; return $ (mods_without_docs, TcHoleFit (fit {hfDoc = map hsDocString <$> doc})) }}} + upd _ mods_without_docs fit@(RawHoleFit {}) = pure (mods_without_docs, fit) nameOrigin name = case nameModule_maybe name of Just m -> Right m Nothing -> @@ -503,7 +503,7 @@ addHoleFitDocs fits = -- refinement level. pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc pprHoleFit _ (RawHoleFit sd) = sd -pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (HoleFit {..}) = +pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (TcHoleFit (HoleFit {..})) = hang display 2 provenance where tyApp = sep $ zipWithEqual "pprHoleFit" pprArg vars hfWrap where pprArg b arg = case binderFlag b of @@ -623,7 +623,9 @@ findValidHoleFits tidy_env implics simples h@(Hole { hole_sort = ExprHole _ tcFilterHoleFits findVLimit hole (hole_ty, []) cands ; (tidy_env, tidy_subs) <- liftZonkM $ zonkSubs tidy_env subs ; tidy_sorted_subs <- sortFits sortingAlg tidy_subs - ; plugin_handled_subs <- foldM (flip ($)) tidy_sorted_subs fitPlugins + ; let apply_plugin :: [HoleFit] -> ([HoleFit] -> TcM [HoleFit]) -> TcM [HoleFit] + apply_plugin fits plug = plug fits + ; plugin_handled_subs <- foldM apply_plugin (map TcHoleFit tidy_sorted_subs) fitPlugins ; let (pVDisc, limited_subs) = possiblyDiscard maxVSubs plugin_handled_subs vDiscards = pVDisc || searchDiscards ; subs_with_docs <- addHoleFitDocs limited_subs @@ -642,19 +644,21 @@ findValidHoleFits tidy_env implics simples h@(Hole { hole_sort = ExprHole _ ; traceTc "ref_tys are" $ ppr ref_tys ; let findRLimit = if sortingAlg > HFSNoSorting then Nothing else maxRSubs - ; refDs <- mapM (flip (tcFilterHoleFits findRLimit hole) - cands) ref_tys - ; (tidy_env, tidy_rsubs) <- liftZonkM $ zonkSubs tidy_env $ concatMap snd refDs - ; tidy_sorted_rsubs <- sortFits sortingAlg tidy_rsubs + ; refDs :: [(Bool, [TcHoleFit])] + <- mapM (flip (tcFilterHoleFits findRLimit hole) cands) ref_tys + ; (tidy_env, tidy_rsubs :: [TcHoleFit]) + <- liftZonkM $ zonkSubs tidy_env $ concatMap snd refDs + ; tidy_sorted_rsubs :: [TcHoleFit] <- sortFits sortingAlg tidy_rsubs -- For refinement substitutions we want matches -- like id (_ :: t), head (_ :: [t]), asTypeOf (_ :: t), -- and others in that vein to appear last, since these are -- unlikely to be the most relevant fits. ; (tidy_env, tidy_hole_ty) <- liftZonkM $ zonkTidyTcType tidy_env hole_ty ; let hasExactApp = any (tcEqType tidy_hole_ty) . hfWrap + exact, not_exact :: [TcHoleFit] (exact, not_exact) = partition hasExactApp tidy_sorted_rsubs - ; plugin_handled_rsubs <- foldM (flip ($)) - (not_exact ++ exact) fitPlugins + fits :: [HoleFit] = map TcHoleFit (not_exact ++ exact) + ; plugin_handled_rsubs <- foldM apply_plugin fits fitPlugins ; let (pRDisc, exact_last_rfits) = possiblyDiscard maxRSubs $ plugin_handled_rsubs rDiscards = pRDisc || any fst refDs @@ -685,8 +689,8 @@ findValidHoleFits tidy_env implics simples h@(Hole { hole_sort = ExprHole _ wrapWithVars vars = mkVisFunTysMany (map mkTyVarTy vars) hole_ty sortFits :: HoleFitSortingAlg -- How we should sort the hole fits - -> [HoleFit] -- The subs to sort - -> TcM [HoleFit] + -> [TcHoleFit] -- The subs to sort + -> TcM [TcHoleFit] sortFits HFSNoSorting subs = return subs sortFits HFSBySize subs = (++) <$> sortHoleFitsBySize (sort lclFits) @@ -731,14 +735,13 @@ relevantCtEvidence hole_ty simples -- We zonk the hole fits so that the output aligns with the rest -- of the typed hole error message output. -zonkSubs :: TidyEnv -> [HoleFit] -> ZonkM (TidyEnv, [HoleFit]) +zonkSubs :: TidyEnv -> [TcHoleFit] -> ZonkM (TidyEnv, [TcHoleFit]) zonkSubs = zonkSubs' [] where zonkSubs' zs env [] = return (env, reverse zs) zonkSubs' zs env (hf:hfs) = do { (env', z) <- zonkSub env hf ; zonkSubs' (z:zs) env' hfs } - zonkSub :: TidyEnv -> HoleFit -> ZonkM (TidyEnv, HoleFit) - zonkSub env hf at RawHoleFit{} = return (env, hf) + zonkSub :: TidyEnv -> TcHoleFit -> ZonkM (TidyEnv, TcHoleFit) zonkSub env hf at HoleFit{hfType = ty, hfMatches = m, hfWrap = wrp} = do { (env, ty') <- zonkTidyTcType env ty ; (env, m') <- zonkTidyTcTypes env m @@ -750,9 +753,9 @@ zonkSubs = zonkSubs' [] -- types needed to instantiate the fit to the type of the hole. -- This is much quicker than sorting by subsumption, and gives reasonable -- results in most cases. -sortHoleFitsBySize :: [HoleFit] -> TcM [HoleFit] +sortHoleFitsBySize :: [TcHoleFit] -> TcM [TcHoleFit] sortHoleFitsBySize = return . sortOn sizeOfFit - where sizeOfFit :: HoleFit -> TypeSize + where sizeOfFit :: TcHoleFit -> TypeSize sizeOfFit = sizeTypes . nubBy tcEqType . hfWrap -- Based on a suggestion by phadej on #ghc, we can sort the found fits @@ -761,12 +764,12 @@ sortHoleFitsBySize = return . sortOn sizeOfFit -- probably those most relevant. This takes a lot of work (but results in -- much more useful output), and can be disabled by -- '-fno-sort-valid-hole-fits'. -sortHoleFitsByGraph :: [HoleFit] -> TcM [HoleFit] +sortHoleFitsByGraph :: [TcHoleFit] -> TcM [TcHoleFit] sortHoleFitsByGraph fits = go [] fits where tcSubsumesWCloning :: TcType -> TcType -> TcM Bool tcSubsumesWCloning ht ty = withoutUnification fvs (tcSubsumes ht ty) where fvs = tyCoFVsOfTypes [ht,ty] - go :: [(HoleFit, [HoleFit])] -> [HoleFit] -> TcM [HoleFit] + go :: [(TcHoleFit, [TcHoleFit])] -> [TcHoleFit] -> TcM [TcHoleFit] go sofar [] = do { traceTc "subsumptionGraph was" $ ppr sofar ; return $ uncurry (++) $ partition hfIsLcl topSorted } where toV (hf, adjs) = (hf, hfId hf, map hfId adjs) @@ -788,7 +791,7 @@ tcFilterHoleFits :: Maybe Int -- additional holes. -> [HoleFitCandidate] -- ^ The candidates to check whether fit. - -> TcM (Bool, [HoleFit]) + -> TcM (Bool, [TcHoleFit]) -- ^ We return whether or not we stopped due to hitting the limit -- and the fits we found. tcFilterHoleFits (Just 0) _ _ _ = return (False, []) -- Stop right away on 0 @@ -803,12 +806,12 @@ tcFilterHoleFits limit typed_hole ht@(hole_ty, _) candidates = -- Kickoff the checking of the elements. -- We iterate over the elements, checking each one in turn for whether -- it fits, and adding it to the results if it does. - go :: [HoleFit] -- What we've found so far. + go :: [TcHoleFit] -- What we've found so far. -> VarSet -- Ids we've already checked -> Maybe Int -- How many we're allowed to find, if limited -> (TcType, [TcTyVar]) -- The type, and its refinement variables. -> [HoleFitCandidate] -- The elements we've yet to check. - -> TcM (Bool, [HoleFit]) + -> TcM (Bool, [TcHoleFit]) go subs _ _ _ [] = return (False, reverse subs) go subs _ (Just 0) _ _ = return (True, reverse subs) go subs seen maxleft ty (el:elts) = ===================================== compiler/GHC/Tc/Errors/Hole.hs-boot ===================================== @@ -4,41 +4,16 @@ -- + which calls 'GHC.Tc.Solver.simpl_top' module GHC.Tc.Errors.Hole where -import GHC.Types.Var ( Id ) import GHC.Tc.Errors.Types ( HoleFitDispConfig, ValidHoleFits ) import GHC.Tc.Types ( TcM ) import GHC.Tc.Types.Constraint ( CtEvidence, Hole, Implication ) -import GHC.Tc.Types.CtLoc( CtLoc ) import GHC.Utils.Outputable ( SDoc ) import GHC.Types.Var.Env ( TidyEnv ) -import GHC.Tc.Errors.Hole.FitTypes ( HoleFit, TypedHole, HoleFitCandidate ) -import GHC.Tc.Utils.TcType ( TcType, TcSigmaType, TcTyVar ) -import GHC.Tc.Zonk.Monad ( ZonkM ) -import GHC.Tc.Types.Evidence ( HsWrapper ) -import GHC.Utils.FV ( FV ) -import Data.Bool ( Bool ) -import Data.Maybe ( Maybe ) -import Data.Int ( Int ) +import GHC.Tc.Errors.Hole.FitTypes ( HoleFit ) findValidHoleFits :: TidyEnv -> [Implication] -> [CtEvidence] -> Hole -> TcM (TidyEnv, ValidHoleFits) -tcCheckHoleFit :: TypedHole -> TcSigmaType -> TcSigmaType - -> TcM (Bool, HsWrapper) - -withoutUnification :: FV -> TcM a -> TcM a -tcSubsumes :: TcSigmaType -> TcSigmaType -> TcM Bool -tcFilterHoleFits :: Maybe Int -> TypedHole -> (TcType, [TcTyVar]) - -> [HoleFitCandidate] -> TcM (Bool, [HoleFit]) -getLocalBindings :: TidyEnv -> CtLoc -> TcM [Id] -addHoleFitDocs :: [HoleFit] -> TcM [HoleFit] - -data HoleFitSortingAlg - -pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc -getHoleFitSortingAlg :: TcM HoleFitSortingAlg getHoleFitDispConfig :: TcM HoleFitDispConfig -zonkSubs :: TidyEnv -> [HoleFit] -> ZonkM (TidyEnv, [HoleFit]) -sortHoleFitsBySize :: [HoleFit] -> TcM [HoleFit] -sortHoleFitsByGraph :: [HoleFit] -> TcM [HoleFit] +pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc ===================================== compiler/GHC/Tc/Errors/Hole/FitTypes.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE ExistentialQuantification #-} module GHC.Tc.Errors.Hole.FitTypes ( - TypedHole (..), HoleFit (..), HoleFitCandidate (..), + TypedHole (..), HoleFit (..), TcHoleFit(..), HoleFitCandidate (..), hfIsLcl, pprHoleFitCand ) where @@ -77,7 +77,7 @@ instance Ord HoleFitCandidate where -- element that was checked, the Id of that element as found by `tcLookup`, -- and the refinement level of the fit, which is the number of extra argument -- holes that this fit uses (e.g. if hfRefLvl is 2, the fit is for `Id _ _`). -data HoleFit = +data TcHoleFit = HoleFit { hfId :: Id -- ^ The elements id in the TcM , hfCand :: HoleFitCandidate -- ^ The candidate that was checked. , hfType :: TcType -- ^ The type of the id, possibly zonked. @@ -88,16 +88,22 @@ data HoleFit = , hfDoc :: Maybe [HsDocString] -- ^ Documentation of this HoleFit, if available. } - | RawHoleFit SDoc - -- ^ A fit that is just displayed as is. Here so thatHoleFitPlugins + +data HoleFit + = TcHoleFit TcHoleFit + | RawHoleFit SDoc + -- ^ A fit that is just displayed as is. Here so that HoleFitPlugins -- can inject any fit they want. -- We define an Eq and Ord instance to be able to build a graph. -instance Eq HoleFit where +instance Eq TcHoleFit where (==) = (==) `on` hfId instance Outputable HoleFit where + ppr (TcHoleFit hf) = ppr hf ppr (RawHoleFit sd) = sd + +instance Outputable TcHoleFit where ppr (HoleFit _ cand ty _ _ mtchs _) = hang (name <+> holes) 2 (text "where" <+> name <+> dcolon <+> (ppr ty)) where name = ppr $ getName cand @@ -107,20 +113,19 @@ instance Outputable HoleFit where -- want our tests to be affected by the non-determinism of `nonDetCmpVar`, -- which is used to compare Ids. When comparing, we want HoleFits with a lower -- refinement level to come first. -instance Ord HoleFit where - compare (RawHoleFit _) (RawHoleFit _) = EQ - compare (RawHoleFit _) _ = LT - compare _ (RawHoleFit _) = GT +instance Ord TcHoleFit where +-- compare (RawHoleFit _) (RawHoleFit _) = EQ +-- compare (RawHoleFit _) _ = LT +-- compare _ (RawHoleFit _) = GT compare a@(HoleFit {}) b@(HoleFit {}) = cmp a b where cmp = if hfRefLvl a == hfRefLvl b then compare `on` (getName . hfCand) else compare `on` hfRefLvl -hfIsLcl :: HoleFit -> Bool +hfIsLcl :: TcHoleFit -> Bool hfIsLcl hf@(HoleFit {}) = case hfCand hf of IdHFCand _ -> True NameHFCand _ -> False GreHFCand gre -> gre_lcl gre -hfIsLcl _ = False ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs ===================================== @@ -215,7 +215,7 @@ ppClass sDocContext decl@(ClassDecl{}) subdocs = ppSig' = flip (ppSigWithDoc sDocContext) subdocs - add_ctxt = addClassContext (tcdName decl) (tyClDeclTyVarsI decl) + add_ctxt = addClassContext (tcdName decl) (tyClDeclTyVars decl) ppTyFams :: String ppTyFams @@ -331,7 +331,7 @@ ppCtor sDocContext dat subdocs con at ConDeclH98{con_args = con_args'} = apps $ map reL $ (HsTyVar noAnn NotPromoted (reL (tcdName dat))) - : map (tyVarArg . unLoc) (hsQTvExplicit $ tyClDeclTyVarsI dat) + : map (tyVarArg . unLoc) (hsQTvExplicit $ tyClDeclTyVars dat) ppCtor sDocContext _dat ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -248,10 +248,6 @@ tyClDeclLNameI (SynDecl{tcdLName = ln}) = ln tyClDeclLNameI (DataDecl{tcdLName = ln}) = ln tyClDeclLNameI (ClassDecl{tcdLName = ln}) = ln -tyClDeclTyVarsI :: TyClDecl DocNameI -> LHsQTyVars DocNameI -tyClDeclTyVarsI (FamDecl { tcdFam = FamilyDecl { fdTyVars = tvs } }) = tvs -tyClDeclTyVarsI d = tcdTyVars d - tcdNameI :: TyClDecl DocNameI -> DocName tcdNameI = unLoc . tyClDeclLNameI ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -847,7 +847,7 @@ extractDecl prr dflags sDocContext name decl -- TODO: document fixity case (matchesMethod, matchesAssociatedType) of ([s0], _) -> - let tyvar_names = tyClDeclTyVarsI d + let tyvar_names = tyClDeclTyVars d L pos sig = addClassContext clsNm tyvar_names s0 in pure (Right $ L pos (SigD noExtField sig)) (_, [L pos fam_decl]) -> pure (Right $ L pos (TyClD noExtField (FamDecl noExtField fam_decl))) @@ -881,7 +881,7 @@ extractDecl prr dflags sDocContext name decl { tcdLName = L _ dataNm , tcdDataDefn = HsDataDefn{dd_cons = dataCons} } -> pure $ do - let ty_args = lHsQTyVarsToTypes (tyClDeclTyVarsI d) + let ty_args = lHsQTyVarsToTypes (tyClDeclTyVars d) lsig <- if isDataConName name then extractPatternSyn name dataNm ty_args (toList dataCons) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24cfa3eb37129e8a53725557e5c7f4604b9a3100 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24cfa3eb37129e8a53725557e5c7f4604b9a3100 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 09:07:23 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 04 Oct 2024 05:07:23 -0400 Subject: [Git][ghc/ghc][wip/romes/25330] Deprecation for WarnCompatUnqualifiedImports Message-ID: <66ffb04b1cadc_35e4cebc480-3ac@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25330 at Glasgow Haskell Compiler / GHC Commits: 81f61fe9 by Rodrigo Mesquita at 2024-10-04T10:06:29+01:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 30 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-warnings.rst - libraries/base/tests/T9586.hs - libraries/base/tests/list001.hs - testsuite/tests/ghci/scripts/T14828.script - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci036.script - testsuite/tests/module/Mod137_A.hs - testsuite/tests/module/Mod138_A.hs - testsuite/tests/module/Mod141_A.hs - testsuite/tests/module/mod154.hs - testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs - testsuite/tests/perf/compiler/T16875.hs - testsuite/tests/perf/compiler/T16875.stderr - testsuite/tests/rename/prog001/rn037.hs - testsuite/tests/rename/should_compile/T17244A.hs - + testsuite/tests/rename/should_compile/T17244A.stderr - testsuite/tests/rename/should_compile/T17244B.hs - testsuite/tests/rename/should_compile/T17244B.stderr - testsuite/tests/rename/should_compile/T17244C.hs - testsuite/tests/rename/should_compile/T17244C.stderr - testsuite/tests/rename/should_compile/T4478.hs - testsuite/tests/rename/should_compile/T7167.hs - testsuite/tests/rename/should_compile/T7167.stderr - testsuite/tests/rename/should_compile/rn025.hs - testsuite/tests/rename/should_compile/rn027.hs - testsuite/tests/rename/should_compile/rn031.hs - testsuite/tests/rename/should_compile/rn060.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81f61fe90a948114735f4172754c4dddd4b5be2e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81f61fe90a948114735f4172754c4dddd4b5be2e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 09:14:49 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 04 Oct 2024 05:14:49 -0400 Subject: [Git][ghc/ghc][wip/exception-propagate] Exception rethrowing Message-ID: <66ffb209d4005_35e4cebca7091cb@gitlab.mail> Rodrigo Mesquita pushed to branch wip/exception-propagate at Glasgow Haskell Compiler / GHC Commits: abf9d404 by Matthew Pickering at 2024-10-04T10:14:36+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - 30 changed files: - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs - libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/concurrent/should_run/T3279.hs - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/abf9d4044d100cfd18721bdfe8d0332973403835 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/abf9d4044d100cfd18721bdfe8d0332973403835 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 09:18:55 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Fri, 04 Oct 2024 05:18:55 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] Apply 1 suggestion(s) to 1 file(s) Message-ID: <66ffb2ff79d54_35e4ce4001c898c2@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: bb2bb34e by Hassan Al-Awwadi at 2024-10-04T09:18:52+00:00 Apply 1 suggestion(s) to 1 file(s) Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 1 changed file: - compiler/GHC/Hs/Type.hs Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1088,47 +1088,54 @@ also forbids them in types involved with `deriving`: * * ************************************************************************ -Note [Lifecycle of an UpdFieldOcc] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When we have an update to a field occurrence (UpdFieldOcc) of the form -rec{ label = value }, its possible that what label refers to is ambiguous, -aka: that there are multiple record types with label as a field. In this case -we can't go from a RdrName in the GhcPs stage to a Name in the GhcRn stage, -because we have multiple Names we could choose from. Once we typecheck, we -also do type-directed disambiguation, so at that stage we can go directly from -a Name to an Id, modulo the disambiguation succeeding. - -To account for this the UpdFieldOcc occurrence has an instantiation for its -XXUpdFieldOcc type family: AmbiguousFieldOcc. AmbiguousFieldOcc just stores -the RdrName directly, whereas the FieldOcc (GhcPass p) field will go from -RdrName to Name to Id as the stage shifts. Note that FieldOcc also stores -the RdrName throughout its lifecycle, for exact printing purpose, after the -Parse stage this RdrName just shifts from the foLabel field to the foExt field. - -Summarised the lifecycle of a FieldOcc is like this: -* GhcPs: FieldOcc noExtField RdrName -* GhcRn: FieldOcc RdrName Name -* GhcTc: FieldOcc RdrName Id +Note [Lifecycle of FieldOcc/UpdFieldOcc] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When renaming a "record field update" (`some_record{ field = expr }`), the field +occurrence may be ambiguous if there are multiple record types with that same +field label in scope. Instead of failing, we may attempt to do type-directed +disambiguation: if we typecheck the record field update, we can disambiguate +the `field` based on the record and field type. + +In practice, this means an identifier of an update field occurrence +(`UpdFieldOcc`) may have to go straight from `RdrName` to `Id`, since field +ambiguity makes it impossible to construct a `Name` for the field. + +Since type-directed disambiguation is a GHC property rather than a property of +the GHC-Haskell AST, we still parametrise an `UpdFieldOcc` occurrence by `IdP p`, +but introduce a constructor `AmbiguousFieldOcc` in the `XXUpdFieldOcc` extension point. +That is: + + * `AmbiguousFieldOcc @GhcRn :: RdrName -> UpdFieldOcc` + * `UpdFieldOcc @GhcRn :: Name -> UpdFieldOcc` -With its extra constructor `XFieldOcc currently being unused and disabled by -instantiation XXFieldOcc (GhcPass p) = DataConCantHappen. In most cases just -having this FieldOcc datatype is enough, but as mentioned the UpdFieldOcc case -requires a case for ambiguity. +If the update field occurrence is ambiguous, the renamer will construct it with +`AmbiguousFieldOcc`. Otherwise, it'll use `UpdFieldOcc` -- an unambiguous +update field occurrence. + +In @GhcTc the `UpdFieldOcc` extension point is "deleted" since all field +occurrences after type checking must be unambiguous. + +A `FieldOcc` is a field occurrence that /does not/ occur in a record update, c.f. `UpdFieldOcc`. +Non-update field occurrences are always unambiguous. The lifecycle of an UpdFieldOcc is as follows * GhcPs: - * UpdFieldOcc noExtField (FieldOcc GhcPs) - * XUpdFieldOcc DataConCantHappen + - UpdFieldOcc noExtField (FieldOcc GhcPs) + - XUpdFieldOcc DataConCantHappen * GhcRn: - * UpdFieldOcc noExtField (FieldOCc GhcRn) - * XUpdFieldOcc AmbiguousFieldOcc + - UpdFieldOcc noExtField (FieldOCc GhcRn) + - XUpdFieldOcc /AmbiguousFieldOcc/ * GhcTc: - * UpdFieldOcc noExtField (FieldOCc GhcRn) - * XUpdFieldOcc DataConCantHappen + - UpdFieldOcc noExtField (FieldOCc GhcRn) + - XUpdFieldOcc DataConCantHappen + +The lifecycle of a FieldOcc is more straightforward: +* GhcPs: FieldOcc noExtField RdrName +* GhcRn: FieldOcc RdrName Name +* GhcTc: FieldOcc RdrName Id -so using DataConCantHappen we statically guarantee that when we go to a -UpdFieldOcc GhcRn to UpdFieldOcc GhcTc we either succesfully disambiguate or -error when we can't. +NB: FieldOcc preserves the RdrName throughout its lifecycle for +exact printing purposes. -} -- | Ambiguous Field Occurrence View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb2bb34e6b07d1dd75330ed6d8dfd25d48a6cf18 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb2bb34e6b07d1dd75330ed6d8dfd25d48a6cf18 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 09:38:01 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 04 Oct 2024 05:38:01 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: ci: Add nightly & release ubuntu-22.04 jobs Message-ID: <66ffb77912837_35e4ce510144110a7@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 2af3c986 by Torsten Schmits at 2024-10-04T05:37:44-04:00 Parallelize getRootSummary computations in dep analysis downsweep This reuses the upsweep step's infrastructure to process batches of modules in parallel. I benchmarked this by running `ghc -M` on two sets of 10,000 modules; one with a linear dependency chain and the other with a binary tree. Comparing different values for the number of modules per thread suggested an optimum at `length targets `div` (n_cap * 2)`, with results similar to this one (6 cores, 12 threads): ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 1.775 s ± 0.026 s [User: 1.377 s, System: 0.399 s] Range (min … max): 1.757 s … 1.793 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 876.2 ms ± 20.9 ms [User: 1833.2 ms, System: 518.6 ms] Range (min … max): 856.2 ms … 898.0 ms 3 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 793.5 ms ± 23.2 ms [User: 2318.9 ms, System: 718.6 ms] Range (min … max): 771.9 ms … 818.0 ms 3 runs ``` Results don't differ much when the batch size is reduced to a quarter of that, but there's significant thread scheduling overhead for a size of 1: ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 2.611 s ± 0.029 s [User: 2.851 s, System: 0.783 s] Range (min … max): 2.591 s … 2.632 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 1.189 s ± 0.007 s [User: 2.707 s, System: 1.103 s] Range (min … max): 1.184 s … 1.194 s 2 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 1.097 s ± 0.006 s [User: 2.938 s, System: 1.300 s] Range (min … max): 1.093 s … 1.101 s 2 runs ``` Larger batches also slightly worsen performance. - - - - - 8d7b73d3 by Cheng Shao at 2024-10-04T05:37:45-04:00 testsuite: remove accidentally checked in debug print logic - - - - - 13 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Driver/Make.hs - compiler/GHC/Unit/Finder.hs - libraries/ghc-experimental/ghc-experimental.cabal.in - testsuite/tests/ghc-api/downsweep/OldModLocation.hs - testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs - testsuite/tests/profiling/should_run/all.T - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1144,6 +1144,8 @@ ghcup-metadata-nightly: artifacts: false - job: nightly-x86_64-linux-centos7-validate artifacts: false + - job: nightly-x86_64-linux-ubuntu22_04-validate + artifacts: false - job: nightly-x86_64-linux-ubuntu20_04-validate artifacts: false - job: nightly-x86_64-linux-ubuntu18_04-validate ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -112,6 +112,7 @@ data LinuxDistro | Debian9 | Fedora33 | Fedora38 + | Ubuntu2204 | Ubuntu2004 | Ubuntu1804 | Centos7 @@ -308,6 +309,7 @@ distroName Fedora33 = "fedora33" distroName Fedora38 = "fedora38" distroName Ubuntu1804 = "ubuntu18_04" distroName Ubuntu2004 = "ubuntu20_04" +distroName Ubuntu2204 = "ubuntu22_04" distroName Centos7 = "centos7" distroName Alpine312 = "alpine3_12" distroName Alpine318 = "alpine3_18" @@ -1060,6 +1062,7 @@ ubuntu_x86 :: [JobGroup Job] ubuntu_x86 = [ disableValidate (standardBuilds Amd64 (Linux Ubuntu1804)) , disableValidate (standardBuilds Amd64 (Linux Ubuntu2004)) + , disableValidate (standardBuilds Amd64 (Linux Ubuntu2204)) ] rhel_x86 :: [JobGroup Job] ===================================== .gitlab/jobs.yaml ===================================== @@ -2745,6 +2745,69 @@ "XZ_OPT": "-9" } }, + "nightly-x86_64-linux-ubuntu22_04-validate": { + "after_script": [ + ".gitlab/ci.sh save_cache", + ".gitlab/ci.sh save_test_output", + ".gitlab/ci.sh clean", + "cat ci_timings" + ], + "allow_failure": false, + "artifacts": { + "expire_in": "8 weeks", + "paths": [ + "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz", + "junit.xml", + "unexpected-test-output.tar.gz" + ], + "reports": { + "junit": "junit.xml" + }, + "when": "always" + }, + "cache": { + "key": "x86_64-linux-ubuntu22_04-$CACHE_REV", + "paths": [ + "cabal-cache", + "toolchain" + ] + }, + "dependencies": [], + "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV", + "needs": [ + { + "artifacts": false, + "job": "hadrian-ghc-in-ghci" + } + ], + "rules": [ + { + "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)", + "when": "on_success" + } + ], + "script": [ + "sudo chown ghc:ghc -R .", + ".gitlab/ci.sh setup", + ".gitlab/ci.sh configure", + ".gitlab/ci.sh build_hadrian", + ".gitlab/ci.sh test_hadrian" + ], + "stage": "full-build", + "tags": [ + "x86_64-linux" + ], + "variables": { + "BIGNUM_BACKEND": "gmp", + "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate", + "BUILD_FLAVOUR": "validate", + "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "RUNTEST_ARGS": "", + "TEST_ENV": "x86_64-linux-ubuntu22_04-validate", + "XZ_OPT": "-9" + } + }, "nightly-x86_64-windows-int_native-validate": { "after_script": [ "bash .gitlab/ci.sh save_cache", @@ -4452,6 +4515,71 @@ "XZ_OPT": "-9" } }, + "release-x86_64-linux-ubuntu22_04-release": { + "after_script": [ + ".gitlab/ci.sh save_cache", + ".gitlab/ci.sh save_test_output", + ".gitlab/ci.sh clean", + "cat ci_timings" + ], + "allow_failure": false, + "artifacts": { + "expire_in": "1 year", + "paths": [ + "ghc-x86_64-linux-ubuntu22_04-release.tar.xz", + "junit.xml", + "unexpected-test-output.tar.gz" + ], + "reports": { + "junit": "junit.xml" + }, + "when": "always" + }, + "cache": { + "key": "x86_64-linux-ubuntu22_04-$CACHE_REV", + "paths": [ + "cabal-cache", + "toolchain" + ] + }, + "dependencies": [], + "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV", + "needs": [ + { + "artifacts": false, + "job": "hadrian-ghc-in-ghci" + } + ], + "rules": [ + { + "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)", + "when": "on_success" + } + ], + "script": [ + "sudo chown ghc:ghc -R .", + ".gitlab/ci.sh setup", + ".gitlab/ci.sh configure", + ".gitlab/ci.sh build_hadrian", + ".gitlab/ci.sh test_hadrian" + ], + "stage": "full-build", + "tags": [ + "x86_64-linux" + ], + "variables": { + "BIGNUM_BACKEND": "gmp", + "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-release", + "BUILD_FLAVOUR": "release", + "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "HADRIAN_ARGS": "--hash-unit-ids", + "IGNORE_PERF_FAILURES": "all", + "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", + "RUNTEST_ARGS": "", + "TEST_ENV": "x86_64-linux-ubuntu22_04-release", + "XZ_OPT": "-9" + } + }, "release-x86_64-windows-int_native-release": { "after_script": [ "bash .gitlab/ci.sh save_cache", ===================================== .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py ===================================== @@ -19,6 +19,7 @@ def job_triple(job_name): 'release-x86_64-windows-release': 'x86_64-unknown-mingw32', 'release-x86_64-windows-int_native-release': 'x86_64-unknown-mingw32-int_native', 'release-x86_64-linux-rocky8-release': 'x86_64-rocky8-linux', + 'release-x86_64-linux-ubuntu22_04-release': 'x86_64-ubuntu22_04-linux', 'release-x86_64-linux-ubuntu20_04-release': 'x86_64-ubuntu20_04-linux', 'release-x86_64-linux-ubuntu18_04-release': 'x86_64-ubuntu18_04-linux', 'release-x86_64-linux-fedora38-release': 'x86_64-fedora38-linux', ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -191,6 +191,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): # Here are all the bindists we can distribute ubuntu1804 = mk(ubuntu("18_04")) ubuntu2004 = mk(ubuntu("20_04")) + ubuntu2204 = mk(ubuntu("22_04")) rocky8 = mk(rocky("8")) centos7 = mk(centos(7)) fedora33 = mk(fedora(33)) @@ -222,7 +223,10 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): , "unknown_versioning": deb11 } , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004 , "( >= 16 && < 18 )": deb9 - , "( >= 18 && < 19 )": ubuntu1804 } + , "( >= 18 && < 19 )": ubuntu1804 + , "( >= 19 && < 21 )": ubuntu2004 + , "( >= 21 )": ubuntu2204 + } , "Linux_Mint" : { "< 20": ubuntu1804 , ">= 20": ubuntu2004 , "unknown_versioning": ubuntu2004 } ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -5,6 +5,8 @@ {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE BlockArguments #-} -- ----------------------------------------------------------------------------- -- @@ -122,7 +124,7 @@ import qualified Control.Monad.Catch as MC import Data.IORef import Data.Maybe import Data.Time -import Data.List (sortOn) +import Data.List (sortOn, unfoldr) import Data.Bifunctor (first) import System.Directory import System.FilePath @@ -169,7 +171,7 @@ depanal :: GhcMonad m => -> Bool -- ^ allow duplicate roots -> m ModuleGraph depanal excluded_mods allow_dup_roots = do - (errs, mod_graph) <- depanalE excluded_mods allow_dup_roots + (errs, mod_graph) <- depanalE mkUnknownDiagnostic Nothing excluded_mods allow_dup_roots if isEmptyMessages errs then pure mod_graph else throwErrors (fmap GhcDriverMessage errs) @@ -177,12 +179,14 @@ depanal excluded_mods allow_dup_roots = do -- | Perform dependency analysis like in 'depanal'. -- In case of errors, the errors and an empty module graph are returned. depanalE :: GhcMonad m => -- New for #17459 - [ModuleName] -- ^ excluded modules + (GhcMessage -> AnyGhcDiagnostic) + -> Maybe Messager + -> [ModuleName] -- ^ excluded modules -> Bool -- ^ allow duplicate roots -> m (DriverMessages, ModuleGraph) -depanalE excluded_mods allow_dup_roots = do +depanalE diag_wrapper msg excluded_mods allow_dup_roots = do hsc_env <- getSession - (errs, mod_graph) <- depanalPartial excluded_mods allow_dup_roots + (errs, mod_graph) <- depanalPartial diag_wrapper msg excluded_mods allow_dup_roots if isEmptyMessages errs then do hsc_env <- getSession @@ -220,11 +224,13 @@ depanalE excluded_mods allow_dup_roots = do -- new module graph. depanalPartial :: GhcMonad m - => [ModuleName] -- ^ excluded modules + => (GhcMessage -> AnyGhcDiagnostic) + -> Maybe Messager + -> [ModuleName] -- ^ excluded modules -> Bool -- ^ allow duplicate roots -> m (DriverMessages, ModuleGraph) -- ^ possibly empty 'Bag' of errors and a module graph. -depanalPartial excluded_mods allow_dup_roots = do +depanalPartial diag_wrapper msg excluded_mods allow_dup_roots = do hsc_env <- getSession let targets = hsc_targets hsc_env @@ -243,7 +249,7 @@ depanalPartial excluded_mods allow_dup_roots = do liftIO $ flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env) (errs, graph_nodes) <- liftIO $ downsweep - hsc_env (mgModSummaries old_graph) + hsc_env diag_wrapper msg (mgModSummaries old_graph) excluded_mods allow_dup_roots let mod_graph = mkModuleGraph graph_nodes @@ -497,8 +503,8 @@ loadWithCache :: GhcMonad m => Maybe ModIfaceCache -- ^ Instructions about how t -> LoadHowMuch -- ^ How much `loadWithCache` should load -> m SuccessFlag loadWithCache cache diag_wrapper how_much = do - (errs, mod_graph) <- depanalE [] False -- #17459 msg <- mkBatchMsg <$> getSession + (errs, mod_graph) <- depanalE diag_wrapper (Just msg) [] False -- #17459 success <- load' cache how_much diag_wrapper (Just msg) mod_graph if isEmptyMessages errs then pure success @@ -506,7 +512,7 @@ loadWithCache cache diag_wrapper how_much = do -- Note [Unused packages] -- ~~~~~~~~~~~~~~~~~~~~~~ --- Cabal passes `--package-id` flag for each direct dependency. But GHC +-- Cabal passes `-package-id` flag for each direct dependency. But GHC -- loads them lazily, so when compilation is done, we have a list of all -- actually loaded packages. All the packages, specified on command line, -- but never loaded, are probably unused dependencies. @@ -1553,6 +1559,8 @@ type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either Driv -- module, plus one for any hs-boot files. The imports of these nodes -- are all there, including the imports of non-home-package modules. downsweep :: HscEnv + -> (GhcMessage -> AnyGhcDiagnostic) + -> Maybe Messager -> [ModSummary] -- ^ Old summaries -> [ModuleName] -- Ignore dependencies on these; treat @@ -1564,17 +1572,38 @@ downsweep :: HscEnv -- The non-error elements of the returned list all have distinct -- (Modules, IsBoot) identifiers, unless the Bool is true in -- which case there can be repeats -downsweep hsc_env old_summaries excl_mods allow_dup_roots +downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do + n_jobs <- mkWorkerLimit (hsc_dflags hsc_env) + new <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary + downsweep_imports hsc_env old_summary_map excl_mods allow_dup_roots new + where + summary = getRootSummary excl_mods old_summary_map + + -- A cache from file paths to the already summarised modules. The same file + -- can be used in multiple units so the map is also keyed by which unit the + -- file was used in. + -- Reuse these if we can because the most expensive part of downsweep is + -- reading the headers. + old_summary_map :: M.Map (UnitId, FilePath) ModSummary + old_summary_map = + M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries] + +downsweep_imports :: HscEnv + -> M.Map (UnitId, FilePath) ModSummary + -> [ModuleName] + -> Bool + -> ([(UnitId, DriverMessages)], [ModSummary]) + -> IO ([DriverMessages], [ModuleGraphNode]) +downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, rootSummariesOk) = do - (root_errs, rootSummariesOk) <- partitionWithM getRootSummary roots -- #17549 let root_map = mkRootMap rootSummariesOk checkDuplicates root_map (deps, map0) <- loopSummaries rootSummariesOk (M.empty, root_map) - let closure_errs = checkHomeUnitsClosed (hsc_unit_env hsc_env) - let unit_env = hsc_unit_env hsc_env - let tmpfs = hsc_tmpfs hsc_env + let closure_errs = checkHomeUnitsClosed unit_env + unit_env = hsc_unit_env hsc_env + tmpfs = hsc_tmpfs hsc_env - let downsweep_errs = lefts $ concat $ M.elems map0 + downsweep_errs = lefts $ concat $ M.elems map0 downsweep_nodes = M.elems deps (other_errs, unit_nodes) = partitionEithers $ unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env) @@ -1606,46 +1635,6 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ] logger = hsc_logger hsc_env - roots = hsc_targets hsc_env - - -- A cache from file paths to the already summarised modules. The same file - -- can be used in multiple units so the map is also keyed by which unit the - -- file was used in. - -- Reuse these if we can because the most expensive part of downsweep is - -- reading the headers. - old_summary_map :: M.Map (UnitId, FilePath) ModSummary - old_summary_map = M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries] - - getRootSummary :: Target -> IO (Either (UnitId, DriverMessages) ModSummary) - getRootSummary Target { targetId = TargetFile file mb_phase - , targetContents = maybe_buf - , targetUnitId = uid - } - = do let offset_file = augmentByWorkingDirectory dflags file - exists <- liftIO $ doesFileExist offset_file - if exists || isJust maybe_buf - then first (uid,) <$> - summariseFile hsc_env home_unit old_summary_map offset_file mb_phase - maybe_buf - else return $ Left $ (uid,) $ singleMessage - $ mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file) - where - dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env)) - home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env) - getRootSummary Target { targetId = TargetModule modl - , targetContents = maybe_buf - , targetUnitId = uid - } - = do maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot - (L rootLoc modl) (ThisPkg (homeUnitId home_unit)) - maybe_buf excl_mods - case maybe_summary of - FoundHome s -> return (Right s) - FoundHomeWithError err -> return (Left err) - _ -> return $ Left $ (uid, moduleNotFoundErr modl) - where - home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env) - rootLoc = mkGeneralSrcSpan (fsLit "") -- In a root module, the filename is allowed to diverge from the module -- name, so we have to check that there aren't multiple root files @@ -1713,7 +1702,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots loopImports ss done summarised | otherwise = do - mb_s <- summariseModule hsc_env home_unit old_summary_map + mb_s <- summariseModule hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg Nothing excl_mods case mb_s of @@ -1738,6 +1727,90 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots GWIB { gwib_mod = L loc mod, gwib_isBoot = is_boot } = gwib wanted_mod = L loc mod +getRootSummary :: + [ModuleName] -> + M.Map (UnitId, FilePath) ModSummary -> + HscEnv -> + Target -> + IO (Either (UnitId, DriverMessages) ModSummary) +getRootSummary excl_mods old_summary_map hsc_env target + | TargetFile file mb_phase <- targetId + = do + let offset_file = augmentByWorkingDirectory dflags file + exists <- liftIO $ doesFileExist offset_file + if exists || isJust maybe_buf + then first (uid,) <$> + summariseFile hsc_env home_unit old_summary_map offset_file mb_phase + maybe_buf + else + return $ Left $ (uid,) $ singleMessage $ + mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file) + | TargetModule modl <- targetId + = do + maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot + (L rootLoc modl) (ThisPkg (homeUnitId home_unit)) + maybe_buf excl_mods + pure case maybe_summary of + FoundHome s -> Right s + FoundHomeWithError err -> Left err + _ -> Left (uid, moduleNotFoundErr modl) + where + Target {targetId, targetContents = maybe_buf, targetUnitId = uid} = target + home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env) + rootLoc = mkGeneralSrcSpan (fsLit "") + dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env)) + +-- | Execute 'getRootSummary' for the 'Target's using the parallelism pipeline +-- system. +-- Create bundles of 'Target's wrapped in a 'MakeAction' that uses +-- 'withAbstractSem' to wait for a free slot, limiting the number of +-- concurrently computed summaries to the value of the @-j@ option or the slots +-- allocated by the job server, if that is used. +-- +-- The 'MakeAction' returns 'Maybe', which is not handled as an error, because +-- 'runLoop' only sets it to 'Nothing' when an exception was thrown, so the +-- result won't be read anyway here. +-- +-- To emulate the current behavior, we funnel exceptions past the concurrency +-- barrier and rethrow the first one afterwards. +rootSummariesParallel :: + WorkerLimit -> + HscEnv -> + (GhcMessage -> AnyGhcDiagnostic) -> + Maybe Messager -> + (HscEnv -> Target -> IO (Either (UnitId, DriverMessages) ModSummary)) -> + IO ([(UnitId, DriverMessages)], [ModSummary]) +rootSummariesParallel n_jobs hsc_env diag_wrapper msg get_summary = do + (actions, get_results) <- unzip <$> mapM action_and_result (zip [1..] bundles) + runPipelines n_jobs hsc_env diag_wrapper msg actions + (sequence . catMaybes <$> sequence get_results) >>= \case + Right results -> pure (partitionEithers (concat results)) + Left exc -> throwIO exc + where + bundles = mk_bundles targets + + mk_bundles = unfoldr \case + [] -> Nothing + ts -> Just (splitAt bundle_size ts) + + bundle_size = 20 + + targets = hsc_targets hsc_env + + action_and_result (log_queue_id, ts) = do + res_var <- liftIO newEmptyMVar + pure $! (MakeAction (action log_queue_id ts) res_var, readMVar res_var) + + action log_queue_id target_bundle = do + env at MakeEnv {compile_sem} <- ask + lift $ lift $ + withAbstractSem compile_sem $ + withLoggerHsc log_queue_id env \ lcl_hsc_env -> + MC.try (mapM (get_summary lcl_hsc_env) target_bundle) >>= \case + Left e | Just (_ :: SomeAsyncException) <- fromException e -> + throwIO e + a -> pure a + -- | This function checks then important property that if both p and q are home units -- then any dependency of p, which transitively depends on q is also a home unit. -- @@ -2455,12 +2528,12 @@ wrapAction msg_wrapper hsc_env k = do let lcl_logger = hsc_logger hsc_env lcl_dynflags = hsc_dflags hsc_env print_config = initPrintConfig lcl_dynflags - let logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err) + logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err) -- MP: It is a bit strange how prettyPrintGhcErrors handles some errors but then we handle -- SourceError and ThreadKilled differently directly below. TODO: Refactor to use `catches` -- directly. MP should probably use safeTry here to not catch async exceptions but that will regress performance due to -- internally using forkIO. - mres <- MC.try $ liftIO $ prettyPrintGhcErrors lcl_logger $ k + mres <- MC.try $ prettyPrintGhcErrors lcl_logger $ k case mres of Right res -> return $ Just res Left exc -> do @@ -2659,7 +2732,7 @@ R.hs: module R where == Why we need to rehydrate A's ModIface before compiling R.hs After compiling A.hs we'll have a TypeEnv in which the Id for `f` has a type -type uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same +that uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same AbstractTyCon. (Abstract because it came from R.hs-boot; we know nothing about it.) ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -86,6 +86,20 @@ type BaseName = OsPath -- Basename of file -- ----------------------------------------------------------------------------- -- The finder's cache +{- +[Note: Monotonic addToFinderCache] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +addToFinderCache is only used by functions that return the cached value +if there is one, or by functions that always write an InstalledFound value. +Without multithreading it is then safe to always directly write the value +without checking the previously cached value. + +However, with multithreading, it is possible that another function has +written a value into cache between the lookup and the addToFinderCache call. +in this case we should check to not overwrite an InstalledFound with an +InstalledNotFound. +-} initFinderCache :: IO FinderCache initFinderCache = do @@ -100,7 +114,12 @@ initFinderCache = do addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO () addToFinderCache key val = - atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ()) + atomicModifyIORef' mod_cache $ \c -> + case (lookupInstalledModuleWithIsBootEnv c key, val) of + -- Don't overwrite an InstalledFound with an InstalledNotFound + -- See [Note Monotonic addToFinderCache] + (Just InstalledFound{}, InstalledNotFound{}) -> (c, ()) + _ -> (extendInstalledModuleWithIsBootEnv c key val, ()) lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult) lookupFinderCache key = do ===================================== libraries/ghc-experimental/ghc-experimental.cabal.in ===================================== @@ -4,7 +4,9 @@ cabal-version: 3.0 -- Make sure you are editing ghc-experimental.cabal.in, not ghc-experimental.cabal name: ghc-experimental -version: 0.1.0.0 +-- The project is ghc's version plus ghc-experimental's version suffix. +-- For example, for ghc=9.10.1, ghc-experimental's version will be 9.1001.0. +version: @ProjectVersionForLib at .0 synopsis: Experimental features of GHC's standard library description: This package is where experimental GHC standard library interfaces start ===================================== testsuite/tests/ghc-api/downsweep/OldModLocation.hs ===================================== @@ -6,6 +6,7 @@ import GHC import GHC.Driver.Make import GHC.Driver.Session import GHC.Driver.Env +import GHC.Types.Error (mkUnknownDiagnostic) import GHC.Unit.Module.Graph import GHC.Unit.Finder @@ -47,13 +48,13 @@ main = do liftIO $ do - _emss <- downsweep hsc_env [] [] False + _emss <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env) createDirectoryIfMissing False "mydir" renameFile "B.hs" "mydir/B.hs" - (_, nodes) <- downsweep hsc_env [] [] False + (_, nodes) <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False -- If 'checkSummaryTimestamp' were to call 'addHomeModuleToFinder' with -- (ms_location old_summary) like summariseFile used to instead of ===================================== testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs ===================================== @@ -6,6 +6,7 @@ import GHC import GHC.Driver.Make import GHC.Driver.Session +import GHC.Types.Error (mkUnknownDiagnostic) import GHC.Utils.Outputable import GHC.Utils.Exception (ExceptionMonad) import GHC.Data.Bag @@ -168,7 +169,7 @@ go label mods cnd = setTargets [tgt] hsc_env <- getSession - (_, nodes) <- liftIO $ downsweep hsc_env [] [] False + (_, nodes) <- liftIO $ downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False it label $ cnd (mapMaybe moduleGraphNodeModSum nodes) ===================================== testsuite/tests/profiling/should_run/all.T ===================================== @@ -2,7 +2,6 @@ setTestOpts(js_skip) # JS backend doesn't support profiling yet prun_ways = (['prof'] if have_profiling() else []) + (['profdyn'] if have_dynamic_prof() else []) -print(prun_ways) # Options to use when comparing .prof files test_opts_dot_prof = [ only_ways(['prof', 'profdyn']) , extra_ways(prun_ways) if prun_ways else skip] ===================================== utils/haddock/haddock-api/src/Haddock/Interface.hs ===================================== @@ -170,7 +170,7 @@ createIfaces verbosity modules flags instIfaceMap = do _ <- setSessionDynFlags dflags'' targets <- mapM (\(filePath, _) -> guessTarget filePath Nothing Nothing) hs_srcs setTargets targets - (_errs, modGraph) <- depanalE [] False + (_errs, modGraph) <- depanalE mkUnknownDiagnostic (Just batchMsg) [] False -- Create (if necessary) and load .hi-files. With --no-compilation this happens later. when (Flag_NoCompilation `notElem` flags) $ do ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -140,7 +140,7 @@ binaryInterfaceMagic = 0xD0Cface -- binaryInterfaceVersion :: Word16 #if MIN_VERSION_ghc(9,11,0) && !MIN_VERSION_ghc(9,14,0) -binaryInterfaceVersion = 44 +binaryInterfaceVersion = 46 binaryInterfaceVersionCompatibility :: [Word16] binaryInterfaceVersionCompatibility = [binaryInterfaceVersion] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbb32e33f2e3dd8f735eb85afc5f7667640eec47...8d7b73d33a71a2fab8f5ac27813f3ecfe225c0fd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbb32e33f2e3dd8f735eb85afc5f7667640eec47...8d7b73d33a71a2fab8f5ac27813f3ecfe225c0fd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 11:01:38 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 04 Oct 2024 07:01:38 -0400 Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.8 Message-ID: <66ffcb1217308_3c14d52fe1e450488@gitlab.mail> Ben Gamari deleted branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 11:01:40 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 04 Oct 2024 07:01:40 -0400 Subject: [Git][ghc/ghc][ghc-9.8] 25 commits: refactor quadratic search in warnMissingHomeModules Message-ID: <66ffcb1437d5b_3c14d52a303c506f0@gitlab.mail> Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC Commits: 2459880b by Torsten Schmits at 2024-09-30T10:01:24-04:00 refactor quadratic search in warnMissingHomeModules (cherry picked from commit bc672166acd8f2815d58b6d214e69373abec4486) - - - - - e3007eea by Simon Peyton Jones at 2024-09-30T10:19:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! (cherry picked from commit be1e60eec0ec37da41643af17d78c698ab2a7083) - - - - - d3e48ec3 by Simon Peyton Jones at 2024-09-30T10:19:38-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code (cherry picked from commit 58408c77f126e685969756d30e050d308fea3786) - - - - - f330b422 by Simon Peyton Jones at 2024-09-30T10:29:29-04:00 Use HasDebugCallStack, rather than HasCallStack (cherry picked from commit e56871861c8a531feaa1a24e37fb56ba6c8cc690) - - - - - 7fed4765 by Simon Peyton Jones at 2024-09-30T14:15:22-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> (cherry picked from commit 5e4f4ba835fd24135759ee7a2d0d5c636a8a1505) - - - - - 491ec3a9 by Andreas Klebinger at 2024-09-30T14:15:43-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 (cherry picked from commit 0fe2b410ac0d8951f07ffcc9f3c6c97bc312df48) - - - - - 692474e0 by Matthew Pickering at 2024-09-30T14:16:08-04:00 Fix off by one error in seekBinNoExpand and seekBin (cherry picked from commit 28009fbc26e4aca7a3b05cedb60c5c9baa31223d) - - - - - ddf9da28 by Ben Gamari at 2024-09-30T14:16:54-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. (cherry picked from commit f8f384a8cc7212284379d109f6dc78c6188f3f18) - - - - - bcdf3e2c by Sylvain Henry at 2024-09-30T16:10:28-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). (cherry picked from commit b36ee57bfbecc628b7f0919e1e59b7066495034f) - - - - - e16be40c by Luite Stegeman at 2024-09-30T16:10:28-04:00 Update correct counter in bumpTickyAllocd (cherry picked from commit 0c4a96862081f03e2946a2ed7e80c108f06205a1) - - - - - 10a6aa18 by Rodrigo Mesquita at 2024-09-30T16:10:28-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. (cherry picked from commit 32a8103f3b3e22907fdd67b69c919c5251d8cc20) - - - - - 067aa6e0 by Zubin Duggal at 2024-09-30T16:10:28-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. (cherry picked from commit a933aff37992ea311a60be878379e7abf650e9fb) - - - - - b0a30ae7 by Cheng Shao at 2024-09-30T16:10:28-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. (cherry picked from commit 7db8c9927fae3369fc4ecff68f80c4cb32eea757) - - - - - ad7b46e7 by Cheng Shao at 2024-09-30T16:10:28-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. (cherry picked from commit 810660b780e1111b36c91326bcd0041e1f62706b) - - - - - 66148140 by Teo Camarasu at 2024-09-30T16:10:28-04:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 (cherry picked from commit 74b24a9b0084459b8aa426a502956bd332b4d0fb) - - - - - 894710fb by Rodrigo Mesquita at 2024-09-30T16:10:28-04:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS (cherry picked from commit 9460d5044b8c7239fb7a6ce875d084617f159c7f) - - - - - 5b3dc9c4 by Zubin Duggal at 2024-09-30T16:10:28-04:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job (cherry picked from commit f3de8a3c6f25b2c7eeb2ec6da95be24eeb496914) - - - - - 98b04cea by Andreas Klebinger at 2024-09-30T16:10:28-04:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 (cherry picked from commit 82ccb8012ba532f0fa06dc6ff96d33217560088a) - - - - - 69ed198f by Ian-Woo Kim at 2024-09-30T16:10:28-04:00 Add missing BCO handling in scavenge_one. (cherry picked from commit 902ebcc2b95707319d37a19d6b23c342cc14b162) - - - - - db376284 by Matthew Craven at 2024-09-30T16:10:28-04:00 Add @since annotation to Data.Data.mkConstrTag (cherry picked from commit 249caf0d2345ac2e6046847522bb8f2fff7f8835) - - - - - 2c18ff79 by Vladislav Zavialov at 2024-09-30T16:10:28-04:00 Fix (~) and (@) infix operators in TH splices (#23748) 8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept the following infix operators: a ~ b = () a @ b = () But not if TH is used to generate those declarations: $([d| a ~ b = () a @ b = () |]) -- Test.hs:5:2: error: [GHC-55017] -- Illegal variable name: ‘~’ -- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.() This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme (cherry picked from commit 46fd8ced0cc031f2e50a1a4b348738fd39b4a741) - - - - - c6a95d27 by Jade at 2024-09-30T16:10:29-04:00 Enhance documentation of Data.Complex (cherry picked from commit cdd939e77f2bb20f80310280400b3426598b4eca) - - - - - 930eb181 by Matthew Craven at 2024-10-03T11:30:15-04:00 testsuite: Give the pre_cmd for mhu-perf more time (cherry picked from commit dba03aababff057c03e2d92677de02d8375cd23a) - - - - - 0c24f3e2 by Cheng Shao at 2024-10-03T11:30:15-04:00 testsuite: give pre_cmd for mhu-perf 5x time (cherry picked from commit 0820750140af2972ca254a42c0fdc537f3b7c447) - - - - - 6bd62051 by Ben Gamari at 2024-10-03T18:16:53-04:00 Accept performance shifts MultiLayerModulesTH_Make performance regresses considerably, but bizarrely only on Darwin. Metric Increase: MultiLayerModulesTH_Make - - - - - 30 changed files: - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Utils.hs - compiler/GHC/Stg/Subst.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Gen/HsType.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e34ba65f6b3c0b58dcf28c1d17efe5211871e5a3...6bd62051db8abee470e4b5481a6a110c319d21cc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e34ba65f6b3c0b58dcf28c1d17efe5211871e5a3...6bd62051db8abee470e4b5481a6a110c319d21cc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 11:01:54 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Fri, 04 Oct 2024 07:01:54 -0400 Subject: [Git][ghc/ghc][wip/backports-9.8-2] 10 commits: Accept performance shifts Message-ID: <66ffcb22a7d05_3c14d52fe1e4508d8@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC Commits: 6bd62051 by Ben Gamari at 2024-10-03T18:16:53-04:00 Accept performance shifts MultiLayerModulesTH_Make performance regresses considerably, but bizarrely only on Darwin. Metric Increase: MultiLayerModulesTH_Make - - - - - 31458e17 by Teo Camarasu at 2024-10-04T11:01:49+00:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 (cherry picked from commit 84357d1143fe4f9076253160f78fac6c2acc8e5b) - - - - - e1a55f94 by Andreas Klebinger at 2024-10-04T11:01:49+00:00 Fix ffi callbacks with >6 args and non-64bit args. Check for ptr/int arguments rather than 64-bit width arguments when counting integer register arguments. The old approach broke when we stopped using exclusively W64-sized types to represent sub-word sized integers. Fixes #24314 (cherry picked from commit de589554386fc173a9019922851c05bb727e3450) - - - - - eb3cfe22 by Teo Camarasu at 2024-10-04T11:01:49+00:00 nonmoving: Add support for heap profiling Add support for heap profiling while using the nonmoving collector. We greatly simply the implementation by disabling concurrent collection for GCs when heap profiling is enabled. This entails that the marked objects on the nonmoving heap are exactly the live objects. Note that we match the behaviour for live bytes accounting by taking the size of objects on the nonmoving heap to be that of the segment's block rather than the object itself. Resolves #22221 (cherry picked from commit bedb4f0de102936099bda4e995cc83f1c344366c) - - - - - 96be2f8a by Teo Camarasu at 2024-10-04T11:01:49+00:00 docs: move -xn flag beside --nonmoving-gc It makes sense to have these beside each other as they are aliases. (cherry picked from commit 98166389e166d4ab7cc2ddbc044261e508859de1) - - - - - a11df2e8 by Teo Camarasu at 2024-10-04T11:01:49+00:00 nonmoving: introduce a family of dense allocators Supplement the existing power 2 sized nonmoving allocators with a family of dense allocators up to a configurable threshold. This should reduce waste from rounding up block sizes while keeping the amount of allocator sizes manageable. This patch: - Adds a new configuration option `--nonmoving-dense-allocator-count` to control the amount of these new dense allocators. - Adds some constants to `NonmovingAllocator` in order to keep marking fast with the new allocators. Resolves #23340 (cherry picked from commit f830d5a34c4c972cced73b6dc25954cedf336747) (cherry picked from commit 47e02c2ae0ea4713a2f22edf21b9a4eb5fe635be) - - - - - fa8dd0ce by Teo Camarasu at 2024-10-04T11:01:49+00:00 rts: use live words to estimate heap size We use live words rather than live blocks to determine the size of the heap for determining memory retention. Most of the time these two metrics align, but they can come apart in normal usage when using the nonmoving collector. The nonmoving collector leads to a lot of partially occupied blocks. So, using live words is more accurate. They can also come apart when the heap is suffering from high levels fragmentation caused by small pinned objects, but in this case, the block size is the more accurate metric. Since this case is best avoided anyway. It is ok to accept the trade-off that we might try (and probably) fail to return more memory in this case. See also the Note [Statistics for retaining memory] Resolves #23397 (cherry picked from commit 35ef8dc83428f5405e092b12eb8cfc440b6504d8) (cherry picked from commit 7991656954a2ba7d66fd75a8202af7d86327f279) - - - - - 5d14190b by Ben Gamari at 2024-10-04T11:01:49+00:00 Add changelog entry for #23340 (cherry picked from commit 2b07bf2e8bcb24520fe78b469c3550b9f4099526) - - - - - 112fa27d by Simon Peyton Jones at 2024-10-04T11:01:49+00:00 Update the unification count in wrapUnifierX Omitting this caused type inference to fail in #24146. This was an accidental omision in my refactoring of the equality solver. - - - - - 926eceaf by Fendor at 2024-10-04T11:01:49+00:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. (cherry picked from commit 31bf85ee49fe2ca0b17eaee0774e395f017a9373) (cherry picked from commit d74ffbbb93cb377e64c557f777089b81710ef873) - - - - - 30 changed files: - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/Tc/Solver/Monad.hs - docs/users_guide/9.8.3-notes.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/runtime_control.rst - hadrian/src/Rules/Generate.hs - rts/Capability.h - rts/ProfHeap.c - rts/RtsFlags.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/gen_event_types.py - rts/include/rts/Flags.h - rts/include/rts/storage/Block.h - rts/sm/GC.c - rts/sm/NonMoving.c - rts/sm/NonMoving.h - rts/sm/NonMovingAllocate.c - rts/sm/NonMovingCensus.c - rts/sm/Sanity.c - rts/sm/Storage.c - rts/sm/Storage.h - + testsuite/tests/ffi/should_run/T24314.hs - + testsuite/tests/ffi/should_run/T24314.stdout - + testsuite/tests/ffi/should_run/T24314_c.c - testsuite/tests/ffi/should_run/all.T - + testsuite/tests/ghc-api/settings-escape/T11938.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7da0c0a847d2e5e8c965d7373ac084a8c8dfe6c9...926eceafa1f3199220047ac7c0bec612414c4a6e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7da0c0a847d2e5e8c965d7373ac084a8c8dfe6c9...926eceafa1f3199220047ac7c0bec612414c4a6e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 11:11:53 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 04 Oct 2024 07:11:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/t25538 Message-ID: <66ffcd7931cda_3c14d54c3ed454758@gitlab.mail> Matthew Pickering pushed new branch wip/t25538 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/t25538 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 11:33:52 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Fri, 04 Oct 2024 07:33:52 -0400 Subject: [Git][ghc/ghc][wip/9.12-submodule-bumps] Deleted 1 commit: Bump xhtml submodule to master Message-ID: <66ffd2a08f0e4_3c14d56435ac58121@gitlab.mail> Zubin pushed to branch wip/9.12-submodule-bumps at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: 40ee2fca by Zubin Duggal at 2024-10-03T15:46:16+05:30 Bump xhtml submodule to master This will also be version 3000.4.0.0 hopefully: https://github.com/haskell/xhtml/issues/21 - - - - - 1 changed file: - libraries/xhtml Changes: ===================================== libraries/xhtml ===================================== @@ -1 +1 @@ -Subproject commit 68353ccd1a2e776d6c2b11619265d8140bb7dc07 +Subproject commit 2dc0c48bc0f37c17afc88c8d6c8cacae5ea9188d View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/40ee2fcaeee497e94e206670a352c053cd3494d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/40ee2fcaeee497e94e206670a352c053cd3494d2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 12:12:11 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 04 Oct 2024 08:12:11 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T20815 Message-ID: <66ffdb9bc623e_3c14d58bab7861576@gitlab.mail> Simon Peyton Jones pushed new branch wip/T20815 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T20815 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 12:16:30 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 04 Oct 2024 08:16:30 -0400 Subject: [Git][ghc/ghc][wip/T25281] Yet more Message-ID: <66ffdc9e7bb81_3c14d58b0e0c633c7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: bf68253d by Simon Peyton Jones at 2024-10-04T13:16:16+01:00 Yet more - - - - - 4 changed files: - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Types/Id.hs Changes: ===================================== compiler/GHC/Core/SimpleOpt.hs ===================================== @@ -1340,8 +1340,7 @@ exprIsConApp_maybe ise@(ISE in_scope id_unf) expr -- [Activation for data constructor wrappers]) but we want to do -- case-of-known-constructor optimisation eagerly (see Note -- [exprIsConApp_maybe on data constructors with wrappers]). - | isDataConWrapId fun - , let rhs = uf_tmpl (realIdUnfolding fun) + | Just rhs <- dataConWrapUnfolding_maybe fun = go (Left in_scope) floats rhs cont -- Look through dictionary functions; see Note [Unfolding DFuns] ===================================== compiler/GHC/Hs/Stats.hs ===================================== @@ -134,9 +134,8 @@ ppSourceStats short (L _ (HsModule{ hsmodExports = exports, hsmodImports = impor spec_info (Just (Exactly, _)) = (0,0,0,0,0,1,0) spec_info (Just (EverythingBut, _)) = (0,0,0,0,0,0,1) - data_info (DataDecl { tcdDataDefn = HsDataDefn - { dd_cons = cs - , dd_derivs = derivs}}) + data_info (DataDecl { tcdDataDefn = dd :: HsDataDefn GhcPs }) + | HsDataDefn { dd_cons = cs, dd_derivs = derivs} <- dd = ( length cs , foldl' (\s dc -> length (deriv_clause_tys $ unLoc dc) + s) 0 derivs ) ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -247,7 +247,7 @@ addTickLHsBind (L pos (XHsBindsLR bind@(AbsBinds { abs_binds = binds | ABE{ abe_poly = pid, abe_mono = mid } <- abs_exports , isInlinePragma (idInlinePragma pid) ] } -addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id }))) = do +addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches }))) = do let name = getOccString id decl_path <- getPathEntry density <- getDensity @@ -264,7 +264,7 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id }))) = do (fvs, mg) <- getFreeVars $ addPathEntry name $ - addTickMatchGroup False (fun_matches funBind) + addTickMatchGroup False matches blackListed <- isBlackListed (locA pos) exported_names <- liftM exports getEnv @@ -272,7 +272,9 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id }))) = do -- We don't want to generate code for blacklisted positions -- We don't want redundant ticks on simple pattern bindings -- We don't want to tick non-exported bindings in TickExportedFunctions - let simple = isSimplePatBind funBind + let simple = matchGroupArity matches == 0 + -- A binding is a "simple pattern binding" if it is a + -- funbind with zero patterns toplev = null decl_path exported = idName id `elemNameSet` exported_names @@ -288,15 +290,10 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id }))) = do , fun_ext = second (tick `mbCons`) (fun_ext funBind) } } - where - -- a binding is a simple pattern binding if it is a funbind with - -- zero patterns - isSimplePatBind :: HsBind GhcTc -> Bool - isSimplePatBind funBind = matchGroupArity (fun_matches funBind) == 0 - -- TODO: Revisit this addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs - , pat_rhs = rhs }))) = do + , pat_rhs = rhs + , pat_ext = (grhs_ty, initial_ticks}))) = do let simplePatId = isSimplePat lhs @@ -314,14 +311,12 @@ addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs then return (L pos pat') else do - let mbCons = maybe id (:) - - let (initial_rhs_ticks, initial_patvar_tickss) = snd $ pat_ext pat' - -- Allocate the ticks - rhs_tick <- bindTick density name (locA pos) fvs - let rhs_ticks = rhs_tick `mbCons` initial_rhs_ticks + + let mbCons = maybe id (:) + (initial_rhs_ticks, initial_patvar_tickss) = initial_ticks + rhs_ticks = rhs_tick `mbCons` initial_rhs_ticks patvar_tickss <- case simplePatId of Just{} -> return initial_patvar_tickss @@ -332,7 +327,7 @@ addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs (zipWith mbCons patvar_ticks (initial_patvar_tickss ++ repeat [])) - return $ L pos $ pat' { pat_ext = second (const (rhs_ticks, patvar_tickss)) (pat_ext pat') } + return $ L pos $ pat' { pat_ext = (ghhs_ty, (rhs_ticks, patvar_tickss)) } -- Only internal stuff, not from source, uses VarBind, so we ignore it. addTickLHsBind var_bind@(L _ (VarBind {})) = return var_bind ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -141,7 +141,9 @@ import GHC.Types.Var( Id, CoVar, JoinId, setIdMult, updateIdTypeAndMult, updateIdTypeButNotMult, updateIdTypeAndMultM) import qualified GHC.Types.Var as Var -import GHC.Core +import GHC.Core ( CoreExpr, CoreRule, Unfolding(..), IdUnfoldingFun + , isStableUnfolding, isCompulsoryUnfolding, isEvaldUnfolding + , hasSomeUnfolding, noUnfolding, evaldUnfolding ) import GHC.Core.Type import GHC.Core.Predicate( isCoVarType ) import GHC.Core.DataCon View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bf68253dee300d576ab478d48490ad6c2f26906b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bf68253dee300d576ab478d48490ad6c2f26906b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 13:32:11 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 04 Oct 2024 09:32:11 -0400 Subject: [Git][ghc/ghc][wip/romes/25330] Deprecation for WarnCompatUnqualifiedImports Message-ID: <66ffee5b655a3_3c14d5ed6fd478722@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25330 at Glasgow Haskell Compiler / GHC Commits: 515bc67e by Rodrigo Mesquita at 2024-10-04T14:31:59+01:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 30 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/using-warnings.rst - libraries/base/tests/T9586.hs - libraries/base/tests/list001.hs - testsuite/tests/ghci/scripts/T14828.script - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci036.script - testsuite/tests/module/Mod137_A.hs - testsuite/tests/module/Mod138_A.hs - testsuite/tests/module/Mod141_A.hs - testsuite/tests/module/mod154.hs - testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs - testsuite/tests/perf/compiler/T16875.hs - testsuite/tests/perf/compiler/T16875.stderr - testsuite/tests/rename/prog001/rn037.hs - testsuite/tests/rename/should_compile/T17244A.hs - + testsuite/tests/rename/should_compile/T17244A.stderr - testsuite/tests/rename/should_compile/T17244B.hs - testsuite/tests/rename/should_compile/T17244B.stderr - testsuite/tests/rename/should_compile/T17244C.hs - testsuite/tests/rename/should_compile/T17244C.stderr - testsuite/tests/rename/should_compile/T4478.hs - testsuite/tests/rename/should_compile/T7167.hs - testsuite/tests/rename/should_compile/T7167.stderr - testsuite/tests/rename/should_compile/rn025.hs - testsuite/tests/rename/should_compile/rn027.hs - testsuite/tests/rename/should_compile/rn031.hs - testsuite/tests/rename/should_compile/rn060.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/515bc67e8447696311b4cb22fd0757bf33f29108 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/515bc67e8447696311b4cb22fd0757bf33f29108 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 14:09:16 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 04 Oct 2024 10:09:16 -0400 Subject: [Git][ghc/ghc][wip/exception-propagate] 3 commits: base: Add `HasCallStack` constraint to `ioError` Message-ID: <66fff70c191f5_338d461117a010173f@gitlab.mail> Rodrigo Mesquita pushed to branch wip/exception-propagate at Glasgow Haskell Compiler / GHC Commits: 876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00 base: Add `HasCallStack` constraint to `ioError` As proposed in core-libraries-committee#275. - - - - - 9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00 Fix toException method for ExceptionWithContext Fixes #25235 - - - - - ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - 30 changed files: - libraries/base/changelog.md - libraries/base/src/Control/Exception.hs - libraries/base/tests/IO/T21336/T21336b.stderr - libraries/base/tests/IO/T4808.stderr - libraries/base/tests/IO/mkdirExists.stderr - libraries/base/tests/IO/openFile002.stderr - libraries/base/tests/IO/openFile002.stderr-mingw32 - libraries/base/tests/IO/withBinaryFile001.stderr - libraries/base/tests/IO/withBinaryFile002.stderr - libraries/base/tests/IO/withFile001.stderr - libraries/base/tests/IO/withFile002.stderr - libraries/base/tests/IO/withFileBlocking001.stderr - libraries/base/tests/IO/withFileBlocking002.stderr - libraries/base/tests/T15349.stderr - libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs - libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs - libraries/ghc-internal/src/GHC/Internal/IO.hs - libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs - libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs - testsuite/tests/codeGen/should_run/cgrun016.stderr - testsuite/tests/codeGen/should_run/cgrun025.stderr - testsuite/tests/concurrent/should_run/T3279.hs - testsuite/tests/ffi/should_run/T7170.stderr - testsuite/tests/ghc-e/should_fail/T18441fail2.stderr - testsuite/tests/ghc-e/should_fail/T18441fail7.stderr - testsuite/tests/ghc-e/should_fail/T18441fail8.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/abf9d4044d100cfd18721bdfe8d0332973403835...ac0040286a8962b728a7cdb3c1be4691db635366 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/abf9d4044d100cfd18721bdfe8d0332973403835...ac0040286a8962b728a7cdb3c1be4691db635366 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 14:38:32 2024 From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi)) Date: Fri, 04 Oct 2024 10:38:32 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] simplified design based on Simon's suggestions. Let see if it passes the tests... Message-ID: <66fffde85bdf7_30be0015988488874@gitlab.mail> Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: fa5fc587 by Hassan Al-Awwadi at 2024-10-04T16:38:03+02:00 simplified design based on Simon's suggestions. Let see if it passes the tests or if I broke something. - - - - - 13 changed files: - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/Pat.hs - compiler/Language/Haskell/Syntax/Type.hs - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -557,11 +557,6 @@ deriving instance Data (ConDeclField GhcTc) deriving instance Data (FieldOcc GhcPs) deriving instance Data (FieldOcc GhcRn) deriving instance Data (FieldOcc GhcTc) -deriving instance Data AmbiguousFieldOcc - -deriving instance Data (UpdFieldOcc GhcPs) -deriving instance Data (UpdFieldOcc GhcRn) -deriving instance Data (UpdFieldOcc GhcTc) -- deriving instance (DataId name) => Data (ImportDecl name) deriving instance Data (ImportDecl GhcPs) ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -59,12 +59,8 @@ module GHC.Hs.Type ( ConDeclField(..), LConDeclField, pprConDeclFields, HsConDetails(..), noTypeArgs, - UpdFieldOcc(..), LUpdFieldOcc, mkUpdFieldOcc, - updFieldOccRdrName, updFieldOccLRdrName, FieldOcc(..), LFieldOcc, mkFieldOcc, fieldOccRdrName, fieldOccLRdrName, - AmbiguousFieldOcc(..), - ambiguousFieldOccRdrName, OpName(..), @@ -1088,7 +1084,7 @@ also forbids them in types involved with `deriving`: * * ************************************************************************ -Note [Lifecycle of FieldOcc/UpdFieldOcc] +Note [Ambiguous FieldOcc in record updates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When renaming a "record field update" (`some_record{ field = expr }`), the field occurrence may be ambiguous if there are multiple record types with that same @@ -1096,64 +1092,22 @@ field label in scope. Instead of failing, we may attempt to do type-directed disambiguation: if we typecheck the record field update, we can disambiguate the `field` based on the record and field type. -In practice, this means an identifier of an update field occurrence -(`UpdFieldOcc`) may have to go straight from `RdrName` to `Id`, since field +In practice, this means an identifier of a field occurrence +(`FieldOcc`) may have to go straight from `RdrName` to `Id`, since field ambiguity makes it impossible to construct a `Name` for the field. Since type-directed disambiguation is a GHC property rather than a property of -the GHC-Haskell AST, we still parametrise an `UpdFieldOcc` occurrence by `IdP p`, -but introduce a constructor `AmbiguousFieldOcc` in the `XXUpdFieldOcc` extension point. -That is: - - * `AmbiguousFieldOcc @GhcRn :: RdrName -> UpdFieldOcc` - * `UpdFieldOcc @GhcRn :: Name -> UpdFieldOcc` - -If the update field occurrence is ambiguous, the renamer will construct it with -`AmbiguousFieldOcc`. Otherwise, it'll use `UpdFieldOcc` -- an unambiguous -update field occurrence. - -In @GhcTc the `UpdFieldOcc` extension point is "deleted" since all field -occurrences after type checking must be unambiguous. - -A `FieldOcc` is a field occurrence that /does not/ occur in a record update, c.f. `UpdFieldOcc`. -Non-update field occurrences are always unambiguous. - -The lifecycle of an UpdFieldOcc is as follows -* GhcPs: - - UpdFieldOcc noExtField (FieldOcc GhcPs) - - XUpdFieldOcc DataConCantHappen -* GhcRn: - - UpdFieldOcc noExtField (FieldOCc GhcRn) - - XUpdFieldOcc /AmbiguousFieldOcc/ -* GhcTc: - - UpdFieldOcc noExtField (FieldOCc GhcRn) - - XUpdFieldOcc DataConCantHappen - -The lifecycle of a FieldOcc is more straightforward: -* GhcPs: FieldOcc noExtField RdrName -* GhcRn: FieldOcc RdrName Name -* GhcTc: FieldOcc RdrName Id +the GHC-Haskell AST, we still parameterise a `FieldOcc` occurrence by `IdP p`, +but in the case of the ambiguity we do the unthinkable and insert a mkUnboundName +in the name. Very bad, yes, but since type-directed disambiguation is on the way +out (see ticket #18966), we consider this acceptable for now. + +see also Wrinkle [Disambiguating fields] and note [Type-directed record disambiguation] NB: FieldOcc preserves the RdrName throughout its lifecycle for exact printing purposes. -} --- | Ambiguous Field Occurrence --- --- Represents an *occurrence* of a field that is definiely --- ambiguous after the renamer, with the ambiguity resolved by the --- typechecker. We always store the 'RdrName' that the user --- originally wrote, and store the selector function after the typechecker (for --- ambiguous occurrences). --- --- Unambiguous field occurrences should be stored in the proper --- UpdFieldOcc datacon of UpdFieldOcc. --- --- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat". --- See Note [Located RdrNames] in "GHC.Hs.Expr". -newtype AmbiguousFieldOcc - = Ambiguous (LocatedN RdrName) - type instance XCFieldOcc GhcPs = NoExtField -- RdrName is stored in the proper IdP field type instance XCFieldOcc GhcRn = RdrName type instance XCFieldOcc GhcTc = RdrName @@ -1162,33 +1116,11 @@ type instance XXFieldOcc GhcPs = DataConCantHappen type instance XXFieldOcc GhcRn = DataConCantHappen type instance XXFieldOcc GhcTc = DataConCantHappen -type instance XCUpdFieldOcc GhcPs = NoExtField -type instance XCUpdFieldOcc GhcRn = NoExtField -type instance XCUpdFieldOcc GhcTc = NoExtField - -type instance XXUpdFieldOcc GhcPs = DataConCantHappen -type instance XXUpdFieldOcc GhcRn = AmbiguousFieldOcc -type instance XXUpdFieldOcc GhcTc = DataConCantHappen - -------------------------------------------------------------------------------- -mkUpdFieldOcc :: LocatedN RdrName -> UpdFieldOcc GhcPs -mkUpdFieldOcc rdr@(L l _) = UpdFieldOcc noExtField (L (l2l l) $ mkFieldOcc rdr) - mkFieldOcc :: LocatedN RdrName -> FieldOcc GhcPs mkFieldOcc rdr = FieldOcc noExtField rdr -updFieldOccRdrName :: forall p. IsPass p => UpdFieldOcc (GhcPass p) -> RdrName -updFieldOccRdrName = unLoc . updFieldOccLRdrName - -updFieldOccLRdrName :: forall p. IsPass p => UpdFieldOcc (GhcPass p) -> LocatedN RdrName -updFieldOccLRdrName (UpdFieldOcc _ (L _ fo)) = fieldOccLRdrName fo -updFieldOccLRdrName (XUpdFieldOcc xfo) = case ghcPass @p of - GhcRn -> case xfo of - Ambiguous l -> l - GhcPs -> dataConCantHappen xfo - GhcTc -> dataConCantHappen xfo - fieldOccRdrName :: forall p. IsPass p => FieldOcc (GhcPass p) -> RdrName fieldOccRdrName fo = case ghcPass @p of GhcPs -> unLoc $ foLabel fo @@ -1206,19 +1138,6 @@ fieldOccLRdrName fo = case ghcPass @p of let (L l _) = foLabel fo in L l (foExt fo) -instance Outputable AmbiguousFieldOcc where - ppr = ppr . ambiguousFieldOccRdrName - -instance OutputableBndr AmbiguousFieldOcc where - pprInfixOcc = pprInfixOcc . ambiguousFieldOccRdrName - pprPrefixOcc = pprPrefixOcc . ambiguousFieldOccRdrName - -instance OutputableBndr (Located AmbiguousFieldOcc) where - pprInfixOcc = pprInfixOcc . unLoc - pprPrefixOcc = pprPrefixOcc . unLoc - -ambiguousFieldOccRdrName :: AmbiguousFieldOcc -> RdrName -ambiguousFieldOccRdrName (Ambiguous rdr) = unLoc rdr {- ************************************************************************ @@ -1359,12 +1278,6 @@ instance (OutputableBndrId pass) => OutputableBndr (GenLocated SrcSpan (FieldOcc pprInfixOcc = pprInfixOcc . unLoc pprPrefixOcc = pprPrefixOcc . unLoc -instance (IsPass p) => Outputable (UpdFieldOcc (GhcPass p))where - ppr = ppr . updFieldOccRdrName - -instance (IsPass p) => OutputableBndr (UpdFieldOcc (GhcPass p)) where - pprInfixOcc = pprInfixOcc . updFieldOccRdrName - pprPrefixOcc = pprPrefixOcc . updFieldOccRdrName ppr_tylit :: (HsTyLit (GhcPass p)) -> SDoc @@ -1663,5 +1576,3 @@ type instance Anno HsIPName = EpAnnCO type instance Anno (ConDeclField (GhcPass p)) = SrcSpanAnnA type instance Anno (FieldOcc (GhcPass p)) = SrcSpanAnnA -type instance Anno AmbiguousFieldOcc = SrcSpanAnnA -type instance Anno (UpdFieldOcc (GhcPass p)) = SrcSpanAnnA ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1823,12 +1823,11 @@ repUpdFields = repListM fieldExpTyConName rep_fld where rep_fld :: LHsRecUpdField GhcRn GhcRn -> MetaM (Core (M TH.FieldExp)) rep_fld (L l fld) = case unLoc (hfbLHS fld) of - UpdFieldOcc _ (L _ (FieldOcc _ (L _ sel_name))) -> + (FieldOcc _ (L _ sel_name)) -> do { fn <- lookupLOcc (L l sel_name) ; e <- repLE (hfbRHS fld) ; repFieldExp fn e } - (XUpdFieldOcc _) -> notHandled (ThAmbiguousRecordUpdates fld) ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -828,7 +828,6 @@ class ( HiePass (NoGhcTcPass p) , Data (Stmt (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) , Data (HsExpr (GhcPass p)) , Data (HsCmd (GhcPass p)) - , Data AmbiguousFieldOcc , Data (HsCmdTop (GhcPass p)) , Data (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) , Data (HsUntypedSplice (GhcPass p)) @@ -1509,10 +1508,6 @@ instance ( ToHie (RFContext label) , toHie expr ] -instance HiePass p => ToHie (RFContext (LocatedA (UpdFieldOcc (GhcPass p)))) where - toHie (RFC c rhs (L nspan (UpdFieldOcc _ (L _ fo)))) = concatM - [toHie (RFC c rhs (L nspan fo))] - toHie (RFC _ _ (L _ (XUpdFieldOcc _))) = concatM [] instance HiePass p => ToHie (RFContext (LocatedA (FieldOcc (GhcPass p)))) where toHie (RFC c rhs (L nspan f)) = concatM $ case hiePass @p of ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -2912,7 +2912,7 @@ mkRdrRecordUpd overloaded_on exp@(L loc _) fbinds anns = do True -> do let qualifiedFields = [ L l lbl | L _ (HsFieldBind _ (L l lbl) _ _) <- fs' - , isQual . updFieldOccRdrName $ lbl + , isQual . fieldOccRdrName $ lbl ] case qualifiedFields of qf:_ -> addFatalError $ mkPlainErrorMsgEnvelope (getLocA qf) $ @@ -2958,7 +2958,7 @@ mk_rec_fields fs (Just s) = HsRecFields { rec_ext = noExtField, rec_flds = fs mk_rec_upd_field :: HsRecField GhcPs (LHsExpr GhcPs) -> HsRecUpdField GhcPs GhcPs mk_rec_upd_field (HsFieldBind noAnn (L loc (FieldOcc _ rdr)) arg pun) - = HsFieldBind noAnn (L loc $ UpdFieldOcc noExtField (L loc (FieldOcc noExtField rdr))) arg pun + = HsFieldBind noAnn (L loc (FieldOcc noExtField rdr)) arg pun mkInlinePragma :: SourceText -> (InlineSpec, RuleMatchInfo) -> Maybe Activation -> InlinePragma ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -1526,7 +1526,7 @@ lookupGlobalOccRn_overloaded rdr_name = return (Just gre) } getFieldUpdLbl :: IsPass p => LHsRecUpdField (GhcPass p) q -> LocatedN RdrName -getFieldUpdLbl = updFieldOccLRdrName . unLoc . hfbLHS . unLoc +getFieldUpdLbl = fieldOccLRdrName . unLoc . hfbLHS . unLoc -- | Returns all possible collections of field labels for the given -- record update. @@ -1623,7 +1623,7 @@ lookupRecUpdFields flds getUpdFieldLbls :: forall p q. IsPass p => [LHsRecUpdField (GhcPass p) q] -> [RdrName] getUpdFieldLbls - = map $ updFieldOccRdrName + = map $ fieldOccRdrName . unXRec @(GhcPass p) . hfbLHS . unXRec @(GhcPass p) ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -890,7 +890,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) -> Maybe Name -- The constructor (Nothing for an -- out of scope constructor) -> [LHsRecField GhcRn (LocatedA arg)] -- Explicit fields - -> RnM ([LHsRecField GhcRn (LocatedA arg)]) -- Field Labels we need to fill in + -> RnM [LHsRecField GhcRn (LocatedA arg)] -- Field Labels we need to fill in rn_dotdot (Just (L loc_e (RecFieldsDotDot n))) (Just con) flds -- ".." on record construction / pat match | not (isUnboundName con) -- This test is because if the constructor -- isn't in scope the constructor lookup will add @@ -1018,7 +1018,7 @@ rnHsRecUpdFields flds -> RnM ([LHsRecUpdField GhcRn GhcRn], FreeVars) rn_flds _ _ [] = return ([], emptyFVs) rn_flds pun_ok mb_unambig_lbls - ((L l (HsFieldBind { hfbLHS = L loc (UpdFieldOcc _ (L _ (FieldOcc _ f))) + ((L l (HsFieldBind { hfbLHS = L loc (FieldOcc _ f) , hfbRHS = arg , hfbPun = pun })):flds) = do { let lbl = unLoc f @@ -1030,12 +1030,15 @@ rnHsRecUpdFields flds ; return (L (l2l loc) (HsVar noExtField (L (l2l loc) arg_rdr))) } else return arg ; (arg'', fvs) <- rnLExpr arg' - ; let lbl' :: UpdFieldOcc GhcRn + ; let lbl' :: FieldOcc GhcRn lbl' = case mb_unambig_lbls of { Just (fl:_) -> let sel_name = flSelector fl - in UpdFieldOcc noExtField (L (l2l loc) (FieldOcc lbl (L (l2l loc) sel_name))) - ; _ -> XUpdFieldOcc (Ambiguous (L (l2l loc) lbl)) } + in FieldOcc lbl (L (l2l loc) sel_name) + -- We have one last chance to be disambiguated during type checking. + -- At least, until type-directed disambiguation stops being supported. + -- see note [Ambiguous FieldOcc in record updates] for more info. + ; _ -> FieldOcc lbl (L (l2l loc) (mkUnboundName $ rdrNameOcc lbl)) } fld' :: LHsRecUpdField GhcRn GhcRn fld' = L l (HsFieldBind { hfbAnn = noAnn , hfbLHS = L (l2l loc) lbl' @@ -1043,8 +1046,6 @@ rnHsRecUpdFields flds , hfbPun = pun }) ; (flds', fvs') <- rn_flds pun_ok (tail <$> mb_unambig_lbls) flds ; return (fld' : flds', fvs `plusFV` fvs') } - rn_flds _ _ ((L _ (HsFieldBind { hfbLHS = L _ (XUpdFieldOcc impossible ) })):_) - = dataConCantHappen impossible getFieldIds :: [LHsRecField GhcRn arg] -> [Name] getFieldIds flds = map (hsRecFieldSel . unLoc) flds ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1298,12 +1298,10 @@ expandRecordUpd record_expr possible_parents rbnds res_ty -- See Note [Disambiguating record updates] in GHC.Rename.Pat. ; (cons, rbinds) <- disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty - ; let upd_flds = map (unLoc . hfbLHS . unLoc) rbinds - -- upd_flds has type 'UpdFieldOcc GhcTc' so ufoField is not partial here. - sel_ids = map (unLoc . foLabel . unLoc . ufoField) upd_flds + ; let sel_ids = map (unLoc . foLabel . unLoc . hfbLHS . unLoc) rbinds upd_fld_names = map idName sel_ids relevant_cons = nonDetEltsUniqSet cons - relevant_con = head relevant_cons + relevant_con = head relevant_cons -- STEP 2: expand the record update. -- @@ -1583,7 +1581,7 @@ disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty -> TcM (LHsRecUpdField GhcTc GhcRn) lookupField fld_gre (L l upd) = do { let L loc af = hfbLHS upd - lbl = updFieldOccRdrName af + lbl = fieldOccRdrName af mb_gre = pickGREs lbl [fld_gre] -- NB: this GRE can be 'Nothing' when in GHCi. -- See test T10439. @@ -1595,7 +1593,7 @@ disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty ; sel <- tcLookupId (greName fld_gre) ; return $ L l HsFieldBind { hfbAnn = hfbAnn upd - , hfbLHS = L (l2l loc) (UpdFieldOcc noExtField (L (l2l loc) $ FieldOcc lbl (L (l2l loc) sel))) + , hfbLHS = L (l2l loc) (FieldOcc lbl (L (l2l loc) sel)) , hfbRHS = hfbRHS upd , hfbPun = hfbPun upd } } ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1159,7 +1159,7 @@ cvtl e = wrapLA (cvt e) ; return $ mkRdrRecordCon c' (HsRecFields noExtField flds' Nothing) noAnn } cvt (RecUpdE e flds) = do { e' <- cvtl e ; flds' - <- mapM (cvtFld (wrapParLA mkUpdFieldOcc)) + <- mapM (cvtFld (wrapParLA mkFieldOcc)) flds ; return $ RecordUpd noAnn e' $ RegularRecUpdFields ===================================== compiler/Language/Haskell/Syntax/Extension.hs ===================================== @@ -685,9 +685,6 @@ type family XXConDeclField x -- --------------------------------------------------------------------- -- FieldOcc type families -type family XCUpdFieldOcc x -type family XXUpdFieldOcc x - type family XCFieldOcc x type family XXFieldOcc x ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -319,14 +319,14 @@ type LHsFieldBind p id arg = XRec p (HsFieldBind id arg) -- | Located Haskell Record Field type LHsRecField p arg = XRec p (HsRecField p arg) --- | Located Haskell Record Update Field -type LHsRecUpdField p q = XRec p (HsRecUpdField p q) - -- | Haskell Record Field type HsRecField p arg = HsFieldBind (LFieldOcc p) arg +-- | Located Haskell Record Update Field +type LHsRecUpdField p q = XRec p (HsRecUpdField p q) + -- | Haskell Record Update Field -type HsRecUpdField p q = HsFieldBind (LUpdFieldOcc p) (LHsExpr q) +type HsRecUpdField p q = HsFieldBind (LFieldOcc p) (LHsExpr q) -- | Haskell Field Binding -- ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -54,7 +54,6 @@ module Language.Haskell.Syntax.Type ( HsConDetails(..), noTypeArgs, - UpdFieldOcc(..), LUpdFieldOcc, FieldOcc(..), LFieldOcc, mapHsOuterImplicit, @@ -1352,21 +1351,6 @@ The SrcSpan is the span of the original HsPar * * ************************************************************************ -} --- | Located Update Field Occurrence -type LUpdFieldOcc pass = XRec pass (UpdFieldOcc pass) - --- | An update field occurrence is a field occurrence that --- occurs in an update position (such as @x{field=...}@). --- --- We differentiate between the two since there may be additional information concerning the update field. --- In particular, in GHC, an update field occurrence *may* be ambiguous, unlike other field occurrences. --- See Note [Lifecycle of an UpdFieldOcc] -data UpdFieldOcc pass - = UpdFieldOcc { - ufoExt :: XCUpdFieldOcc pass, - ufoField :: LFieldOcc pass - } - | XUpdFieldOcc (XXUpdFieldOcc pass) -- | Located Field Occurrence type LFieldOcc pass = XRec pass (FieldOcc pass) @@ -1381,6 +1365,11 @@ type LFieldOcc pass = XRec pass (FieldOcc pass) -- We store both the 'RdrName' the user originally wrote, and after -- the renamer we use the extension field to store the selector -- function. +-- +-- There is a wrinkle in that update field occurances are sometimes +-- ambiguous during the rename stage. See note +-- [Ambiguous FieldOcc in record updates] to see how we currently +-- handle this. data FieldOcc pass = FieldOcc { foExt :: XCFieldOcc pass ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -3505,22 +3505,6 @@ instance (ExactPrint body) -- --------------------------------------------------------------------- -instance (ExactPrint (LocatedA body)) - => ExactPrint (HsFieldBind (LocatedA (UpdFieldOcc GhcPs)) (LocatedA body)) where - getAnnotationEntry _ = NoEntryVal - setAnnotationAnchor a _ _ _ = a - - exact (HsFieldBind an f arg isPun) = do - debugM $ "HsRecUpdField" - f' <- markAnnotated f - an0 <- if isPun then return an - else markEpAnnL an lidl AnnEqual - arg' <- if isPun - then return arg - else markAnnotated arg - return (HsFieldBind an0 f' arg' isPun) - --- --------------------------------------------------------------------- instance ExactPrint (LHsRecUpdFields GhcPs) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a @@ -4591,13 +4575,6 @@ instance ExactPrint (FieldOcc GhcPs) where -- --------------------------------------------------------------------- -instance ExactPrint (UpdFieldOcc GhcPs) where - getAnnotationEntry = const NoEntryVal - setAnnotationAnchor a _ _ _ = a - exact f@(UpdFieldOcc _ n) = markAnnotated n >> return f - exact (XUpdFieldOcc impossible) = dataConCantHappen impossible --- --------------------------------------------------------------------- - instance (ExactPrint a) => ExactPrint (HsScaled GhcPs a) where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa5fc5871229d011f56a0606afa6dc1123875716 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa5fc5871229d011f56a0606afa6dc1123875716 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 14:42:00 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Fri, 04 Oct 2024 10:42:00 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/simd_test Message-ID: <66fffeb86a3ff_30be00275efc895b1@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/simd_test at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/simd_test You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 14:44:58 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 04 Oct 2024 10:44:58 -0400 Subject: [Git][ghc/ghc][wip/T25281] Wibble Message-ID: <66ffff6a52ed4_30be00185b28913e1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC Commits: e6d281e3 by Simon Peyton Jones at 2024-10-04T15:44:41+01:00 Wibble - - - - - 1 changed file: - compiler/GHC/HsToCore/Ticks.hs Changes: ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -293,7 +293,7 @@ addTickLHsBind (L pos (funBind@(FunBind { fun_id = L _ id, fun_matches = matches -- TODO: Revisit this addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs , pat_rhs = rhs - , pat_ext = (grhs_ty, initial_ticks}))) = do + , pat_ext = (grhs_ty, initial_ticks)}))) = do let simplePatId = isSimplePat lhs @@ -327,7 +327,7 @@ addTickLHsBind (L pos (pat@(PatBind { pat_lhs = lhs (zipWith mbCons patvar_ticks (initial_patvar_tickss ++ repeat [])) - return $ L pos $ pat' { pat_ext = (ghhs_ty, (rhs_ticks, patvar_tickss)) } + return $ L pos $ pat' { pat_ext = (grhs_ty, (rhs_ticks, patvar_tickss)) } -- Only internal stuff, not from source, uses VarBind, so we ignore it. addTickLHsBind var_bind@(L _ (VarBind {})) = return var_bind View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6d281e3595eaee513094a6c5d996337b432e380 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6d281e3595eaee513094a6c5d996337b432e380 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Oct 4 14:49:55 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 04 Oct 2024 10:49:55 -0400 Subject: [Git][ghc/ghc][wip/romes/25304] determinism: Interface re-export list det Message-ID: <670000935d97f_30be001910cc9234d@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC Commits: a790f697 by Rodrigo Mesquita at 2024-10-04T15:48:18+01:00 determinism: Interface re-export list det In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for interface file determinism. This commit introduces 'SortedAvails', an abstract newtype that can only be constructed by sorting Avails with 'sortAvails'. This newtype is used by 'DocStructureItem' where 'Avails' was previously used to ensure the list of avails is deterministically sorted by construction. Note: Even though we order the constructors and avails in the interface file, the order of constructors in the haddock output is still determined from the order of declaration in the source. This was also true before, when the list of constructors in the interface file <docs> section was non-deterministic. Some haddock tests such as "ConstructorArgs" observe this (check the order of constructors in out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file) Fixes #25304 - - - - - 17 changed files: - compiler/GHC/Hs/Doc.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Types/Avail.hs - + testsuite/tests/determinism/T25304/A.hs - + testsuite/tests/determinism/T25304/B.hs - + testsuite/tests/determinism/T25304/Makefile - + testsuite/tests/determinism/T25304/T25304a.stdout - + testsuite/tests/determinism/T25304/all.T - testsuite/tests/showIface/DocsInHiFileTH.stdout - testsuite/tests/showIface/NoExportList.stdout - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/html-test/ref/BundledPatterns2.html - utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex - utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex - utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex - utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex Changes: ===================================== compiler/GHC/Hs/Doc.hs ===================================== @@ -124,7 +124,7 @@ data DocStructureItem = DsiSectionHeading !Int !(HsDoc GhcRn) | DsiDocChunk !(HsDoc GhcRn) | DsiNamedChunkRef !String - | DsiExports !Avails + | DsiExports !SortedAvails | DsiModExport !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple -- modules with a single export declaration. E.g. @@ -136,7 +136,7 @@ data DocStructureItem -- -- Invariant: This list of ModuleNames must be -- sorted to guarantee interface file determinism. - !Avails + !SortedAvails -- ^ Invariant: This list of Avails must be sorted -- to guarantee interface file determinism. ===================================== compiler/GHC/HsToCore/Docs.hs ===================================== @@ -160,7 +160,11 @@ mkDocStructureFromExportList mdl import_avails export_list = (IEGroup _ level doc, _) -> DsiSectionHeading level (unLoc doc) (IEDoc _ doc, _) -> DsiDocChunk (unLoc doc) (IEDocNamed _ name, _) -> DsiNamedChunkRef name - (_, avails) -> DsiExports (nubAvails avails) + (IEThingWith{}, avails) -> + DsiExports $ + {- For explicit export lists, use the explicit order. It is deterministic by construction -} + UnsafeSortedAvails (nubAvails avails) + (_, avails) -> DsiExports (sortAvails (nubAvails avails)) moduleExport :: ModuleName -- Alias -> Avails @@ -201,10 +205,10 @@ mkDocStructureFromDecls env all_exports decls = avails :: [Located DocStructureItem] avails = flip fmap all_exports $ \avail -> case M.lookup (availName avail) name_locs of - Just loc -> L loc (DsiExports [avail]) + Just loc -> L loc (DsiExports (sortAvails [avail])) -- FIXME: This is just a workaround that we use when handling e.g. -- associated data families like in the html-test Instances.hs. - Nothing -> noLoc (DsiExports []) + Nothing -> noLoc (DsiExports (sortAvails [])) -- This causes the associated data family to be incorrectly documented -- separately from its class: ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -518,8 +518,8 @@ mkIfaceImports = map go go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) -mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical -mkIfaceExports = sortAvails +mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical +mkIfaceExports as = case sortAvails as of SortedAvails sas -> sas {- Note [Original module] ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PatternSynonyms #-} -- -- (c) The University of Glasgow -- @@ -20,6 +22,7 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, + SortedAvails(SortedAvails, UnsafeSortedAvails) ) where import GHC.Prelude @@ -65,6 +68,20 @@ data AvailInfo -- | A collection of 'AvailInfo' - several things that are \"available\" type Avails = [AvailInfo] +-- | Occurrences of Avails in interface files must be sorted to guarantee +-- interface file determinism. +-- +-- To construct 'SortedAvails' using 'UnsafeSortedAvails' you must be sure the +-- 'Avails' are already sorted. Otherwise, you should use 'sortAvails'. +newtype SortedAvails = UnsafeSortedAvails Avails + deriving newtype (Binary, Outputable, NFData) + +-- | Safe matching on 'SortedAvails' +-- To construct 'SortedAvails' use 'sortAvails'. +pattern SortedAvails :: Avails -> SortedAvails +pattern SortedAvails x <- UnsafeSortedAvails x +{-# COMPLETE SortedAvails #-} + {- Note [Representing pattern synonym fields in AvailInfo] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Record pattern synonym fields cannot be represented using AvailTC like fields of @@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns) | otherwise = ns -- | Sort 'Avails'/'AvailInfo's -sortAvails :: Avails -> Avails -sortAvails = sortBy stableAvailCmp . map sort_subs +sortAvails :: Avails -> SortedAvails +sortAvails = UnsafeSortedAvails . sortBy stableAvailCmp . map sort_subs where sort_subs :: AvailInfo -> AvailInfo sort_subs (Avail n) = Avail n ===================================== testsuite/tests/determinism/T25304/A.hs ===================================== @@ -0,0 +1,84 @@ +module A + ( MyType(..) + ) where + +data MyType + = A + | B + | C + | D + | E + | F + | G + | H + | I + | J + | K + | L + | M + | N + | O + | P + | Q + | R + | S + | T + | U + | V + | W + | X + | Y + | Z + | AA + | AB + | AC + | AD + | AE + | AF + | AG + | AH + | AI + | AJ + | AK + | AL + | AM + | AN + | AO + | AP + | AQ + | AR + | AS + | AT + | AU + | AV + | AW + | AX + | AY + | AZ + | BA + | BB + | BC + | BD + | BE + | BF + | BG + | BH + | BI + | BJ + | BK + | BL + | BM + | BN + | BO + | BP + | BQ + | BR + | BS + | BT + | BU + | BV + | BW + | BX + | BY + | BZ + | CA ===================================== testsuite/tests/determinism/T25304/B.hs ===================================== @@ -0,0 +1,86 @@ +module B +( MyType + ( BA + , BB + , BC + , BD + , BE + , BF + , BG + , BH + , BI + , BJ + , BK + , BL + , BM + , BN + , BO + , BP + , BQ + , BR + , BS + , BT + , BU + , BV + , BW + , BX + , BY + , BZ + , CA + , AA + , AB + , AC + , AD + , AE + , AF + , AG + , AH + , AI + , AJ + , AK + , AL + , AM + , AN + , AO + , AP + , AQ + , AR + , AS + , AT + , AU + , AV + , AW + , AX + , AY + , AZ + , A + , B + , C + , D + , E + , F + , G + , H + , I + , J + , K + , L + , M + , N + , O + , P + , Q + , R + , S + , T + , U + , V + , W + , X + , Y + , Z + ) +) where + +import A + ===================================== testsuite/tests/determinism/T25304/Makefile ===================================== @@ -0,0 +1,25 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +T25304: + $(RM) A.hi A.o B.hi B.o + # Use -haddock to get docs: output in the interface file + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs + '$(TEST_HC)' --show-iface A.hi > A_clean_iface + '$(TEST_HC)' --show-iface B.hi > B_clean_iface + '$(TEST_HC)' $(TEST_HC_OPTS) -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp + '$(TEST_HC)' --show-iface A.hi > A_dirty_iface + '$(TEST_HC)' --show-iface B.hi > B_dirty_iface + diff A_clean_iface A_dirty_iface + diff B_clean_iface B_dirty_iface + +T25304a: + $(RM) A.hi A.o B.hi B.o + # Use -haddock to get docs: output in the interface file + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs + '$(TEST_HC)' --show-iface B.hi > B_clean_iface + # The goal is to see the export list in the documentation structure of the + # interface file preserves the order used in the source + cat B_clean_iface | grep -A7 "documentation structure" + ===================================== testsuite/tests/determinism/T25304/T25304a.stdout ===================================== @@ -0,0 +1,8 @@ + documentation structure: + avails: + [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH, + A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS, + A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC, + A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN, + A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY, + A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L, ===================================== testsuite/tests/determinism/T25304/all.T ===================================== @@ -0,0 +1,2 @@ +test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304']) +test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a']) ===================================== testsuite/tests/showIface/DocsInHiFileTH.stdout ===================================== @@ -187,7 +187,7 @@ docs: avails: [i] avails: - [WD11{WD11, WD11Bool, WD11Int, WD11Foo}] + [WD11{WD11, WD11Bool, WD11Foo, WD11Int}] avails: [WD13{WD13}] avails: @@ -221,11 +221,11 @@ docs: avails: [Pretty{Pretty, prettyPrint}] avails: - [Corge{Corge, runCorge, Corge}] + [Corge{Corge, Corge, runCorge}] avails: - [Quuz{Quuz, quuz1_a, Quuz}] + [Quuz{Quuz, Quuz, quuz1_a}] avails: - [Quux{Quux, Quux2, Quux1}] + [Quux{Quux, Quux1, Quux2}] avails: [Tup2] avails: ===================================== testsuite/tests/showIface/NoExportList.stdout ===================================== @@ -32,7 +32,7 @@ docs: -- Actually we have only one type. identifiers: avails: - [R{R, fβ, fα, R}] + [R{R, R, fα, fβ}] section heading, level 1: text: -- * Functions ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -201,7 +201,14 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces -- See Note [Exporting built-in items] let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") []) bonus_ds mods - | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods + | mdl == gHC_PRIM = + [ builtinTys + , DsiExports $ + {- Haddock does not want to sort avails, the order should be derived from the source. + In this particular case, sorting funAvail would be a no-op anyway. -} + UnsafeSortedAvails + funAvail + ] <> mods | otherwise = mods let @@ -461,11 +468,11 @@ mkExportItems Just hsDoc' -> do doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc' pure [ExportDoc doc] - DsiExports avails -> + DsiExports (SortedAvails avails) -> -- TODO: We probably don't need nubAvails here. -- mkDocStructureFromExportList already uses it. concat <$> traverse availExport (nubAvails avails) - DsiModExport mod_names avails -> do + DsiModExport mod_names (SortedAvails avails) -> do -- only consider exporting a module if we are sure we are really -- exporting the whole module and not some subset. (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names) ===================================== utils/haddock/html-test/ref/BundledPatterns2.html ===================================== @@ -96,14 +96,6 @@ >wherepattern LR :: a -> BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 14:59:10 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 04 Oct 2024 10:59:10 -0400
Subject: [Git][ghc/ghc][wip/bump-process] 71 commits: ci: Run abi-test on
 test-abi label
Message-ID: <670002be55d8_30be006224b095181@gitlab.mail>



Ben Gamari pushed to branch wip/bump-process at Glasgow Haskell Compiler / GHC


Commits:
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
ddfc6573 by Ben Gamari at 2024-10-04T10:58:52-04:00
Bump process submodule to v1.6.25.0

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69ae6b2ef9e11552786693246f7374d104a8331c...ddfc6573780b8fbae307ef7fba48edd4eb78002f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69ae6b2ef9e11552786693246f7374d104a8331c...ddfc6573780b8fbae307ef7fba48edd4eb78002f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 15:04:04 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Fri, 04 Oct 2024 11:04:04 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Don't store boot locations in finder
 cache
Message-ID: <670003e4a488a_30be0074b2389578b@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
780949a6 by Sjoerd Visscher at 2024-10-04T17:03:53+02:00
Don't store boot locations in finder cache

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location HsigFile
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -861,7 +861,6 @@ hsModuleToModSummary home_keys pn hsc_src modname
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
     let location = case hsc_src of
                         HsBootFile -> addBootSuffixLocnOut location0
                         _ -> location0
@@ -893,7 +892,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location hsc_src
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2077,7 +2077,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location hsc_src
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2110,10 +2110,9 @@ checkSummaryHash
            -- Also, only add to finder cache for non-boot modules as the finder cache
            -- makes sure to add a boot suffix for boot files.
            _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
+              let fc        = hsc_FC hsc_env
               case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
+                HsSrcFile -> addModuleToFinder fc (ms_mod old_summary) location
                 _ -> return ()
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -734,7 +734,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location src_flavour
 
   -- Make the ModSummary to hand to hscMain
   let


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -897,7 +897,7 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
           -- Look for the file
           mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -55,6 +55,7 @@ import GHC.Utils.Panic
 
 import GHC.Linker.Types
 import GHC.Types.PkgQual
+import GHC.Types.SourceFile
 
 import GHC.Fingerprint
 import Data.IORef
@@ -89,23 +90,23 @@ type BaseName = OsPath  -- Basename of file
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
-  mod_cache <- newIORef emptyInstalledModuleWithIsBootEnv
+  mod_cache <- newIORef emptyInstalledModuleEnv
   file_cache <- newIORef M.empty
   let flushFinderCaches :: UnitEnv -> IO ()
       flushFinderCaches ue = do
-        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
         atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
        where
-        is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+        is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-      addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+      addToFinderCache :: InstalledModule -> InstalledFindResult -> IO ()
       addToFinderCache key val =
-        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleEnv c key val, ())
 
-      lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+      lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do
          c <- readIORef mod_cache
-         return $! lookupInstalledModuleWithIsBootEnv c key
+         return $! lookupInstalledModuleEnv c key
 
       lookupFileCache :: FilePath -> IO Fingerprint
       lookupFileCache key = do
@@ -255,7 +256,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -277,7 +278,7 @@ findLookupResult fc fopts r = case r of
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -312,7 +313,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -322,17 +323,18 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  let imod = toUnitId <$> mod
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
-addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> HscSource -> IO Module
+addHomeModuleToFinder fc home_unit mod_name loc src_flavour = do
+  let mod = mkHomeInstalledModule home_unit mod_name
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc mod (InstalledFound loc)
+  return (mkHomeModule home_unit mod_name)
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -342,7 +344,7 @@ findHomeModule fc fopts  home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -367,7 +369,7 @@ findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -437,7 +439,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -466,11 +468,11 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -494,7 +496,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -528,7 +530,7 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
 mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -30,9 +30,9 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                -- ^ remove all the home modules from the cache; package modules are
                                -- assumed to not move around during a session; also flush the file hash
                                -- cache.
-                               , addToFinderCache  :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+                               , addToFinderCache  :: InstalledModule -> InstalledFindResult -> IO ()
                                -- ^ Add a found location to the cache for the module.
-                               , lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+                               , lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
                                -- ^ Look for a location in the cache.
                                , lookupFileCache   :: FilePath -> IO Fingerprint
                                -- ^ Look for the hash of a file in the cache. This should add it to the
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -84,8 +84,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -720,8 +718,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -735,6 +731,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/780949a6ec1ea5da777af99d70c177b134dd78c9

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 15:19:48 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Fri, 04 Oct 2024 11:19:48 -0400
Subject: [Git][ghc/ghc][wip/andreask/simd_test] Compile T25062 simd tests even
 if we can't run them.
Message-ID: <6700079492425_30be007b8dec10005@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/simd_test at Glasgow Haskell Compiler / GHC


Commits:
b16b01f1 by Andreas Klebinger at 2024-10-04T17:00:43+02:00
Compile T25062 simd tests even if we can't run them.

Helps avoid them being utterly broken.

Fixes #25341

- - - - -


2 changed files:

- testsuite/tests/simd/should_run/T25062_V64.hs
- testsuite/tests/simd/should_run/all.T


Changes:

=====================================
testsuite/tests/simd/should_run/T25062_V64.hs
=====================================
@@ -10,7 +10,7 @@ main =
   case foo ( \ x y -> plusDoubleX8# x y ) of
     v -> case unpackDoubleX8# v of
       (# d1, d2, d3, d4, d5, d6, d7, d8 #) ->
-        print [ D# d1, D# d2, D# d3, D# d4, D# d5, D# d6, D# d7, D# d8s ]
+        print [ D# d1, D# d2, D# d3, D# d4, D# d5, D# d6, D# d7, D# d8 ]
 
 {-# NOINLINE foo #-}
 foo :: ( DoubleX8# -> DoubleX8# -> DoubleX8# ) -> DoubleX8#


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -58,13 +58,21 @@ test('simd014',
 test('T22187', [],compile,[''])
 test('T22187_run', [],compile_and_run,[''])
 test('T25062_V16', [], compile_and_run, [''])
-test('T25062_V32', [ unless(have_cpu_feature('avx2'), skip)
-                   , only_ways(llvm_ways) # SIMD NCG TODO: support 256 bit wide vectors
-                   ]
-                 , compile_and_run, [''])
-test('T25062_V64', [ unless(have_cpu_feature('avx512f'), skip)
-                   , only_ways(llvm_ways) # SIMD NCG TODO: support 512 bit wide vectors
-                   ]
-                 , compile_and_run, [''])
+
+# Even if the CPU we run on doesn't support *executing* those tests we should try to
+# compile them.
+test('T25062_V32'
+    ,   [ extra_hc_opts('-mavx2')
+        , only_ways(llvm_ways) # SIMD NCG TODO: support 256 bit wide vectors
+        ]
+    , compile_and_run if have_cpu_feature('avx2') else compile
+    , [''])
+
+test('T25062_V64'
+    ,   [ extra_hc_opts('-mavx512f')
+        , only_ways(llvm_ways) # SIMD NCG TODO: support 256 bit wide vectors
+        ]
+    , compile_and_run if have_cpu_feature('avx512f') else compile
+    , [''])
 
 test('T25169', [], compile_and_run, [''])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 15:41:01 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Fri, 04 Oct 2024 11:41:01 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/interpreterDynamic
Message-ID: <67000c8dbfd81_30be009c9aa0104439@gitlab.mail>



Cheng Shao deleted branch wip/interpreterDynamic at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 15:41:29 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Fri, 04 Oct 2024 11:41:29 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/targetSupportsRPaths
Message-ID: <67000ca935d89_30be009e4e18104646@gitlab.mail>



Cheng Shao deleted branch wip/targetSupportsRPaths at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 16:11:13 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 04 Oct 2024 12:11:13 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] determinism: Interface re-export list
 det
Message-ID: <670013a174d14_30be00b77d981118ca@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
ad07d4ec by Rodrigo Mesquita at 2024-10-04T17:05:41+01:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'SortedAvails', an
abstract newtype that can only be constructed by sorting Avails with
'sortAvails'. This newtype is used by 'DocStructureItem' where 'Avails'
was previously used to ensure the list of avails is deterministically
sorted by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -


17 changed files:

- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Types/Avail.hs
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout
- + testsuite/tests/determinism/T25304/all.T
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/NoExportList.stdout
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
- utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
- utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
- utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex


Changes:

=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -124,7 +124,7 @@ data DocStructureItem
   = DsiSectionHeading !Int !(HsDoc GhcRn)
   | DsiDocChunk !(HsDoc GhcRn)
   | DsiNamedChunkRef !String
-  | DsiExports !Avails
+  | DsiExports !SortedAvails
   | DsiModExport
       !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple
                             -- modules with a single export declaration. E.g.
@@ -136,7 +136,7 @@ data DocStructureItem
                             --
                             -- Invariant: This list of ModuleNames must be
                             -- sorted to guarantee interface file determinism.
-      !Avails
+      !SortedAvails
                             -- ^ Invariant: This list of Avails must be sorted
                             -- to guarantee interface file determinism.
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -160,7 +160,11 @@ mkDocStructureFromExportList mdl import_avails export_list =
       (IEGroup _ level doc, _)         -> DsiSectionHeading level (unLoc doc)
       (IEDoc _ doc, _)                 -> DsiDocChunk (unLoc doc)
       (IEDocNamed _ name, _)           -> DsiNamedChunkRef name
-      (_, avails)                      -> DsiExports (nubAvails avails)
+      (IEThingWith{}, avails)          ->
+        DsiExports $
+          {- For explicit export lists, use the explicit order. It is deterministic by construction -}
+          UnsafeSortedAvails (nubAvails avails)
+      (_, avails)                      -> DsiExports (sortAvails (nubAvails avails))
 
     moduleExport :: ModuleName -- Alias
                  -> Avails
@@ -201,10 +205,10 @@ mkDocStructureFromDecls env all_exports decls =
     avails :: [Located DocStructureItem]
     avails = flip fmap all_exports $ \avail ->
       case M.lookup (availName avail) name_locs of
-        Just loc -> L loc (DsiExports [avail])
+        Just loc -> L loc (DsiExports (sortAvails [avail]))
         -- FIXME: This is just a workaround that we use when handling e.g.
         -- associated data families like in the html-test Instances.hs.
-        Nothing -> noLoc (DsiExports [])
+        Nothing -> noLoc (DsiExports (sortAvails []))
 
         -- This causes the associated data family to be incorrectly documented
         -- separately from its class:


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -518,8 +518,8 @@ mkIfaceImports = map go
     go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
     go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
 
-mkIfaceExports :: [AvailInfo] -> [IfaceExport]  -- Sort to make canonical
-mkIfaceExports = sortAvails
+mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
+mkIfaceExports as = case sortAvails as of SortedAvails sas -> sas
 
 {-
 Note [Original module]


=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -1,5 +1,7 @@
 
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE PatternSynonyms #-}
 --
 -- (c) The University of Glasgow
 --
@@ -20,6 +22,7 @@ module GHC.Types.Avail (
     filterAvails,
     nubAvails,
     sortAvails,
+    SortedAvails(SortedAvails, UnsafeSortedAvails)
   ) where
 
 import GHC.Prelude
@@ -65,6 +68,20 @@ data AvailInfo
 -- | A collection of 'AvailInfo' - several things that are \"available\"
 type Avails = [AvailInfo]
 
+-- | Occurrences of Avails in interface files must be sorted to guarantee
+-- interface file determinism.
+--
+-- To construct 'SortedAvails' using 'UnsafeSortedAvails' you must be sure the
+-- 'Avails' are already sorted. Otherwise, you should use 'sortAvails'.
+newtype SortedAvails = UnsafeSortedAvails Avails
+  deriving newtype (Binary, Outputable, NFData)
+
+-- | Safe matching on 'SortedAvails'
+-- To construct 'SortedAvails' use 'sortAvails'.
+pattern SortedAvails :: Avails -> SortedAvails
+pattern SortedAvails x <- UnsafeSortedAvails x
+{-# COMPLETE SortedAvails #-}
+
 {- Note [Representing pattern synonym fields in AvailInfo]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Record pattern synonym fields cannot be represented using AvailTC like fields of
@@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns)
   | otherwise              = ns
 
 -- | Sort 'Avails'/'AvailInfo's
-sortAvails :: Avails -> Avails
-sortAvails = sortBy stableAvailCmp . map sort_subs
+sortAvails :: Avails -> SortedAvails
+sortAvails = UnsafeSortedAvails . sortBy stableAvailCmp . map sort_subs
   where
     sort_subs :: AvailInfo -> AvailInfo
     sort_subs (Avail n) = Avail n


=====================================
testsuite/tests/determinism/T25304/A.hs
=====================================
@@ -0,0 +1,84 @@
+module A
+  ( MyType(..)
+  ) where
+
+data MyType
+    = A
+    | B
+    | C
+    | D
+    | E
+    | F
+    | G
+    | H
+    | I
+    | J
+    | K
+    | L
+    | M
+    | N
+    | O
+    | P
+    | Q
+    | R
+    | S
+    | T
+    | U
+    | V
+    | W
+    | X
+    | Y
+    | Z
+    | AA
+    | AB
+    | AC
+    | AD
+    | AE
+    | AF
+    | AG
+    | AH
+    | AI
+    | AJ
+    | AK
+    | AL
+    | AM
+    | AN
+    | AO
+    | AP
+    | AQ
+    | AR
+    | AS
+    | AT
+    | AU
+    | AV
+    | AW
+    | AX
+    | AY
+    | AZ
+    | BA
+    | BB
+    | BC
+    | BD
+    | BE
+    | BF
+    | BG
+    | BH
+    | BI
+    | BJ
+    | BK
+    | BL
+    | BM
+    | BN
+    | BO
+    | BP
+    | BQ
+    | BR
+    | BS
+    | BT
+    | BU
+    | BV
+    | BW
+    | BX
+    | BY
+    | BZ
+    | CA


=====================================
testsuite/tests/determinism/T25304/B.hs
=====================================
@@ -0,0 +1,86 @@
+module B
+( MyType
+    ( BA
+    , BB
+    , BC
+    , BD
+    , BE
+    , BF
+    , BG
+    , BH
+    , BI
+    , BJ
+    , BK
+    , BL
+    , BM
+    , BN
+    , BO
+    , BP
+    , BQ
+    , BR
+    , BS
+    , BT
+    , BU
+    , BV
+    , BW
+    , BX
+    , BY
+    , BZ
+    , CA
+    , AA
+    , AB
+    , AC
+    , AD
+    , AE
+    , AF
+    , AG
+    , AH
+    , AI
+    , AJ
+    , AK
+    , AL
+    , AM
+    , AN
+    , AO
+    , AP
+    , AQ
+    , AR
+    , AS
+    , AT
+    , AU
+    , AV
+    , AW
+    , AX
+    , AY
+    , AZ
+    , A
+    , B
+    , C
+    , D
+    , E
+    , F
+    , G
+    , H
+    , I
+    , J
+    , K
+    , L
+    , M
+    , N
+    , O
+    , P
+    , Q
+    , R
+    , S
+    , T
+    , U
+    , V
+    , W
+    , X
+    , Y
+    , Z
+    )
+) where
+
+import A
+


=====================================
testsuite/tests/determinism/T25304/Makefile
=====================================
@@ -0,0 +1,25 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25304:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface A.hi > A_clean_iface
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	'$(TEST_HC)' $(TEST_HC_OPTS) -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp
+	'$(TEST_HC)' --show-iface A.hi > A_dirty_iface
+	'$(TEST_HC)' --show-iface B.hi > B_dirty_iface
+	diff A_clean_iface A_dirty_iface
+	diff B_clean_iface B_dirty_iface
+
+T25304a:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	# The goal is to see the export list in the documentation structure of the
+	# interface file preserves the order used in the source
+	cat B_clean_iface | grep -A7 "documentation structure"
+


=====================================
testsuite/tests/determinism/T25304/T25304a.stdout
=====================================
@@ -0,0 +1,8 @@
+       documentation structure:
+         avails:
+           [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH,
+                     A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS,
+                     A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC,
+                     A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN,
+                     A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY,
+                     A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L,


=====================================
testsuite/tests/determinism/T25304/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304'])
+test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a'])


=====================================
testsuite/tests/showIface/DocsInHiFileTH.stdout
=====================================
@@ -187,7 +187,7 @@ docs:
          avails:
            [i]
          avails:
-           [WD11{WD11, WD11Bool, WD11Int, WD11Foo}]
+           [WD11{WD11, WD11Bool, WD11Foo, WD11Int}]
          avails:
            [WD13{WD13}]
          avails:
@@ -221,11 +221,11 @@ docs:
          avails:
            [Pretty{Pretty, prettyPrint}]
          avails:
-           [Corge{Corge, runCorge, Corge}]
+           [Corge{Corge, Corge, runCorge}]
          avails:
-           [Quuz{Quuz, quuz1_a, Quuz}]
+           [Quuz{Quuz, Quuz, quuz1_a}]
          avails:
-           [Quux{Quux, Quux2, Quux1}]
+           [Quux{Quux, Quux1, Quux2}]
          avails:
            [Tup2]
          avails:


=====================================
testsuite/tests/showIface/NoExportList.stdout
=====================================
@@ -32,7 +32,7 @@ docs:
 -- Actually we have only one type.
            identifiers:
          avails:
-           [R{R, fβ, fα, R}]
+           [R{R, R, fα, fβ}]
          section heading, level 1:
            text:
              -- * Functions


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -201,7 +201,14 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
   -- See Note [Exporting built-in items]
   let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") [])
       bonus_ds mods
-        | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods
+        | mdl == gHC_PRIM =
+            [ builtinTys
+            , DsiExports $
+                {- Haddock does not want to sort avails, the order should be derived from the source.
+                   In this particular case, sorting funAvail would be a no-op anyway. -}
+                UnsafeSortedAvails
+                  funAvail
+            ] <> mods
         | otherwise = mods
 
   let
@@ -461,11 +468,11 @@ mkExportItems
             Just hsDoc' -> do
               doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc'
               pure [ExportDoc doc]
-        DsiExports avails ->
+        DsiExports (SortedAvails avails) ->
           -- TODO: We probably don't need nubAvails here.
           -- mkDocStructureFromExportList already uses it.
           concat <$> traverse availExport (nubAvails avails)
-        DsiModExport mod_names avails -> do
+        DsiModExport mod_names (SortedAvails avails) -> do
           -- only consider exporting a module if we are sure we are really
           -- exporting the whole module and not some subset.
           (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names)


=====================================
utils/haddock/html-test/ref/BundledPatterns2.html
=====================================
@@ -96,14 +96,6 @@
 	      >wherepattern LR :: a ->  BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 17:28:51 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 04 Oct 2024 13:28:51 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: base: Add
 `HasCallStack` constraint to `ioError`
Message-ID: <670025d382280_14f3bf35c3701015cb@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
54673115 by Cheng Shao at 2024-10-04T13:28:46-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -


30 changed files:

- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/openFile002.stderr-mingw32
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile001.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking001.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/T15349.stderr
- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs
- testsuite/tests/codeGen/should_run/cgrun016.stderr
- testsuite/tests/codeGen/should_run/cgrun025.stderr
- testsuite/tests/concurrent/should_run/T3279.hs
- testsuite/tests/ffi/should_run/T7170.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail2.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail7.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail8.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d7b73d33a71a2fab8f5ac27813f3ecfe225c0fd...54673115e4703199d61895050893ea694e1e4265

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d7b73d33a71a2fab8f5ac27813f3ecfe225c0fd...54673115e4703199d61895050893ea694e1e4265
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 20:06:43 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 04 Oct 2024 16:06:43 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 10 commits: rts: only collect
 live words in nonmoving census when non-concurrent
Message-ID: <67004ad3d074_3743db3c0b18713b2@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
fede0d99 by Teo Camarasu at 2024-10-04T16:05:22-04:00
rts: only collect live words in nonmoving census when non-concurrent

This avoids segfaults when the mutator modifies closures as we examine
them.

Resolves #24393

(cherry picked from commit 84357d1143fe4f9076253160f78fac6c2acc8e5b)

- - - - -
47182b77 by Andreas Klebinger at 2024-10-04T16:05:22-04:00
Fix ffi callbacks with >6 args and non-64bit args.

Check for ptr/int arguments rather than 64-bit width arguments when counting
integer register arguments.
The old approach broke when we stopped using exclusively W64-sized types to represent
sub-word sized integers.

Fixes #24314

(cherry picked from commit de589554386fc173a9019922851c05bb727e3450)

- - - - -
72c537ce by Teo Camarasu at 2024-10-04T16:05:22-04:00
nonmoving: Add support for heap profiling

Add support for heap profiling while using the nonmoving collector.

We greatly simply the implementation by disabling concurrent collection for
GCs when heap profiling is enabled. This entails that the marked objects on
the nonmoving heap are exactly the live objects.

Note that we match the behaviour for live bytes accounting by taking the size
of objects on the nonmoving heap to be that of the segment's block
rather than the object itself.

Resolves #22221

(cherry picked from commit bedb4f0de102936099bda4e995cc83f1c344366c)

- - - - -
b2712f69 by Teo Camarasu at 2024-10-04T16:05:22-04:00
docs: move -xn flag beside --nonmoving-gc

It makes sense to have these beside each other as they are aliases.

(cherry picked from commit 98166389e166d4ab7cc2ddbc044261e508859de1)

- - - - -
60f97ccb by Teo Camarasu at 2024-10-04T16:05:22-04:00
nonmoving: introduce a family of dense allocators

Supplement the existing power 2 sized nonmoving allocators with a family
of dense allocators up to a configurable threshold.

This should reduce waste from rounding up block sizes while keeping the
amount of allocator sizes manageable.

This patch:
  - Adds a new configuration option `--nonmoving-dense-allocator-count`
    to control the amount of these new dense allocators.
  - Adds some constants to `NonmovingAllocator` in order to keep
    marking fast with the new allocators.

Resolves #23340

(cherry picked from commit f830d5a34c4c972cced73b6dc25954cedf336747)
(cherry picked from commit 47e02c2ae0ea4713a2f22edf21b9a4eb5fe635be)

- - - - -
8031ebaa by Teo Camarasu at 2024-10-04T16:05:22-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

(cherry picked from commit 35ef8dc83428f5405e092b12eb8cfc440b6504d8)
(cherry picked from commit 7991656954a2ba7d66fd75a8202af7d86327f279)

- - - - -
c71191f7 by Ben Gamari at 2024-10-04T16:05:22-04:00
Add changelog entry for #23340

(cherry picked from commit 2b07bf2e8bcb24520fe78b469c3550b9f4099526)

- - - - -
3ff6bbbe by Simon Peyton Jones at 2024-10-04T16:05:22-04:00
Update the unification count in wrapUnifierX

Omitting this caused type inference to fail in #24146.
This was an accidental omision in my refactoring of the
equality solver.

- - - - -
7e5f2ac0 by Fendor at 2024-10-04T16:05:22-04:00
Escape multiple arguments in the settings file

Uses responseFile syntax.

The issue arises when GHC is installed on windows into a location that
has a space, for example the user name is 'Fake User'.
The $topdir will also contain a space, consequentially.
When we resolve the top dir in the string `-I$topdir/mingw/include`,
then `words` will turn this single argument into `-I/C/Users/Fake` and
`User/.../mingw/include` which trips up the flag argument parser of
various tools such as gcc or clang.
We avoid this by escaping the $topdir before replacing it in
`initSettngs`.
Additionally, we allow to escape spaces and quotation marks for
arguments in `settings` file.

Add regression test case to count the number of options after variable
expansion and argument escaping took place.
Additionally, we check that escaped spaces and double quotation marks are
correctly parsed.

(cherry picked from commit 31bf85ee49fe2ca0b17eaee0774e395f017a9373)
(cherry picked from commit d74ffbbb93cb377e64c557f777089b81710ef873)

- - - - -
3d90849d by Ben Gamari at 2024-10-04T16:05:44-04:00
Accept performance shifts

The metrics of MultiLayerModulesTH_Make are remarkably unstable but
bizarrely only on Darwin.

Metric Decrease:
    MultiLayerModulesTH_Make

- - - - -


30 changed files:

- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Tc/Solver/Monad.hs
- docs/users_guide/9.8.3-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/runtime_control.rst
- hadrian/src/Rules/Generate.hs
- rts/Capability.h
- rts/ProfHeap.c
- rts/RtsFlags.c
- rts/Trace.c
- rts/Trace.h
- rts/eventlog/EventLog.c
- rts/eventlog/EventLog.h
- rts/gen_event_types.py
- rts/include/rts/Flags.h
- rts/include/rts/storage/Block.h
- rts/sm/GC.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/NonMovingCensus.c
- rts/sm/Sanity.c
- rts/sm/Storage.c
- rts/sm/Storage.h
- + testsuite/tests/ffi/should_run/T24314.hs
- + testsuite/tests/ffi/should_run/T24314.stdout
- + testsuite/tests/ffi/should_run/T24314_c.c
- testsuite/tests/ffi/should_run/all.T
- + testsuite/tests/ghc-api/settings-escape/T11938.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/926eceafa1f3199220047ac7c0bec612414c4a6e...3d90849d00871853c68dbb7b9b4e97349a999459

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/926eceafa1f3199220047ac7c0bec612414c4a6e...3d90849d00871853c68dbb7b9b4e97349a999459
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 21:06:01 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 04 Oct 2024 17:06:01 -0400
Subject: [Git][ghc/ghc][wip/T25281] 17 commits: SpecConstr: Introduce a
 separate argument limit for forced specs.
Message-ID: <670058b9ca2df_3743db622d0c7764b@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
f2103575 by Sebastian Graf at 2024-10-04T22:04:47+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
70a9d1f4 by Simon Peyton Jones at 2024-10-04T22:05:45+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6d281e3595eaee513094a6c5d996337b432e380...70a9d1f404edf37a913ffc6467897ed79c884e00

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6d281e3595eaee513094a6c5d996337b432e380...70a9d1f404edf37a913ffc6467897ed79c884e00
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 21:59:22 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 04 Oct 2024 17:59:22 -0400
Subject: [Git][ghc/ghc][master] 3 commits: base: Add `HasCallStack` constraint
 to `ioError`
Message-ID: <6700653ae181c_613efef2b846317@gitlab.mail>



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


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -


30 changed files:

- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/openFile002.stderr-mingw32
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile001.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking001.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/T15349.stderr
- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs
- testsuite/tests/codeGen/should_run/cgrun016.stderr
- testsuite/tests/codeGen/should_run/cgrun025.stderr
- testsuite/tests/concurrent/should_run/T3279.hs
- testsuite/tests/ffi/should_run/T7170.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail2.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail7.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail8.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2293c0b7d709df7be04f596e72c97fd2435c4134...ac0040286a8962b728a7cdb3c1be4691db635366

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2293c0b7d709df7be04f596e72c97fd2435c4134...ac0040286a8962b728a7cdb3c1be4691db635366
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 21:59:58 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 04 Oct 2024 17:59:58 -0400
Subject: [Git][ghc/ghc][master] testsuite: remove accidentally checked in
 debug print logic
Message-ID: <6700655e4cc13_613ef4283d05105c@gitlab.mail>



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


Commits:
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -


1 changed file:

- testsuite/tests/profiling/should_run/all.T


Changes:

=====================================
testsuite/tests/profiling/should_run/all.T
=====================================
@@ -2,7 +2,6 @@ setTestOpts(js_skip) # JS backend doesn't support profiling yet
 
 prun_ways = (['prof'] if have_profiling() else []) + (['profdyn'] if have_dynamic_prof() else [])
 
-print(prun_ways)
 # Options to use when comparing .prof files
 test_opts_dot_prof = [ only_ways(['prof', 'profdyn'])
             , extra_ways(prun_ways) if prun_ways else skip]



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 22:06:12 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Fri, 04 Oct 2024 18:06:12 -0400
Subject: [Git][ghc/ghc][wip/monomorphic-nonempty-unzip] 5 commits: base: Add
 `HasCallStack` constraint to `ioError`
Message-ID: <670066d445a4d_613efd2000622a2@gitlab.mail>



Bodigrim pushed to branch wip/monomorphic-nonempty-unzip at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
6e39778b by Andrew Lelechenko at 2024-10-04T23:06:03+01:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -


30 changed files:

- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/openFile002.stderr-mingw32
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile001.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking001.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/T15349.stderr
- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/Text.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO/Error.hs
- testsuite/tests/codeGen/should_run/cgrun016.stderr
- testsuite/tests/codeGen/should_run/cgrun025.stderr
- testsuite/tests/concurrent/should_run/T3279.hs
- testsuite/tests/ffi/should_run/T7170.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail2.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail7.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ceb34978c85cf2e87f67bd2d907285b9402ec3e...6e39778b4dcb1a1d773ee0c1747f893cb0b6ac10

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ceb34978c85cf2e87f67bd2d907285b9402ec3e...6e39778b4dcb1a1d773ee0c1747f893cb0b6ac10
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct  4 22:37:24 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 04 Oct 2024 18:37:24 -0400
Subject: [Git][ghc/ghc][wip/T25281] Rec-sel wibble
Message-ID: <67006e24186fb_613ef86c9f07178d@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
a21e05d2 by Simon Peyton Jones at 2024-10-04T23:37:08+01:00
Rec-sel wibble

- - - - -


1 changed file:

- compiler/GHC/HsToCore/Docs.hs


Changes:

=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -2,6 +2,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE RecordWildCards #-}
 
 module GHC.HsToCore.Docs where
 
@@ -29,7 +30,7 @@ import Data.Map.Strict (Map)
 import qualified Data.Map as M
 import qualified Data.Set as Set
 import Data.Maybe
-import Data.Semigroup
+import qualified Data.Semigroup as S
 import GHC.IORef (readIORef)
 import GHC.Unit.Types
 import GHC.Hs
@@ -41,6 +42,8 @@ import GHC.Driver.DynFlags
 import GHC.Types.TypeEnv
 import GHC.Types.Id
 import GHC.Types.Unique.Map
+import GHC.Utils.Outputable
+import GHC.Utils.Panic
 
 -- | Extract docs from renamer output.
 -- This is monadic since we need to be able to read documentation added from
@@ -180,7 +183,7 @@ mkDocStructureFromExportList mdl import_avails export_list =
     -- Map from aliases to true module names.
     aliasMap :: Map ModuleName (NonEmpty ModuleName)
     aliasMap =
-        M.fromListWith (<>) $
+        M.fromListWith (S.<>) $
           (this_mdl_name, this_mdl_name :| [])
           : (flip concatMap (M.toList imported) $ \(mdl, imvs) ->
               [(imv_name imv, moduleName mdl :| []) | imv <- imvs])
@@ -253,7 +256,7 @@ mkMaps :: OccEnv Name
        -> (UniqMap Name [HsDoc GhcRn], UniqMap Name (IntMap (HsDoc GhcRn)))
 mkMaps env instances decls =
     ( listsToMapWith (++) (map (nubByName fst) decls')
-    , listsToMapWith (<>) (filterMapping (not . IM.null) args)
+    , listsToMapWith (S.<>) (filterMapping (not . IM.null) args)
     )
   where
     (decls', args) = unzip (map mappings decls)
@@ -446,14 +449,20 @@ isValD _ = False
 
 -- | All the sub declarations of a class (that we handle), ordered by
 -- source location, with documentation attached if it exists.
-classDecls :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDoc GhcRn])]
-classDecls class_ = filterDecls . collectDocs . sortLocatedA $ decls
-  where
-    decls = docs ++ defs ++ sigs ++ ats
-    docs  = mkDecls tcdDocs (DocD noExtField) class_
-    defs  = mkDecls tcdMeths (ValD noExtField) class_
-    sigs  = mkDecls tcdSigs (SigD noExtField) class_
-    ats   = mkDecls tcdATs (TyClD noExtField . FamDecl noExtField) class_
+classDecls :: TyClDecl GhcRn  -- Always a ClassDecl
+           -> [(LHsDecl GhcRn, [HsDoc GhcRn])]
+classDecls decl
+  | ClassDecl { .. } <- decl
+  , let decls = docs ++ defs ++ sigs ++ ats
+        docs  = mkDecls (DocD noExtField) tcdDocs
+        defs  = mkDecls (ValD noExtField) tcdMeths
+        sigs  = mkDecls (SigD noExtField) tcdSigs
+        ats   = mkDecls (TyClD noExtField . FamDecl noExtField) tcdATs
+
+  = filterDecls . collectDocs . sortLocatedA $ decls
+
+  | otherwise
+  = pprPanic "classDecls" (ppr decl)
 
 -- | Extract function argument docs from inside top-level decls.
 declTypeDocs :: HsDecl GhcRn -> IntMap (HsDoc GhcRn)
@@ -499,15 +508,15 @@ topDecls = filterClasses . filterDecls . collectDocs . sortLocatedA . ungroup
 
 -- | Take all declarations except pragmas, infix decls, rules from an 'HsGroup'.
 ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn]
-ungroup group_ =
-  mkDecls (tyClGroupTyClDecls . hs_tyclds) (TyClD noExtField)  group_ ++
-  mkDecls hs_derivds             (DerivD noExtField) group_ ++
-  mkDecls hs_defds               (DefD noExtField)   group_ ++
-  mkDecls hs_fords               (ForD noExtField)   group_ ++
-  mkDecls hs_docs                (DocD noExtField)   group_ ++
-  mkDecls (tyClGroupInstDecls . hs_tyclds) (InstD noExtField)  group_ ++
-  mkDecls (typesigs . hs_valds)  (SigD noExtField)   group_ ++
-  mkDecls (valbinds . hs_valds)  (ValD noExtField)   group_
+ungroup (HsGroup {..}) =
+  mkDecls (TyClD noExtField) (tyClGroupTyClDecls hs_tyclds)  ++
+  mkDecls (DerivD noExtField) hs_derivds ++
+  mkDecls (DefD noExtField)   hs_defds ++
+  mkDecls (ForD noExtField)   hs_fords ++
+  mkDecls (DocD noExtField)   hs_docs ++
+  mkDecls (InstD noExtField)  (tyClGroupInstDecls hs_tyclds) ++
+  mkDecls (SigD noExtField)   (typesigs  hs_valds) ++
+  mkDecls (ValD noExtField)   (valbinds hs_valds)  
   where
     typesigs :: HsValBinds GhcRn -> [LSig GhcRn]
     typesigs (XValBindsLR (NValBinds _ sig)) = filter (isUserSig . unLoc) sig
@@ -569,11 +578,10 @@ isUserSig _             = False
 
 -- | Take a field of declarations from a data structure and create HsDecls
 -- using the given constructor
-mkDecls :: (struct -> [GenLocated l decl])
-        -> (decl -> hsDecl)
-        -> struct
+mkDecls :: (decl -> hsDecl)
+        -> [GenLocated l decl]
         -> [GenLocated l hsDecl]
-mkDecls field con = map (fmap con) . field
+mkDecls con = map (fmap con)
 
 -- | Extracts out individual maps of documentation added via Template Haskell's
 -- @putDoc at .



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 06:25:56 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sat, 05 Oct 2024 02:25:56 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] A simplified design for handling
 ambiguous field occurances
Message-ID: <6700dbf45dbfc_38f0bb8b9264109556@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
d1432d31 by Hassan Al-Awwadi at 2024-10-05T08:25:09+02:00
A simplified design for handling ambiguous field occurances

- - - - -


13 changed files:

- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Type.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -557,11 +557,6 @@ deriving instance Data (ConDeclField GhcTc)
 deriving instance Data (FieldOcc GhcPs)
 deriving instance Data (FieldOcc GhcRn)
 deriving instance Data (FieldOcc GhcTc)
-deriving instance Data AmbiguousFieldOcc
-
-deriving instance Data (UpdFieldOcc GhcPs)
-deriving instance Data (UpdFieldOcc GhcRn)
-deriving instance Data (UpdFieldOcc GhcTc)
 
 -- deriving instance (DataId name) => Data (ImportDecl name)
 deriving instance Data (ImportDecl GhcPs)


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -59,12 +59,8 @@ module GHC.Hs.Type (
         ConDeclField(..), LConDeclField, pprConDeclFields,
 
         HsConDetails(..), noTypeArgs,
-        UpdFieldOcc(..), LUpdFieldOcc, mkUpdFieldOcc,
-        updFieldOccRdrName, updFieldOccLRdrName,
         FieldOcc(..), LFieldOcc, mkFieldOcc,
         fieldOccRdrName, fieldOccLRdrName,
-        AmbiguousFieldOcc(..),
-        ambiguousFieldOccRdrName,
 
         OpName(..),
 
@@ -1088,64 +1084,29 @@ also forbids them in types involved with `deriving`:
 *                                                                      *
 ************************************************************************
 
-Note [Lifecycle of an UpdFieldOcc]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When we have an update to a field occurrence (UpdFieldOcc) of the form
-rec{ label = value }, its possible that what label refers to is ambiguous,
-aka: that there are multiple record types with label as a field. In this case
-we can't go from a RdrName in the GhcPs stage to a Name in the GhcRn stage,
-because we have multiple Names we could choose from. Once we typecheck, we
-also do type-directed disambiguation, so at that stage we can go directly from
-a Name to an Id, modulo the disambiguation succeeding.
-
-To account for this the UpdFieldOcc occurrence has an instantiation for its
-XXUpdFieldOcc type family: AmbiguousFieldOcc. AmbiguousFieldOcc just stores
-the RdrName directly, whereas the FieldOcc (GhcPass p) field will go from
-RdrName to Name to Id as the stage shifts. Note that FieldOcc also stores
-the RdrName throughout its lifecycle, for exact printing purpose, after the
-Parse stage this RdrName just shifts from the foLabel field to the foExt field.
-
-Summarised the lifecycle of a FieldOcc is like this:
-* GhcPs: FieldOcc noExtField RdrName
-* GhcRn: FieldOcc RdrName    Name
-* GhcTc: FieldOcc RdrName    Id
-
-With its extra constructor `XFieldOcc currently being unused and disabled by
-instantiation XXFieldOcc (GhcPass p) = DataConCantHappen. In most cases just
-having this FieldOcc datatype is enough, but as mentioned the UpdFieldOcc case
-requires a case for ambiguity.
-
-The lifecycle of an UpdFieldOcc is as follows
-* GhcPs:
-  * UpdFieldOcc noExtField (FieldOcc GhcPs)
-  * XUpdFieldOcc DataConCantHappen
-* GhcRn:
-  * UpdFieldOcc noExtField (FieldOCc GhcRn)
-  * XUpdFieldOcc AmbiguousFieldOcc
-* GhcTc:
-  * UpdFieldOcc noExtField (FieldOCc GhcRn)
-  * XUpdFieldOcc DataConCantHappen
-
-so using DataConCantHappen we statically guarantee that when we go to a
-UpdFieldOcc GhcRn to UpdFieldOcc GhcTc we either succesfully disambiguate or
-error when we can't.
--}
+Note [Ambiguous FieldOcc in record updates]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+When renaming a "record field update" (`some_record{ field = expr }`), the field
+occurrence may be ambiguous if there are multiple record types with that same
+field label in scope. Instead of failing, we may attempt to do type-directed
+disambiguation: if we typecheck the record field update, we can disambiguate
+the `field` based on the record and field type.
 
--- | Ambiguous Field Occurrence
---
--- Represents an *occurrence* of a field that is definiely
--- ambiguous after the renamer, with the ambiguity resolved by the
--- typechecker. We always store the 'RdrName' that the user
--- originally wrote, and store the selector function after the typechecker (for
--- ambiguous occurrences).
---
--- Unambiguous field occurrences should be stored in the proper
--- UpdFieldOcc datacon of UpdFieldOcc.
---
--- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat".
--- See Note [Located RdrNames] in "GHC.Hs.Expr".
-newtype AmbiguousFieldOcc
-  = Ambiguous (LocatedN RdrName)
+In practice, this means an identifier of a field occurrence
+(`FieldOcc`) may have to go straight from `RdrName` to `Id`, since field
+ambiguity makes it impossible to construct a `Name` for the field.
+
+Since type-directed disambiguation is a GHC property rather than a property of
+the GHC-Haskell AST, we still parameterise a `FieldOcc` occurrence by `IdP p`,
+but in the case of the ambiguity we do the unthinkable and insert a mkUnboundName
+in the name. Very bad, yes, but since type-directed disambiguation is on the way
+out (see ticket #18966), we consider this acceptable for now.
+
+see also Wrinkle [Disambiguating fields] and note [Type-directed record disambiguation]
+
+NB: FieldOcc preserves the RdrName throughout its lifecycle for
+exact printing purposes.
+-}
 
 type instance XCFieldOcc GhcPs = NoExtField -- RdrName is stored in the proper IdP field
 type instance XCFieldOcc GhcRn = RdrName
@@ -1155,33 +1116,11 @@ type instance XXFieldOcc GhcPs = DataConCantHappen
 type instance XXFieldOcc GhcRn = DataConCantHappen
 type instance XXFieldOcc GhcTc = DataConCantHappen
 
-type instance XCUpdFieldOcc GhcPs = NoExtField
-type instance XCUpdFieldOcc GhcRn = NoExtField
-type instance XCUpdFieldOcc GhcTc = NoExtField
-
-type instance XXUpdFieldOcc GhcPs = DataConCantHappen
-type instance XXUpdFieldOcc GhcRn = AmbiguousFieldOcc
-type instance XXUpdFieldOcc GhcTc = DataConCantHappen
-
 --------------------------------------------------------------------------------
 
-mkUpdFieldOcc :: LocatedN RdrName -> UpdFieldOcc GhcPs
-mkUpdFieldOcc rdr@(L l _) = UpdFieldOcc noExtField (L (l2l l) $ mkFieldOcc rdr)
-
 mkFieldOcc :: LocatedN RdrName -> FieldOcc GhcPs
 mkFieldOcc rdr = FieldOcc noExtField rdr
 
-updFieldOccRdrName :: forall p. IsPass p => UpdFieldOcc (GhcPass p) -> RdrName
-updFieldOccRdrName = unLoc . updFieldOccLRdrName
-
-updFieldOccLRdrName :: forall p. IsPass p => UpdFieldOcc (GhcPass p) -> LocatedN RdrName
-updFieldOccLRdrName (UpdFieldOcc _ (L _ fo)) = fieldOccLRdrName fo
-updFieldOccLRdrName (XUpdFieldOcc xfo) = case ghcPass @p of
-  GhcRn -> case xfo of
-    Ambiguous l -> l
-  GhcPs -> dataConCantHappen xfo
-  GhcTc -> dataConCantHappen xfo
-
 fieldOccRdrName :: forall p. IsPass p => FieldOcc (GhcPass p) -> RdrName
 fieldOccRdrName fo = case ghcPass @p of
   GhcPs -> unLoc $ foLabel fo
@@ -1199,19 +1138,6 @@ fieldOccLRdrName fo = case ghcPass @p of
     let (L l _) = foLabel fo
      in L l (foExt fo)
 
-instance Outputable AmbiguousFieldOcc where
-  ppr = ppr . ambiguousFieldOccRdrName
-
-instance OutputableBndr AmbiguousFieldOcc where
-  pprInfixOcc  = pprInfixOcc . ambiguousFieldOccRdrName
-  pprPrefixOcc = pprPrefixOcc . ambiguousFieldOccRdrName
-
-instance OutputableBndr (Located AmbiguousFieldOcc) where
-  pprInfixOcc  = pprInfixOcc . unLoc
-  pprPrefixOcc = pprPrefixOcc . unLoc
-
-ambiguousFieldOccRdrName :: AmbiguousFieldOcc -> RdrName
-ambiguousFieldOccRdrName (Ambiguous rdr) = unLoc rdr
 
 {-
 ************************************************************************
@@ -1352,12 +1278,6 @@ instance (OutputableBndrId pass) => OutputableBndr (GenLocated SrcSpan (FieldOcc
   pprInfixOcc  = pprInfixOcc . unLoc
   pprPrefixOcc = pprPrefixOcc . unLoc
 
-instance (IsPass p) => Outputable (UpdFieldOcc (GhcPass p))where
-  ppr = ppr . updFieldOccRdrName
-
-instance (IsPass p) => OutputableBndr (UpdFieldOcc (GhcPass p)) where
-  pprInfixOcc  = pprInfixOcc . updFieldOccRdrName
-  pprPrefixOcc = pprPrefixOcc . updFieldOccRdrName
 
 
 ppr_tylit :: (HsTyLit (GhcPass p)) -> SDoc
@@ -1656,5 +1576,3 @@ type instance Anno HsIPName = EpAnnCO
 type instance Anno (ConDeclField (GhcPass p)) = SrcSpanAnnA
 
 type instance Anno (FieldOcc (GhcPass p)) = SrcSpanAnnA
-type instance Anno AmbiguousFieldOcc = SrcSpanAnnA
-type instance Anno (UpdFieldOcc (GhcPass p)) = SrcSpanAnnA


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -1822,13 +1822,14 @@ repUpdFields :: [LHsRecUpdField GhcRn GhcRn] -> MetaM (Core [M TH.FieldExp])
 repUpdFields = repListM fieldExpTyConName rep_fld
   where
     rep_fld :: LHsRecUpdField GhcRn GhcRn -> MetaM (Core (M TH.FieldExp))
-    rep_fld (L l fld) = case unLoc (hfbLHS fld) of
-      UpdFieldOcc _ (L _ (FieldOcc _ (L _ sel_name))) ->
-          do  { fn <- lookupLOcc (L l sel_name)
-              ; e  <- repLE (hfbRHS fld)
-              ; repFieldExp fn e
-              }
-      (XUpdFieldOcc _)                                -> notHandled (ThAmbiguousRecordUpdates fld)
+    rep_fld (L l fld) = 
+       let (FieldOcc _ (L _ sel_name)) = unLoc (hfbLHS fld)
+       in if  isUnboundName sel_name
+        then  notHandled (ThAmbiguousRecordUpdates fld)
+        else  do  { fn <- lookupLOcc (L l sel_name)
+                  ; e  <- repLE (hfbRHS fld)
+                  ; repFieldExp fn e
+                  }
 
 
 


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -828,7 +828,6 @@ class ( HiePass (NoGhcTcPass p)
       , Data (Stmt  (GhcPass p) (LocatedA (HsCmd  (GhcPass p))))
       , Data (HsExpr (GhcPass p))
       , Data (HsCmd  (GhcPass p))
-      , Data AmbiguousFieldOcc
       , Data (HsCmdTop (GhcPass p))
       , Data (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p))))
       , Data (HsUntypedSplice (GhcPass p))
@@ -1509,10 +1508,6 @@ instance ( ToHie (RFContext label)
       , toHie expr
       ]
 
-instance HiePass p => ToHie (RFContext (LocatedA (UpdFieldOcc (GhcPass p)))) where
-  toHie (RFC c rhs (L nspan (UpdFieldOcc _ (L _ fo)))) = concatM
-    [toHie (RFC c rhs (L nspan fo))]
-  toHie (RFC _ _ (L _ (XUpdFieldOcc _))) = concatM []
 instance HiePass p => ToHie (RFContext (LocatedA (FieldOcc (GhcPass p)))) where
   toHie (RFC c rhs (L nspan f)) = concatM $
     case hiePass @p of


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -2912,7 +2912,7 @@ mkRdrRecordUpd overloaded_on exp@(L loc _) fbinds anns = do
     True -> do
       let qualifiedFields =
             [ L l lbl | L _ (HsFieldBind _ (L l lbl) _ _) <- fs'
-                      , isQual . updFieldOccRdrName $ lbl
+                      , isQual . fieldOccRdrName $ lbl
             ]
       case qualifiedFields of
           qf:_ -> addFatalError $ mkPlainErrorMsgEnvelope (getLocA qf) $
@@ -2958,7 +2958,7 @@ mk_rec_fields fs (Just s)  = HsRecFields { rec_ext = noExtField, rec_flds = fs
 
 mk_rec_upd_field :: HsRecField GhcPs (LHsExpr GhcPs) -> HsRecUpdField GhcPs GhcPs
 mk_rec_upd_field (HsFieldBind noAnn (L loc (FieldOcc _ rdr)) arg pun)
-  = HsFieldBind noAnn (L loc $ UpdFieldOcc noExtField (L loc (FieldOcc noExtField rdr))) arg pun
+  = HsFieldBind noAnn (L loc (FieldOcc noExtField rdr)) arg pun
 
 mkInlinePragma :: SourceText -> (InlineSpec, RuleMatchInfo) -> Maybe Activation
                -> InlinePragma


=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -1526,7 +1526,7 @@ lookupGlobalOccRn_overloaded rdr_name =
               return (Just gre) }
 
 getFieldUpdLbl :: IsPass p => LHsRecUpdField (GhcPass p) q -> LocatedN RdrName
-getFieldUpdLbl = updFieldOccLRdrName . unLoc . hfbLHS . unLoc
+getFieldUpdLbl = fieldOccLRdrName . unLoc . hfbLHS . unLoc
 
 -- | Returns all possible collections of field labels for the given
 -- record update.
@@ -1623,7 +1623,7 @@ lookupRecUpdFields flds
 getUpdFieldLbls :: forall p q. IsPass p
                 => [LHsRecUpdField (GhcPass p) q] -> [RdrName]
 getUpdFieldLbls
-  = map $ updFieldOccRdrName
+  = map $ fieldOccRdrName
         . unXRec @(GhcPass p)
         . hfbLHS
         . unXRec @(GhcPass p)


=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -890,7 +890,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
               -> Maybe Name -- The constructor (Nothing for an
                                 --    out of scope constructor)
               -> [LHsRecField GhcRn (LocatedA arg)] -- Explicit fields
-              -> RnM ([LHsRecField GhcRn (LocatedA arg)])   -- Field Labels we need to fill in
+              -> RnM [LHsRecField GhcRn (LocatedA arg)]   -- Field Labels we need to fill in
     rn_dotdot (Just (L loc_e (RecFieldsDotDot n))) (Just con) flds -- ".." on record construction / pat match
       | not (isUnboundName con) -- This test is because if the constructor
                                 -- isn't in scope the constructor lookup will add
@@ -1018,7 +1018,7 @@ rnHsRecUpdFields flds
               -> RnM ([LHsRecUpdField GhcRn GhcRn], FreeVars)
       rn_flds _ _ [] = return ([], emptyFVs)
       rn_flds pun_ok mb_unambig_lbls
-              ((L l (HsFieldBind { hfbLHS = L loc (UpdFieldOcc _ (L _ (FieldOcc _ f)))
+              ((L l (HsFieldBind { hfbLHS = L loc (FieldOcc _ f)
                                  , hfbRHS = arg
                                  , hfbPun = pun })):flds)
         = do { let lbl = unLoc f
@@ -1030,12 +1030,15 @@ rnHsRecUpdFields flds
                                ; return (L (l2l loc) (HsVar noExtField (L (l2l loc) arg_rdr))) }
                        else return arg
              ; (arg'', fvs) <- rnLExpr arg'
-             ; let lbl' :: UpdFieldOcc GhcRn
+             ; let lbl' :: FieldOcc GhcRn
                    lbl' = case mb_unambig_lbls of
                             { Just (fl:_) ->
                                 let sel_name = flSelector fl
-                                in UpdFieldOcc noExtField (L (l2l loc) (FieldOcc lbl (L (l2l loc) sel_name)))
-                            ; _ -> XUpdFieldOcc (Ambiguous (L (l2l loc) lbl)) }
+                                in FieldOcc lbl (L (l2l loc) sel_name)
+                                -- We have one last chance to be disambiguated during type checking.
+                                -- At least, until type-directed disambiguation stops being supported.
+                                -- see note [Ambiguous FieldOcc in record updates] for more info.
+                            ; _ -> FieldOcc lbl (L (l2l loc) (mkUnboundName $ rdrNameOcc lbl)) }
                    fld' :: LHsRecUpdField GhcRn GhcRn
                    fld' = L l (HsFieldBind { hfbAnn = noAnn
                                            , hfbLHS = L (l2l loc) lbl'
@@ -1043,8 +1046,6 @@ rnHsRecUpdFields flds
                                            , hfbPun = pun })
              ; (flds', fvs') <- rn_flds pun_ok (tail <$> mb_unambig_lbls) flds
              ; return (fld' : flds', fvs `plusFV` fvs') }
-      rn_flds _ _ ((L _ (HsFieldBind { hfbLHS = L _ (XUpdFieldOcc impossible ) })):_)
-        = dataConCantHappen impossible
 
 getFieldIds :: [LHsRecField GhcRn arg] -> [Name]
 getFieldIds flds = map (hsRecFieldSel . unLoc) flds


=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -1298,12 +1298,10 @@ expandRecordUpd record_expr possible_parents rbnds res_ty
        -- See Note [Disambiguating record updates] in GHC.Rename.Pat.
        ; (cons, rbinds)
            <- disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty
-       ; let upd_flds      = map (unLoc . hfbLHS . unLoc) rbinds
-             -- upd_flds has type 'UpdFieldOcc GhcTc' so ufoField is not partial here.
-             sel_ids       = map (unLoc . foLabel . unLoc . ufoField) upd_flds
+       ; let sel_ids       = map (unLoc . foLabel . unLoc . hfbLHS . unLoc) rbinds
              upd_fld_names = map idName sel_ids
              relevant_cons = nonDetEltsUniqSet cons
-             relevant_con = head relevant_cons
+             relevant_con  = head relevant_cons
 
       -- STEP 2: expand the record update.
       --
@@ -1583,7 +1581,7 @@ disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty
                 -> TcM (LHsRecUpdField GhcTc GhcRn)
     lookupField fld_gre (L l upd)
       = do { let L loc af = hfbLHS upd
-                 lbl      = updFieldOccRdrName af
+                 lbl      = fieldOccRdrName af
                  mb_gre   = pickGREs lbl [fld_gre]
                       -- NB: this GRE can be 'Nothing' when in GHCi.
                       -- See test T10439.
@@ -1595,7 +1593,7 @@ disambiguateRecordBinds record_expr record_rho possible_parents rbnds res_ty
            ; sel <- tcLookupId (greName fld_gre)
            ; return $ L l HsFieldBind
                { hfbAnn = hfbAnn upd
-               , hfbLHS = L (l2l loc) (UpdFieldOcc noExtField (L (l2l loc) $ FieldOcc lbl  (L (l2l loc) sel)))
+               , hfbLHS = L (l2l loc) (FieldOcc lbl  (L (l2l loc) sel))
                , hfbRHS = hfbRHS upd
                , hfbPun = hfbPun upd
                } }


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -1159,7 +1159,7 @@ cvtl e = wrapLA (cvt e)
                               ; return $ mkRdrRecordCon c' (HsRecFields noExtField flds' Nothing) noAnn }
     cvt (RecUpdE e flds) = do { e' <- cvtl e
                               ; flds'
-                                  <- mapM (cvtFld (wrapParLA mkUpdFieldOcc))
+                                  <- mapM (cvtFld (wrapParLA mkFieldOcc))
                                            flds
                               ; return $ RecordUpd noAnn e' $
                                          RegularRecUpdFields


=====================================
compiler/Language/Haskell/Syntax/Extension.hs
=====================================
@@ -685,9 +685,6 @@ type family XXConDeclField x
 
 -- ---------------------------------------------------------------------
 -- FieldOcc type families
-type family XCUpdFieldOcc x
-type family XXUpdFieldOcc x
-
 type family XCFieldOcc x
 type family XXFieldOcc x
 


=====================================
compiler/Language/Haskell/Syntax/Pat.hs
=====================================
@@ -319,14 +319,14 @@ type LHsFieldBind p id arg = XRec p (HsFieldBind id arg)
 -- | Located Haskell Record Field
 type LHsRecField  p arg = XRec p (HsRecField  p arg)
 
--- | Located Haskell Record Update Field
-type LHsRecUpdField p q = XRec p (HsRecUpdField p q)
-
 -- | Haskell Record Field
 type HsRecField p arg   = HsFieldBind (LFieldOcc p) arg
 
+-- | Located Haskell Record Update Field
+type LHsRecUpdField p q = XRec p (HsRecUpdField p q)
+
 -- | Haskell Record Update Field
-type HsRecUpdField p q  = HsFieldBind (LUpdFieldOcc p) (LHsExpr q)
+type HsRecUpdField p q  = HsFieldBind (LFieldOcc p) (LHsExpr q)
 
 -- | Haskell Field Binding
 --


=====================================
compiler/Language/Haskell/Syntax/Type.hs
=====================================
@@ -54,7 +54,6 @@ module Language.Haskell.Syntax.Type (
 
         HsConDetails(..), noTypeArgs,
 
-        UpdFieldOcc(..), LUpdFieldOcc,
         FieldOcc(..), LFieldOcc,
 
         mapHsOuterImplicit,
@@ -1352,21 +1351,6 @@ The SrcSpan is the span of the original HsPar
 *                                                                      *
 ************************************************************************
 -}
--- | Located Update Field Occurrence
-type LUpdFieldOcc pass = XRec pass (UpdFieldOcc pass)
-
--- | An update field occurrence is a field occurrence that
--- occurs in an update position (such as @x{field=...}@).
---
--- We differentiate between the two since there may be additional information concerning the update field.
--- In particular, in GHC, an update field occurrence *may* be ambiguous, unlike other field occurrences.
--- See Note [Lifecycle of an UpdFieldOcc]
-data UpdFieldOcc pass
-  = UpdFieldOcc {
-    ufoExt   :: XCUpdFieldOcc pass,
-    ufoField :: LFieldOcc pass
-  }
-  | XUpdFieldOcc (XXUpdFieldOcc pass)
 
 -- | Located Field Occurrence
 type LFieldOcc pass = XRec pass (FieldOcc pass)
@@ -1381,6 +1365,11 @@ type LFieldOcc pass = XRec pass (FieldOcc pass)
 -- We store both the 'RdrName' the user originally wrote, and after
 -- the renamer we use the extension field to store the selector
 -- function.
+--
+-- There is a wrinkle in that update field occurances are sometimes
+-- ambiguous during the rename stage. See note
+-- [Ambiguous FieldOcc in record updates] to see how we currently
+-- handle this.
 data FieldOcc pass
   = FieldOcc {
         foExt :: XCFieldOcc pass


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3505,22 +3505,6 @@ instance (ExactPrint body)
 
 -- ---------------------------------------------------------------------
 
-instance (ExactPrint (LocatedA body))
-    => ExactPrint (HsFieldBind (LocatedA (UpdFieldOcc GhcPs)) (LocatedA body)) where
-  getAnnotationEntry _ = NoEntryVal
-  setAnnotationAnchor a _ _ _ = a
-
-  exact (HsFieldBind an f arg isPun) = do
-    debugM $ "HsRecUpdField"
-    f' <- markAnnotated f
-    an0 <- if isPun then return an
-             else markEpAnnL an lidl AnnEqual
-    arg' <- if isPun
-              then return arg
-              else markAnnotated arg
-    return (HsFieldBind an0 f' arg' isPun)
-
--- ---------------------------------------------------------------------
 instance ExactPrint (LHsRecUpdFields GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
@@ -4591,13 +4575,6 @@ instance ExactPrint (FieldOcc GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (UpdFieldOcc GhcPs) where
-  getAnnotationEntry = const NoEntryVal
-  setAnnotationAnchor a _ _ _ = a
-  exact f@(UpdFieldOcc _ n)       = markAnnotated n >> return f
-  exact (XUpdFieldOcc impossible) = dataConCantHappen impossible
--- ---------------------------------------------------------------------
-
 instance (ExactPrint a) => ExactPrint (HsScaled GhcPs a) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 06:41:02 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sat, 05 Oct 2024 02:41:02 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] Refactor FieldOcc and AmbiguousFieldOcc
 with TTG
Message-ID: <6700df7e6a397_38f0bb97e1041102a7@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
3ff46ce0 by Hassan Al-Awwadi at 2024-10-05T08:40:05+02:00
Refactor FieldOcc and AmbiguousFieldOcc with TTG

The main purpose of this commit is to rip RdrName out of FieldOcc, and
as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

co-authored by: @Jade <Jade512 at proton.me>
                @Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3ff46ce015f15f532f7bbca1b551cb54eac51949

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 06:42:23 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sat, 05 Oct 2024 02:42:23 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] 5 commits: base: Add `HasCallStack`
 constraint to `ioError`
Message-ID: <6700dfcf661c7_38f0bb9c5dc41109f@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
4e2d3926 by Hassan Al-Awwadi at 2024-10-05T08:42:02+02:00
Refactor FieldOcc and AmbiguousFieldOcc with TTG

The main purpose of this commit is to rip RdrName out of FieldOcc, and
as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

co-authored by: @Jade <Jade512 at proton.me>
                @Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ff46ce015f15f532f7bbca1b551cb54eac51949...4e2d3926a2d547f7fa072fa52ee9de2b168a6e89

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3ff46ce015f15f532f7bbca1b551cb54eac51949...4e2d3926a2d547f7fa072fa52ee9de2b168a6e89
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 09:53:26 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 05 Oct 2024 05:53:26 -0400
Subject: [Git][ghc/ghc][wip/T25281] 6 commits: base: Add `HasCallStack`
 constraint to `ioError`
Message-ID: <67010c9643d5f_24e4ec44ab6046769@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
e47a5808 by Sebastian Graf at 2024-10-05T10:53:16+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
b9d85416 by Simon Peyton Jones at 2024-10-05T10:53:16+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a21e05d2b0429e09cc1e69c706de9ca834c9a97f...b9d854166c1f8f950cbaeb3ad0e4d40d70ea3d07

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a21e05d2b0429e09cc1e69c706de9ca834c9a97f...b9d854166c1f8f950cbaeb3ad0e4d40d70ea3d07
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 10:29:49 2024
From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo))
Date: Sat, 05 Oct 2024 06:29:49 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/teo/unwired-th-changelog
Message-ID: <6701151d82bca_24e4ec65f270473f3@gitlab.mail>



Teo Camarasu pushed new branch wip/teo/unwired-th-changelog at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/unwired-th-changelog
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 11:06:14 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 05 Oct 2024 07:06:14 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: testsuite:
 remove accidentally checked in debug print logic
Message-ID: <67011da619f3_24e4ec8fd9dc58585@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
3c6b5905 by Rodrigo Mesquita at 2024-10-05T07:06:08-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
d369ced5 by Andrew Lelechenko at 2024-10-05T07:06:09-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -


30 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/using-warnings.rst
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/tests/T9586.hs
- libraries/base/tests/list001.hs
- testsuite/tests/ghci/scripts/T14828.script
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci036.script
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/module/Mod137_A.hs
- testsuite/tests/module/Mod138_A.hs
- testsuite/tests/module/Mod141_A.hs
- testsuite/tests/module/mod154.hs
- testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs
- testsuite/tests/perf/compiler/T16875.hs
- testsuite/tests/perf/compiler/T16875.stderr
- testsuite/tests/profiling/should_run/all.T
- testsuite/tests/rename/prog001/rn037.hs
- testsuite/tests/rename/should_compile/T17244A.hs
- + testsuite/tests/rename/should_compile/T17244A.stderr
- testsuite/tests/rename/should_compile/T17244B.hs
- testsuite/tests/rename/should_compile/T17244B.stderr
- testsuite/tests/rename/should_compile/T17244C.hs
- testsuite/tests/rename/should_compile/T17244C.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54673115e4703199d61895050893ea694e1e4265...d369ced51dc60c01bd4cce3881f37c138a10e73a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54673115e4703199d61895050893ea694e1e4265...d369ced51dc60c01bd4cce3881f37c138a10e73a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 14:01:18 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 05 Oct 2024 10:01:18 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann] 89 commits: ci: Run
 abi-test on test-abi label
Message-ID: <670146ae339dd_2c6e91508318105c5@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann at Glasgow Haskell Compiler / GHC


Commits:
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
0e68fdaa by Alan Zimmerman at 2024-10-05T11:51:32+01:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
abde3b52 by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: introduce EpAnnLam for lambda annotations

And remove `glAA` from `Parser.y`, it is the same as `glR`

- - - - -
2ce56c4f by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: Remove unused annotation from XOpApp

- - - - -
5c5ccc84 by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: Use EpToken for XNPat and XNegApp

- - - - -
b48332bd by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

More removing [AddEpAnn] in favour of specific versions instead.

- - - - -
9f07fcfd by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: Use specific annotation for MultiIf

Instead of [AddEpAnn]

- - - - -
896735ae by Alan Zimmerman at 2024-10-05T11:51:33+01:00
EPA: Move annotations into FunRhs

- - - - -
c8d057a4 by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

- - - - -
a5c623c1 by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from ArithSeq

- - - - -
24755f66 by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from HsProc

- - - - -
544d8663 by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from HsStatic

- - - - -
4426a37a by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from BindStmt

- - - - -
caf94c01 by Alan Zimmerman at 2024-10-05T11:51:45+01:00
EPA: Remove [AddEpAnn] from TransStmt

- - - - -
ee14b1bc by Alan Zimmerman at 2024-10-05T14:10:06+01:00
EPA: Remove [AddEpAnn] from HsTypedSplice

- - - - -
5b1f1a39 by Alan Zimmerman at 2024-10-05T14:58:27+01:00
EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6669f49a91a4de5b6cc48efc9ffd643eaf8b70b8...5b1f1a392585c79f06cc37e799533f912eb24c97

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6669f49a91a4de5b6cc48efc9ffd643eaf8b70b8...5b1f1a392585c79f06cc37e799533f912eb24c97
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 14:36:40 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 05 Oct 2024 10:36:40 -0400
Subject: [Git][ghc/ghc][master] Deprecation for WarnCompatUnqualifiedImports
Message-ID: <67014ef83cceb_2c6e9164ae10215c0@gitlab.mail>



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


Commits:
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -


30 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/using-warnings.rst
- libraries/base/tests/T9586.hs
- libraries/base/tests/list001.hs
- testsuite/tests/ghci/scripts/T14828.script
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci036.script
- testsuite/tests/module/Mod137_A.hs
- testsuite/tests/module/Mod138_A.hs
- testsuite/tests/module/Mod141_A.hs
- testsuite/tests/module/mod154.hs
- testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs
- testsuite/tests/perf/compiler/T16875.hs
- testsuite/tests/perf/compiler/T16875.stderr
- testsuite/tests/rename/prog001/rn037.hs
- testsuite/tests/rename/should_compile/T17244A.hs
- + testsuite/tests/rename/should_compile/T17244A.stderr
- testsuite/tests/rename/should_compile/T17244B.hs
- testsuite/tests/rename/should_compile/T17244B.stderr
- testsuite/tests/rename/should_compile/T17244C.hs
- testsuite/tests/rename/should_compile/T17244C.stderr
- testsuite/tests/rename/should_compile/T4478.hs
- testsuite/tests/rename/should_compile/T7167.hs
- testsuite/tests/rename/should_compile/T7167.stderr
- testsuite/tests/rename/should_compile/rn025.hs
- testsuite/tests/rename/should_compile/rn027.hs
- testsuite/tests/rename/should_compile/rn031.hs
- testsuite/tests/rename/should_compile/rn060.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68e2da5a9ed2f0221b0b17a19032d909a1ea1037

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 14:37:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 05 Oct 2024 10:37:15 -0400
Subject: [Git][ghc/ghc][master] Restrict Data.List.NonEmpty.unzip to NonEmpty
 (a, b) -> (NonEmpty a, NonEmpty b)
Message-ID: <67014f1af31fb_2c6e91662a60244f7@gitlab.mail>



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


Commits:
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -


6 changed files:

- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -1,5 +1,8 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
+## 4.22.0.0 *TBA*
+  * Restrict `Data.List.NonEmpty.unzip` to `NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)`. ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+
 ## 4.21.0.0 *TBA*
   * `GHC.Desugar` has been deprecated and should be removed in GHC 9.14. ([CLC proposal #216](https://github.com/haskell/core-libraries-committee/issues/216))
   * Add a `readTixFile` field to the `HpcFlags` record in `GHC.RTS.Flags` ([CLC proposal #276](https://github.com/haskell/core-libraries-committee/issues/276))


=====================================
libraries/base/src/Data/List/NonEmpty.hs
=====================================
@@ -537,11 +537,9 @@ isPrefixOf (y:ys) (x :| xs) = (y == x) && List.isPrefixOf ys xs
   | otherwise = error "NonEmpty.!! negative index"
 infixl 9 !!
 
-
 -- | The 'unzip' function is the inverse of the 'zip' function.
-unzip :: Functor f => f (a,b) -> (f a, f b)
+unzip :: NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
 unzip xs = (fst <$> xs, snd <$> xs)
-{-# WARNING in "x-data-list-nonempty-unzip" unzip "This function will be made monomorphic in base-4.22, consider switching to Data.Functor.unzip" #-}
 
 -- | The 'nub' function removes duplicate elements from a list. In
 -- particular, it keeps only the first occurrence of each element.


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1486,7 +1486,7 @@ module Data.List.NonEmpty where
   uncons :: forall a. NonEmpty a -> (a, GHC.Internal.Maybe.Maybe (NonEmpty a))
   unfold :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
   unfoldr :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
-  unzip :: forall (f :: * -> *) a b. GHC.Internal.Base.Functor f => f (a, b) -> (f a, f b)
+  unzip :: forall a b. NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
   xor :: NonEmpty GHC.Types.Bool -> GHC.Types.Bool
   zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
   zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1486,7 +1486,7 @@ module Data.List.NonEmpty where
   uncons :: forall a. NonEmpty a -> (a, GHC.Internal.Maybe.Maybe (NonEmpty a))
   unfold :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
   unfoldr :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
-  unzip :: forall (f :: * -> *) a b. GHC.Internal.Base.Functor f => f (a, b) -> (f a, f b)
+  unzip :: forall a b. NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
   xor :: NonEmpty GHC.Types.Bool -> GHC.Types.Bool
   zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
   zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1486,7 +1486,7 @@ module Data.List.NonEmpty where
   uncons :: forall a. NonEmpty a -> (a, GHC.Internal.Maybe.Maybe (NonEmpty a))
   unfold :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
   unfoldr :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
-  unzip :: forall (f :: * -> *) a b. GHC.Internal.Base.Functor f => f (a, b) -> (f a, f b)
+  unzip :: forall a b. NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
   xor :: NonEmpty GHC.Types.Bool -> GHC.Types.Bool
   zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
   zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1486,7 +1486,7 @@ module Data.List.NonEmpty where
   uncons :: forall a. NonEmpty a -> (a, GHC.Internal.Maybe.Maybe (NonEmpty a))
   unfold :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
   unfoldr :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
-  unzip :: forall (f :: * -> *) a b. GHC.Internal.Base.Functor f => f (a, b) -> (f a, f b)
+  unzip :: forall a b. NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)
   xor :: NonEmpty GHC.Types.Bool -> GHC.Types.Bool
   zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
   zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4327f0e8c5091dae9ab0f58e2e3c8af5bacd12ea

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 17:09:06 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 05 Oct 2024 13:09:06 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Deprecation
 for WarnCompatUnqualifiedImports
Message-ID: <670172b24c245_554c31ad8447377d@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
8fda6b89 by Daniel Díaz at 2024-10-05T13:08:54-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
766a6a57 by Teo Camarasu at 2024-10-05T13:08:55-04:00
Add changelog entries for !12479

- - - - -


30 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/using-warnings.rst
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/tests/T9586.hs
- libraries/base/tests/list001.hs
- libraries/template-haskell/changelog.md
- testsuite/tests/ghci/scripts/T14828.script
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci036.script
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/module/Mod137_A.hs
- testsuite/tests/module/Mod138_A.hs
- testsuite/tests/module/Mod141_A.hs
- testsuite/tests/module/mod154.hs
- testsuite/tests/overloadedlists/should_run/overloadedlistsrun05.hs
- testsuite/tests/perf/compiler/T16875.hs
- testsuite/tests/perf/compiler/T16875.stderr
- testsuite/tests/rename/prog001/rn037.hs
- testsuite/tests/rename/should_compile/T17244A.hs
- + testsuite/tests/rename/should_compile/T17244A.stderr
- testsuite/tests/rename/should_compile/T17244B.hs
- testsuite/tests/rename/should_compile/T17244B.stderr
- testsuite/tests/rename/should_compile/T17244C.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d369ced51dc60c01bd4cce3881f37c138a10e73a...766a6a57fd9e52bb6918cf5f60bd6123ac760b83

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d369ced51dc60c01bd4cce3881f37c138a10e73a...766a6a57fd9e52bb6918cf5f60bd6123ac760b83
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 17:29:58 2024
From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal))
Date: Sat, 05 Oct 2024 13:29:58 -0400
Subject: [Git][ghc/ghc][wip/T25243] 133 commits: AArch64: Implement
 takeRegRegMoveInstr
Message-ID: <67017796130a5_554c3437c40808b8@gitlab.mail>



Krzysztof Gogolewski pushed to branch wip/T25243 at Glasgow Haskell Compiler / GHC


Commits:
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
1a47fa6f by Krzysztof Gogolewski at 2024-10-05T19:29:09+02:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -


25 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b436a004bc2bbc90579b2c879d419a3e0b27ad2...1a47fa6fbf1d20ec41d89ae4506dc6def22b558a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b436a004bc2bbc90579b2c879d419a3e0b27ad2...1a47fa6fbf1d20ec41d89ae4506dc6def22b558a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 17:35:58 2024
From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal))
Date: Sat, 05 Oct 2024 13:35:58 -0400
Subject: [Git][ghc/ghc][wip/T25243] Only allow (a => b) :: Constraint rather
 than CONSTRAINT rep
Message-ID: <670178fe3b5c7_554c33e8f64811fd@gitlab.mail>



Krzysztof Gogolewski pushed to branch wip/T25243 at Glasgow Haskell Compiler / GHC


Commits:
bb7a8460 by Krzysztof Gogolewski at 2024-10-05T19:33:52+02:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -


4 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 19:32:18 2024
From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal))
Date: Sat, 05 Oct 2024 15:32:18 -0400
Subject: [Git][ghc/ghc][wip/T25243] Only allow (a => b) :: Constraint rather
 than CONSTRAINT rep
Message-ID: <670194426db64_402742f1ee428295@gitlab.mail>



Krzysztof Gogolewski pushed to branch wip/T25243 at Glasgow Haskell Compiler / GHC


Commits:
8cc3482b by Krzysztof Gogolewski at 2024-10-05T21:32:10+02:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -


5 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T
- testsuite/tests/rename/should_fail/rnfail026.stderr


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail026.stderr
=====================================
@@ -1,6 +1,6 @@
-
 rnfail026.hs:16:27: error: [GHC-83865]
-    • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’
+    • Expected kind ‘* -> *’, but ‘Eq a => Set a’ has kind ‘*’
     • In the first argument of ‘Monad’, namely
         ‘(forall a. Eq a => Set a)’
       In the instance declaration for ‘Monad (forall a. Eq a => Set a)’
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8cc3482bdb1f6a021ef617f9af623641aee3e171

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 20:50:57 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 05 Oct 2024 16:50:57 -0400
Subject: [Git][ghc/ghc][wip/T25281] Yet more
Message-ID: <6701a6b1ee8b2_8c3bcd7d701222@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
1768fb71 by Simon Peyton Jones at 2024-10-05T21:50:39+01:00
Yet more

- - - - -


2 changed files:

- compiler/GHC/Rename/Env.hs
- compiler/GHC/Tc/Instance/Typeable.hs


Changes:

=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -563,7 +563,7 @@ lookupRecFieldOcc mb_con rdr_name
           ; Just nm -> return nm } }
 
   | otherwise  -- Can't use the data constructor to disambiguate
-  = lookupGlobalOccRn' (RelevantGREsFOS WantField) rdr_name
+  = lookupGlobalOccRn' WantField rdr_name
     -- This use of Global is right as we are looking up a selector,
     -- which can only be defined at the top level.
 
@@ -1405,20 +1405,23 @@ lookupGlobalOccRn :: RdrName -> RnM Name
 -- environment.
 --
 -- Used by exports_from_avail
-lookupGlobalOccRn = lookupGlobalOccRn' (RelevantGREsFOS WantNormal)
-
-lookupGlobalOccRn' :: WhichGREs GREInfo -> RdrName -> RnM Name
-lookupGlobalOccRn' which_gres rdr_name =
-  lookupExactOrOrig rdr_name greName $ do
-    mb_gre <- lookupGlobalOccRn_base which_gres rdr_name
-    case mb_gre of
-      Just gre -> return (greName gre)
-      Nothing -> do { traceRn "lookupGlobalOccRn" (ppr rdr_name)
-                    ; unboundName (LF which_suggest WL_Global) rdr_name }
-        where which_suggest = case includeFieldSelectors which_gres of
-                WantBoth   -> WL_RecField
-                WantField  -> WL_RecField
-                WantNormal -> WL_Anything
+lookupGlobalOccRn = lookupGlobalOccRn' WantNormal
+
+lookupGlobalOccRn' :: FieldsOrSelectors -> RdrName -> RnM Name
+lookupGlobalOccRn' fos rdr_name
+  = lookupExactOrOrig rdr_name greName $
+    do { mb_gre <- lookupGlobalOccRn_base which_gres rdr_name
+       ; case mb_gre of
+           Just gre -> return (greName gre)
+           Nothing  -> do { traceRn "lookupGlobalOccRn" (ppr rdr_name)
+                          ; unboundName looking_for rdr_name } }
+  where
+    which_gres   = RelevantGREsFOS fos
+    looking_for  = LF { lf_which = what_looking, lf_where =  WL_Global }
+    what_looking = case fos of
+                      WantBoth   -> WL_RecField
+                      WantField  -> WL_RecField
+                      WantNormal -> WL_Anything
 
 -- Looks up a RdrName occurrence in the GlobalRdrEnv and with
 -- lookupQualifiedNameGHCi. Does not try to find an Exact or Orig name first.


=====================================
compiler/GHC/Tc/Instance/Typeable.hs
=====================================
@@ -221,18 +221,21 @@ data TypeableTyCon
       , tycon_rep_id :: !Id
       }
 
--- | A group of 'TyCon's in need of type-rep bindings.
 data TypeRepTodo
-    = TypeRepTodo
-      { mod_rep_expr    :: LHsExpr GhcTc    -- ^ Module's typerep binding
-      , pkg_fingerprint :: !Fingerprint     -- ^ Package name fingerprint
-      , mod_fingerprint :: !Fingerprint     -- ^ Module name fingerprint
-      , todo_tycons     :: [TypeableTyCon]
-        -- ^ The 'TyCon's in need of bindings kinds
-      }
-    | ExportedKindRepsTodo [(Kind, Id)]
+  = TyConTodo TyConTodo
+  | ExportedKindRepsTodo [(Kind, Id)]
       -- ^ Build exported 'KindRep' bindings for the given set of kinds.
 
+
+-- | A group of 'TyCon's in need of type-rep bindings.
+data TyConTodo
+    = TCTD { mod_rep_expr    :: LHsExpr GhcTc    -- ^ Module's typerep binding
+           , pkg_fingerprint :: !Fingerprint     -- ^ Package name fingerprint
+           , mod_fingerprint :: !Fingerprint     -- ^ Module name fingerprint
+           , todo_tycons     :: [TypeableTyCon]
+                -- ^ The 'TyCon's in need of bindings kinds
+           }
+
 todoForTyCons :: Module -> Id -> [TyCon] -> TcM TypeRepTodo
 todoForTyCons mod mod_id tycons = do
     trTyConTy <- mkTyConTy <$> tcLookupTyCon trTyConTyConName
@@ -255,11 +258,11 @@ todoForTyCons mod mod_id tycons = do
             , Just rep_name <- pure $ tyConRepName_maybe tc''
             , tyConIsTypeable tc''
             ]
-    return TypeRepTodo { mod_rep_expr    = nlHsVar mod_id
-                       , pkg_fingerprint = pkg_fpr
-                       , mod_fingerprint = mod_fpr
-                       , todo_tycons     = typeable_tycons
-                       }
+    return $ TyConTodo $
+             TCTD { mod_rep_expr    = nlHsVar mod_id
+                  , pkg_fingerprint = pkg_fpr
+                  , mod_fingerprint = mod_fpr
+                  , todo_tycons     = typeable_tycons }
   where
     mod_fpr = fingerprintString $ moduleNameString $ moduleName mod
     pkg_fpr = fingerprintString $ unitString $ moduleUnit mod
@@ -283,8 +286,8 @@ mkTypeRepTodoBinds todos
          -- TyCon associated with the applied type constructor).
        ; let produced_bndrs :: [Id]
              produced_bndrs = [ tycon_rep_id
-                              | todo@(TypeRepTodo{}) <- todos
-                              , TypeableTyCon {..} <- todo_tycons todo
+                              | TyConTodo (TCTD { todo_tycons = tcs }) <- todos
+                              , TypeableTyCon {..} <- tcs
                               ] ++
                               [ rep_id
                               | ExportedKindRepsTodo kinds <- todos
@@ -293,8 +296,8 @@ mkTypeRepTodoBinds todos
        ; gbl_env <- tcExtendGlobalValEnv produced_bndrs getGblEnv
 
        ; let mk_binds :: TypeRepTodo -> KindRepM [LHsBinds GhcTc]
-             mk_binds todo@(TypeRepTodo {}) =
-                 mapM (mkTyConRepBinds stuff todo) (todo_tycons todo)
+             mk_binds (TyConTodo (todo@(TCTD { todo_tycons = tcs }))) =
+                 mapM (mkTyConRepBinds stuff todo) tcs
              mk_binds (ExportedKindRepsTodo kinds) =
                  mkExportedKindReps stuff kinds >> return []
 
@@ -413,7 +416,7 @@ mkTrNameLit = do
     return trNameLit
 
 -- | Make Typeable bindings for the given 'TyCon'.
-mkTyConRepBinds :: TypeableStuff -> TypeRepTodo
+mkTyConRepBinds :: TypeableStuff -> TyConTodo
                 -> TypeableTyCon -> KindRepM (LHsBinds GhcTc)
 mkTyConRepBinds stuff todo (TypeableTyCon {..})
   = do -- Make a KindRep
@@ -649,7 +652,7 @@ mkKindRepRhs stuff@(Stuff {..}) in_scope = new_kind_rep_shortcut
       = pprPanic "mkTyConKindRepBinds.go(coercion)" (ppr co)
 
 -- | Produce the right-hand-side of a @TyCon@ representation.
-mkTyConRepTyConRHS :: TypeableStuff -> TypeRepTodo
+mkTyConRepTyConRHS :: TypeableStuff -> TyConTodo
                    -> TyCon      -- ^ the 'TyCon' we are producing a binding for
                    -> LHsExpr GhcTc -- ^ its 'KindRep'
                    -> LHsExpr GhcTc



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1768fb718bc5a37d667fa91f617767621dad2dae

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct  5 22:14:31 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sat, 05 Oct 2024 18:14:31 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 22 commits: SpecConstr:
 Introduce a separate argument limit for forced specs.
Message-ID: <6701ba47ba5e7_8c3bc5c5e5414497@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
2bb27101 by Hassan Al-Awwadi at 2024-10-06T00:10:29+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

This means two things:
  We moved the definition of BooleanFormula to L.H.S.BooleanFormula
  We went from 'BooleanFormula a' with the datacon (Var a) to
  BooleanFormula p, where the datacon is instead (Var (LIdp p)).
And a lot of churn to make everything compile. We will see if the test cases
succeed. I assume not, as I have changed data types without touching the
test cases...

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/20a8610b821a16a9796c252bbee82a843ad6f7e8...2bb27101310179a66e80e45fae62659538cc3d7a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/20a8610b821a16a9796c252bbee82a843ad6f7e8...2bb27101310179a66e80e45fae62659538cc3d7a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 02:10:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 05 Oct 2024 22:10:15 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Clarify the
 meaning of "exactly once" in LinearTypes
Message-ID: <6701f18751f8c_c2337f2008622ba@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
762674b2 by Daniel Díaz at 2024-10-05T22:09:53-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
a02a5b3b by Krzysztof Gogolewski at 2024-10-05T22:09:54-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
7ef29dd2 by Teo Camarasu at 2024-10-05T22:09:54-04:00
Add changelog entries for !12479

- - - - -


8 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- docs/users_guide/exts/linear_types.rst
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T
- testsuite/tests/rename/should_fail/rnfail026.stderr


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -28,8 +28,9 @@ once*, then its argument is consumed *exactly once*. Intuitively, it
 means that in every branch of the definition of ``f``, its argument
 ``x`` must be used exactly once. Which can be done by
 
-* Returning ``x`` unmodified
-* Passing ``x`` to a *linear* function
+* Returning ``x`` unmodified.
+* Passing ``x`` to a *linear* function and using the result exactly once
+  in the same fashion.
 * Pattern-matching on ``x`` and using each argument exactly once in the
   same fashion.
 * Calling it as a function and using the result exactly once in the same


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail026.stderr
=====================================
@@ -1,6 +1,6 @@
-
 rnfail026.hs:16:27: error: [GHC-83865]
-    • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’
+    • Expected kind ‘* -> *’, but ‘Eq a => Set a’ has kind ‘*’
     • In the first argument of ‘Monad’, namely
         ‘(forall a. Eq a => Set a)’
       In the instance declaration for ‘Monad (forall a. Eq a => Set a)’
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/766a6a57fd9e52bb6918cf5f60bd6123ac760b83...7ef29dd2eea6cd64e04fbf9cf40bbaebe516efbc

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/766a6a57fd9e52bb6918cf5f60bd6123ac760b83...7ef29dd2eea6cd64e04fbf9cf40bbaebe516efbc
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 02:18:43 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sat, 05 Oct 2024 22:18:43 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/parallel-depanal-downsweep] 78
 commits: ci: Run abi-test on test-abi label
Message-ID: <6701f383b78d4_c233728df2065059@gitlab.mail>



Cheng Shao pushed to branch wip/torsten.schmits/parallel-depanal-downsweep at Glasgow Haskell Compiler / GHC


Commits:
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8237a881600064e45fdcdda263405c95e4f78ea9...135fd1ac9212ba7d3517e4e4c0bf85bf247ac3b3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8237a881600064e45fdcdda263405c95e4f78ea9...135fd1ac9212ba7d3517e4e4c0bf85bf247ac3b3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 08:31:30 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 04:31:30 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: driver: fix
 runWorkerLimit on wasm
Message-ID: <67024ae2c22e5_120aecbc688344e6@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
29b9d72d by Daniel Díaz at 2024-10-06T04:30:51-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
182e02e6 by Krzysztof Gogolewski at 2024-10-06T04:30:52-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
5cbdba5f by John Paul Adrian Glaubitz at 2024-10-06T04:30:57-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
de75e423 by Teo Camarasu at 2024-10-06T04:30:58-04:00
Add changelog entries for !12479

- - - - -


14 changed files:

- compiler/GHC/Driver/Make.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Unit/Finder.hs
- docs/users_guide/exts/linear_types.rst
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- rts/posix/Signals.c
- testsuite/tests/ghc-api/downsweep/OldModLocation.hs
- testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T
- testsuite/tests/rename/should_fail/rnfail026.stderr
- utils/haddock/haddock-api/src/Haddock/Interface.hs


Changes:

=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1,10 +1,12 @@
 {-# LANGUAGE NondecreasingIndentation #-}
-
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE DerivingStrategies #-}
 {-# LANGUAGE ApplicativeDo #-}
 {-# LANGUAGE MultiWayIf #-}
 {-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE BlockArguments #-}
 
 -- -----------------------------------------------------------------------------
 --
@@ -122,7 +124,7 @@ import qualified Control.Monad.Catch as MC
 import Data.IORef
 import Data.Maybe
 import Data.Time
-import Data.List (sortOn)
+import Data.List (sortOn, unfoldr)
 import Data.Bifunctor (first)
 import System.Directory
 import System.FilePath
@@ -169,7 +171,7 @@ depanal :: GhcMonad m =>
         -> Bool          -- ^ allow duplicate roots
         -> m ModuleGraph
 depanal excluded_mods allow_dup_roots = do
-    (errs, mod_graph) <- depanalE excluded_mods allow_dup_roots
+    (errs, mod_graph) <- depanalE mkUnknownDiagnostic Nothing excluded_mods allow_dup_roots
     if isEmptyMessages errs
       then pure mod_graph
       else throwErrors (fmap GhcDriverMessage errs)
@@ -177,12 +179,14 @@ depanal excluded_mods allow_dup_roots = do
 -- | Perform dependency analysis like in 'depanal'.
 -- In case of errors, the errors and an empty module graph are returned.
 depanalE :: GhcMonad m =>     -- New for #17459
-            [ModuleName]      -- ^ excluded modules
+               (GhcMessage -> AnyGhcDiagnostic)
+            -> Maybe Messager
+            -> [ModuleName]      -- ^ excluded modules
             -> Bool           -- ^ allow duplicate roots
             -> m (DriverMessages, ModuleGraph)
-depanalE excluded_mods allow_dup_roots = do
+depanalE diag_wrapper msg excluded_mods allow_dup_roots = do
     hsc_env <- getSession
-    (errs, mod_graph) <- depanalPartial excluded_mods allow_dup_roots
+    (errs, mod_graph) <- depanalPartial diag_wrapper msg excluded_mods allow_dup_roots
     if isEmptyMessages errs
       then do
         hsc_env <- getSession
@@ -220,11 +224,13 @@ depanalE excluded_mods allow_dup_roots = do
 -- new module graph.
 depanalPartial
     :: GhcMonad m
-    => [ModuleName]  -- ^ excluded modules
+    => (GhcMessage -> AnyGhcDiagnostic)
+    -> Maybe Messager
+    -> [ModuleName]  -- ^ excluded modules
     -> Bool          -- ^ allow duplicate roots
     -> m (DriverMessages, ModuleGraph)
     -- ^ possibly empty 'Bag' of errors and a module graph.
-depanalPartial excluded_mods allow_dup_roots = do
+depanalPartial diag_wrapper msg excluded_mods allow_dup_roots = do
   hsc_env <- getSession
   let
          targets = hsc_targets hsc_env
@@ -243,7 +249,7 @@ depanalPartial excluded_mods allow_dup_roots = do
     liftIO $ flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env)
 
     (errs, graph_nodes) <- liftIO $ downsweep
-      hsc_env (mgModSummaries old_graph)
+      hsc_env diag_wrapper msg (mgModSummaries old_graph)
       excluded_mods allow_dup_roots
     let
       mod_graph = mkModuleGraph graph_nodes
@@ -497,8 +503,8 @@ loadWithCache :: GhcMonad m => Maybe ModIfaceCache -- ^ Instructions about how t
                             -> LoadHowMuch -- ^ How much `loadWithCache` should load
                             -> m SuccessFlag
 loadWithCache cache diag_wrapper how_much = do
-    (errs, mod_graph) <- depanalE [] False                        -- #17459
     msg <- mkBatchMsg <$> getSession
+    (errs, mod_graph) <- depanalE diag_wrapper (Just msg) [] False                        -- #17459
     success <- load' cache how_much diag_wrapper (Just msg) mod_graph
     if isEmptyMessages errs
       then pure success
@@ -506,7 +512,7 @@ loadWithCache cache diag_wrapper how_much = do
 
 -- Note [Unused packages]
 -- ~~~~~~~~~~~~~~~~~~~~~~
--- Cabal passes `--package-id` flag for each direct dependency. But GHC
+-- Cabal passes `-package-id` flag for each direct dependency. But GHC
 -- loads them lazily, so when compilation is done, we have a list of all
 -- actually loaded packages. All the packages, specified on command line,
 -- but never loaded, are probably unused dependencies.
@@ -1553,6 +1559,8 @@ type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either Driv
 -- module, plus one for any hs-boot files.  The imports of these nodes
 -- are all there, including the imports of non-home-package modules.
 downsweep :: HscEnv
+          -> (GhcMessage -> AnyGhcDiagnostic)
+          -> Maybe Messager
           -> [ModSummary]
           -- ^ Old summaries
           -> [ModuleName]       -- Ignore dependencies on these; treat
@@ -1564,17 +1572,38 @@ downsweep :: HscEnv
                 -- The non-error elements of the returned list all have distinct
                 -- (Modules, IsBoot) identifiers, unless the Bool is true in
                 -- which case there can be repeats
-downsweep hsc_env old_summaries excl_mods allow_dup_roots
+downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do
+  n_jobs <- mkWorkerLimit (hsc_dflags hsc_env)
+  new <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
+  downsweep_imports hsc_env old_summary_map excl_mods allow_dup_roots new
+  where
+    summary = getRootSummary excl_mods old_summary_map
+
+    -- A cache from file paths to the already summarised modules. The same file
+    -- can be used in multiple units so the map is also keyed by which unit the
+    -- file was used in.
+    -- Reuse these if we can because the most expensive part of downsweep is
+    -- reading the headers.
+    old_summary_map :: M.Map (UnitId, FilePath) ModSummary
+    old_summary_map =
+      M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
+
+downsweep_imports :: HscEnv
+                  -> M.Map (UnitId, FilePath) ModSummary
+                  -> [ModuleName]
+                  -> Bool
+                  -> ([(UnitId, DriverMessages)], [ModSummary])
+                  -> IO ([DriverMessages], [ModuleGraphNode])
+downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, rootSummariesOk)
    = do
-       (root_errs, rootSummariesOk) <- partitionWithM getRootSummary roots -- #17549
        let root_map = mkRootMap rootSummariesOk
        checkDuplicates root_map
        (deps, map0) <- loopSummaries rootSummariesOk (M.empty, root_map)
-       let closure_errs = checkHomeUnitsClosed (hsc_unit_env hsc_env)
-       let unit_env = hsc_unit_env hsc_env
-       let tmpfs    = hsc_tmpfs    hsc_env
+       let closure_errs = checkHomeUnitsClosed unit_env
+           unit_env = hsc_unit_env hsc_env
+           tmpfs    = hsc_tmpfs    hsc_env
 
-       let downsweep_errs = lefts $ concat $ M.elems map0
+           downsweep_errs = lefts $ concat $ M.elems map0
            downsweep_nodes = M.elems deps
 
            (other_errs, unit_nodes) = partitionEithers $ unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
@@ -1606,46 +1635,6 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
           [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
 
         logger = hsc_logger hsc_env
-        roots  = hsc_targets hsc_env
-
-        -- A cache from file paths to the already summarised modules. The same file
-        -- can be used in multiple units so the map is also keyed by which unit the
-        -- file was used in.
-        -- Reuse these if we can because the most expensive part of downsweep is
-        -- reading the headers.
-        old_summary_map :: M.Map (UnitId, FilePath) ModSummary
-        old_summary_map = M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
-
-        getRootSummary :: Target -> IO (Either (UnitId, DriverMessages) ModSummary)
-        getRootSummary Target { targetId = TargetFile file mb_phase
-                              , targetContents = maybe_buf
-                              , targetUnitId = uid
-                              }
-           = do let offset_file = augmentByWorkingDirectory dflags file
-                exists <- liftIO $ doesFileExist offset_file
-                if exists || isJust maybe_buf
-                    then first (uid,) <$>
-                        summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
-                                       maybe_buf
-                    else return $ Left $ (uid,) $ singleMessage
-                                $ mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
-            where
-              dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env))
-              home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
-        getRootSummary Target { targetId = TargetModule modl
-                              , targetContents = maybe_buf
-                              , targetUnitId = uid
-                              }
-           = do maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot
-                                           (L rootLoc modl) (ThisPkg (homeUnitId home_unit))
-                                           maybe_buf excl_mods
-                case maybe_summary of
-                   FoundHome s  -> return (Right s)
-                   FoundHomeWithError err -> return (Left err)
-                   _ -> return $ Left $ (uid, moduleNotFoundErr modl)
-            where
-              home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
-        rootLoc = mkGeneralSrcSpan (fsLit "")
 
         -- In a root module, the filename is allowed to diverge from the module
         -- name, so we have to check that there aren't multiple root files
@@ -1713,7 +1702,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
                 loopImports ss done summarised
           | otherwise
           = do
-               mb_s <- summariseModule hsc_env home_unit old_summary_map
+               mb_s <- summariseModule hsc_env home_unit old_summaries
                                        is_boot wanted_mod mb_pkg
                                        Nothing excl_mods
                case mb_s of
@@ -1738,6 +1727,90 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
             GWIB { gwib_mod = L loc mod, gwib_isBoot = is_boot } = gwib
             wanted_mod = L loc mod
 
+getRootSummary ::
+  [ModuleName] ->
+  M.Map (UnitId, FilePath) ModSummary ->
+  HscEnv ->
+  Target ->
+  IO (Either (UnitId, DriverMessages) ModSummary)
+getRootSummary excl_mods old_summary_map hsc_env target
+  | TargetFile file mb_phase <- targetId
+  = do
+    let offset_file = augmentByWorkingDirectory dflags file
+    exists <- liftIO $ doesFileExist offset_file
+    if exists || isJust maybe_buf
+    then first (uid,) <$>
+         summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
+         maybe_buf
+    else
+      return $ Left $ (uid,) $ singleMessage $
+      mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
+  | TargetModule modl <- targetId
+  = do
+    maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot
+                     (L rootLoc modl) (ThisPkg (homeUnitId home_unit))
+                     maybe_buf excl_mods
+    pure case maybe_summary of
+      FoundHome s  -> Right s
+      FoundHomeWithError err -> Left err
+      _ -> Left (uid, moduleNotFoundErr modl)
+    where
+      Target {targetId, targetContents = maybe_buf, targetUnitId = uid} = target
+      home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
+      rootLoc = mkGeneralSrcSpan (fsLit "")
+      dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env))
+
+-- | Execute 'getRootSummary' for the 'Target's using the parallelism pipeline
+-- system.
+-- Create bundles of 'Target's wrapped in a 'MakeAction' that uses
+-- 'withAbstractSem' to wait for a free slot, limiting the number of
+-- concurrently computed summaries to the value of the @-j@ option or the slots
+-- allocated by the job server, if that is used.
+--
+-- The 'MakeAction' returns 'Maybe', which is not handled as an error, because
+-- 'runLoop' only sets it to 'Nothing' when an exception was thrown, so the
+-- result won't be read anyway here.
+--
+-- To emulate the current behavior, we funnel exceptions past the concurrency
+-- barrier and rethrow the first one afterwards.
+rootSummariesParallel ::
+  WorkerLimit ->
+  HscEnv ->
+  (GhcMessage -> AnyGhcDiagnostic) ->
+  Maybe Messager ->
+  (HscEnv -> Target -> IO (Either (UnitId, DriverMessages) ModSummary)) ->
+  IO ([(UnitId, DriverMessages)], [ModSummary])
+rootSummariesParallel n_jobs hsc_env diag_wrapper msg get_summary = do
+  (actions, get_results) <- unzip <$> mapM action_and_result (zip [1..] bundles)
+  runPipelines n_jobs hsc_env diag_wrapper msg actions
+  (sequence . catMaybes <$> sequence get_results) >>= \case
+    Right results -> pure (partitionEithers (concat results))
+    Left exc -> throwIO exc
+  where
+    bundles = mk_bundles targets
+
+    mk_bundles = unfoldr \case
+      [] -> Nothing
+      ts -> Just (splitAt bundle_size ts)
+
+    bundle_size = 20
+
+    targets = hsc_targets hsc_env
+
+    action_and_result (log_queue_id, ts) = do
+      res_var <- liftIO newEmptyMVar
+      pure $! (MakeAction (action log_queue_id ts) res_var, readMVar res_var)
+
+    action log_queue_id target_bundle = do
+      env at MakeEnv {compile_sem} <- ask
+      lift $ lift $
+        withAbstractSem compile_sem $
+        withLoggerHsc log_queue_id env \ lcl_hsc_env ->
+          MC.try (mapM (get_summary lcl_hsc_env) target_bundle) >>= \case
+            Left e | Just (_ :: SomeAsyncException) <- fromException e ->
+              throwIO e
+            a -> pure a
+
 -- | This function checks then important property that if both p and q are home units
 -- then any dependency of p, which transitively depends on q is also a home unit.
 --
@@ -2455,12 +2528,12 @@ wrapAction msg_wrapper hsc_env k = do
   let lcl_logger = hsc_logger hsc_env
       lcl_dynflags = hsc_dflags hsc_env
       print_config = initPrintConfig lcl_dynflags
-  let logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err)
+      logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err)
   -- MP: It is a bit strange how prettyPrintGhcErrors handles some errors but then we handle
   -- SourceError and ThreadKilled differently directly below. TODO: Refactor to use `catches`
   -- directly. MP should probably use safeTry here to not catch async exceptions but that will regress performance due to
   -- internally using forkIO.
-  mres <- MC.try $ liftIO $ prettyPrintGhcErrors lcl_logger $ k
+  mres <- MC.try $ prettyPrintGhcErrors lcl_logger $ k
   case mres of
     Right res -> return $ Just res
     Left exc -> do
@@ -2659,7 +2732,7 @@ R.hs:        module R where
 == Why we need to rehydrate A's ModIface before compiling R.hs
 
 After compiling A.hs we'll have a TypeEnv in which the Id for `f` has a type
-type uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same
+that uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same
 AbstractTyCon. (Abstract because it came from R.hs-boot; we know nothing about
 it.)
 
@@ -2901,11 +2974,17 @@ runNjobsAbstractSem n_jobs action = do
   MC.bracket_ updNumCapabilities resetNumCapabilities $ action asem
 
 runWorkerLimit :: WorkerLimit -> (AbstractSem -> IO a) -> IO a
+#if defined(wasm32_HOST_ARCH)
+runWorkerLimit _ action = do
+  lock <- newMVar ()
+  action $ AbstractSem (takeMVar lock) (putMVar lock ())
+#else
 runWorkerLimit worker_limit action = case worker_limit of
     NumProcessorsLimit n_jobs ->
       runNjobsAbstractSem n_jobs action
     JSemLimit sem ->
       runJSemAbstractSem sem action
+#endif
 
 -- | Build and run a pipeline
 runParPipelines :: WorkerLimit -- ^ How to limit work parallelism


=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -86,6 +86,20 @@ type BaseName = OsPath  -- Basename of file
 -- -----------------------------------------------------------------------------
 -- The finder's cache
 
+{-
+[Note: Monotonic addToFinderCache]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+addToFinderCache is only used by functions that return the cached value
+if there is one, or by functions that always write an InstalledFound value.
+Without multithreading it is then safe to always directly write the value
+without checking the previously cached value.
+
+However, with multithreading, it is possible that another function has
+written a value into cache between the lookup and the addToFinderCache call.
+in this case we should check to not overwrite an InstalledFound with an
+InstalledNotFound.
+-}
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
@@ -100,7 +114,12 @@ initFinderCache = do
 
       addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
       addToFinderCache key val =
-        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+        atomicModifyIORef' mod_cache $ \c ->
+          case (lookupInstalledModuleWithIsBootEnv c key, val) of
+            -- Don't overwrite an InstalledFound with an InstalledNotFound
+            -- See [Note Monotonic addToFinderCache]
+            (Just InstalledFound{}, InstalledNotFound{}) -> (c, ())
+            _ -> (extendInstalledModuleWithIsBootEnv c key val, ())
 
       lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do


=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -28,8 +28,9 @@ once*, then its argument is consumed *exactly once*. Intuitively, it
 means that in every branch of the definition of ``f``, its argument
 ``x`` must be used exactly once. Which can be done by
 
-* Returning ``x`` unmodified
-* Passing ``x`` to a *linear* function
+* Returning ``x`` unmodified.
+* Passing ``x`` to a *linear* function and using the result exactly once
+  in the same fashion.
 * Pattern-matching on ``x`` and using each argument exactly once in the
   same fashion.
 * Calling it as a function and using the result exactly once in the same


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
rts/posix/Signals.c
=====================================
@@ -27,7 +27,7 @@
 
 #if defined(alpha_HOST_ARCH)
 # if defined(linux_HOST_OS)
-#  include 
+#  include 
 # else
 #  include 
 # endif
@@ -721,7 +721,11 @@ initDefaultHandlers(void)
 #endif
 
 #if defined(alpha_HOST_ARCH)
+# if defined(linux_HOST_OS)
+    __ieee_set_fp_control(0);
+# else
     ieee_set_fp_control(0);
+# endif
 #endif
 
     // ignore SIGPIPE; see #1619


=====================================
testsuite/tests/ghc-api/downsweep/OldModLocation.hs
=====================================
@@ -6,6 +6,7 @@ import GHC
 import GHC.Driver.Make
 import GHC.Driver.Session
 import GHC.Driver.Env
+import GHC.Types.Error (mkUnknownDiagnostic)
 import GHC.Unit.Module.Graph
 import GHC.Unit.Finder
 
@@ -47,13 +48,13 @@ main = do
 
     liftIO $ do
 
-    _emss <- downsweep hsc_env [] [] False
+    _emss <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env)
     createDirectoryIfMissing False "mydir"
     renameFile "B.hs" "mydir/B.hs"
 
-    (_, nodes) <- downsweep hsc_env [] [] False
+    (_, nodes) <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     -- If 'checkSummaryTimestamp' were to call 'addHomeModuleToFinder' with
     -- (ms_location old_summary) like summariseFile used to instead of


=====================================
testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
=====================================
@@ -6,6 +6,7 @@
 import GHC
 import GHC.Driver.Make
 import GHC.Driver.Session
+import GHC.Types.Error (mkUnknownDiagnostic)
 import GHC.Utils.Outputable
 import GHC.Utils.Exception (ExceptionMonad)
 import GHC.Data.Bag
@@ -168,7 +169,7 @@ go label mods cnd =
     setTargets [tgt]
 
     hsc_env <- getSession
-    (_, nodes) <- liftIO $ downsweep hsc_env [] [] False
+    (_, nodes) <- liftIO $ downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     it label $ cnd (mapMaybe moduleGraphNodeModSum nodes)
 


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail026.stderr
=====================================
@@ -1,6 +1,6 @@
-
 rnfail026.hs:16:27: error: [GHC-83865]
-    • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’
+    • Expected kind ‘* -> *’, but ‘Eq a => Set a’ has kind ‘*’
     • In the first argument of ‘Monad’, namely
         ‘(forall a. Eq a => Set a)’
       In the instance declaration for ‘Monad (forall a. Eq a => Set a)’
+


=====================================
utils/haddock/haddock-api/src/Haddock/Interface.hs
=====================================
@@ -170,7 +170,7 @@ createIfaces verbosity modules flags instIfaceMap = do
   _ <- setSessionDynFlags dflags''
   targets <- mapM (\(filePath, _) -> guessTarget filePath Nothing Nothing) hs_srcs
   setTargets targets
-  (_errs, modGraph) <- depanalE [] False
+  (_errs, modGraph) <- depanalE mkUnknownDiagnostic (Just batchMsg) [] False
 
   -- Create (if necessary) and load .hi-files. With --no-compilation this happens later.
   when (Flag_NoCompilation `notElem` flags) $ do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ef29dd2eea6cd64e04fbf9cf40bbaebe516efbc...de75e423af3d3e64e4cec487ad6358f75ee5edc0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ef29dd2eea6cd64e04fbf9cf40bbaebe516efbc...de75e423af3d3e64e4cec487ad6358f75ee5edc0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 08:35:30 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 06 Oct 2024 04:35:30 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25325
Message-ID: <67024bd2de680_120aecbc598388a7@gitlab.mail>



Simon Peyton Jones pushed new branch wip/T25325 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25325
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 08:57:34 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 06 Oct 2024 04:57:34 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] cleaned up unused imports
Message-ID: <670250fe4496b_120aec4ece4c43684@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
8066448a by Hassan Al-Awwadi at 2024-10-06T10:57:15+02:00
cleaned up unused imports

- - - - -


1 changed file:

- compiler/GHC/Iface/Syntax.hs


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -74,14 +74,13 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..) )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
 import GHC.Builtin.Types ( constraintKindTyConName )
 import GHC.Stg.InferTags.TagSig
 import GHC.Parser.Annotation (noLocA)
-import GHC.Hs.Extension ( GhcRn, GhcPass )
+import GHC.Hs.Extension ( GhcRn )
 import GHC.Hs.Doc ( WithHsDocIdentifiers(..) )
 
 import GHC.Utils.Lexeme (isLexSym)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8066448a7a7e95db9b58dc549fef23c5050dfb51

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 09:20:38 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 06 Oct 2024 05:20:38 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann] 3 commits: Deprecation for
 WarnCompatUnqualifiedImports
Message-ID: <670256665d6b5_120aec6ee43447252@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann at Glasgow Haskell Compiler / GHC


Commits:
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
1ecfc64d by Alan Zimmerman at 2024-10-06T10:17:42+01:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: Remove unused hsCaseAnnsRest. We never populate it, so remove it.

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- docs/users_guide/using-warnings.rst
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/tests/T9586.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b1f1a392585c79f06cc37e799533f912eb24c97...1ecfc64d67184d31c332076022cc8650eba588a6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b1f1a392585c79f06cc37e799533f912eb24c97...1ecfc64d67184d31c332076022cc8650eba588a6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 10:14:51 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 06 Oct 2024 06:14:51 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] cleaned up remaing instances
 of BooleanFormula (RdrName)
Message-ID: <6702631b4dac0_3d4d8e19f2d05755@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
41731de8 by Hassan Al-Awwadi at 2024-10-06T12:14:35+02:00
cleaned up remaing instances of BooleanFormula (RdrName)

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2989,7 +2989,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4706,7 +4706,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41731de827a3222773068f68305b711570c8741e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 12:22:28 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 06 Oct 2024 08:22:28 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] remove unneeded imports
Message-ID: <6702810467ab6_3d4d8e71c460714fa@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
42effa94 by Hassan Al-Awwadi at 2024-10-06T14:22:09+02:00
remove unneeded imports

- - - - -


2 changed files:

- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y


Changes:

=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -37,7 +37,6 @@ import GHC.Core.FVs
 import GHC.Core.DataCon           ( dataConNonlinearType )
 import GHC.Types.FieldLabel ( FieldLabel(flSelector) )
 import GHC.Hs
-import GHC.Hs.Instances()
 import GHC.Hs.Syn.Type
 import GHC.Utils.Monad            ( concatMapM, MonadIO(liftIO) )
 import GHC.Types.Id               ( isDataConId_maybe )


=====================================
compiler/GHC/Parser.y
=====================================
@@ -47,7 +47,6 @@ import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
 
 import GHC.Hs
-import GHC.Hs.Extension (GhcPass, Pass(..))
 
 import GHC.Driver.Backpack.Syntax
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42effa949f9827d812ebc3a1dc78fed219748ca4

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 13:51:39 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 09:51:39 -0400
Subject: [Git][ghc/ghc][master] 2 commits: driver: fix runWorkerLimit on wasm
Message-ID: <670295eb21b4_31a0682f33fc105396@gitlab.mail>



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


Commits:
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -


5 changed files:

- compiler/GHC/Driver/Make.hs
- compiler/GHC/Unit/Finder.hs
- testsuite/tests/ghc-api/downsweep/OldModLocation.hs
- testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs


Changes:

=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1,10 +1,12 @@
 {-# LANGUAGE NondecreasingIndentation #-}
-
+{-# LANGUAGE CPP #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE DerivingStrategies #-}
 {-# LANGUAGE ApplicativeDo #-}
 {-# LANGUAGE MultiWayIf #-}
 {-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE BlockArguments #-}
 
 -- -----------------------------------------------------------------------------
 --
@@ -122,7 +124,7 @@ import qualified Control.Monad.Catch as MC
 import Data.IORef
 import Data.Maybe
 import Data.Time
-import Data.List (sortOn)
+import Data.List (sortOn, unfoldr)
 import Data.Bifunctor (first)
 import System.Directory
 import System.FilePath
@@ -169,7 +171,7 @@ depanal :: GhcMonad m =>
         -> Bool          -- ^ allow duplicate roots
         -> m ModuleGraph
 depanal excluded_mods allow_dup_roots = do
-    (errs, mod_graph) <- depanalE excluded_mods allow_dup_roots
+    (errs, mod_graph) <- depanalE mkUnknownDiagnostic Nothing excluded_mods allow_dup_roots
     if isEmptyMessages errs
       then pure mod_graph
       else throwErrors (fmap GhcDriverMessage errs)
@@ -177,12 +179,14 @@ depanal excluded_mods allow_dup_roots = do
 -- | Perform dependency analysis like in 'depanal'.
 -- In case of errors, the errors and an empty module graph are returned.
 depanalE :: GhcMonad m =>     -- New for #17459
-            [ModuleName]      -- ^ excluded modules
+               (GhcMessage -> AnyGhcDiagnostic)
+            -> Maybe Messager
+            -> [ModuleName]      -- ^ excluded modules
             -> Bool           -- ^ allow duplicate roots
             -> m (DriverMessages, ModuleGraph)
-depanalE excluded_mods allow_dup_roots = do
+depanalE diag_wrapper msg excluded_mods allow_dup_roots = do
     hsc_env <- getSession
-    (errs, mod_graph) <- depanalPartial excluded_mods allow_dup_roots
+    (errs, mod_graph) <- depanalPartial diag_wrapper msg excluded_mods allow_dup_roots
     if isEmptyMessages errs
       then do
         hsc_env <- getSession
@@ -220,11 +224,13 @@ depanalE excluded_mods allow_dup_roots = do
 -- new module graph.
 depanalPartial
     :: GhcMonad m
-    => [ModuleName]  -- ^ excluded modules
+    => (GhcMessage -> AnyGhcDiagnostic)
+    -> Maybe Messager
+    -> [ModuleName]  -- ^ excluded modules
     -> Bool          -- ^ allow duplicate roots
     -> m (DriverMessages, ModuleGraph)
     -- ^ possibly empty 'Bag' of errors and a module graph.
-depanalPartial excluded_mods allow_dup_roots = do
+depanalPartial diag_wrapper msg excluded_mods allow_dup_roots = do
   hsc_env <- getSession
   let
          targets = hsc_targets hsc_env
@@ -243,7 +249,7 @@ depanalPartial excluded_mods allow_dup_roots = do
     liftIO $ flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env)
 
     (errs, graph_nodes) <- liftIO $ downsweep
-      hsc_env (mgModSummaries old_graph)
+      hsc_env diag_wrapper msg (mgModSummaries old_graph)
       excluded_mods allow_dup_roots
     let
       mod_graph = mkModuleGraph graph_nodes
@@ -497,8 +503,8 @@ loadWithCache :: GhcMonad m => Maybe ModIfaceCache -- ^ Instructions about how t
                             -> LoadHowMuch -- ^ How much `loadWithCache` should load
                             -> m SuccessFlag
 loadWithCache cache diag_wrapper how_much = do
-    (errs, mod_graph) <- depanalE [] False                        -- #17459
     msg <- mkBatchMsg <$> getSession
+    (errs, mod_graph) <- depanalE diag_wrapper (Just msg) [] False                        -- #17459
     success <- load' cache how_much diag_wrapper (Just msg) mod_graph
     if isEmptyMessages errs
       then pure success
@@ -506,7 +512,7 @@ loadWithCache cache diag_wrapper how_much = do
 
 -- Note [Unused packages]
 -- ~~~~~~~~~~~~~~~~~~~~~~
--- Cabal passes `--package-id` flag for each direct dependency. But GHC
+-- Cabal passes `-package-id` flag for each direct dependency. But GHC
 -- loads them lazily, so when compilation is done, we have a list of all
 -- actually loaded packages. All the packages, specified on command line,
 -- but never loaded, are probably unused dependencies.
@@ -1553,6 +1559,8 @@ type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either Driv
 -- module, plus one for any hs-boot files.  The imports of these nodes
 -- are all there, including the imports of non-home-package modules.
 downsweep :: HscEnv
+          -> (GhcMessage -> AnyGhcDiagnostic)
+          -> Maybe Messager
           -> [ModSummary]
           -- ^ Old summaries
           -> [ModuleName]       -- Ignore dependencies on these; treat
@@ -1564,17 +1572,38 @@ downsweep :: HscEnv
                 -- The non-error elements of the returned list all have distinct
                 -- (Modules, IsBoot) identifiers, unless the Bool is true in
                 -- which case there can be repeats
-downsweep hsc_env old_summaries excl_mods allow_dup_roots
+downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do
+  n_jobs <- mkWorkerLimit (hsc_dflags hsc_env)
+  new <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
+  downsweep_imports hsc_env old_summary_map excl_mods allow_dup_roots new
+  where
+    summary = getRootSummary excl_mods old_summary_map
+
+    -- A cache from file paths to the already summarised modules. The same file
+    -- can be used in multiple units so the map is also keyed by which unit the
+    -- file was used in.
+    -- Reuse these if we can because the most expensive part of downsweep is
+    -- reading the headers.
+    old_summary_map :: M.Map (UnitId, FilePath) ModSummary
+    old_summary_map =
+      M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
+
+downsweep_imports :: HscEnv
+                  -> M.Map (UnitId, FilePath) ModSummary
+                  -> [ModuleName]
+                  -> Bool
+                  -> ([(UnitId, DriverMessages)], [ModSummary])
+                  -> IO ([DriverMessages], [ModuleGraphNode])
+downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, rootSummariesOk)
    = do
-       (root_errs, rootSummariesOk) <- partitionWithM getRootSummary roots -- #17549
        let root_map = mkRootMap rootSummariesOk
        checkDuplicates root_map
        (deps, map0) <- loopSummaries rootSummariesOk (M.empty, root_map)
-       let closure_errs = checkHomeUnitsClosed (hsc_unit_env hsc_env)
-       let unit_env = hsc_unit_env hsc_env
-       let tmpfs    = hsc_tmpfs    hsc_env
+       let closure_errs = checkHomeUnitsClosed unit_env
+           unit_env = hsc_unit_env hsc_env
+           tmpfs    = hsc_tmpfs    hsc_env
 
-       let downsweep_errs = lefts $ concat $ M.elems map0
+           downsweep_errs = lefts $ concat $ M.elems map0
            downsweep_nodes = M.elems deps
 
            (other_errs, unit_nodes) = partitionEithers $ unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
@@ -1606,46 +1635,6 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
           [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
 
         logger = hsc_logger hsc_env
-        roots  = hsc_targets hsc_env
-
-        -- A cache from file paths to the already summarised modules. The same file
-        -- can be used in multiple units so the map is also keyed by which unit the
-        -- file was used in.
-        -- Reuse these if we can because the most expensive part of downsweep is
-        -- reading the headers.
-        old_summary_map :: M.Map (UnitId, FilePath) ModSummary
-        old_summary_map = M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
-
-        getRootSummary :: Target -> IO (Either (UnitId, DriverMessages) ModSummary)
-        getRootSummary Target { targetId = TargetFile file mb_phase
-                              , targetContents = maybe_buf
-                              , targetUnitId = uid
-                              }
-           = do let offset_file = augmentByWorkingDirectory dflags file
-                exists <- liftIO $ doesFileExist offset_file
-                if exists || isJust maybe_buf
-                    then first (uid,) <$>
-                        summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
-                                       maybe_buf
-                    else return $ Left $ (uid,) $ singleMessage
-                                $ mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
-            where
-              dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env))
-              home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
-        getRootSummary Target { targetId = TargetModule modl
-                              , targetContents = maybe_buf
-                              , targetUnitId = uid
-                              }
-           = do maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot
-                                           (L rootLoc modl) (ThisPkg (homeUnitId home_unit))
-                                           maybe_buf excl_mods
-                case maybe_summary of
-                   FoundHome s  -> return (Right s)
-                   FoundHomeWithError err -> return (Left err)
-                   _ -> return $ Left $ (uid, moduleNotFoundErr modl)
-            where
-              home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
-        rootLoc = mkGeneralSrcSpan (fsLit "")
 
         -- In a root module, the filename is allowed to diverge from the module
         -- name, so we have to check that there aren't multiple root files
@@ -1713,7 +1702,7 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
                 loopImports ss done summarised
           | otherwise
           = do
-               mb_s <- summariseModule hsc_env home_unit old_summary_map
+               mb_s <- summariseModule hsc_env home_unit old_summaries
                                        is_boot wanted_mod mb_pkg
                                        Nothing excl_mods
                case mb_s of
@@ -1738,6 +1727,90 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
             GWIB { gwib_mod = L loc mod, gwib_isBoot = is_boot } = gwib
             wanted_mod = L loc mod
 
+getRootSummary ::
+  [ModuleName] ->
+  M.Map (UnitId, FilePath) ModSummary ->
+  HscEnv ->
+  Target ->
+  IO (Either (UnitId, DriverMessages) ModSummary)
+getRootSummary excl_mods old_summary_map hsc_env target
+  | TargetFile file mb_phase <- targetId
+  = do
+    let offset_file = augmentByWorkingDirectory dflags file
+    exists <- liftIO $ doesFileExist offset_file
+    if exists || isJust maybe_buf
+    then first (uid,) <$>
+         summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
+         maybe_buf
+    else
+      return $ Left $ (uid,) $ singleMessage $
+      mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
+  | TargetModule modl <- targetId
+  = do
+    maybe_summary <- summariseModule hsc_env home_unit old_summary_map NotBoot
+                     (L rootLoc modl) (ThisPkg (homeUnitId home_unit))
+                     maybe_buf excl_mods
+    pure case maybe_summary of
+      FoundHome s  -> Right s
+      FoundHomeWithError err -> Left err
+      _ -> Left (uid, moduleNotFoundErr modl)
+    where
+      Target {targetId, targetContents = maybe_buf, targetUnitId = uid} = target
+      home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
+      rootLoc = mkGeneralSrcSpan (fsLit "")
+      dflags = homeUnitEnv_dflags (ue_findHomeUnitEnv uid (hsc_unit_env hsc_env))
+
+-- | Execute 'getRootSummary' for the 'Target's using the parallelism pipeline
+-- system.
+-- Create bundles of 'Target's wrapped in a 'MakeAction' that uses
+-- 'withAbstractSem' to wait for a free slot, limiting the number of
+-- concurrently computed summaries to the value of the @-j@ option or the slots
+-- allocated by the job server, if that is used.
+--
+-- The 'MakeAction' returns 'Maybe', which is not handled as an error, because
+-- 'runLoop' only sets it to 'Nothing' when an exception was thrown, so the
+-- result won't be read anyway here.
+--
+-- To emulate the current behavior, we funnel exceptions past the concurrency
+-- barrier and rethrow the first one afterwards.
+rootSummariesParallel ::
+  WorkerLimit ->
+  HscEnv ->
+  (GhcMessage -> AnyGhcDiagnostic) ->
+  Maybe Messager ->
+  (HscEnv -> Target -> IO (Either (UnitId, DriverMessages) ModSummary)) ->
+  IO ([(UnitId, DriverMessages)], [ModSummary])
+rootSummariesParallel n_jobs hsc_env diag_wrapper msg get_summary = do
+  (actions, get_results) <- unzip <$> mapM action_and_result (zip [1..] bundles)
+  runPipelines n_jobs hsc_env diag_wrapper msg actions
+  (sequence . catMaybes <$> sequence get_results) >>= \case
+    Right results -> pure (partitionEithers (concat results))
+    Left exc -> throwIO exc
+  where
+    bundles = mk_bundles targets
+
+    mk_bundles = unfoldr \case
+      [] -> Nothing
+      ts -> Just (splitAt bundle_size ts)
+
+    bundle_size = 20
+
+    targets = hsc_targets hsc_env
+
+    action_and_result (log_queue_id, ts) = do
+      res_var <- liftIO newEmptyMVar
+      pure $! (MakeAction (action log_queue_id ts) res_var, readMVar res_var)
+
+    action log_queue_id target_bundle = do
+      env at MakeEnv {compile_sem} <- ask
+      lift $ lift $
+        withAbstractSem compile_sem $
+        withLoggerHsc log_queue_id env \ lcl_hsc_env ->
+          MC.try (mapM (get_summary lcl_hsc_env) target_bundle) >>= \case
+            Left e | Just (_ :: SomeAsyncException) <- fromException e ->
+              throwIO e
+            a -> pure a
+
 -- | This function checks then important property that if both p and q are home units
 -- then any dependency of p, which transitively depends on q is also a home unit.
 --
@@ -2455,12 +2528,12 @@ wrapAction msg_wrapper hsc_env k = do
   let lcl_logger = hsc_logger hsc_env
       lcl_dynflags = hsc_dflags hsc_env
       print_config = initPrintConfig lcl_dynflags
-  let logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err)
+      logg err = printMessages lcl_logger print_config (initDiagOpts lcl_dynflags) (msg_wrapper <$> srcErrorMessages err)
   -- MP: It is a bit strange how prettyPrintGhcErrors handles some errors but then we handle
   -- SourceError and ThreadKilled differently directly below. TODO: Refactor to use `catches`
   -- directly. MP should probably use safeTry here to not catch async exceptions but that will regress performance due to
   -- internally using forkIO.
-  mres <- MC.try $ liftIO $ prettyPrintGhcErrors lcl_logger $ k
+  mres <- MC.try $ prettyPrintGhcErrors lcl_logger $ k
   case mres of
     Right res -> return $ Just res
     Left exc -> do
@@ -2659,7 +2732,7 @@ R.hs:        module R where
 == Why we need to rehydrate A's ModIface before compiling R.hs
 
 After compiling A.hs we'll have a TypeEnv in which the Id for `f` has a type
-type uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same
+that uses the AbstractTyCon T; and a TyCon for `S` that also mentions that same
 AbstractTyCon. (Abstract because it came from R.hs-boot; we know nothing about
 it.)
 
@@ -2901,11 +2974,17 @@ runNjobsAbstractSem n_jobs action = do
   MC.bracket_ updNumCapabilities resetNumCapabilities $ action asem
 
 runWorkerLimit :: WorkerLimit -> (AbstractSem -> IO a) -> IO a
+#if defined(wasm32_HOST_ARCH)
+runWorkerLimit _ action = do
+  lock <- newMVar ()
+  action $ AbstractSem (takeMVar lock) (putMVar lock ())
+#else
 runWorkerLimit worker_limit action = case worker_limit of
     NumProcessorsLimit n_jobs ->
       runNjobsAbstractSem n_jobs action
     JSemLimit sem ->
       runJSemAbstractSem sem action
+#endif
 
 -- | Build and run a pipeline
 runParPipelines :: WorkerLimit -- ^ How to limit work parallelism


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -86,6 +86,20 @@ type BaseName = OsPath  -- Basename of file
 -- -----------------------------------------------------------------------------
 -- The finder's cache
 
+{-
+[Note: Monotonic addToFinderCache]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+addToFinderCache is only used by functions that return the cached value
+if there is one, or by functions that always write an InstalledFound value.
+Without multithreading it is then safe to always directly write the value
+without checking the previously cached value.
+
+However, with multithreading, it is possible that another function has
+written a value into cache between the lookup and the addToFinderCache call.
+in this case we should check to not overwrite an InstalledFound with an
+InstalledNotFound.
+-}
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
@@ -100,7 +114,12 @@ initFinderCache = do
 
       addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
       addToFinderCache key val =
-        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+        atomicModifyIORef' mod_cache $ \c ->
+          case (lookupInstalledModuleWithIsBootEnv c key, val) of
+            -- Don't overwrite an InstalledFound with an InstalledNotFound
+            -- See [Note Monotonic addToFinderCache]
+            (Just InstalledFound{}, InstalledNotFound{}) -> (c, ())
+            _ -> (extendInstalledModuleWithIsBootEnv c key val, ())
 
       lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do


=====================================
testsuite/tests/ghc-api/downsweep/OldModLocation.hs
=====================================
@@ -6,6 +6,7 @@ import GHC
 import GHC.Driver.Make
 import GHC.Driver.Session
 import GHC.Driver.Env
+import GHC.Types.Error (mkUnknownDiagnostic)
 import GHC.Unit.Module.Graph
 import GHC.Unit.Finder
 
@@ -47,13 +48,13 @@ main = do
 
     liftIO $ do
 
-    _emss <- downsweep hsc_env [] [] False
+    _emss <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env)
     createDirectoryIfMissing False "mydir"
     renameFile "B.hs" "mydir/B.hs"
 
-    (_, nodes) <- downsweep hsc_env [] [] False
+    (_, nodes) <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     -- If 'checkSummaryTimestamp' were to call 'addHomeModuleToFinder' with
     -- (ms_location old_summary) like summariseFile used to instead of


=====================================
testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
=====================================
@@ -6,6 +6,7 @@
 import GHC
 import GHC.Driver.Make
 import GHC.Driver.Session
+import GHC.Types.Error (mkUnknownDiagnostic)
 import GHC.Utils.Outputable
 import GHC.Utils.Exception (ExceptionMonad)
 import GHC.Data.Bag
@@ -168,7 +169,7 @@ go label mods cnd =
     setTargets [tgt]
 
     hsc_env <- getSession
-    (_, nodes) <- liftIO $ downsweep hsc_env [] [] False
+    (_, nodes) <- liftIO $ downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
 
     it label $ cnd (mapMaybe moduleGraphNodeModSum nodes)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Interface.hs
=====================================
@@ -170,7 +170,7 @@ createIfaces verbosity modules flags instIfaceMap = do
   _ <- setSessionDynFlags dflags''
   targets <- mapM (\(filePath, _) -> guessTarget filePath Nothing Nothing) hs_srcs
   setTargets targets
-  (_errs, modGraph) <- depanalE [] False
+  (_errs, modGraph) <- depanalE mkUnknownDiagnostic (Just batchMsg) [] False
 
   -- Create (if necessary) and load .hi-files. With --no-compilation this happens later.
   when (Flag_NoCompilation `notElem` flags) $ do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4327f0e8c5091dae9ab0f58e2e3c8af5bacd12ea...135fd1ac9212ba7d3517e4e4c0bf85bf247ac3b3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4327f0e8c5091dae9ab0f58e2e3c8af5bacd12ea...135fd1ac9212ba7d3517e4e4c0bf85bf247ac3b3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 13:52:12 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 09:52:12 -0400
Subject: [Git][ghc/ghc][master] Clarify the meaning of "exactly once" in
 LinearTypes
Message-ID: <6702960c6d0f6_31a0682e07341084c4@gitlab.mail>



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


Commits:
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -


1 changed file:

- docs/users_guide/exts/linear_types.rst


Changes:

=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -28,8 +28,9 @@ once*, then its argument is consumed *exactly once*. Intuitively, it
 means that in every branch of the definition of ``f``, its argument
 ``x`` must be used exactly once. Which can be done by
 
-* Returning ``x`` unmodified
-* Passing ``x`` to a *linear* function
+* Returning ``x`` unmodified.
+* Passing ``x`` to a *linear* function and using the result exactly once
+  in the same fashion.
 * Pattern-matching on ``x`` and using each argument exactly once in the
   same fashion.
 * Calling it as a function and using the result exactly once in the same



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/535a2117239f0d0e4588c6616fcd8deed725cfc0

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 13:52:55 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 09:52:55 -0400
Subject: [Git][ghc/ghc][master] Only allow (a => b) :: Constraint rather than
 CONSTRAINT rep
Message-ID: <6702963777cac_31a0681b8e4c11436@gitlab.mail>



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


Commits:
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -


5 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T
- testsuite/tests/rename/should_fail/rnfail026.stderr


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail026.stderr
=====================================
@@ -1,6 +1,6 @@
-
 rnfail026.hs:16:27: error: [GHC-83865]
-    • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’
+    • Expected kind ‘* -> *’, but ‘Eq a => Set a’ has kind ‘*’
     • In the first argument of ‘Monad’, namely
         ‘(forall a. Eq a => Set a)’
       In the instance declaration for ‘Monad (forall a. Eq a => Set a)’
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92f8939a5fa689dc0143501cfeac0b3b2cd7abd6

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 13:54:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 09:54:53 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Clarify the
 meaning of "exactly once" in LinearTypes
Message-ID: <670296ada19fd_31a068197b481206c6@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
2173bce4 by Alan Zimmerman at 2024-10-06T09:54:42-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
50d9fc5e by Teo Camarasu at 2024-10-06T09:54:42-04:00
Add changelog entries for !12479

- - - - -


12 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Tc/Gen/HsType.hs
- docs/users_guide/exts/linear_types.rst
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- + testsuite/tests/quantified-constraints/T25243.hs
- + testsuite/tests/quantified-constraints/T25243.stderr
- testsuite/tests/quantified-constraints/all.T
- testsuite/tests/rename/should_fail/rnfail026.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -202,11 +202,10 @@ type instance XUntypedBracket GhcTc = HsBracketTc
 data EpAnnHsCase = EpAnnHsCase
       { hsCaseAnnCase :: EpaLocation
       , hsCaseAnnOf   :: EpaLocation
-      , hsCaseAnnsRest :: [AddEpAnn]
       } deriving Data
 
 instance NoAnn EpAnnHsCase where
-  noAnn = EpAnnHsCase noAnn noAnn noAnn
+  noAnn = EpAnnHsCase noAnn noAnn
 
 data EpAnnUnboundVar = EpAnnUnboundVar
      { hsUnboundBackquotes :: (EpaLocation, EpaLocation)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3042,7 +3042,7 @@ aexp    :: { ECP }
                                              return $ ECP $
                                                $4 >>= \ $4 ->
                                                mkHsCasePV (comb3 $1 $3 $4) $2 $4
-                                                    (EpAnnHsCase (glAA $1) (glAA $3) []) }
+                                                    (EpAnnHsCase (glAA $1) (glAA $3)) }
         -- QualifiedDo.
         | DO  stmtlist               {% do
                                       hintQualifiedDo $1


=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1154,14 +1154,17 @@ tcHsType mode t@(HsForAllTy { hst_tele = tele, hst_body = ty }) exp_kind
              -- Do not kind-generalise here!  See Note [Kind generalisation]
            ; return (mkForAllTys tv_bndrs ty') }
 
-tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
+tcHsType mode t@(HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
   | null (unLoc ctxt)
   = tcLHsType mode rn_ty exp_kind
-    -- See Note [Body kind of a HsQualTy]
-  | Check kind <- exp_kind, isConstraintLikeKind kind
+    -- See Note [Body kind of a HsQualTy], point (BK1)
+  | Check kind <- exp_kind     -- Checking mode
+  , isConstraintLikeKind kind  -- CONSTRAINT rep
   = do { ctxt' <- tc_hs_context mode ctxt
-      ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
-      ; return (tcMkDFunPhiTy ctxt' ty') }
+         -- See Note [Body kind of a HsQualTy], point (BK2)
+       ; ty'   <- tc_check_lhs_type mode rn_ty constraintKind
+       ; let res_ty = tcMkDFunPhiTy ctxt' ty'
+       ; checkExpKind t res_ty constraintKind exp_kind }
 
   | otherwise
   = do { ctxt' <- tc_hs_context mode ctxt
@@ -1170,8 +1173,7 @@ tcHsType mode (HsQualTy { hst_ctxt = ctxt, hst_body = rn_ty }) exp_kind
                                 -- be TYPE r, for any r, hence newOpenTypeKind
       ; ty' <- tc_check_lhs_type mode rn_ty ek
       ; let res_ty = tcMkPhiTy ctxt' ty'
-      ; checkExpKind (unLoc rn_ty) res_ty
-                      liftedTypeKind exp_kind }
+      ; checkExpKind t res_ty liftedTypeKind exp_kind }
 
 --------- Lists, arrays, and tuples
 tcHsType mode rn_ty@(HsListTy _ elt_ty) exp_kind
@@ -2110,22 +2112,36 @@ However, consider
     instance Eq a => Eq [a] where ...
 or
     f :: (Eq a => Eq [a]) => blah
-Here both body-kind of the HsQualTy is Constraint rather than *.
+Here both body-kind and result kind of the HsQualTy is Constraint rather than *.
 Rather crudely we tell the difference by looking at exp_kind. It's
 very convenient to typecheck instance types like any other HsSigType.
 
-Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's
-better to reject in checkValidType.  If we say that the body kind
-should be '*' we risk getting TWO error messages, one saying that Eq
-[a] doesn't have kind '*', and one saying that we need a Constraint to
-the left of the outer (=>).
-
-How do we figure out the right body kind?  Well, it's a bit of a
-kludge: I just look at the expected kind.  If it's Constraint, we
-must be in this instance situation context. It's a kludge because it
-wouldn't work if any unification was involved to compute that result
-kind -- but it isn't.  (The true way might be to use the 'mode'
-parameter, but that seemed like a sledgehammer to crack a nut.)
+(BK1) How do we figure out the right body kind?
+
+Well, it's a bit of a kludge: I just look at the expected kind, `exp_kind`.
+If we are in checking mode (`exp_kind` = `Check k`), and the pushed-in kind
+`k` is `CONSTRAINT rep`, then we check that the body type has kind `Constraint` too.
+
+This is a kludge because it wouldn't work if any unification was
+involved to compute that result kind -- but it isn't.
+
+Note that in the kludgy "figure out whether we are in a type or constraint"
+check, we only check if `k` is a `CONSTRAINT rep`, not `Constraint`.
+That turns out to give a better error message in T25243.
+
+(BK2)
+
+Note that, once we are in the constraint case, we check that the body has
+kind Constraint; see the call to tc_check_lhs_type. (In contrast, for
+types we check that the body has kind TYPE kappa for some fresh unification
+variable kappa.)
+Reason: we don't yet have support for constraints that are not lifted: it's
+not possible to declare a class returning a different type than CONSTRAINT LiftedRep.
+Evidence is always lifted, the fat arrow c => t requires c to be
+a lifted constraint. In a far future, if we add support for non-lifted
+constraints, we could allow c1 => c2 where
+c1 :: CONSTRAINT rep1, c2 :: CONSTRAINT rep2
+have arbitrary representations rep1 and rep2.
 
 Note [Inferring tuple kinds]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -28,8 +28,9 @@ once*, then its argument is consumed *exactly once*. Intuitively, it
 means that in every branch of the definition of ``f``, its argument
 ``x`` must be used exactly once. Which can be done by
 
-* Returning ``x`` unmodified
-* Passing ``x`` to a *linear* function
+* Returning ``x`` unmodified.
+* Passing ``x`` to a *linear* function and using the result exactly once
+  in the same fashion.
 * Pattern-matching on ``x`` and using each argument exactly once in the
   same fashion.
 * Calling it as a function and using the result exactly once in the same


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -2170,8 +2170,7 @@
                 (HsCase
                  (EpAnnHsCase
                   (EpaSpan { DumpSemis.hs:37:3-6 })
-                  (EpaSpan { DumpSemis.hs:37:10-11 })
-                  [])
+                  (EpaSpan { DumpSemis.hs:37:10-11 }))
                  (L
                   (EpAnn
                    (EpaSpan { DumpSemis.hs:37:8 })


=====================================
testsuite/tests/quantified-constraints/T25243.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE DataKinds, QuantifiedConstraints, UndecidableInstances #-}
+module T25243 where
+
+import GHC.Exts
+import Data.Kind
+
+type T :: Constraint -> Constraint -> CONSTRAINT IntRep
+type T a b = a => b


=====================================
testsuite/tests/quantified-constraints/T25243.stderr
=====================================
@@ -0,0 +1,6 @@
+T25243.hs:8:14: error: [GHC-83865]
+    • Expected an IntRep constraint,
+      but ‘a => b’ is a lifted constraint
+    • In the type ‘a => b’
+      In the type declaration for ‘T’
+


=====================================
testsuite/tests/quantified-constraints/all.T
=====================================
@@ -45,3 +45,4 @@ test('T23143', normal, compile, [''])
 test('T23333', normal, compile, [''])
 test('T23323', normal, compile, [''])
 test('T22238', normal, compile, [''])
+test('T25243', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail026.stderr
=====================================
@@ -1,6 +1,6 @@
-
 rnfail026.hs:16:27: error: [GHC-83865]
-    • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’
+    • Expected kind ‘* -> *’, but ‘Eq a => Set a’ has kind ‘*’
     • In the first argument of ‘Monad’, namely
         ‘(forall a. Eq a => Set a)’
       In the instance declaration for ‘Monad (forall a. Eq a => Set a)’
+


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1211,7 +1211,6 @@ laiElseSemi k parent = fmap (\new -> parent { aiElseSemi = new })
 -- data EpAnnHsCase = EpAnnHsCase
 --       { hsCaseAnnCase :: EpaLocation
 --       , hsCaseAnnOf   :: EpaLocation
---       , hsCaseAnnsRest :: [AddEpAnn]
 --       } deriving Data
 
 lhsCaseAnnCase :: Lens EpAnnHsCase EpaLocation
@@ -1222,10 +1221,6 @@ lhsCaseAnnOf :: Lens EpAnnHsCase EpaLocation
 lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
                                (k (hsCaseAnnOf parent))
 
-lhsCaseAnnsRest :: Lens EpAnnHsCase [AddEpAnn]
-lhsCaseAnnsRest k parent = fmap (\new -> parent { hsCaseAnnsRest = new })
-                                (k (hsCaseAnnsRest parent))
-
 -- ---------------------------------------------------------------------
 
 -- data HsRuleAnn
@@ -3161,11 +3156,8 @@ instance ExactPrint (HsExpr GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- setLayoutBoth $ markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCase an4 e' alts')
+    return (HsCase an1 e' alts')
 
   exact (HsIf an e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf
@@ -3635,11 +3627,8 @@ instance ExactPrint (HsCmd GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCmdCase an4 e' alts')
+    return (HsCmdCase an1 e' alts')
 
   exact (HsCmdIf an a e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de75e423af3d3e64e4cec487ad6358f75ee5edc0...50d9fc5e73228228c5ca79fb615df38544688108

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de75e423af3d3e64e4cec487ad6358f75ee5edc0...50d9fc5e73228228c5ca79fb615df38544688108
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 15:23:36 2024
From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal))
Date: Sun, 06 Oct 2024 11:23:36 -0400
Subject: [Git][ghc/ghc][wip/forall-kind-rule] 137 commits: AArch64: Implement
 takeRegRegMoveInstr
Message-ID: <6702ab78d5af3_2147501bb2b439932@gitlab.mail>



Krzysztof Gogolewski pushed to branch wip/forall-kind-rule at Glasgow Haskell Compiler / GHC


Commits:
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
9c3e33e4 by Krzysztof Gogolewski at 2024-10-06T17:06:57+02:00
Limit forall to TYPE r and CONSTRAINT r

Fixes #22063.

- - - - -


25 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8fe9967f16535d7515403ad43631ca23aa10913...9c3e33e49eea60452c62f20c51705291fe68c1ab

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8fe9967f16535d7515403ad43631ca23aa10913...9c3e33e49eea60452c62f20c51705291fe68c1ab
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 15:55:20 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 06 Oct 2024 11:55:20 -0400
Subject: [Git][ghc/ghc][wip/T25325] Consider Wanteds with rewriters as
 insoluble
Message-ID: <6702b2e8cc68c_21475038608040737@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25325 at Glasgow Haskell Compiler / GHC


Commits:
67eb3db8 by Simon Peyton Jones at 2024-10-06T16:54:22+01:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -


5 changed files:

- compiler/GHC/Tc/Types/Constraint.hs
- testsuite/tests/polykinds/T14172.stderr
- + testsuite/tests/typecheck/should_fail/T25325.hs
- + testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -76,7 +76,7 @@ module GHC.Tc.Types.Constraint (
         ctEvPred, ctEvLoc, ctEvOrigin, ctEvEqRel,
         ctEvExpr, ctEvTerm, ctEvCoercion, ctEvEvId,
         ctEvRewriters, ctEvUnique, tcEvDestUnique,
-        ctEvRewriteRole, ctEvRewriteEqRel, setCtEvPredType, setCtEvLoc, arisesFromGivens,
+        ctEvRewriteRole, ctEvRewriteEqRel, setCtEvPredType, setCtEvLoc,
         tyCoVarsOfCtEvList, tyCoVarsOfCtEv, tyCoVarsOfCtEvsList,
 
         -- RewriterSet
@@ -1317,25 +1317,51 @@ nonDefaultableTyVarsOfWC (WC { wc_simple = simples, wc_impl = implics, wc_errors
 insolubleWC :: WantedConstraints -> Bool
 insolubleWC (WC { wc_impl = implics, wc_simple = simples, wc_errors = errors })
   =  anyBag insolubleWantedCt simples
+       -- insolubleWantedCt: wanteds only: see Note [Given insolubles]
   || anyBag insolubleImplic implics
   || anyBag is_insoluble errors
-
-    where
+  where
       is_insoluble (DE_Hole hole) = isOutOfScopeHole hole -- See Note [Insoluble holes]
       is_insoluble (DE_NotConcrete {}) = True
 
 insolubleWantedCt :: Ct -> Bool
 -- Definitely insoluble, in particular /excluding/ type-hole constraints
 -- Namely:
---   a) an insoluble constraint as per 'insolubleCt', i.e. either
+--   a) an insoluble constraint as per 'insolubleirredCt', i.e. either
 --        - an insoluble equality constraint (e.g. Int ~ Bool), or
 --        - a custom type error constraint, TypeError msg :: Constraint
 --   b) that does not arise from a Given or a Wanted/Wanted fundep interaction
+-- See Note [Insoluble Wanteds]
+insolubleWantedCt ct
+  | CIrredCan ir_ct <- ct
+      -- CIrredCan: see (IW1) in Note [Insoluble Wanteds]
+  , IrredCt { ir_ev = ev } <- ir_ct
+  , CtWanted { ctev_loc = loc, ctev_rewriters = rewriters }  <- ev
+      -- It's a Wanted
+  , insolubleIrredCt ir_ct
+      -- It's insoluble
+  , isEmptyRewriterSet rewriters
+      -- rewriters; see (IW2) in Note [Insoluble Wanteds]
+  , not (isGivenLoc loc)
+      -- isGivenLoc: see (IW3) in Note [Insoluble Wanteds]
+  , not (isWantedWantedFunDepOrigin (ctLocOrigin loc))
+      -- origin check: see (IW4) in Note [Insoluble Wanteds]
+  = True
+
+  | otherwise
+  = False
+
+-- | Returns True of constraints that are definitely insoluble,
+--   as well as TypeError constraints.
+-- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
 --
--- See Note [Given insolubles].
-insolubleWantedCt ct = insolubleCt ct &&
-                       not (arisesFromGivens ct) &&
-                       not (isWantedWantedFunDepOrigin (ctOrigin ct))
+-- The function is tuned for application /after/ constraint solving
+--       i.e. assuming canonicalisation has been done
+-- That's why it looks only for IrredCt; all insoluble constraints
+-- are put into CIrredCan
+insolubleCt :: Ct -> Bool
+insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
+insolubleCt _                 = False
 
 insolubleIrredCt :: IrredCt -> Bool
 -- Returns True of Irred constraints that are /definitely/ insoluble
@@ -1365,18 +1391,6 @@ insolubleIrredCt (IrredCt { ir_ev = ev, ir_reason = reason })
   -- >   Assert 'True  _errMsg = ()
   -- >   Assert _check errMsg  = errMsg
 
--- | Returns True of constraints that are definitely insoluble,
---   as well as TypeError constraints.
--- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
---
--- The function is tuned for application /after/ constraint solving
---       i.e. assuming canonicalisation has been done
--- That's why it looks only for IrredCt; all insoluble constraints
--- are put into CIrredCan
-insolubleCt :: Ct -> Bool
-insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
-insolubleCt _                 = False
-
 -- | Does this hole represent an "out of scope" error?
 -- See Note [Insoluble holes]
 isOutOfScopeHole :: Hole -> Bool
@@ -1420,6 +1434,31 @@ in GHC.Tc.Errors), so we may fail to report anything at all!  Yikes.
 Bottom line: insolubleWC (called in GHC.Tc.Solver.setImplicationStatus)
              should ignore givens even if they are insoluble.
 
+Note [Insoluble Wanteds]
+~~~~~~~~~~~~~~~~~~~~~~~~
+insolubleWantedCt returns True of a Wanted constraint that definitely
+can't be solved.  But not quite all such constraints; see wrinkles.
+
+(IW1) insolubleWantedCt is tuned for application /after/ constraint
+   solving i.e. assuming canonicalisation has been done.  That's why
+   it looks only for IrredCt; all insoluble constraints oare put into
+   CIrredCan
+
+(IW2) We only treat it as insoluble if it has an empty rewriter set.
+   Otherwise #25325 happens: a Wanted constraint A that is /not/ insoluble
+   rewrites some other Wanted constraint B, so B has A in its rewriter
+   set.  Now B looks insoluble.  The danger is that we'll suppress reporting
+   B becuase of its empty rewriter set; and suppress reporting A because
+   there is an insoluble B lying around.  (This suppression happens in
+   GHC.Tc.Errors.)  Solution: don't treat B as insoluble.
+
+(IW3) If the Wanted arises from a Given (how can that happen?), don't
+   treat it as a Wanted insoluble (obviously).
+
+(IW4) If the Wanted came from a  Wanted/Wanted fundep interaction, don't
+   treat the constraint as insoluble. See Note [Suppressing confusing errors]
+   in GHC.Tc.Errors
+
 Note [Insoluble holes]
 ~~~~~~~~~~~~~~~~~~~~~~
 Hole constraints that ARE NOT treated as truly insoluble:
@@ -2080,9 +2119,6 @@ tcEvDestUnique (HoleDest co_hole) = varUnique (coHoleCoVar co_hole)
 setCtEvLoc :: CtEvidence -> CtLoc -> CtEvidence
 setCtEvLoc ctev loc = ctev { ctev_loc = loc }
 
-arisesFromGivens :: Ct -> Bool
-arisesFromGivens ct = isGivenCt ct || isGivenLoc (ctLoc ct)
-
 -- | Set the type of CtEvidence.
 --
 -- This function ensures that the invariants on 'CtEvidence' hold, by updating


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,10 +1,7 @@
-
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'’
-      Where: ‘a'’ is a rigid type variable bound by
-               the inferred type of
-                 traverseCompose :: (a -> f b) -> g a -> f (h a')
-               at T14172.hs:8:1-46
+    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
+      Where: ‘k0’ is an ambiguous type variable
+             ‘a'1’ is an ambiguous type variable
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -13,17 +10,19 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
-        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
-                -> Compose f'0 g'1 a'0 -> f (h a')
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
+        Actual: (Unwrapped (Compose f'0 g'1 a'0)
+                 -> f (Unwrapped (h a'1)))
+                -> Compose f'0 g'1 a'0 -> f (h a'1)
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a')
+          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a')
+        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
           (bound at T14172.hs:8:1)
+


=====================================
testsuite/tests/typecheck/should_fail/T25325.hs
=====================================
@@ -0,0 +1,14 @@
+module T25325 where
+
+import Control.Monad.State
+
+data (f :+: g) a = Inl (f a) | Inr (g a)
+
+newtype Buggy f m = Buggy { thing :: m Int }
+
+class GhcBug f where
+  demo :: MonadState (Buggy f m) m => f (m Int) -> m Int
+
+instance (GhcBug f, GhcBug g) => GhcBug (f :+: g) where
+    demo (Inl l) = demo l
+    demo (Inr r) = demo r


=====================================
testsuite/tests/typecheck/should_fail/T25325.stderr
=====================================
@@ -0,0 +1,15 @@
+T25325.hs:14:20: error: [GHC-39999]
+    • Could not deduce ‘MonadState (Buggy g m) m’
+        arising from a use of ‘demo’
+      from the context: (GhcBug f, GhcBug g)
+        bound by the instance declaration at T25325.hs:12:10-49
+      or from: MonadState (Buggy (f :+: g) m) m
+        bound by the type signature for:
+                   demo :: forall (m :: * -> *).
+                           MonadState (Buggy (f :+: g) m) m =>
+                           (:+:) f g (m Int) -> m Int
+        at T25325.hs:13:5-8
+    • In the expression: demo r
+      In an equation for ‘demo’: demo (Inr r) = demo r
+      In the instance declaration for ‘GhcBug (f :+: g)’
+


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -730,3 +730,4 @@ test('T23739b', normal, compile_fail, [''])
 test('T23739c', normal, compile_fail, [''])
 test('T24868', normal, compile_fail, [''])
 test('T24938', normal, compile_fail, [''])
+test('T25325', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67eb3db8acf778660ab50dd04e894bb9667746fa

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 16:01:15 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 06 Oct 2024 12:01:15 -0400
Subject: [Git][ghc/ghc][wip/T25281] One more
Message-ID: <6702b44b2362f_2147503bf17841241@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
1fc154cc by Simon Peyton Jones at 2024-10-06T17:01:02+01:00
One more

- - - - -


1 changed file:

- compiler/GHC/Iface/Ext/Ast.hs


Changes:

=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -939,7 +939,7 @@ instance HiePass p => ToHie (Located (PatSynBind (GhcPass p) (GhcPass p))) where
             (PrefixCon _ args) -> foldr combineScopes NoScope $ map mkScope args
             (InfixCon a b) -> combineScopes (mkScope a) (mkScope b)
             (RecCon r) -> foldr go NoScope r
-          go (RecordPatSynField a b) c = combineScopes c
+          go (RecordPatSynField (a :: FieldOcc (GhcPass p)) b) c = combineScopes c
             $ combineScopes (mkScope (foLabel a)) (mkScope b)
           detSpan = case detScope of
             LocalScope a -> Just a



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1fc154cc67b5f0d8928397ba829397bd951993e8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 16:37:58 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Sun, 06 Oct 2024 12:37:58 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/fix-ccallconv-test
Message-ID: <6702bce652bdd_2a4b85156f6c69728@gitlab.mail>



Sven Tennie pushed new branch wip/supersven/fix-ccallconv-test at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/fix-ccallconv-test
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 21:31:58 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 06 Oct 2024 17:31:58 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/spj-apporv-Oct24
Message-ID: <670301ceeaf1a_aa5df2d79a4302dc@gitlab.mail>



Simon Peyton Jones pushed new branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/spj-apporv-Oct24
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 22:13:17 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 06 Oct 2024 18:13:17 -0400
Subject: [Git][ghc/ghc][wip/T25281] More
Message-ID: <67030b7d56ef8_aa5df5b80743535b@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
90e4736b by Simon Peyton Jones at 2024-10-06T23:13:02+01:00
More

- - - - -


1 changed file:

- compiler/GHC/Rename/Names.hs


Changes:

=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -208,7 +208,7 @@ rnImports imports = do
     -- module to import from its implementor
     let this_mod = tcg_mod tcg_env
     let (source, ordinary) = partition (is_source_import . fst) imports
-        is_source_import d = ideclSource (unLoc d) == IsBoot
+        is_source_import (d::LImportDecl GhcPs) = ideclSource (unLoc d) == IsBoot
     stuff1 <- mapAndReportM (rnImportDecl this_mod) ordinary
     stuff2 <- mapAndReportM (rnImportDecl this_mod) source
     -- Safe Haskell: See Note [Tracking Trust Transitively]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90e4736b624a9eb9485fce56e027e59d5e6f8d6c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct  6 22:15:56 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 06 Oct 2024 18:15:56 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: EPA: Remove
 unused hsCaseAnnsRest
Message-ID: <67030c1cdb68b_aa5df6869603718c@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
08943213 by Alan Zimmerman at 2024-10-06T18:15:37-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
f1c38322 by John Paul Adrian Glaubitz at 2024-10-06T18:15:43-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
a2f4b35e by Teo Camarasu at 2024-10-06T18:15:44-04:00
Add changelog entries for !12479

- - - - -


7 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- rts/posix/Signals.c
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -202,11 +202,10 @@ type instance XUntypedBracket GhcTc = HsBracketTc
 data EpAnnHsCase = EpAnnHsCase
       { hsCaseAnnCase :: EpaLocation
       , hsCaseAnnOf   :: EpaLocation
-      , hsCaseAnnsRest :: [AddEpAnn]
       } deriving Data
 
 instance NoAnn EpAnnHsCase where
-  noAnn = EpAnnHsCase noAnn noAnn noAnn
+  noAnn = EpAnnHsCase noAnn noAnn
 
 data EpAnnUnboundVar = EpAnnUnboundVar
      { hsUnboundBackquotes :: (EpaLocation, EpaLocation)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3042,7 +3042,7 @@ aexp    :: { ECP }
                                              return $ ECP $
                                                $4 >>= \ $4 ->
                                                mkHsCasePV (comb3 $1 $3 $4) $2 $4
-                                                    (EpAnnHsCase (glAA $1) (glAA $3) []) }
+                                                    (EpAnnHsCase (glAA $1) (glAA $3)) }
         -- QualifiedDo.
         | DO  stmtlist               {% do
                                       hintQualifiedDo $1


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
rts/posix/Signals.c
=====================================
@@ -27,7 +27,7 @@
 
 #if defined(alpha_HOST_ARCH)
 # if defined(linux_HOST_OS)
-#  include 
+#  include 
 # else
 #  include 
 # endif
@@ -721,7 +721,11 @@ initDefaultHandlers(void)
 #endif
 
 #if defined(alpha_HOST_ARCH)
+# if defined(linux_HOST_OS)
+    __ieee_set_fp_control(0);
+# else
     ieee_set_fp_control(0);
+# endif
 #endif
 
     // ignore SIGPIPE; see #1619


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -2170,8 +2170,7 @@
                 (HsCase
                  (EpAnnHsCase
                   (EpaSpan { DumpSemis.hs:37:3-6 })
-                  (EpaSpan { DumpSemis.hs:37:10-11 })
-                  [])
+                  (EpaSpan { DumpSemis.hs:37:10-11 }))
                  (L
                   (EpAnn
                    (EpaSpan { DumpSemis.hs:37:8 })


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1211,7 +1211,6 @@ laiElseSemi k parent = fmap (\new -> parent { aiElseSemi = new })
 -- data EpAnnHsCase = EpAnnHsCase
 --       { hsCaseAnnCase :: EpaLocation
 --       , hsCaseAnnOf   :: EpaLocation
---       , hsCaseAnnsRest :: [AddEpAnn]
 --       } deriving Data
 
 lhsCaseAnnCase :: Lens EpAnnHsCase EpaLocation
@@ -1222,10 +1221,6 @@ lhsCaseAnnOf :: Lens EpAnnHsCase EpaLocation
 lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
                                (k (hsCaseAnnOf parent))
 
-lhsCaseAnnsRest :: Lens EpAnnHsCase [AddEpAnn]
-lhsCaseAnnsRest k parent = fmap (\new -> parent { hsCaseAnnsRest = new })
-                                (k (hsCaseAnnsRest parent))
-
 -- ---------------------------------------------------------------------
 
 -- data HsRuleAnn
@@ -3161,11 +3156,8 @@ instance ExactPrint (HsExpr GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- setLayoutBoth $ markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCase an4 e' alts')
+    return (HsCase an1 e' alts')
 
   exact (HsIf an e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf
@@ -3635,11 +3627,8 @@ instance ExactPrint (HsCmd GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCmdCase an4 e' alts')
+    return (HsCmdCase an1 e' alts')
 
   exact (HsCmdIf an a e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50d9fc5e73228228c5ca79fb615df38544688108...a2f4b35e3120c11a13fe785cbd6b8901cfcc6a14

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50d9fc5e73228228c5ca79fb615df38544688108...a2f4b35e3120c11a13fe785cbd6b8901cfcc6a14
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 05:07:00 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 01:07:00 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: EPA: Remove
 unused hsCaseAnnsRest
Message-ID: <67036c7482743_2f4573162f4c43224@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
7558fc97 by Alan Zimmerman at 2024-10-07T01:06:40-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
f14bebc0 by John Paul Adrian Glaubitz at 2024-10-07T01:06:46-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
99bd564f by Teo Camarasu at 2024-10-07T01:06:46-04:00
Add changelog entries for !12479

- - - - -


7 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- rts/posix/Signals.c
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -202,11 +202,10 @@ type instance XUntypedBracket GhcTc = HsBracketTc
 data EpAnnHsCase = EpAnnHsCase
       { hsCaseAnnCase :: EpaLocation
       , hsCaseAnnOf   :: EpaLocation
-      , hsCaseAnnsRest :: [AddEpAnn]
       } deriving Data
 
 instance NoAnn EpAnnHsCase where
-  noAnn = EpAnnHsCase noAnn noAnn noAnn
+  noAnn = EpAnnHsCase noAnn noAnn
 
 data EpAnnUnboundVar = EpAnnUnboundVar
      { hsUnboundBackquotes :: (EpaLocation, EpaLocation)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3042,7 +3042,7 @@ aexp    :: { ECP }
                                              return $ ECP $
                                                $4 >>= \ $4 ->
                                                mkHsCasePV (comb3 $1 $3 $4) $2 $4
-                                                    (EpAnnHsCase (glAA $1) (glAA $3) []) }
+                                                    (EpAnnHsCase (glAA $1) (glAA $3)) }
         -- QualifiedDo.
         | DO  stmtlist               {% do
                                       hintQualifiedDo $1


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
rts/posix/Signals.c
=====================================
@@ -27,7 +27,7 @@
 
 #if defined(alpha_HOST_ARCH)
 # if defined(linux_HOST_OS)
-#  include 
+#  include 
 # else
 #  include 
 # endif
@@ -721,7 +721,11 @@ initDefaultHandlers(void)
 #endif
 
 #if defined(alpha_HOST_ARCH)
+# if defined(linux_HOST_OS)
+    __ieee_set_fp_control(0);
+# else
     ieee_set_fp_control(0);
+# endif
 #endif
 
     // ignore SIGPIPE; see #1619


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -2170,8 +2170,7 @@
                 (HsCase
                  (EpAnnHsCase
                   (EpaSpan { DumpSemis.hs:37:3-6 })
-                  (EpaSpan { DumpSemis.hs:37:10-11 })
-                  [])
+                  (EpaSpan { DumpSemis.hs:37:10-11 }))
                  (L
                   (EpAnn
                    (EpaSpan { DumpSemis.hs:37:8 })


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1211,7 +1211,6 @@ laiElseSemi k parent = fmap (\new -> parent { aiElseSemi = new })
 -- data EpAnnHsCase = EpAnnHsCase
 --       { hsCaseAnnCase :: EpaLocation
 --       , hsCaseAnnOf   :: EpaLocation
---       , hsCaseAnnsRest :: [AddEpAnn]
 --       } deriving Data
 
 lhsCaseAnnCase :: Lens EpAnnHsCase EpaLocation
@@ -1222,10 +1221,6 @@ lhsCaseAnnOf :: Lens EpAnnHsCase EpaLocation
 lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
                                (k (hsCaseAnnOf parent))
 
-lhsCaseAnnsRest :: Lens EpAnnHsCase [AddEpAnn]
-lhsCaseAnnsRest k parent = fmap (\new -> parent { hsCaseAnnsRest = new })
-                                (k (hsCaseAnnsRest parent))
-
 -- ---------------------------------------------------------------------
 
 -- data HsRuleAnn
@@ -3161,11 +3156,8 @@ instance ExactPrint (HsExpr GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- setLayoutBoth $ markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCase an4 e' alts')
+    return (HsCase an1 e' alts')
 
   exact (HsIf an e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf
@@ -3635,11 +3627,8 @@ instance ExactPrint (HsCmd GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCmdCase an4 e' alts')
+    return (HsCmdCase an1 e' alts')
 
   exact (HsCmdIf an a e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2f4b35e3120c11a13fe785cbd6b8901cfcc6a14...99bd564f21429c03603755b792ce840aaa0022cd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2f4b35e3120c11a13fe785cbd6b8901cfcc6a14...99bd564f21429c03603755b792ce840aaa0022cd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 08:07:24 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 07 Oct 2024 04:07:24 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/remove-ghciWithDebugger
Message-ID: <670396bcc3f7d_6ec1121bc2c547ec@gitlab.mail>



Cheng Shao pushed new branch wip/remove-ghciWithDebugger at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/remove-ghciWithDebugger
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 08:17:27 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 07 Oct 2024 04:17:27 -0400
Subject: [Git][ghc/ghc][wip/T23479] 26 commits: SpecConstr: Introduce a
 separate argument limit for forced specs.
Message-ID: <6703991748438_6ec1121bc685655@gitlab.mail>



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


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
a95ca477 by Serge S. Gulin at 2024-10-07T11:15:40+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Unit/Finder.hs
- compiler/ghc.cabal.in


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3650b382f006777edc1a144b5dce183d8871926...a95ca477c336cc13b4ca221741b08e98b4a1455d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3650b382f006777edc1a144b5dce183d8871926...a95ca477c336cc13b4ca221741b08e98b4a1455d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:17:23 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 05:17:23 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove unused hsCaseAnnsRest
Message-ID: <6703a723d93d_29c3ac2d8b1038039@gitlab.mail>



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


Commits:
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -


4 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -202,11 +202,10 @@ type instance XUntypedBracket GhcTc = HsBracketTc
 data EpAnnHsCase = EpAnnHsCase
       { hsCaseAnnCase :: EpaLocation
       , hsCaseAnnOf   :: EpaLocation
-      , hsCaseAnnsRest :: [AddEpAnn]
       } deriving Data
 
 instance NoAnn EpAnnHsCase where
-  noAnn = EpAnnHsCase noAnn noAnn noAnn
+  noAnn = EpAnnHsCase noAnn noAnn
 
 data EpAnnUnboundVar = EpAnnUnboundVar
      { hsUnboundBackquotes :: (EpaLocation, EpaLocation)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3042,7 +3042,7 @@ aexp    :: { ECP }
                                              return $ ECP $
                                                $4 >>= \ $4 ->
                                                mkHsCasePV (comb3 $1 $3 $4) $2 $4
-                                                    (EpAnnHsCase (glAA $1) (glAA $3) []) }
+                                                    (EpAnnHsCase (glAA $1) (glAA $3)) }
         -- QualifiedDo.
         | DO  stmtlist               {% do
                                       hintQualifiedDo $1


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -2170,8 +2170,7 @@
                 (HsCase
                  (EpAnnHsCase
                   (EpaSpan { DumpSemis.hs:37:3-6 })
-                  (EpaSpan { DumpSemis.hs:37:10-11 })
-                  [])
+                  (EpaSpan { DumpSemis.hs:37:10-11 }))
                  (L
                   (EpAnn
                    (EpaSpan { DumpSemis.hs:37:8 })


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1211,7 +1211,6 @@ laiElseSemi k parent = fmap (\new -> parent { aiElseSemi = new })
 -- data EpAnnHsCase = EpAnnHsCase
 --       { hsCaseAnnCase :: EpaLocation
 --       , hsCaseAnnOf   :: EpaLocation
---       , hsCaseAnnsRest :: [AddEpAnn]
 --       } deriving Data
 
 lhsCaseAnnCase :: Lens EpAnnHsCase EpaLocation
@@ -1222,10 +1221,6 @@ lhsCaseAnnOf :: Lens EpAnnHsCase EpaLocation
 lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
                                (k (hsCaseAnnOf parent))
 
-lhsCaseAnnsRest :: Lens EpAnnHsCase [AddEpAnn]
-lhsCaseAnnsRest k parent = fmap (\new -> parent { hsCaseAnnsRest = new })
-                                (k (hsCaseAnnsRest parent))
-
 -- ---------------------------------------------------------------------
 
 -- data HsRuleAnn
@@ -3161,11 +3156,8 @@ instance ExactPrint (HsExpr GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- setLayoutBoth $ markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCase an4 e' alts')
+    return (HsCase an1 e' alts')
 
   exact (HsIf an e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf
@@ -3635,11 +3627,8 @@ instance ExactPrint (HsCmd GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCmdCase an4 e' alts')
+    return (HsCmdCase an1 e' alts')
 
   exact (HsCmdIf an a e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a2f0f1302f5919dfc9c8cbc410fceb19e7309ba

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:18:02 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 05:18:02 -0400
Subject: [Git][ghc/ghc][wip/T25281] 12 commits: Deprecation for
 WarnCompatUnqualifiedImports
Message-ID: <6703a74a402e1_29c3ac2e3a4c4156d@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
19bd6a1f by Sebastian Graf at 2024-10-07T08:34:07+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
5b5b6cc2 by Simon Peyton Jones at 2024-10-07T08:34:07+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
4e69c01e by Simon Peyton Jones at 2024-10-07T08:34:07+01:00
Yet more

- - - - -
0614c061 by Simon Peyton Jones at 2024-10-07T08:34:07+01:00
One more

- - - - -
cabe5e38 by Simon Peyton Jones at 2024-10-07T08:34:07+01:00
More

- - - - -
c43bf0aa by Simon Peyton Jones at 2024-10-07T10:17:40+01:00
More

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/90e4736b624a9eb9485fce56e027e59d5e6f8d6c...c43bf0aaed81c6a9b5d370f5ae7ddde86fe644ae

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/90e4736b624a9eb9485fce56e027e59d5e6f8d6c...c43bf0aaed81c6a9b5d370f5ae7ddde86fe644ae
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:18:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 05:18:15 -0400
Subject: [Git][ghc/ghc][master] rts: Fix invocation of __ieee_set_fp_control()
 on alpha-linux
Message-ID: <6703a7573501_29c3ac4d0f584215f@gitlab.mail>



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


Commits:
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -


1 changed file:

- rts/posix/Signals.c


Changes:

=====================================
rts/posix/Signals.c
=====================================
@@ -27,7 +27,7 @@
 
 #if defined(alpha_HOST_ARCH)
 # if defined(linux_HOST_OS)
-#  include 
+#  include 
 # else
 #  include 
 # endif
@@ -721,7 +721,11 @@ initDefaultHandlers(void)
 #endif
 
 #if defined(alpha_HOST_ARCH)
+# if defined(linux_HOST_OS)
+    __ieee_set_fp_control(0);
+# else
     ieee_set_fp_control(0);
+# endif
 #endif
 
     // ignore SIGPIPE; see #1619



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5099057b7eaa08d53c8ab07be0f6d626496ec79d

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:19:10 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 05:19:10 -0400
Subject: [Git][ghc/ghc][master] Add changelog entries for !12479
Message-ID: <6703a78e6c68_29c3ac82053c45274@gitlab.mail>



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


Commits:
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -


2 changed files:

- libraries/base/changelog.md
- libraries/template-haskell/changelog.md


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:43:09 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 07 Oct 2024 05:43:09 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes 23479 (muted temporary))
Message-ID: <6703ad2d4afc3_2db8d919b02c680d2@gitlab.mail>



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


Commits:
48af9822 by Serge S. Gulin at 2024-10-07T12:42:51+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

- - - - -


19 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479.hs
- + testsuite/tests/javascript/T23479.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,29 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,149 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < 3
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -7,3 +7,9 @@ T24495:
 	./T24495
 	# check that the optimization occurred
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479
+	# check that the optimization occurred
+	grep -c " h\$$decodeUtf8z" T23479.dump-js


=====================================
testsuite/tests/javascript/T23479.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE MagicHash #-}
+
+import GHC.Prim
+
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## test_addr_1))
+  where
+    test_addr_1 :: Addr#
+    test_addr_1 = "test_val_1"#


=====================================
testsuite/tests/javascript/T23479.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_1
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,5 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479', normal, makefile_test, ['T23479'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48af9822ce106d5880d449ea938a6a076ff34bb1

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:46:35 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 05:46:35 -0400
Subject: [Git][ghc/ghc][wip/T25281] Wibble
Message-ID: <6703adfb3fe79_2db8d921c9106868a@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
1fd17319 by Simon Peyton Jones at 2024-10-07T10:46:24+01:00
Wibble

- - - - -


1 changed file:

- compiler/GHC/Runtime/Heap/Inspect.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -1,4 +1,4 @@
-{-# OPTIONS_GHC -Wwarn=no-incomplete-record-selectors #-}
+{-# OPTIONS_GHC -Wwarn=incomplete-record-selectors #-}
 -- This module has a bunch of uses of incomplete record selectors
 -- and it is FAR from obvious that they won't cause crashes.
 -- But I don't want them to kill CI, so the above flag turns



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1fd17319702c749fd793fa5ea88d984ac3c7068b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 09:49:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 05:49:53 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: EPA: Remove
 unused hsCaseAnnsRest
Message-ID: <6703aec1d1171_2db8d91994207452e@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
822ab964 by Matthew Pickering at 2024-10-07T05:49:17-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
57b540e0 by Matthew Pickering at 2024-10-07T05:49:18-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
f2eda0b2 by Matthew Pickering at 2024-10-07T05:49:19-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -


12 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- rts/posix/Signals.c
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -631,6 +631,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
+          | I386Backend  -- ^ Run this job when the "i386" label is set
           deriving (Show, Enum, Bounded, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
@@ -678,6 +679,7 @@ validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
 validateRuleString IpeData      = labelString "IPE"
 validateRuleString TestPrimops  = labelString "test-primops"
+validateRuleString I386Backend  = labelString "i386"
 
 -- | A 'Job' is the description of a single job in a gitlab pipeline. The
 -- job contains all the information about how to do the build but can be further
@@ -1055,7 +1057,7 @@ debian_aarch64 =
 debian_i386 :: [JobGroup Job]
 debian_i386 =
   [ disableValidate (standardBuildsWithConfig I386 (Linux Debian10) (splitSectionsBroken vanilla))
-  , standardBuildsWithConfig I386 (Linux Debian12) (splitSectionsBroken vanilla)
+  , addValidateRule I386Backend (standardBuildsWithConfig I386 (Linux Debian12) (splitSectionsBroken vanilla))
   ]
 
 ubuntu_x86 :: [JobGroup Job]


=====================================
.gitlab/jobs.yaml
=====================================
@@ -227,7 +227,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*i386.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],


=====================================
compiler/GHC/Core/Opt/SpecConstr.hs
=====================================
@@ -2512,13 +2512,11 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls
     partitionByWorkerSize worker_size pats = go pats [] []
       where
         go [] small warnings = (small, warnings)
-        go (p:ps) small warnings
-          | WorkerSmallEnough <- worker_size p
-          = go ps (p:small) warnings
-          | WorkerTooLarge <- worker_size p
-          = go ps small warnings
-          | WorkerTooLargeForced name <- worker_size p
-          = go ps small (SpecFailForcedArgCount name : warnings)
+        go (p:ps) small warnings =
+          case worker_size p of
+            WorkerSmallEnough -> go ps (p:small) warnings
+            WorkerTooLarge -> go ps small warnings
+            WorkerTooLargeForced name -> go ps small (SpecFailForcedArgCount name : warnings)
 
 
 trim_pats :: ScEnv -> Id -> SpecInfo -> [CallPat] -> (Bool, [CallPat])


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -202,11 +202,10 @@ type instance XUntypedBracket GhcTc = HsBracketTc
 data EpAnnHsCase = EpAnnHsCase
       { hsCaseAnnCase :: EpaLocation
       , hsCaseAnnOf   :: EpaLocation
-      , hsCaseAnnsRest :: [AddEpAnn]
       } deriving Data
 
 instance NoAnn EpAnnHsCase where
-  noAnn = EpAnnHsCase noAnn noAnn noAnn
+  noAnn = EpAnnHsCase noAnn noAnn
 
 data EpAnnUnboundVar = EpAnnUnboundVar
      { hsUnboundBackquotes :: (EpaLocation, EpaLocation)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3042,7 +3042,7 @@ aexp    :: { ECP }
                                              return $ ECP $
                                                $4 >>= \ $4 ->
                                                mkHsCasePV (comb3 $1 $3 $4) $2 $4
-                                                    (EpAnnHsCase (glAA $1) (glAA $3) []) }
+                                                    (EpAnnHsCase (glAA $1) (glAA $3)) }
         -- QualifiedDo.
         | DO  stmtlist               {% do
                                       hintQualifiedDo $1


=====================================
compiler/GHC/StgToJS/Object.hs
=====================================
@@ -255,23 +255,23 @@ instance Outputable ExportedFun where
 -- index
 putObjBlock :: WriteBinHandle -> ObjBlock -> IO ()
 putObjBlock bh (ObjBlock _syms b c d e f g) = do
-    put_ bh b
-    put_ bh c
+    lazyPut bh b
+    lazyPut bh c
     lazyPut bh d
-    put_ bh e
-    put_ bh f
-    put_ bh g
+    lazyPut bh e
+    lazyPut bh f
+    lazyPut bh g
 
 -- | Read an ObjBlock and associate it to the given symbols (that must have been
 -- read from the index)
 getObjBlock :: [FastString] -> ReadBinHandle -> IO ObjBlock
 getObjBlock syms bh = do
-    b <- get bh
-    c <- get bh
+    b <- lazyGet bh
+    c <- lazyGet bh
     d <- lazyGet bh
-    e <- get bh
-    f <- get bh
-    g <- get bh
+    e <- lazyGet bh
+    f <- lazyGet bh
+    g <- lazyGet bh
     pure $ ObjBlock
       { oiSymbols  = syms
       , oiClInfo   = b


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -312,13 +312,13 @@ data LinkableUnit = LinkableUnit
 
 -- | one toplevel block in the object file
 data ObjBlock = ObjBlock
-  { oiSymbols  :: ![FastString]   -- ^ toplevel symbols (stored in index)
-  , oiClInfo   :: ![ClosureInfo]  -- ^ closure information of all closures in block
-  , oiStatic   :: ![StaticInfo]   -- ^ static closure data
+  { oiSymbols  :: [FastString]   -- ^ toplevel symbols (stored in index)
+  , oiClInfo   :: [ClosureInfo]  -- ^ closure information of all closures in block
+  , oiStatic   :: [StaticInfo]   -- ^ static closure data
   , oiStat     :: Sat.JStat       -- ^ the code
-  , oiRaw      :: !BS.ByteString  -- ^ raw JS code
-  , oiFExports :: ![ExpFun]
-  , oiFImports :: ![ForeignJSRef]
+  , oiRaw      :: BS.ByteString  -- ^ raw JS code
+  , oiFExports :: [ExpFun]
+  , oiFImports :: [ForeignJSRef]
   }
 
 data ExpFun = ExpFun


=====================================
libraries/base/changelog.md
=====================================
@@ -34,6 +34,7 @@
       the context since it will be redundant. These functions are mostly useful
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
+  * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -4,6 +4,7 @@
 
   * Extend `Exp` with `ForallE`, `ForallVisE`, `ConstraintedE`,
     introduce functions `forallE`, `forallVisE`, `constraintedE` (GHC Proposal #281).
+  * `template-haskell` is no longer wired-in. All wired-in identifiers have been moved to `ghc-internal`.
 
 ## 2.22.1.0
 


=====================================
rts/posix/Signals.c
=====================================
@@ -27,7 +27,7 @@
 
 #if defined(alpha_HOST_ARCH)
 # if defined(linux_HOST_OS)
-#  include 
+#  include 
 # else
 #  include 
 # endif
@@ -721,7 +721,11 @@ initDefaultHandlers(void)
 #endif
 
 #if defined(alpha_HOST_ARCH)
+# if defined(linux_HOST_OS)
+    __ieee_set_fp_control(0);
+# else
     ieee_set_fp_control(0);
+# endif
 #endif
 
     // ignore SIGPIPE; see #1619


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -2170,8 +2170,7 @@
                 (HsCase
                  (EpAnnHsCase
                   (EpaSpan { DumpSemis.hs:37:3-6 })
-                  (EpaSpan { DumpSemis.hs:37:10-11 })
-                  [])
+                  (EpaSpan { DumpSemis.hs:37:10-11 }))
                  (L
                   (EpAnn
                    (EpaSpan { DumpSemis.hs:37:8 })


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1211,7 +1211,6 @@ laiElseSemi k parent = fmap (\new -> parent { aiElseSemi = new })
 -- data EpAnnHsCase = EpAnnHsCase
 --       { hsCaseAnnCase :: EpaLocation
 --       , hsCaseAnnOf   :: EpaLocation
---       , hsCaseAnnsRest :: [AddEpAnn]
 --       } deriving Data
 
 lhsCaseAnnCase :: Lens EpAnnHsCase EpaLocation
@@ -1222,10 +1221,6 @@ lhsCaseAnnOf :: Lens EpAnnHsCase EpaLocation
 lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
                                (k (hsCaseAnnOf parent))
 
-lhsCaseAnnsRest :: Lens EpAnnHsCase [AddEpAnn]
-lhsCaseAnnsRest k parent = fmap (\new -> parent { hsCaseAnnsRest = new })
-                                (k (hsCaseAnnsRest parent))
-
 -- ---------------------------------------------------------------------
 
 -- data HsRuleAnn
@@ -3161,11 +3156,8 @@ instance ExactPrint (HsExpr GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- setLayoutBoth $ markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCase an4 e' alts')
+    return (HsCase an1 e' alts')
 
   exact (HsIf an e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf
@@ -3635,11 +3627,8 @@ instance ExactPrint (HsCmd GhcPs) where
     an0 <- markLensKw an lhsCaseAnnCase AnnCase
     e' <- markAnnotated e
     an1 <- markLensKw an0 lhsCaseAnnOf AnnOf
-    an2 <- markEpAnnL an1 lhsCaseAnnsRest AnnOpenC
-    an3 <- markEpAnnAllL' an2 lhsCaseAnnsRest AnnSemi
     alts' <- markAnnotated alts
-    an4 <- markEpAnnL an3 lhsCaseAnnsRest AnnCloseC
-    return (HsCmdCase an4 e' alts')
+    return (HsCmdCase an1 e' alts')
 
   exact (HsCmdIf an a e1 e2 e3) = do
     an0 <- markLensKw an laiIf AnnIf



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/99bd564f21429c03603755b792ce840aaa0022cd...f2eda0b22fd3ba08812a3f68e7e4fc4abe71d186

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/99bd564f21429c03603755b792ce840aaa0022cd...f2eda0b22fd3ba08812a3f68e7e4fc4abe71d186
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 10:25:00 2024
From: gitlab at gitlab.haskell.org (sheaf (@sheaf))
Date: Mon, 07 Oct 2024 06:25:00 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/x86-flags-user-guide
Message-ID: <6703b6fccf87d_276c1a172aa018453@gitlab.mail>



sheaf pushed new branch wip/x86-flags-user-guide at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/x86-flags-user-guide
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 10:30:35 2024
From: gitlab at gitlab.haskell.org (sheaf (@sheaf))
Date: Mon, 07 Oct 2024 06:30:35 -0400
Subject: [Git][ghc/ghc][wip/x86-flags-user-guide] user's guide: update docs
 for X86 CPU flags
Message-ID: <6703b84b3641c_276c1a1240f820244@gitlab.mail>



sheaf pushed to branch wip/x86-flags-user-guide at Glasgow Haskell Compiler / GHC


Commits:
c04addb3 by sheaf at 2024-10-07T12:29:42+02:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -


1 changed file:

- docs/users_guide/using.rst


Changes:

=====================================
docs/users_guide/using.rst
=====================================
@@ -1590,78 +1590,48 @@ Some flags only make sense for particular target platforms.
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX instructions.
 
 .. ghc-flag:: -mavx2
     :shortdesc: (x86 only) Enable support for AVX2 SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX2 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX2 instructions.
 
 .. ghc-flag:: -mavx512cd
     :shortdesc: (x86 only) Enable support for AVX512-CD SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-CD instructions.
 
 .. ghc-flag:: -mavx512er
     :shortdesc: (x86 only) Enable support for AVX512-ER SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-ER instructions.
 
 .. ghc-flag:: -mavx512f
     :shortdesc: (x86 only) Enable support for AVX512-F SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-F instructions.
 
 .. ghc-flag:: -mavx512pf
     :shortdesc: (x86 only) Enable support for AVX512-PF SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-PF instructions.
 
 .. ghc-flag:: -msse
     :shortdesc: (x86 only) Use SSE for floating-point operations
@@ -1706,15 +1676,9 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only) Use the SSE3 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `.
-
-    Note that the current version does not use SSE3 specific instructions
-    and only requires SSE2 processor support.
-
-    The :ref:`LLVM backend ` will also use
-    SSE3 if your processor supports it but detects this automatically
-    so no flag is required.
+    implement some floating point and bit operations
+    (whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `).
 
 .. ghc-flag:: -msse4
     :shortdesc: (x86 only) Use SSE4 for floating-point operations
@@ -1722,15 +1686,8 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only) Use the SSE4 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `.
-
-    Note that the current version does not use SSE4 specific instructions
-    and only requires SSE2 processor support.
-
-    The :ref:`LLVM backend ` will also use
-    SSE4 if your processor supports it but detects this automatically
-    so no flag is required.
+    implement some floating point and bit operations(whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `).
 
 .. ghc-flag:: -msse4.2
     :shortdesc: (x86 only) Use SSE4.2 for floating-point operations
@@ -1738,23 +1695,21 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only, added in GHC 7.4.1) Use the SSE4.2 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `. The resulting compiled
+    implement some floating point and bit operations,
+    whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `. The resulting compiled
     code will only run on processors that support SSE4.2 (Intel Core i7
-    and later). The :ref:`LLVM backend ` will also use
-    SSE4.2 if your processor supports it but detects this automatically
-    so no flag is required.
+    and later).
 
 .. ghc-flag:: -mbmi
     :shortdesc: (x86 only) Use BMI1 for bit manipulation operations
     :type: dynamic
     :category: platform-options
 
-    (x86 only) Use the BMI1 instruction set to implement some bit operations
-    when using the :ref:`native code generator `.
+    (x86 only) Use the BMI1 instruction set to implement some bit operations.
 
-    Note that the current version does not use BMI specific instructions,
-    so using this flag has no effect.
+    Note that GHC currently does not use BMI specific instructions,
+    so this flag has no effect when used with the :ref:`native code generator `.
 
 .. ghc-flag:: -mbmi2
     :shortdesc: (x86 only) Use BMI2 for bit manipulation operations
@@ -1762,9 +1717,11 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only, added in GHC 7.4.1) Use the BMI2 instruction set to
-    implement some bit operations when using the
-    :ref:`native code generator `. The resulting compiled
-    code will only run on processors that support BMI2 (Intel Haswell and newer, AMD Excavator, Zen and newer).
+    implement some bit operations, whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `.
+
+    The resulting compiled code will only run on processors that support BMI2
+    (Intel Haswell and newer, AMD Excavator, Zen and newer).
 
 .. ghc-flag:: -mfma
     :shortdesc: Use native FMA instructions for fused multiply-add floating-point operations



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 11:02:43 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 07:02:43 -0400
Subject: [Git][ghc/ghc][wip/T25281] Wibble warning
Message-ID: <6703bfd379771_276c1a4157d0245fb@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
190ee795 by Simon Peyton Jones at 2024-10-07T12:02:30+01:00
Wibble warning

- - - - -


1 changed file:

- compiler/GHC/Runtime/Heap/Inspect.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -Wwarn=incomplete-record-selectors #-}
+{- # OPTIONS_GHC -Wwarn=incomplete-record-selectors # -}
+--     Boo.  The bootstrap compiler falls over on this
 -- This module has a bunch of uses of incomplete record selectors
 -- and it is FAR from obvious that they won't cause crashes.
 -- But I don't want them to kill CI, so the above flag turns



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/190ee795ed061a45989ec68b784691e0c059f12a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 11:48:53 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Mon, 07 Oct 2024 07:48:53 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Don't store boot locations in finder
 cache
Message-ID: <6703caa541379_28e3da1c8b9445386@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
2cc76f86 by Sjoerd Visscher at 2024-10-07T13:48:42+02:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends addHomeModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location HsigFile
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -861,7 +861,6 @@ hsModuleToModSummary home_keys pn hsc_src modname
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
     let location = case hsc_src of
                         HsBootFile -> addBootSuffixLocnOut location0
                         _ -> location0
@@ -893,7 +892,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location hsc_src
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2077,7 +2077,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location hsc_src
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2110,10 +2110,9 @@ checkSummaryHash
            -- Also, only add to finder cache for non-boot modules as the finder cache
            -- makes sure to add a boot suffix for boot files.
            _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
+              let fc        = hsc_FC hsc_env
               case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
+                HsSrcFile -> addModuleToFinder fc (ms_mod old_summary) location
                 _ -> return ()
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -734,7 +734,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location src_flavour
 
   -- Make the ModSummary to hand to hscMain
   let


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -897,7 +897,7 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
           -- Look for the file
           mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -55,6 +55,7 @@ import GHC.Utils.Panic
 
 import GHC.Linker.Types
 import GHC.Types.PkgQual
+import GHC.Types.SourceFile
 
 import GHC.Fingerprint
 import Data.IORef
@@ -89,23 +90,23 @@ type BaseName = OsPath  -- Basename of file
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
-  mod_cache <- newIORef emptyInstalledModuleWithIsBootEnv
+  mod_cache <- newIORef emptyInstalledModuleEnv
   file_cache <- newIORef M.empty
   let flushFinderCaches :: UnitEnv -> IO ()
       flushFinderCaches ue = do
-        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
         atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
        where
-        is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+        is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-      addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+      addToFinderCache :: InstalledModule -> InstalledFindResult -> IO ()
       addToFinderCache key val =
-        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+        atomicModifyIORef' mod_cache $ \c -> (extendInstalledModuleEnv c key val, ())
 
-      lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+      lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do
          c <- readIORef mod_cache
-         return $! lookupInstalledModuleWithIsBootEnv c key
+         return $! lookupInstalledModuleEnv c key
 
       lookupFileCache :: FilePath -> IO Fingerprint
       lookupFileCache key = do
@@ -255,7 +256,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -277,7 +278,7 @@ findLookupResult fc fopts r = case r of
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -312,7 +313,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -322,17 +323,18 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  let imod = toUnitId <$> mod
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
-addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> HscSource -> IO Module
+addHomeModuleToFinder fc home_unit mod_name loc src_flavour = do
+  let mod = mkHomeInstalledModule home_unit mod_name
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc mod (InstalledFound loc)
+  return (mkHomeModule home_unit mod_name)
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -342,7 +344,7 @@ findHomeModule fc fopts  home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -367,7 +369,7 @@ findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -437,7 +439,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -466,11 +468,11 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -494,7 +496,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -528,7 +530,7 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
 mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -30,9 +30,9 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                -- ^ remove all the home modules from the cache; package modules are
                                -- assumed to not move around during a session; also flush the file hash
                                -- cache.
-                               , addToFinderCache  :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+                               , addToFinderCache  :: InstalledModule -> InstalledFindResult -> IO ()
                                -- ^ Add a found location to the cache for the module.
-                               , lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+                               , lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
                                -- ^ Look for a location in the cache.
                                , lookupFileCache   :: FilePath -> IO Fingerprint
                                -- ^ Look for the hash of a file in the cache. This should add it to the
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -84,8 +84,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -720,8 +718,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -735,6 +731,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2cc76f8698940ab69c6429594cbbf35a0ae839bf

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 12:27:09 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 08:27:09 -0400
Subject: [Git][ghc/ghc][wip/supersven/riscv64-cross-ci] 34 commits: Fix typo
 in Prelude doc for (>>=)
Message-ID: <6703d39d27688_28e3da396f0c54667@gitlab.mail>



Matthew Pickering pushed to branch wip/supersven/riscv64-cross-ci at Glasgow Haskell Compiler / GHC


Commits:
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
aea6b358 by Sven Tennie at 2024-10-07T12:27:01+00:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6dfe9ba50d5097348c2d3c7ffdb1d9ad903c57a3...aea6b358a89d1b2639543ea36f83ff293ed54711

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6dfe9ba50d5097348c2d3c7ffdb1d9ad903c57a3...aea6b358a89d1b2639543ea36f83ff293ed54711
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 12:35:37 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 07 Oct 2024 08:35:37 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/cross-no-cpu-features
Message-ID: <6703d5992d0ae_28e3da633724650a8@gitlab.mail>



Cheng Shao pushed new branch wip/cross-no-cpu-features at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/cross-no-cpu-features
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 12:36:36 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 08:36:36 -0400
Subject: [Git][ghc/ghc][wip/hadrian-cross-stage2] 56 commits: Fix typo in
 Prelude doc for (>>=)
Message-ID: <6703d5d4e8b36_28e3da6ff194682a0@gitlab.mail>



Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC


Commits:
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
b53bcbff by Matthew Pickering at 2024-10-07T13:36:23+01:00
Add missing req_interp modifier to T18441fail3 and T18441fail19

These tests require the interpreter but they were failing in a different
way with the javascript backend because the interpreter was disabled and
stderr is ignored by the test.

- - - - -
9a57a966 by Matthew Pickering at 2024-10-07T13:36:23+01:00
Use explicit syntax rather than pure

- - - - -
66e417ff by Matthew Pickering at 2024-10-07T13:36:23+01:00
packaging: correctly propagate build/host/target to bindist configure script

At the moment the host and target which we will produce a compiler for
is fixed at the initial configure time. Therefore we need to persist
the choice made at this time into the installation bindist as well so we
look for the right tools, with the right prefixes at install time.

In the future, we want to provide a bit more control about what kind of
bindist we produce so the logic about what the host/target will have to
be written by hadrian rather than persisted by the configure script. In
particular with cross compilers we want to either build a normal stage 2
cross bindist or a stage 3 bindist, which creates a bindist which has a
native compiler for the target platform.

Fixes #21970

- - - - -
5864d6e6 by Matthew Pickering at 2024-10-07T13:36:23+01:00
hadrian: Fill in more of the default.host toolchain file

When you are building a cross compiler this file will be used to build
stage1 and it's libraries, so we need enough information here to work
accurately. There is still more work to be done (see for example, word
size is still fixed).

- - - - -
f7633798 by Matthew Pickering at 2024-10-07T13:36:23+01:00
hadrian: Disable docs when cross compiling

Before there were a variety of ad-hoc places where doc building was
disabled when cross compiling.

* Some CI jobs sets --docs=none in gen_ci.hs
* Some CI jobs set --docs=none in .gitlab/ci.sh
* There was some logic in hadrian to not need the ["docs"] target when
  making a bindist.

Now the situation is simple:

* If you are cross compiling then defaultDocsTargets is empty by
  default.

In theory, there is no reason why we can't build documentation for cross
compiler bindists, but this is left to future work to generalise the
documentation building rules to allow this (#24289)

- - - - -
9e4cf949 by Matthew Pickering at 2024-10-07T13:36:23+01:00
hadrian: Build stage 2 cross compilers

* Most of hadrian is abstracted over the stage in order to remove the
  assumption that the target of all stages is the same platform. This
  allows the RTS to be built for two different targets for example.
* Abstracts the bindist creation logic to allow building either normal
  or cross bindists. Normal bindists use stage 1 libraries and a stage 2
  compiler. Cross bindists use stage 2 libararies and a stage 2
  compiler.
* hadrian: Make binary-dist-dir the default build target. This allows us
  to have the logic in one place about which libraries/stages to build
  with cross compilers. Fixes #24192

New hadrian target:

* `binary-dist-dir-cross`: Build a cross compiler bindist (compiler =
  stage 1, libraries = stage 2)

-------------------------
Metric Decrease:
    T10421a
    T10858
    T11195
    T11276
    T11374
    T11822
    T15630
    T17096
    T18478
    T20261
Metric Increase:
    parsing001
-------------------------

- - - - -
017554ef by Matthew Pickering at 2024-10-07T13:36:23+01:00
ci: Test cross bindists

We remove the special logic for testing in-tree cross
compilers and instead test cross compiler bindists, like we do for all
other platforms.

- - - - -
5d2f2a8a by Matthew Pickering at 2024-10-07T13:36:23+01:00
ci: Javascript don't set CROSS_EMULATOR

There is no CROSS_EMULATOR needed to run javascript binaries, so we
don't set the CROSS_EMULATOR to some dummy value.

- - - - -
4c0f5b39 by Matthew Pickering at 2024-10-07T13:36:23+01:00
ci: Introduce CROSS_STAGE variable

In preparation for building and testing stage3 bindists we introduce the
CROSS_STAGE variable which is used by a CI job to determine what kind of
bindist the CI job should produce.

At the moment we are only using CROSS_STAGE=2 but in the future we will
have some jobs which set CROSS_STAGE=3 to produce native bindists for a
target, but produced by a cross compiler, which can be tested on by
another CI job on the native platform.

CROSS_STAGE=2: Build a normal cross compiler bindist
CROSS_STAGE=3: Build a stage 3 bindist, one which is a native compiler and library for the target

- - - - -
d98d6101 by Matthew Pickering at 2024-10-07T13:36:23+01:00
Split up system.config into host/target config files

There were a number of settings which were not applied per-stage, for
example if you specified `--ffi-include-dir` then that was applied to
both host and target. Now this will just be passed when building the
crosscompiler.

The solution for now is to separate these two files into host/target and
the host file contains very bare-bones . There isn't currently a way to
specify with configure anything in the host file, so if you are building
a cross-compiler and you need to do that, you have to modify the file
yourself.

- - - - -
99fb9c32 by Matthew Pickering at 2024-10-07T13:36:23+01:00
wip fixup

- - - - -
42aa03a3 by Matthew Pickering at 2024-10-07T13:36:23+01:00
Fix location of emsdk-version

- - - - -
0aba64f1 by Matthew Pickering at 2024-10-07T13:36:23+01:00
fix distrib/configure file

- - - - -
a0b19724 by Matthew Pickering at 2024-10-07T13:36:24+01:00
Fix hardcoded stage1

- - - - -
59b05b54 by Matthew Pickering at 2024-10-07T13:36:24+01:00
Don't recache

- - - - -
93bba4a6 by Matthew Pickering at 2024-10-07T13:36:24+01:00
hadrian: Make text_simdutf flavour transformer configurable per-stage

Before it was globally enabled, which was probably not what you want as
you don't need text-simd for your boot compiler nor your boot compiler
if you're building a cross-compiler.

This brings it into line with the other modifiers.. such as ghcProfiled
etc

Fixes #25302

- - - - -
6751321b by Matthew Pickering at 2024-10-07T13:36:24+01:00
hadrian: Refactor system-cxx-std-lib rules0

I noticed a few things wrong with the hadrian rules for `system-cxx-std-lib` rules.

* For `text` there is an ad-hoc check to depend on `system-cxx-std-lib` outside of `configurePackage`.
* The `system-cxx-std-lib` dependency is not read from cabal files.
* Recache is not called on the packge database after the `.conf` file is generated, a more natural place for this rule is `registerRules`.

Treating this uniformly like other packages is complicated by it not having any source code or a cabal file. However we can do a bit better by reporting the dependency firstly in `PackageData` and then needing the `.conf` file in the same place as every other package in `configurePackage`.

Fixes #25303

- - - - -
25113a12 by Matthew Pickering at 2024-10-07T13:36:24+01:00
fixes for simdutf8

- - - - -
76798e42 by Matthew Pickering at 2024-10-07T13:36:24+01:00
use building for target in llvm flavour transformer

- - - - -
194098db by Matthew Pickering at 2024-10-07T13:36:24+01:00
bindist: Pass path to package database we want to recache

This fixes recaching on cross compilers

- - - - -
7a7e174c by Matthew Pickering at 2024-10-07T13:36:24+01:00
testsuite: T9930fail now passes on javascript

I didn't investigate why, but the comment says it should be fixed by
building a stage2 cross compiler (and it is).

- - - - -
7bd8882e by Matthew Pickering at 2024-10-07T13:36:24+01:00
hadrian: Fix predicate for building shared libraries in defaultLibraries

Obviously we should only attempt to build shared libraries if the target
supports building shared libraries.

- - - - -
bc085f1e by Matthew Pickering at 2024-10-07T13:36:24+01:00
Hard-code ways in settings

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6cdccbe9843350f35a55169cb2d97f3e48dd1bf...bc085f1ea5cbf2165e2619cf0f08154ff1b5e1bd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6cdccbe9843350f35a55169cb2d97f3e48dd1bf...bc085f1ea5cbf2165e2619cf0f08154ff1b5e1bd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 13:34:31 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 09:34:31 -0400
Subject: [Git][ghc/ghc][wip/hadrian-cross-stage2] Hard-code ways in settings
Message-ID: <6703e367b7193_32966a1c3fcc5787a@gitlab.mail>



Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC


Commits:
241691c9 by Matthew Pickering at 2024-10-07T14:34:22+01:00
Hard-code ways in settings

- - - - -


1 changed file:

- hadrian/src/Rules/Generate.hs


Changes:

=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -523,7 +523,10 @@ generateSettings settingsFile = do
 
         , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter stage)
         , ("Support SMP", expr $ yesNo <$> targetSupportsSMP stage)
-        , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
+        -- Hard-coded as Cabal queries these to determine way support and we
+        -- need to always advertise all ways when bootstrapping.
+        -- The settings file is generated at install time when installing a bindist.
+        , ("RTS ways", return "v p p p_dyn")
         , ("Tables next to code", queryTarget stage (yesNo . tgtTablesNextToCode))
         , ("Leading underscore",  queryTarget stage (yesNo . tgtSymbolsHaveLeadingUnderscore))
         , ("Use LibFFI", expr $ yesNo <$> targetUseLibffiForAdjustors stage)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/241691c9c56248390395b5461676803fde07a328

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:14:32 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 10:14:32 -0400
Subject: [Git][ghc/ghc][wip/hadrian-cross-stage2] Hard-code ways in settings
Message-ID: <6703ecc852c08_135b9824fd74680d5@gitlab.mail>



Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC


Commits:
e2582850 by Matthew Pickering at 2024-10-07T15:14:21+01:00
Hard-code ways in settings

- - - - -


1 changed file:

- hadrian/src/Rules/Generate.hs


Changes:

=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -7,7 +7,6 @@ module Rules.Generate (
 
 import Development.Shake.FilePath
 import Data.Char (isSpace)
-import qualified Data.Set as Set
 import Base
 import qualified Context
 import Expression
@@ -523,7 +522,10 @@ generateSettings settingsFile = do
 
         , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter stage)
         , ("Support SMP", expr $ yesNo <$> targetSupportsSMP stage)
-        , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
+        -- Hard-coded as Cabal queries these to determine way support and we
+        -- need to always advertise all ways when bootstrapping.
+        -- The settings file is generated at install time when installing a bindist.
+        , ("RTS ways", return "v p p p_dyn")
         , ("Tables next to code", queryTarget stage (yesNo . tgtTablesNextToCode))
         , ("Leading underscore",  queryTarget stage (yesNo . tgtSymbolsHaveLeadingUnderscore))
         , ("Use LibFFI", expr $ yesNo <$> targetUseLibffiForAdjustors stage)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:14:47 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Mon, 07 Oct 2024 10:14:47 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] 29 commits: SpecConstr: Introduce a
 separate argument limit for forced specs.
Message-ID: <6703ecd71f1ac_135b9824facc69414@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
c74a4799 by Sjoerd Visscher at 2024-10-07T16:14:36+02:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends addHomeModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Parser.y
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs
- configure.ac
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using-warnings.rst


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2cc76f8698940ab69c6429594cbbf35a0ae839bf...c74a4799a72f99fde3a696b3c3351b6d1b461f32

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2cc76f8698940ab69c6429594cbbf35a0ae839bf...c74a4799a72f99fde3a696b3c3351b6d1b461f32
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:46:39 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Mon, 07 Oct 2024 10:46:39 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Don't store boot locations in finder
 cache
Message-ID: <6703f44fa764b_135b984de5b8784f0@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
786cbfb5 by Sjoerd Visscher at 2024-10-07T16:46:29+02:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location HsigFile
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -861,7 +861,6 @@ hsModuleToModSummary home_keys pn hsc_src modname
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
     let location = case hsc_src of
                         HsBootFile -> addBootSuffixLocnOut location0
                         _ -> location0
@@ -893,7 +892,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location hsc_src
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2150,7 +2150,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location hsc_src
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2180,14 +2180,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
-           _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+           let fc      = hsc_FC hsc_env
+               mod     = ms_mod old_summary
+               hsc_src = ms_hsc_src old_summary
+           addModuleToFinder fc mod location hsc_src
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -734,7 +734,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location src_flavour
 
   -- Make the ModSummary to hand to hscMain
   let


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -897,7 +897,7 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
           -- Look for the file
           mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -55,6 +55,7 @@ import GHC.Utils.Panic
 
 import GHC.Linker.Types
 import GHC.Types.PkgQual
+import GHC.Types.SourceFile
 
 import GHC.Fingerprint
 import Data.IORef
@@ -103,28 +104,28 @@ InstalledNotFound.
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
-  mod_cache <- newIORef emptyInstalledModuleWithIsBootEnv
+  mod_cache <- newIORef emptyInstalledModuleEnv
   file_cache <- newIORef M.empty
   let flushFinderCaches :: UnitEnv -> IO ()
       flushFinderCaches ue = do
-        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
         atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
        where
-        is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+        is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-      addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+      addToFinderCache :: InstalledModule -> InstalledFindResult -> IO ()
       addToFinderCache key val =
         atomicModifyIORef' mod_cache $ \c ->
-          case (lookupInstalledModuleWithIsBootEnv c key, val) of
+          case (lookupInstalledModuleEnv c key, val) of
             -- Don't overwrite an InstalledFound with an InstalledNotFound
             -- See [Note Monotonic addToFinderCache]
             (Just InstalledFound{}, InstalledNotFound{}) -> (c, ())
-            _ -> (extendInstalledModuleWithIsBootEnv c key val, ())
+            _ -> (extendInstalledModuleEnv c key val, ())
 
-      lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+      lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do
          c <- readIORef mod_cache
-         return $! lookupInstalledModuleWithIsBootEnv c key
+         return $! lookupInstalledModuleEnv c key
 
       lookupFileCache :: FilePath -> IO Fingerprint
       lookupFileCache key = do
@@ -274,7 +275,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -296,7 +297,7 @@ findLookupResult fc fopts r = case r of
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -331,7 +332,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -341,17 +342,19 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
-addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> HscSource -> IO ()
+addModuleToFinder fc mod loc src_flavour = do
+  let imod = toUnitId <$> mod
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
-addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> HscSource -> IO Module
+addHomeModuleToFinder fc home_unit mod_name loc src_flavour = do
+  let mod = mkHomeInstalledModule home_unit mod_name
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc mod (InstalledFound loc)
+  return (mkHomeModule home_unit mod_name)
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -361,7 +364,7 @@ findHomeModule fc fopts  home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -386,7 +389,7 @@ findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -456,7 +459,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -485,11 +488,11 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +516,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,7 +550,7 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
 mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -30,9 +30,9 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                -- ^ remove all the home modules from the cache; package modules are
                                -- assumed to not move around during a session; also flush the file hash
                                -- cache.
-                               , addToFinderCache  :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+                               , addToFinderCache  :: InstalledModule -> InstalledFindResult -> IO ()
                                -- ^ Add a found location to the cache for the module.
-                               , lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+                               , lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
                                -- ^ Look for a location in the cache.
                                , lookupFileCache   :: FilePath -> IO Fingerprint
                                -- ^ Look for the hash of a file in the cache. This should add it to the
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -84,8 +84,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -720,8 +718,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -735,6 +731,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/786cbfb558d3d9aa2469a04035eabad4ea1b0f74

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:49:40 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 07 Oct 2024 10:49:40 -0400
Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass]
 389 commits: JS: establish single source of truth for symbols
Message-ID: <6703f50477cd7_135b984cb8148212c@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC


Commits:
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
79725997 by Alexander Foremny at 2024-10-07T15:48:05+01:00
ttg: StringLiteral -> StringLit (type)

`GHC.Types.SourceText.StringLiteral` does not abbreviate "Literal",
while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` do. To increase
consistency, `StringLiteral` was renamed to `StringLit`.

- - - - -
e54adb38 by Alexander Foremny at 2024-10-07T15:49:22+01:00
ttg: StringLiteral -> SL (data constructor)

`GHC.Types.SourceText.StringLit` has data constructor `StringLiteral`,
while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` have data
constructors `{IL,FL}`. To increase consistency, the data constructor
`StringLiteral` was renamed to `SL`.

- - - - -
c58f68c0 by Alexander Foremny at 2024-10-07T15:49:23+01:00
ttg: use `StringLit` for `HsIsString`

While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional`
carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only
`SourceText` and `FastString`. We will want to parameterize over
`SourceText`, which `StringLit`s will support. So we change `HsIsString`
to carry a `StringLit`.

- - - - -


18 changed files:

- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3c2baf141dd99c5daa0981c76b76916d564958e...c58f68c0b5514b65419aab04cbe685caaa132fdd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3c2baf141dd99c5daa0981c76b76916d564958e...c58f68c0b5514b65419aab04cbe685caaa132fdd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:54:36 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 10:54:36 -0400
Subject: [Git][ghc/ghc][wip/T25281] Try again
Message-ID: <6703f62c6cd85_37633e173810267d4@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
9b876dea by Simon Peyton Jones at 2024-10-07T15:54:13+01:00
Try again

- - - - -


1 changed file:

- compiler/GHC/Runtime/Heap/Inspect.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -1,11 +1,15 @@
-{- # OPTIONS_GHC -Wwarn=incomplete-record-selectors # -}
---     Boo.  The bootstrap compiler falls over on this
+{-# LANGUAGE MagicHash #-}
+
+{-# LANGUAGE CPP #-}
+
+#if __GLASGOW_HASKELL__ > 912
+{-# OPTIONS_GHC -Wwarn=incomplete-record-selectors #-}
 -- This module has a bunch of uses of incomplete record selectors
 -- and it is FAR from obvious that they won't cause crashes.
 -- But I don't want them to kill CI, so the above flag turns
 -- them into warnings
+#endif
 
-{-# LANGUAGE MagicHash #-}
 
 -----------------------------------------------------------------------------
 --



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9b876dea2f738bfda6e54dbad885f218f24f8673

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:55:31 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 10:55:31 -0400
Subject: [Git][ghc/ghc][wip/T25266] Iterating in decideAndPromote
Message-ID: <6703f66370d30_37633e17387427353@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
0af76403 by Simon Peyton Jones at 2024-10-07T15:55:01+01:00
Iterating in decideAndPromote

- - - - -


1 changed file:

- compiler/GHC/Tc/Solver.hs


Changes:

=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1473,9 +1473,28 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
 
              -- mono_tvs0 are all the type variables we
              -- can't quantify over, ignoring the MR
-             mono_tvs0 = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
-                         `unionVarSet` tyCoVarsOfTypes (ctsPreds no_quant)
-                         `unionVarSet` co_var_tvs
+
+             -- At top level: we want to promote tyvars that are
+             --  (a) free in envt (already promoted)
+             --  (b) will be defaulted
+             --  (c) determined by (a) or (b)
+             mono_tvs0
+               | isTopTcLevel tc_lvl
+               = outerLevelTyVars tc_lvl (tyCoVarsOfTypes (ctsPreds post_mr_quant))
+                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
+
+               | otherwise
+
+               = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
+                     -- outerLevelTyVars are free in the envt, so can't quantify them
+                 `unionVarSet` tyCoVarsOfTypes (ctsPreds no_quant)
+                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
+                 `unionVarSet` co_var_tvs
+                     -- If we don't quantify over a constraint in no_quant, we
+                     -- can either not-quantify its free vars (hoping that call
+                     -- sites will fix them) or just ignore it for the purposes
+                     -- of mono_tvs0 (leaving behind a perhaps insoluble residual
+                     -- constraint)
 
              -- Next, use closeWrtFunDeps to find any other variables that are determined
              -- by mono_tvs0 + mr_no_quant, by functional dependencies or equalities.
@@ -1513,10 +1532,13 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
 
        -- In /top-level bindings/ do not quantify over any constraints
        -- that mention a promoted tyvar. See Note [Generalising top-level bindings]
+{-
        ; let final_quant | isTopTcLevel tc_lvl
                          = filterOut (predMentions mono_tvs) post_mr_quant
                          | otherwise
                          = post_mr_quant
+-}
+       ; let final_quant = post_mr_quant
 
        -- Promote the mono_tvs: see Note [Promote monomorphic tyvars]
        ; _ <- promoteTyVarSet mono_tvs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0af764039011d433416d91fee6f444ba63acff1e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 14:56:25 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 10:56:25 -0400
Subject: [Git][ghc/ghc][wip/T25325] Wibbles
Message-ID: <6703f699ddaf7_37633e15435c27774@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25325 at Glasgow Haskell Compiler / GHC


Commits:
c15a7e65 by Simon Peyton Jones at 2024-10-07T15:56:12+01:00
Wibbles

- - - - -


2 changed files:

- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -470,6 +470,8 @@ mkErrorItem ct
              flav = ctFlavour ct
 
        ; (suppress, m_evdest) <- case ctEvidence ct of
+         -- For this `suppress` stuff
+         -- see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
            CtGiven {} -> return (False, Nothing)
            CtWanted { ctev_rewriters = rewriters, ctev_dest = dest }
              -> do { rewriters' <- zonkRewriterSet rewriters


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1444,13 +1444,13 @@ can't be solved.  But not quite all such constraints; see wrinkles.
    it looks only for IrredCt; all insoluble constraints oare put into
    CIrredCan
 
-(IW2) We only treat it as insoluble if it has an empty rewriter set.
-   Otherwise #25325 happens: a Wanted constraint A that is /not/ insoluble
-   rewrites some other Wanted constraint B, so B has A in its rewriter
-   set.  Now B looks insoluble.  The danger is that we'll suppress reporting
-   B becuase of its empty rewriter set; and suppress reporting A because
-   there is an insoluble B lying around.  (This suppression happens in
-   GHC.Tc.Errors.)  Solution: don't treat B as insoluble.
+(IW2) We only treat it as insoluble if it has an empty rewriter set.  (See Note
+   [Wanteds rewrite Wanteds].)  Otherwise #25325 happens: a Wanted constraint A
+   that is /not/ insoluble rewrites some other Wanted constraint B, so B has A
+   in its rewriter set.  Now B looks insoluble.  The danger is that we'll
+   suppress reporting B becuase of its empty rewriter set; and suppress
+   reporting A because there is an insoluble B lying around.  (This suppression
+   happens in GHC.Tc.Errors.mkErrorItem.)  Solution: don't treat B as insoluble.
 
 (IW3) If the Wanted arises from a Given (how can that happen?), don't
    treat it as a Wanted insoluble (obviously).



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:14:29 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 07 Oct 2024 11:14:29 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] determinism: Interface re-export list
 det
Message-ID: <6703fad53da8b_37633e523ab434620@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
77d2c1d9 by Rodrigo Mesquita at 2024-10-07T16:14:16+01:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'SortedAvails', an
abstract newtype that can only be constructed by sorting Avails with
'sortAvails'. This newtype is used by 'DocStructureItem' where 'Avails'
was previously used to ensure the list of avails is deterministically
sorted by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -


17 changed files:

- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Types/Avail.hs
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout
- + testsuite/tests/determinism/T25304/all.T
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/NoExportList.stdout
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
- utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
- utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
- utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex


Changes:

=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -124,7 +124,7 @@ data DocStructureItem
   = DsiSectionHeading !Int !(HsDoc GhcRn)
   | DsiDocChunk !(HsDoc GhcRn)
   | DsiNamedChunkRef !String
-  | DsiExports !Avails
+  | DsiExports !SortedAvails
   | DsiModExport
       !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple
                             -- modules with a single export declaration. E.g.
@@ -136,7 +136,7 @@ data DocStructureItem
                             --
                             -- Invariant: This list of ModuleNames must be
                             -- sorted to guarantee interface file determinism.
-      !Avails
+      !SortedAvails
                             -- ^ Invariant: This list of Avails must be sorted
                             -- to guarantee interface file determinism.
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -160,7 +160,11 @@ mkDocStructureFromExportList mdl import_avails export_list =
       (IEGroup _ level doc, _)         -> DsiSectionHeading level (unLoc doc)
       (IEDoc _ doc, _)                 -> DsiDocChunk (unLoc doc)
       (IEDocNamed _ name, _)           -> DsiNamedChunkRef name
-      (_, avails)                      -> DsiExports (nubAvails avails)
+      (IEThingWith{}, avails)          ->
+        DsiExports $
+          {- For explicit export lists, use the explicit order. It is deterministic by construction -}
+          UnsafeSortedAvails (nubAvails avails)
+      (_, avails)                      -> DsiExports (sortAvails (nubAvails avails))
 
     moduleExport :: ModuleName -- Alias
                  -> Avails
@@ -201,10 +205,10 @@ mkDocStructureFromDecls env all_exports decls =
     avails :: [Located DocStructureItem]
     avails = flip fmap all_exports $ \avail ->
       case M.lookup (availName avail) name_locs of
-        Just loc -> L loc (DsiExports [avail])
+        Just loc -> L loc (DsiExports (sortAvails [avail]))
         -- FIXME: This is just a workaround that we use when handling e.g.
         -- associated data families like in the html-test Instances.hs.
-        Nothing -> noLoc (DsiExports [])
+        Nothing -> noLoc (DsiExports (sortAvails []))
 
         -- This causes the associated data family to be incorrectly documented
         -- separately from its class:


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -518,8 +518,8 @@ mkIfaceImports = map go
     go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
     go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
 
-mkIfaceExports :: [AvailInfo] -> [IfaceExport]  -- Sort to make canonical
-mkIfaceExports = sortAvails
+mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
+mkIfaceExports as = case sortAvails as of SortedAvails sas -> sas
 
 {-
 Note [Original module]


=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -1,5 +1,7 @@
 
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE PatternSynonyms #-}
 --
 -- (c) The University of Glasgow
 --
@@ -20,6 +22,7 @@ module GHC.Types.Avail (
     filterAvails,
     nubAvails,
     sortAvails,
+    SortedAvails(SortedAvails, UnsafeSortedAvails)
   ) where
 
 import GHC.Prelude
@@ -65,6 +68,20 @@ data AvailInfo
 -- | A collection of 'AvailInfo' - several things that are \"available\"
 type Avails = [AvailInfo]
 
+-- | Occurrences of Avails in interface files must be sorted to guarantee
+-- interface file determinism.
+--
+-- To construct 'SortedAvails' using 'UnsafeSortedAvails' you must be sure the
+-- 'Avails' are already sorted. Otherwise, you should use 'sortAvails'.
+newtype SortedAvails = UnsafeSortedAvails Avails
+  deriving newtype (Binary, Outputable, NFData)
+
+-- | Safe matching on 'SortedAvails'
+-- To construct 'SortedAvails' use 'sortAvails'.
+pattern SortedAvails :: Avails -> SortedAvails
+pattern SortedAvails x <- UnsafeSortedAvails x
+{-# COMPLETE SortedAvails #-}
+
 {- Note [Representing pattern synonym fields in AvailInfo]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Record pattern synonym fields cannot be represented using AvailTC like fields of
@@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns)
   | otherwise              = ns
 
 -- | Sort 'Avails'/'AvailInfo's
-sortAvails :: Avails -> Avails
-sortAvails = sortBy stableAvailCmp . map sort_subs
+sortAvails :: Avails -> SortedAvails
+sortAvails = UnsafeSortedAvails . sortBy stableAvailCmp . map sort_subs
   where
     sort_subs :: AvailInfo -> AvailInfo
     sort_subs (Avail n) = Avail n


=====================================
testsuite/tests/determinism/T25304/A.hs
=====================================
@@ -0,0 +1,84 @@
+module A
+  ( MyType(..)
+  ) where
+
+data MyType
+    = A
+    | B
+    | C
+    | D
+    | E
+    | F
+    | G
+    | H
+    | I
+    | J
+    | K
+    | L
+    | M
+    | N
+    | O
+    | P
+    | Q
+    | R
+    | S
+    | T
+    | U
+    | V
+    | W
+    | X
+    | Y
+    | Z
+    | AA
+    | AB
+    | AC
+    | AD
+    | AE
+    | AF
+    | AG
+    | AH
+    | AI
+    | AJ
+    | AK
+    | AL
+    | AM
+    | AN
+    | AO
+    | AP
+    | AQ
+    | AR
+    | AS
+    | AT
+    | AU
+    | AV
+    | AW
+    | AX
+    | AY
+    | AZ
+    | BA
+    | BB
+    | BC
+    | BD
+    | BE
+    | BF
+    | BG
+    | BH
+    | BI
+    | BJ
+    | BK
+    | BL
+    | BM
+    | BN
+    | BO
+    | BP
+    | BQ
+    | BR
+    | BS
+    | BT
+    | BU
+    | BV
+    | BW
+    | BX
+    | BY
+    | BZ
+    | CA


=====================================
testsuite/tests/determinism/T25304/B.hs
=====================================
@@ -0,0 +1,86 @@
+module B
+( MyType
+    ( BA
+    , BB
+    , BC
+    , BD
+    , BE
+    , BF
+    , BG
+    , BH
+    , BI
+    , BJ
+    , BK
+    , BL
+    , BM
+    , BN
+    , BO
+    , BP
+    , BQ
+    , BR
+    , BS
+    , BT
+    , BU
+    , BV
+    , BW
+    , BX
+    , BY
+    , BZ
+    , CA
+    , AA
+    , AB
+    , AC
+    , AD
+    , AE
+    , AF
+    , AG
+    , AH
+    , AI
+    , AJ
+    , AK
+    , AL
+    , AM
+    , AN
+    , AO
+    , AP
+    , AQ
+    , AR
+    , AS
+    , AT
+    , AU
+    , AV
+    , AW
+    , AX
+    , AY
+    , AZ
+    , A
+    , B
+    , C
+    , D
+    , E
+    , F
+    , G
+    , H
+    , I
+    , J
+    , K
+    , L
+    , M
+    , N
+    , O
+    , P
+    , Q
+    , R
+    , S
+    , T
+    , U
+    , V
+    , W
+    , X
+    , Y
+    , Z
+    )
+) where
+
+import A
+


=====================================
testsuite/tests/determinism/T25304/Makefile
=====================================
@@ -0,0 +1,25 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25304:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface A.hi > A_clean_iface
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	'$(TEST_HC)' $(TEST_HC_OPTS) -dinitial-unique=16777215 -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp
+	'$(TEST_HC)' --show-iface A.hi > A_dirty_iface
+	'$(TEST_HC)' --show-iface B.hi > B_dirty_iface
+	diff A_clean_iface A_dirty_iface
+	diff B_clean_iface B_dirty_iface
+
+T25304a:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	# The goal is to see the export list in the documentation structure of the
+	# interface file preserves the order used in the source
+	cat B_clean_iface | grep -A7 "documentation structure"
+


=====================================
testsuite/tests/determinism/T25304/T25304a.stdout
=====================================
@@ -0,0 +1,8 @@
+       documentation structure:
+         avails:
+           [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH,
+                     A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS,
+                     A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC,
+                     A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN,
+                     A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY,
+                     A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L,


=====================================
testsuite/tests/determinism/T25304/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304'])
+test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a'])


=====================================
testsuite/tests/showIface/DocsInHiFileTH.stdout
=====================================
@@ -187,7 +187,7 @@ docs:
          avails:
            [i]
          avails:
-           [WD11{WD11, WD11Bool, WD11Int, WD11Foo}]
+           [WD11{WD11, WD11Bool, WD11Foo, WD11Int}]
          avails:
            [WD13{WD13}]
          avails:
@@ -221,11 +221,11 @@ docs:
          avails:
            [Pretty{Pretty, prettyPrint}]
          avails:
-           [Corge{Corge, runCorge, Corge}]
+           [Corge{Corge, Corge, runCorge}]
          avails:
-           [Quuz{Quuz, quuz1_a, Quuz}]
+           [Quuz{Quuz, Quuz, quuz1_a}]
          avails:
-           [Quux{Quux, Quux2, Quux1}]
+           [Quux{Quux, Quux1, Quux2}]
          avails:
            [Tup2]
          avails:


=====================================
testsuite/tests/showIface/NoExportList.stdout
=====================================
@@ -32,7 +32,7 @@ docs:
 -- Actually we have only one type.
            identifiers:
          avails:
-           [R{R, fβ, fα, R}]
+           [R{R, R, fα, fβ}]
          section heading, level 1:
            text:
              -- * Functions


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -201,7 +201,14 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
   -- See Note [Exporting built-in items]
   let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") [])
       bonus_ds mods
-        | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods
+        | mdl == gHC_PRIM =
+            [ builtinTys
+            , DsiExports $
+                {- Haddock does not want to sort avails, the order should be derived from the source.
+                   In this particular case, sorting funAvail would be a no-op anyway. -}
+                UnsafeSortedAvails
+                  funAvail
+            ] <> mods
         | otherwise = mods
 
   let
@@ -461,11 +468,11 @@ mkExportItems
             Just hsDoc' -> do
               doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc'
               pure [ExportDoc doc]
-        DsiExports avails ->
+        DsiExports (SortedAvails avails) ->
           -- TODO: We probably don't need nubAvails here.
           -- mkDocStructureFromExportList already uses it.
           concat <$> traverse availExport (nubAvails avails)
-        DsiModExport mod_names avails -> do
+        DsiModExport mod_names (SortedAvails avails) -> do
           -- only consider exporting a module if we are sure we are really
           -- exporting the whole module and not some subset.
           (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names)


=====================================
utils/haddock/html-test/ref/BundledPatterns2.html
=====================================
@@ -96,14 +96,6 @@
 	      >wherepattern LR :: a ->  BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/77d2c1d9b81aca0ca75432888a8068da2b306a87

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:18:20 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 07 Oct 2024 11:18:20 -0400
Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 25 commits:
 SpecConstr: Introduce a separate argument limit for forced specs.
Message-ID: <6703fbbccbbe5_37633e3f9030350c2@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
6d11c698 by Matthew Pickering at 2024-10-07T16:17:40+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
1e655560 by Matthew Pickering at 2024-10-07T16:17:40+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
0055cea2 by Rodrigo Mesquita at 2024-10-07T16:17:41+01:00
Add test for #25300

- - - - -
1a760d4d by Rodrigo Mesquita at 2024-10-07T16:17:41+01:00
exceptions: Improve the message layout as per #285

This commit fixes the layout of the additional information included when
displaying an exception, namely the type of the exception.

It also fixes the default handler's heading message to work well
together with the improved display message of SomeException.

CLC proposal#285

- - - - -
90ea7b3d by Rodrigo Mesquita at 2024-10-07T16:17:41+01:00
Display type and callstack of exception on handler

This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.

At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.

However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).

This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.

The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.

Discussion of the ammendment is part of CLC#285.

- - - - -
f75300fa by Rodrigo Mesquita at 2024-10-07T16:17:55+01:00
Remove redundant CallStack from exceptions

Before the exception backtraces proposal was implemented, ErrorCall
accumulated its own callstack via HasCallStack constraints, but
ExceptionContext is now accumulated automatically.

The original ErrorCall mechanism is now redundant and we get a duplicate
CallStack

Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall

CLC proposal#285

Fixes #25283

- - - - -
fc354973 by Rodrigo Mesquita at 2024-10-07T16:17:58+01:00
Freeze call stack in error throwing functions

CLC proposal#285

- - - - -
9a0c2be6 by Rodrigo Mesquita at 2024-10-07T16:17:59+01:00
De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too,
which was missing.

- - - - -
b4bdb610 by Rodrigo Mesquita at 2024-10-07T16:17:59+01:00
Re-export NoBacktrace from Control.Exception

This was originally proposed and accepted in section
    "2.7   Capturing Backtraces on Exceptions"
of the CLC proposal for exception backtraces.

However, the implementation missed this re-export, which this commit now
fixes.

- - - - -
8670c3f3 by Rodrigo Mesquita at 2024-10-07T16:17:59+01:00
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Utils/Panic/Plain.hs
- configure.ac
- docs/users_guide/using-optimisation.rst
- ghc/GHCi/UI/Monad.hs
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/GHC/Exception.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Stack.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/encoding004.stdout
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe6c5f626f06b6f72a61f8b0086fecb6cbdf02c0...8670c3f3772121d5c430184204d155f241c808a2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe6c5f626f06b6f72a61f8b0086fecb6cbdf02c0...8670c3f3772121d5c430184204d155f241c808a2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:34:27 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 11:34:27 -0400
Subject: [Git][ghc/ghc][wip/T25325] Spelling errors
Message-ID: <6703ff838405a_37633e783d7c40130@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25325 at Glasgow Haskell Compiler / GHC


Commits:
904852da by Simon Peyton Jones at 2024-10-07T16:34:12+01:00
Spelling errors

- - - - -


1 changed file:

- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1327,7 +1327,7 @@ insolubleWC (WC { wc_impl = implics, wc_simple = simples, wc_errors = errors })
 insolubleWantedCt :: Ct -> Bool
 -- Definitely insoluble, in particular /excluding/ type-hole constraints
 -- Namely:
---   a) an insoluble constraint as per 'insolubleirredCt', i.e. either
+--   a) an insoluble constraint as per 'insolubleIrredCt', i.e. either
 --        - an insoluble equality constraint (e.g. Int ~ Bool), or
 --        - a custom type error constraint, TypeError msg :: Constraint
 --   b) that does not arise from a Given or a Wanted/Wanted fundep interaction
@@ -1341,7 +1341,7 @@ insolubleWantedCt ct
   , insolubleIrredCt ir_ct
       -- It's insoluble
   , isEmptyRewriterSet rewriters
-      -- rewriters; see (IW2) in Note [Insoluble Wanteds]
+      -- It has no rewriters; see (IW2) in Note [Insoluble Wanteds]
   , not (isGivenLoc loc)
       -- isGivenLoc: see (IW3) in Note [Insoluble Wanteds]
   , not (isWantedWantedFunDepOrigin (ctLocOrigin loc))
@@ -1441,14 +1441,14 @@ can't be solved.  But not quite all such constraints; see wrinkles.
 
 (IW1) insolubleWantedCt is tuned for application /after/ constraint
    solving i.e. assuming canonicalisation has been done.  That's why
-   it looks only for IrredCt; all insoluble constraints oare put into
+   it looks only for IrredCt; all insoluble constraints are put into
    CIrredCan
 
 (IW2) We only treat it as insoluble if it has an empty rewriter set.  (See Note
    [Wanteds rewrite Wanteds].)  Otherwise #25325 happens: a Wanted constraint A
    that is /not/ insoluble rewrites some other Wanted constraint B, so B has A
    in its rewriter set.  Now B looks insoluble.  The danger is that we'll
-   suppress reporting B becuase of its empty rewriter set; and suppress
+   suppress reporting B because of its empty rewriter set; and suppress
    reporting A because there is an insoluble B lying around.  (This suppression
    happens in GHC.Tc.Errors.mkErrorItem.)  Solution: don't treat B as insoluble.
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/904852da052e0f3b5df8b2c979fa07105f5f5227

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:38:13 2024
From: gitlab at gitlab.haskell.org (jeffrey young (@doyougnu))
Date: Mon, 07 Oct 2024 11:38:13 -0400
Subject: [Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef]
 ghc-internal: hide linkerOptimistic in MiscFlags
Message-ID: <67040065eb266_37633e8fdcc04176@gitlab.mail>



jeffrey young pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
6893b080 by doyougnu at 2024-10-07T11:37:50-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -


5 changed files:

- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,7 +162,8 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
-    , linkerOptimistic      :: Bool
+    -- TODO: #25354 uncomment to expose this flag to base.
+    -- , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9106,7 +9106,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -12148,7 +12148,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -9330,7 +9330,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -9106,7 +9106,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6893b080b065ebfc5a97333cb767ecc96980e2c4

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:45:46 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 07 Oct 2024 11:45:46 -0400
Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass]
 ttg: use `StringLit` for `HsIsString`
Message-ID: <6704022a8b924_3da464bf540524f8@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC


Commits:
bb6016cb by Alexander Foremny at 2024-10-07T16:45:08+01:00
ttg: use `StringLit` for `HsIsString`

While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional`
carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only
`SourceText` and `FastString`. We will want to parameterize over
`SourceText`, which `StringLit`s will support. So we change `HsIsString`
to carry a `StringLit`.

- - - - -


11 changed files:

- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Types/SourceText.hs
- compiler/Language/Haskell/Syntax/Lit.hs


Changes:

=====================================
compiler/GHC/Builtin/Utils.hs
=====================================
@@ -271,7 +271,7 @@ ghcPrimWarns = WarnSome
   []
   where
     mk_txt msg =
-      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText msg Nothing) []]
+      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (SL NoSourceText msg Nothing) []]
     mk_decl_dep (occ, msg) = (occ, mk_txt msg)
 
 ghcPrimFixities :: [(OccName,Fixity)]


=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -227,9 +227,9 @@ instance OutputableBndrId p
         = ppr val <+> (whenPprDebug (parens (pprXOverLit (ghcPass @p) ext)))
 
 instance Outputable OverLitVal where
-  ppr (HsIntegral i)     = pprWithSourceText (il_text i) (integer (il_value i))
-  ppr (HsFractional f)   = ppr f
-  ppr (HsIsString st s)  = pprWithSourceText st (pprHsString s)
+  ppr (HsIntegral i)   = pprWithSourceText (il_text i) (integer (il_value i))
+  ppr (HsFractional f) = ppr f
+  ppr (HsIsString s)   = pprWithSourceText (sl_st s) (pprHsString (sl_fs s))
 
 -- | pmPprHsLit pretty prints literals and is used when pretty printing pattern
 -- match warnings. All are printed the same (i.e., without hashes if they are


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -380,9 +380,9 @@ mkRecStmt anns stmts  = (emptyRecStmt' anns :: StmtLR (GhcPass idL) GhcPs bodyR)
                              { recS_stmts = stmts }
 
 
-mkHsIntegral     i  = OverLit noExtField (HsIntegral       i)
-mkHsFractional   f  = OverLit noExtField (HsFractional     f)
-mkHsIsString src s  = OverLit noExtField (HsIsString   src s)
+mkHsIntegral     i  = OverLit noExtField (HsIntegral           i)
+mkHsFractional   f  = OverLit noExtField (HsFractional         f)
+mkHsIsString src s  = OverLit noExtField (HsIsString   (SL src s Nothing))
 
 mkHsDo     ctxt stmts      = HsDo noAnn ctxt stmts
 mkHsDoAnns ctxt stmts anns = HsDo anns  ctxt stmts


=====================================
compiler/GHC/HsToCore/Match.hs
=====================================
@@ -32,6 +32,7 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
     ( FractionalLit,
       IntegralLit(il_value),
+      StringLit(sl_fs),
       negateFractionalLit,
       integralFractionalLit )
 import GHC.Driver.DynFlags
@@ -1291,8 +1292,8 @@ patGroup _ (NPat _ (L _ (OverLit {ol_val=oval})) mb_neg _) =
     (HsFractional f, is_neg)
       | is_neg    -> PgN $! negateFractionalLit f
       | otherwise -> PgN f
-    (HsIsString _ s, _) -> assert (isNothing mb_neg) $
-                            PgOverS s
+    (HsIsString s, _) -> assert (isNothing mb_neg) $
+                            PgOverS (sl_fs s)
 patGroup _ (NPlusKPat _ _ (L _ (OverLit {ol_val=oval})) _ _ _) =
   case oval of
    HsIntegral i -> PgNpK (il_value i)


=====================================
compiler/GHC/HsToCore/Match/Literal.hs
=====================================
@@ -592,7 +592,7 @@ tidyNPat (OverLit (OverLitTc False _ ty) val) mb_neg _eq outer_ty
 
     mb_str_lit :: Maybe FastString
     mb_str_lit = case (mb_neg, val) of
-                   (Nothing, HsIsString _ s) -> Just s
+                   (Nothing, HsIsString s) -> Just (sl_fs s)
                    _ -> Nothing
 
 tidyNPat over_lit mb_neg eq outer_ty


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -3058,7 +3058,7 @@ repOverloadedLiteral (OverLit { ol_val = val})
 mk_lit :: OverLitVal -> MetaM (HsLit GhcRn)
 mk_lit (HsIntegral i)     = mk_integer  (il_value i)
 mk_lit (HsFractional f)   = mk_rational f
-mk_lit (HsIsString _ s)   = mk_string   s
+mk_lit (HsIsString s)     = mk_string   (sl_fs s)
 
 repRdrName :: RdrName -> MetaM (Core TH.Name)
 repRdrName rdr_name = do


=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -4765,5 +4765,5 @@ tyLitFromLit _ = Nothing
 
 tyLitFromOverloadedLit :: OverLitVal -> Maybe (HsTyLit GhcRn)
 tyLitFromOverloadedLit (HsIntegral n) = Just $ HsNumTy NoSourceText (il_value n)
-tyLitFromOverloadedLit (HsIsString _ s) = Just $ HsStrTy NoSourceText s
+tyLitFromOverloadedLit (HsIsString s) = Just $ HsStrTy NoSourceText (sl_fs s)
 tyLitFromOverloadedLit HsFractional{} = Nothing


=====================================
compiler/GHC/Tc/Utils/Instantiate.hs
=====================================
@@ -817,7 +817,7 @@ mkOverLit (HsFractional r)
   = do  { rat_ty <- tcMetaTy rationalTyConName
         ; return (HsRat noExtField r rat_ty) }
 
-mkOverLit (HsIsString src s) = return (HsString src s)
+mkOverLit (HsIsString s) = return (HsString (sl_st s) (sl_fs s))
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -2363,7 +2363,7 @@ shortCutLit platform val res_ty
   = case val of
       HsIntegral int_lit    -> go_integral int_lit
       HsFractional frac_lit -> go_fractional frac_lit
-      HsIsString s src      -> go_string   s src
+      HsIsString s_lit      -> go_string (sl_st s_lit) (sl_fs s_lit)
   where
     go_integral int@(IL src neg i)
       | isIntTy res_ty  && platformInIntRange  platform i


=====================================
compiler/GHC/Types/SourceText.hs
=====================================
@@ -317,5 +317,8 @@ data StringLit = SL
 instance Eq StringLit where
   (SL _ a _) == (SL _ b _) = a == b
 
+instance Ord StringLit where
+  (SL _ a _) `compare` (SL _ b _) = a `lexicalCompareFS` b
+
 instance Outputable StringLit where
   ppr sl = pprWithSourceText (sl_st sl) (doubleQuotes $ ftext $ sl_fs sl)


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -20,10 +20,10 @@ module Language.Haskell.Syntax.Lit where
 
 import Language.Haskell.Syntax.Extension
 
-import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText)
+import GHC.Types.SourceText (IntegralLit, FractionalLit, StringLit)
 import GHC.Core.Type (Type)
 
-import GHC.Data.FastString (FastString, lexicalCompareFS)
+import GHC.Data.FastString (FastString)
 
 import Data.ByteString (ByteString)
 import Data.Data hiding ( Fixity )
@@ -124,24 +124,24 @@ data HsOverLit p
 -- the following
 -- | Overloaded Literal Value
 data OverLitVal
-  = HsIntegral   !IntegralLit            -- ^ Integer-looking literals;
-  | HsFractional !FractionalLit          -- ^ Frac-looking literals
-  | HsIsString   !SourceText !FastString -- ^ String-looking literals
+  = HsIntegral   !IntegralLit   -- ^ Integer-looking literals;
+  | HsFractional !FractionalLit -- ^ Frac-looking literals
+  | HsIsString   !StringLit     -- ^ String-looking literals
   deriving Data
 
 instance Eq OverLitVal where
   (HsIntegral   i1)   == (HsIntegral   i2)   = i1 == i2
   (HsFractional f1)   == (HsFractional f2)   = f1 == f2
-  (HsIsString _ s1)   == (HsIsString _ s2)   = s1 == s2
+  (HsIsString   s1)   == (HsIsString   s2)   = s1 == s2
   _                   == _                   = False
 
 instance Ord OverLitVal where
   compare (HsIntegral i1)     (HsIntegral i2)     = i1 `compare` i2
   compare (HsIntegral _)      (HsFractional _)    = LT
-  compare (HsIntegral _)      (HsIsString _ _)    = LT
+  compare (HsIntegral _)      (HsIsString   _)    = LT
   compare (HsFractional f1)   (HsFractional f2)   = f1 `compare` f2
   compare (HsFractional _)    (HsIntegral   _)    = GT
-  compare (HsFractional _)    (HsIsString _ _)    = LT
-  compare (HsIsString _ s1)   (HsIsString _ s2)   = s1 `lexicalCompareFS` s2
-  compare (HsIsString _ _)    (HsIntegral   _)    = GT
-  compare (HsIsString _ _)    (HsFractional _)    = GT
+  compare (HsFractional _)    (HsIsString   _)    = LT
+  compare (HsIsString   s1)   (HsIsString   s2)   = s1 `compare` s2
+  compare (HsIsString   _)    (HsIntegral   _)    = GT
+  compare (HsIsString   _)    (HsFractional _)    = GT



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:46:06 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 11:46:06 -0400
Subject: [Git][ghc/ghc][wip/only_job] 14 commits: base: Add `HasCallStack`
 constraint to `ioError`
Message-ID: <6704023eb56e3_3da464bc444529c7@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
67bb8021 by Matthew Pickering at 2024-10-07T16:42:55+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Unit/Finder.hs
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/using-warnings.rst
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/openFile002.stderr-mingw32
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile001.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking001.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/T15349.stderr
- libraries/base/tests/T9586.hs
- libraries/base/tests/list001.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/273c2df446707185fbc2125fc1a6505d3236266f...67bb80210c19630b7297d75ce9e21745ec486c05

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/273c2df446707185fbc2125fc1a6505d3236266f...67bb80210c19630b7297d75ce9e21745ec486c05
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 15:59:10 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 11:59:10 -0400
Subject: [Git][ghc/ghc][wip/only_job] ci: Add support for ONLY_JOBS variable
 to trigger any validation pipeline
Message-ID: <6704054e935b8_3da4644093b857949@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
00fc431a by Matthew Pickering at 2024-10-07T16:58:33+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -541,8 +541,8 @@ data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
                              }
 
 -- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
-emptyRules :: OnOffRules
-emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
+emptyRules :: String -> OnOffRules
+emptyRules jobName = OnOffRules (ValidateOnly jobName (S.fromList [FullCI])) OnSuccess
 
 -- When to run the job
 data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
@@ -559,10 +559,10 @@ onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
 onlyValidateRule r  = modifyValidateRules (const (S.singleton r))
 
 removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
-removeValidateRule r = modifyValidateRules (S.delete r)
+removeValidateRule v = modifyValidateRules (S.delete v)
 
 modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
-modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules f (OnOffRules (ValidateOnly s rs) m) = OnOffRules (ValidateOnly s (f rs)) m
 modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
 
 manualRule :: OnOffRules -> OnOffRules
@@ -575,13 +575,13 @@ enumRules :: OnOffRules -> [OnOffRule]
 enumRules (OnOffRules r _) = rulesList
   where
     rulesList = case r of
-                  ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+                  ValidateOnly s rs -> [OnOffRule On (ValidateOnly s rs)
                                     , OnOffRule Off ReleaseOnly
                                     , OnOffRule Off Nightly ]
-                  Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  Nightly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                              , OnOffRule Off ReleaseOnly
                              , OnOffRule On Nightly ]
-                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                                  , OnOffRule On ReleaseOnly
                                  , OnOffRule Off Nightly ]
 
@@ -619,11 +619,12 @@ or_all rs = intercalate " || " (map parens rs)
 -- run the job.
 data Rule = ReleaseOnly  -- ^ Only run this job in a release pipeline
           | Nightly      -- ^ Only run this job in the nightly pipeline
-          | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+          | ValidateOnly String (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
           deriving (Show, Ord, Eq)
 
 data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
+          | FastCI       -- ^ Run this job on every validation pipeline
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
@@ -631,7 +632,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
-          deriving (Show, Enum, Bounded, Ord, Eq)
+          deriving (Show, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
 -- expression language.
@@ -644,25 +645,43 @@ _false = "\"disabled\" != \"disabled\""
 
 -- Convert the state of the rule into a string that gitlab understand.
 ruleString :: OnOff -> Rule -> String
-ruleString On (ValidateOnly vs) =
-  case S.toList vs of
-    [] -> true
-    conds -> or_all (map validateRuleString conds)
+ruleString On (ValidateOnly only_job_name vs) =
+  let conds = S.toList vs
+      empty_only_job = envVarNull "ONLY_JOBS"
+      run_cond = case conds of
+                  [] -> _false
+                  cs -> or_all (map validateRuleString conds)
+      escape :: String -> String
+      escape = concatMap (\c -> if c == '+' then "\\+" else [c])
+
+  in
+    or_all  [
+    -- 1. Case when ONLY_JOBS is set
+      and_all [ "$ONLY_JOBS", "$ONLY_JOBS =~ /.*\\b" ++  escape only_job_name ++ "\\b.*/" ]
+    -- 2. Case when ONLY_JOBS is null
+    , and_all [ empty_only_job, run_cond ]
+    ]
 ruleString Off (ValidateOnly {}) = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
-ruleString Off Nightly = "$NIGHTLY == null"
+ruleString Off Nightly = envVarNull "NIGHTLY"
 
 labelString :: String -> String
 labelString s =  "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
 
 branchStringExact :: String -> String
-branchStringExact s = "$CI_COMMIT_BRANCH == \"" ++ s ++ "\""
+branchStringExact s = envVarString "CI_COMMIT_BRANCH" s
 
 branchStringLike :: String -> String
 branchStringLike s = "$CI_COMMIT_BRANCH =~ /" ++ s ++ "/"
 
+envVarString :: String -> String -> String
+envVarString var s = "$" ++ var ++ " == \"" ++ s ++ "\""
+
+envVarNull :: String ->  String
+envVarNull var = "$" ++ var ++ " == null"
+
 
 validateRuleString :: ValidateRule -> String
 validateRuleString FullCI = or_all ([ labelString "full-ci"
@@ -670,6 +689,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
                                     , branchStringExact "master"
                                     , branchStringLike "ghc-[0-9]+\\.[0-9]+"
                                     ])
+validateRuleString FastCI = true
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
@@ -725,7 +745,7 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} }
   where
     jobPlatform = (arch, opsys)
 
-    jobRules = emptyRules
+    jobRules = emptyRules jobName
 
     jobName = testEnv arch opsys buildConfig
 
@@ -917,7 +937,7 @@ perfProfilingJobTag arch opsys j = j { jobTags = [ runnerPerfTag arch opsys ] }
 -- | Mark the validate job to run in fast-ci mode
 -- This is default way, to enable all jobs you have to apply the `full-ci` label.
 fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
+fastCI = onlyRule FastCI
 
 -- | Mark a group of jobs as allowed to fail.
 allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -934,8 +954,10 @@ onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
 
 -- | Don't run the validate job, normally used to alleviate CI load by marking
 -- jobs which are unlikely to fail (ie different linux distros)
+--
+-- These jobs can still be triggered by using the ONLY_JOBS environment variable
 disableValidate :: JobGroup Job -> JobGroup Job
-disableValidate st = st { v = Nothing }
+disableValidate = modifyValidateJobs (removeValidateJobRule FastCI . removeValidateJobRule FullCI)
 
 data NamedJob a = NamedJob { name :: String, jobInfo :: a } deriving (Show, Functor)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-darwin-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -66,6 +66,131 @@
       "TEST_ENV": "aarch64-darwin-validate"
     }
   },
+  "aarch64-linux-alpine3_18-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-alpine3_18-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-alpine3_18-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-alpine3_18:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-alpine3_18-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-alpine3_18-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-alpine3_18-validate"
+    }
+  },
+  "aarch64-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-deb10-validate"
+    }
+  },
   "aarch64-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -103,7 +228,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -165,7 +290,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\+llvm\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -190,6 +315,68 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-deb10-validate"
+    }
+  },
   "i386-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -227,7 +414,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4745,7 +4932,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-darwin-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4777,18 +4964,18 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-linux-alpine3_12-validate+fully_static": {
+  "x86_64-linux-alpine3_12-int_native-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": false,
+    "allow_failure": true,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4814,7 +5001,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-int_native-validate\\+fully_static\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4830,17 +5017,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static",
       "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
       "BUILD_FLAVOUR": "validate+fully_static",
       "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
+      "TEST_ENV": "x86_64-linux-alpine3_12-int_native-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4851,7 +5038,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4861,14 +5048,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4877,7 +5064,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4894,16 +5081,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4914,7 +5101,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4924,14 +5111,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4940,9 +5127,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\+fully_static\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -4957,17 +5143,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
+      "BUILD_FLAVOUR": "validate+fully_static",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4978,7 +5164,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5004,9 +5190,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5022,16 +5207,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
       "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
       "CROSS_TARGET": "wasm32-wasi",
       "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
+  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5042,7 +5227,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5052,14 +5237,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5068,8 +5253,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5084,18 +5270,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
-      "CROSS_TARGET": "aarch64-linux-gnu",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5106,7 +5291,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5116,14 +5301,78 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+    }
+  },
+  "x86_64-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5132,7 +5381,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5148,19 +5397,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CONFIGURE_WRAPPER": "emconfigure",
-      "CROSS_EMULATOR": "js-emulator",
-      "CROSS_TARGET": "javascript-unknown-ghcjs",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-validate"
     }
   },
-  "x86_64-linux-deb12-int_native-validate": {
+  "x86_64-linux-centos7-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5171,7 +5418,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
+        "ghc-x86_64-linux-centos7-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5181,14 +5428,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-centos7-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5197,7 +5444,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-centos7-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5213,16 +5460,18 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate",
+      "BROKEN_TESTS": "T22012",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=no-sphinx",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
+      "TEST_ENV": "x86_64-linux-centos7-validate"
     }
   },
-  "x86_64-linux-deb12-no_tntc-validate": {
+  "x86_64-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5233,7 +5482,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5243,14 +5492,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5259,9 +5508,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5277,15 +5525,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate"
     }
   },
-  "x86_64-linux-deb12-numa-slow-validate": {
+  "x86_64-linux-deb10-validate+debug_info": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5296,7 +5544,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate+debug_info.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5306,14 +5554,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5322,7 +5570,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\+debug_info\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5339,16 +5587,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
-      "BUILD_FLAVOUR": "slow-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate+debug_info"
     }
   },
-  "x86_64-linux-deb12-unreg-validate": {
+  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5359,7 +5606,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5369,14 +5616,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5385,7 +5632,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-cross_aarch64-linux-gnu-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5402,15 +5649,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
+      "CROSS_TARGET": "aarch64-linux-gnu",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb12-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5421,7 +5670,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5431,14 +5680,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5447,7 +5696,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5463,16 +5712,19 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_WRAPPER": "emconfigure",
+      "CROSS_EMULATOR": "js-emulator",
+      "CROSS_TARGET": "javascript-unknown-ghcjs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
-  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+  "x86_64-linux-deb11-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5483,7 +5735,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "ghc-x86_64-linux-deb11-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5493,14 +5745,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5509,7 +5761,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5526,15 +5778,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
-      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
-      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb11-validate"
     }
   },
-  "x86_64-linux-deb12-validate+llvm": {
+  "x86_64-linux-deb12-int_native-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5545,7 +5797,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5571,7 +5823,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-int_native-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5587,27 +5839,27 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
-      "BUILD_FLAVOUR": "validate+llvm",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
     }
   },
-  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+  "x86_64-linux-deb12-no_tntc-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": true,
+    "allow_failure": false,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5634,7 +5886,7 @@
     "rules": [
       {
         "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-no_tntc-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "manual"
       }
     ],
@@ -5651,17 +5903,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
     }
   },
-  "x86_64-linux-deb12-zstd-validate": {
+  "x86_64-linux-deb12-numa-slow-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5672,7 +5922,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5698,7 +5948,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-numa-slow-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5715,15 +5965,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
+      "BUILD_FLAVOUR": "slow-validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
-  "x86_64-linux-fedora33-release": {
+  "x86_64-linux-deb12-release-perf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5734,7 +5985,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "ghc-x86_64-linux-deb12-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5744,14 +5995,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "key": "x86_64-linux-deb12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5760,7 +6011,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-release\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5773,18 +6024,1018 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-linux"
+      "x86_64-linux-perf"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-release",
       "BUILD_FLAVOUR": "release",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "LLC": "/bin/false",
-      "OPT": "/bin/false",
-      "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-fedora33-release"
+      "RUNTEST_ARGS": " --config perf_path=perf",
+      "TEST_ENV": "x86_64-linux-deb12-release"
+    }
+  },
+  "x86_64-linux-deb12-unreg-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-unreg-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+boot_nonmoving_gc\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
+      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
+      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+    }
+  },
+  "x86_64-linux-deb12-validate+llvm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+llvm\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
+      "BUILD_FLAVOUR": "validate+llvm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+    }
+  },
+  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+thread_sanitizer_cmm\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=none",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+    }
+  },
+  "x86_64-linux-deb12-zstd-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-zstd-validate\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+    }
+  },
+  "x86_64-linux-deb9-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb9-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb9-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb9-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb9-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb9-validate"
+    }
+  },
+  "x86_64-linux-fedora33-release": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-release-hackage": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--haddock-for-hackage",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-validate+debug_info": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+    }
+  },
+  "x86_64-linux-fedora38-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora38-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora38-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora38-validate"
+    }
+  },
+  "x86_64-linux-rocky8-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-rocky8-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-rocky8-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-rocky8:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-rocky8-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-rocky8-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-rocky8-validate"
+    }
+  },
+  "x86_64-linux-ubuntu18_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu18_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu18_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu18_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu18_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu18_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu18_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu20_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu20_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu20_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu20_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu20_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu20_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu22_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu22_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu22_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu22_04-validate"
+    }
+  },
+  "x86_64-windows-int_native-validate": {
+    "after_script": [
+      "bash .gitlab/ci.sh save_cache",
+      "bash .gitlab/ci.sh save_test_output",
+      "bash .gitlab/ci.sh clean"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-windows-int_native-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "no-caching",
+      "paths": []
+    },
+    "dependencies": [],
+    "image": null,
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-int_native-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "bash .gitlab/ci.sh setup",
+      "bash .gitlab/ci.sh configure",
+      "bash .gitlab/ci.sh build_hadrian",
+      "bash .gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "new-x86_64-windows"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CABAL_INSTALL_VERSION": "3.10.2.0",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "GHC_VERSION": "9.6.4",
+      "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LANG": "en_US.UTF-8",
+      "MSYSTEM": "CLANG64",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-windows-int_native-validate"
     }
   },
   "x86_64-windows-validate": {
@@ -5820,7 +7071,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/00fc431ae5fa156a90ceada11e79f9f38bac90dc

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 16:10:52 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 12:10:52 -0400
Subject: [Git][ghc/ghc][wip/only_job] ci: Add support for ONLY_JOBS variable
 to trigger any validation pipeline
Message-ID: <6704080c56a37_3da4643c5f3c59240@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
ae0ab8d7 by Matthew Pickering at 2024-10-07T17:10:12+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -541,8 +541,8 @@ data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
                              }
 
 -- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
-emptyRules :: OnOffRules
-emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
+emptyRules :: String -> OnOffRules
+emptyRules jobName = OnOffRules (ValidateOnly jobName (S.fromList [FullCI])) OnSuccess
 
 -- When to run the job
 data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
@@ -559,10 +559,10 @@ onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
 onlyValidateRule r  = modifyValidateRules (const (S.singleton r))
 
 removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
-removeValidateRule r = modifyValidateRules (S.delete r)
+removeValidateRule v = modifyValidateRules (S.delete v)
 
 modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
-modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules f (OnOffRules (ValidateOnly s rs) m) = OnOffRules (ValidateOnly s (f rs)) m
 modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
 
 manualRule :: OnOffRules -> OnOffRules
@@ -575,13 +575,13 @@ enumRules :: OnOffRules -> [OnOffRule]
 enumRules (OnOffRules r _) = rulesList
   where
     rulesList = case r of
-                  ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+                  ValidateOnly s rs -> [OnOffRule On (ValidateOnly s rs)
                                     , OnOffRule Off ReleaseOnly
                                     , OnOffRule Off Nightly ]
-                  Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  Nightly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                              , OnOffRule Off ReleaseOnly
                              , OnOffRule On Nightly ]
-                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                                  , OnOffRule On ReleaseOnly
                                  , OnOffRule Off Nightly ]
 
@@ -619,11 +619,12 @@ or_all rs = intercalate " || " (map parens rs)
 -- run the job.
 data Rule = ReleaseOnly  -- ^ Only run this job in a release pipeline
           | Nightly      -- ^ Only run this job in the nightly pipeline
-          | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+          | ValidateOnly String (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
           deriving (Show, Ord, Eq)
 
 data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
+          | FastCI       -- ^ Run this job on every validation pipeline
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
@@ -631,7 +632,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
-          deriving (Show, Enum, Bounded, Ord, Eq)
+          deriving (Show, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
 -- expression language.
@@ -644,25 +645,43 @@ _false = "\"disabled\" != \"disabled\""
 
 -- Convert the state of the rule into a string that gitlab understand.
 ruleString :: OnOff -> Rule -> String
-ruleString On (ValidateOnly vs) =
-  case S.toList vs of
-    [] -> true
-    conds -> or_all (map validateRuleString conds)
+ruleString On (ValidateOnly only_job_name vs) =
+  let conds = S.toList vs
+      empty_only_job = envVarNull "ONLY_JOBS"
+      run_cond = case conds of
+                  [] -> _false
+                  cs -> or_all (map validateRuleString conds)
+      escape :: String -> String
+      escape = concatMap (\c -> if c == '+' then "\\+" else [c])
+
+  in
+    or_all  [
+    -- 1. Case when ONLY_JOBS is set
+      and_all [ "$ONLY_JOBS", "$ONLY_JOBS =~ /.*\\b" ++  escape only_job_name ++ "(?=\\s|$).*/" ]
+    -- 2. Case when ONLY_JOBS is null
+    , and_all [ empty_only_job, run_cond ]
+    ]
 ruleString Off (ValidateOnly {}) = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
-ruleString Off Nightly = "$NIGHTLY == null"
+ruleString Off Nightly = envVarNull "NIGHTLY"
 
 labelString :: String -> String
 labelString s =  "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
 
 branchStringExact :: String -> String
-branchStringExact s = "$CI_COMMIT_BRANCH == \"" ++ s ++ "\""
+branchStringExact s = envVarString "CI_COMMIT_BRANCH" s
 
 branchStringLike :: String -> String
 branchStringLike s = "$CI_COMMIT_BRANCH =~ /" ++ s ++ "/"
 
+envVarString :: String -> String -> String
+envVarString var s = "$" ++ var ++ " == \"" ++ s ++ "\""
+
+envVarNull :: String ->  String
+envVarNull var = "$" ++ var ++ " == null"
+
 
 validateRuleString :: ValidateRule -> String
 validateRuleString FullCI = or_all ([ labelString "full-ci"
@@ -670,6 +689,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
                                     , branchStringExact "master"
                                     , branchStringLike "ghc-[0-9]+\\.[0-9]+"
                                     ])
+validateRuleString FastCI = true
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
@@ -725,7 +745,7 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} }
   where
     jobPlatform = (arch, opsys)
 
-    jobRules = emptyRules
+    jobRules = emptyRules jobName
 
     jobName = testEnv arch opsys buildConfig
 
@@ -917,7 +937,7 @@ perfProfilingJobTag arch opsys j = j { jobTags = [ runnerPerfTag arch opsys ] }
 -- | Mark the validate job to run in fast-ci mode
 -- This is default way, to enable all jobs you have to apply the `full-ci` label.
 fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
+fastCI = onlyRule FastCI
 
 -- | Mark a group of jobs as allowed to fail.
 allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -934,8 +954,10 @@ onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
 
 -- | Don't run the validate job, normally used to alleviate CI load by marking
 -- jobs which are unlikely to fail (ie different linux distros)
+--
+-- These jobs can still be triggered by using the ONLY_JOBS environment variable
 disableValidate :: JobGroup Job -> JobGroup Job
-disableValidate st = st { v = Nothing }
+disableValidate = modifyValidateJobs (removeValidateJobRule FastCI . removeValidateJobRule FullCI)
 
 data NamedJob a = NamedJob { name :: String, jobInfo :: a } deriving (Show, Functor)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-darwin-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -66,6 +66,131 @@
       "TEST_ENV": "aarch64-darwin-validate"
     }
   },
+  "aarch64-linux-alpine3_18-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-alpine3_18-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-alpine3_18-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-alpine3_18:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-alpine3_18-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-alpine3_18-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-alpine3_18-validate"
+    }
+  },
+  "aarch64-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb10-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-deb10-validate"
+    }
+  },
   "aarch64-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -103,7 +228,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -165,7 +290,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\+llvm(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -190,6 +315,68 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb10-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-deb10-validate"
+    }
+  },
   "i386-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -227,7 +414,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb12-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4745,7 +4932,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-darwin-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4777,18 +4964,18 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-linux-alpine3_12-validate+fully_static": {
+  "x86_64-linux-alpine3_12-int_native-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": false,
+    "allow_failure": true,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4814,7 +5001,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-int_native-validate\\+fully_static(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4830,17 +5017,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static",
       "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
       "BUILD_FLAVOUR": "validate+fully_static",
       "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
+      "TEST_ENV": "x86_64-linux-alpine3_12-int_native-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4851,7 +5038,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4861,14 +5048,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4877,7 +5064,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4894,16 +5081,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4914,7 +5101,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4924,14 +5111,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4940,9 +5127,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\+fully_static(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -4957,17 +5143,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
+      "BUILD_FLAVOUR": "validate+fully_static",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4978,7 +5164,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5004,9 +5190,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5022,16 +5207,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
       "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
       "CROSS_TARGET": "wasm32-wasi",
       "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
+  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5042,7 +5227,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5052,14 +5237,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5068,8 +5253,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5084,18 +5270,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
-      "CROSS_TARGET": "aarch64-linux-gnu",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5106,7 +5291,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5116,14 +5301,78 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+    }
+  },
+  "x86_64-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5132,7 +5381,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5148,19 +5397,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CONFIGURE_WRAPPER": "emconfigure",
-      "CROSS_EMULATOR": "js-emulator",
-      "CROSS_TARGET": "javascript-unknown-ghcjs",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-validate"
     }
   },
-  "x86_64-linux-deb12-int_native-validate": {
+  "x86_64-linux-centos7-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5171,7 +5418,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
+        "ghc-x86_64-linux-centos7-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5181,14 +5428,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-centos7-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5197,7 +5444,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-centos7-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5213,16 +5460,18 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate",
+      "BROKEN_TESTS": "T22012",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=no-sphinx",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
+      "TEST_ENV": "x86_64-linux-centos7-validate"
     }
   },
-  "x86_64-linux-deb12-no_tntc-validate": {
+  "x86_64-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5233,7 +5482,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5243,14 +5492,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5259,9 +5508,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5277,15 +5525,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate"
     }
   },
-  "x86_64-linux-deb12-numa-slow-validate": {
+  "x86_64-linux-deb10-validate+debug_info": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5296,7 +5544,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate+debug_info.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5306,14 +5554,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5322,7 +5570,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\+debug_info(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5339,16 +5587,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
-      "BUILD_FLAVOUR": "slow-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate+debug_info"
     }
   },
-  "x86_64-linux-deb12-unreg-validate": {
+  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5359,7 +5606,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5369,14 +5616,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5385,7 +5632,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-cross_aarch64-linux-gnu-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5402,15 +5649,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
+      "CROSS_TARGET": "aarch64-linux-gnu",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb12-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5421,7 +5670,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5431,14 +5680,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5447,7 +5696,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5463,16 +5712,19 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_WRAPPER": "emconfigure",
+      "CROSS_EMULATOR": "js-emulator",
+      "CROSS_TARGET": "javascript-unknown-ghcjs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
-  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+  "x86_64-linux-deb11-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5483,7 +5735,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "ghc-x86_64-linux-deb11-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5493,14 +5745,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5509,7 +5761,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5526,15 +5778,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
-      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
-      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb11-validate"
     }
   },
-  "x86_64-linux-deb12-validate+llvm": {
+  "x86_64-linux-deb12-int_native-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5545,7 +5797,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5571,7 +5823,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-int_native-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5587,27 +5839,27 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
-      "BUILD_FLAVOUR": "validate+llvm",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
     }
   },
-  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+  "x86_64-linux-deb12-no_tntc-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": true,
+    "allow_failure": false,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5634,7 +5886,7 @@
     "rules": [
       {
         "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-no_tntc-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "manual"
       }
     ],
@@ -5651,17 +5903,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
     }
   },
-  "x86_64-linux-deb12-zstd-validate": {
+  "x86_64-linux-deb12-numa-slow-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5672,7 +5922,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5698,7 +5948,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-numa-slow-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5715,15 +5965,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
+      "BUILD_FLAVOUR": "slow-validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
-  "x86_64-linux-fedora33-release": {
+  "x86_64-linux-deb12-release-perf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5734,7 +5985,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "ghc-x86_64-linux-deb12-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5744,14 +5995,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "key": "x86_64-linux-deb12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5760,7 +6011,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-release(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5773,18 +6024,1018 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-linux"
+      "x86_64-linux-perf"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-release",
       "BUILD_FLAVOUR": "release",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "LLC": "/bin/false",
-      "OPT": "/bin/false",
-      "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-fedora33-release"
+      "RUNTEST_ARGS": " --config perf_path=perf",
+      "TEST_ENV": "x86_64-linux-deb12-release"
+    }
+  },
+  "x86_64-linux-deb12-unreg-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-unreg-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+boot_nonmoving_gc(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
+      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
+      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+    }
+  },
+  "x86_64-linux-deb12-validate+llvm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+llvm(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
+      "BUILD_FLAVOUR": "validate+llvm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+    }
+  },
+  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+thread_sanitizer_cmm(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=none",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+    }
+  },
+  "x86_64-linux-deb12-zstd-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-zstd-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+    }
+  },
+  "x86_64-linux-deb9-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb9-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb9-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb9-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb9-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb9-validate"
+    }
+  },
+  "x86_64-linux-fedora33-release": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-release-hackage": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--haddock-for-hackage",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-validate+debug_info": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+    }
+  },
+  "x86_64-linux-fedora38-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora38-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora38-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora38-validate"
+    }
+  },
+  "x86_64-linux-rocky8-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-rocky8-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-rocky8-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-rocky8:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-rocky8-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-rocky8-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-rocky8-validate"
+    }
+  },
+  "x86_64-linux-ubuntu18_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu18_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu18_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu18_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu18_04-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu18_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu18_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu20_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu20_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu20_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu20_04-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu20_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu20_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu22_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu22_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu22_04-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu22_04-validate"
+    }
+  },
+  "x86_64-windows-int_native-validate": {
+    "after_script": [
+      "bash .gitlab/ci.sh save_cache",
+      "bash .gitlab/ci.sh save_test_output",
+      "bash .gitlab/ci.sh clean"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-windows-int_native-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "no-caching",
+      "paths": []
+    },
+    "dependencies": [],
+    "image": null,
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-int_native-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "bash .gitlab/ci.sh setup",
+      "bash .gitlab/ci.sh configure",
+      "bash .gitlab/ci.sh build_hadrian",
+      "bash .gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "new-x86_64-windows"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CABAL_INSTALL_VERSION": "3.10.2.0",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "GHC_VERSION": "9.6.4",
+      "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LANG": "en_US.UTF-8",
+      "MSYSTEM": "CLANG64",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-windows-int_native-validate"
     }
   },
   "x86_64-windows-validate": {
@@ -5820,7 +7071,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-validate(?=\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 16:14:37 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 12:14:37 -0400
Subject: [Git][ghc/ghc][wip/only_job] ci: Add support for ONLY_JOBS variable
 to trigger any validation pipeline
Message-ID: <670408ed50a12_3da4644093f46138a@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
8db02d93 by Matthew Pickering at 2024-10-07T17:13:12+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -541,8 +541,8 @@ data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
                              }
 
 -- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
-emptyRules :: OnOffRules
-emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
+emptyRules :: String -> OnOffRules
+emptyRules jobName = OnOffRules (ValidateOnly jobName (S.fromList [FullCI])) OnSuccess
 
 -- When to run the job
 data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
@@ -559,10 +559,10 @@ onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
 onlyValidateRule r  = modifyValidateRules (const (S.singleton r))
 
 removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
-removeValidateRule r = modifyValidateRules (S.delete r)
+removeValidateRule v = modifyValidateRules (S.delete v)
 
 modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
-modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules f (OnOffRules (ValidateOnly s rs) m) = OnOffRules (ValidateOnly s (f rs)) m
 modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
 
 manualRule :: OnOffRules -> OnOffRules
@@ -575,13 +575,13 @@ enumRules :: OnOffRules -> [OnOffRule]
 enumRules (OnOffRules r _) = rulesList
   where
     rulesList = case r of
-                  ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+                  ValidateOnly s rs -> [OnOffRule On (ValidateOnly s rs)
                                     , OnOffRule Off ReleaseOnly
                                     , OnOffRule Off Nightly ]
-                  Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  Nightly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                              , OnOffRule Off ReleaseOnly
                              , OnOffRule On Nightly ]
-                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                                  , OnOffRule On ReleaseOnly
                                  , OnOffRule Off Nightly ]
 
@@ -619,11 +619,12 @@ or_all rs = intercalate " || " (map parens rs)
 -- run the job.
 data Rule = ReleaseOnly  -- ^ Only run this job in a release pipeline
           | Nightly      -- ^ Only run this job in the nightly pipeline
-          | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+          | ValidateOnly String (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
           deriving (Show, Ord, Eq)
 
 data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
+          | FastCI       -- ^ Run this job on every validation pipeline
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
@@ -631,7 +632,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
-          deriving (Show, Enum, Bounded, Ord, Eq)
+          deriving (Show, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
 -- expression language.
@@ -644,25 +645,43 @@ _false = "\"disabled\" != \"disabled\""
 
 -- Convert the state of the rule into a string that gitlab understand.
 ruleString :: OnOff -> Rule -> String
-ruleString On (ValidateOnly vs) =
-  case S.toList vs of
-    [] -> true
-    conds -> or_all (map validateRuleString conds)
+ruleString On (ValidateOnly only_job_name vs) =
+  let conds = S.toList vs
+      empty_only_job = envVarNull "ONLY_JOBS"
+      run_cond = case conds of
+                  [] -> _false
+                  cs -> or_all (map validateRuleString conds)
+      escape :: String -> String
+      escape = concatMap (\c -> if c == '+' then "\\+" else [c])
+
+  in
+    or_all  [
+    -- 1. Case when ONLY_JOBS is set
+      and_all [ "$ONLY_JOBS", "$ONLY_JOBS =~ /.*\\b" ++  escape only_job_name ++ "\\b.*/" ]
+    -- 2. Case when ONLY_JOBS is null
+    , and_all [ empty_only_job, run_cond ]
+    ]
 ruleString Off (ValidateOnly {}) = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
-ruleString Off Nightly = "$NIGHTLY == null"
+ruleString Off Nightly = envVarNull "NIGHTLY"
 
 labelString :: String -> String
 labelString s =  "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
 
 branchStringExact :: String -> String
-branchStringExact s = "$CI_COMMIT_BRANCH == \"" ++ s ++ "\""
+branchStringExact s = envVarString "CI_COMMIT_BRANCH" s
 
 branchStringLike :: String -> String
 branchStringLike s = "$CI_COMMIT_BRANCH =~ /" ++ s ++ "/"
 
+envVarString :: String -> String -> String
+envVarString var s = "$" ++ var ++ " == \"" ++ s ++ "\""
+
+envVarNull :: String ->  String
+envVarNull var = "$" ++ var ++ " == null"
+
 
 validateRuleString :: ValidateRule -> String
 validateRuleString FullCI = or_all ([ labelString "full-ci"
@@ -670,6 +689,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
                                     , branchStringExact "master"
                                     , branchStringLike "ghc-[0-9]+\\.[0-9]+"
                                     ])
+validateRuleString FastCI = true
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
@@ -725,7 +745,7 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} }
   where
     jobPlatform = (arch, opsys)
 
-    jobRules = emptyRules
+    jobRules = emptyRules jobName
 
     jobName = testEnv arch opsys buildConfig
 
@@ -917,7 +937,7 @@ perfProfilingJobTag arch opsys j = j { jobTags = [ runnerPerfTag arch opsys ] }
 -- | Mark the validate job to run in fast-ci mode
 -- This is default way, to enable all jobs you have to apply the `full-ci` label.
 fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
+fastCI = onlyRule FastCI
 
 -- | Mark a group of jobs as allowed to fail.
 allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -934,8 +954,10 @@ onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
 
 -- | Don't run the validate job, normally used to alleviate CI load by marking
 -- jobs which are unlikely to fail (ie different linux distros)
+--
+-- These jobs can still be triggered by using the ONLY_JOBS environment variable
 disableValidate :: JobGroup Job -> JobGroup Job
-disableValidate st = st { v = Nothing }
+disableValidate = modifyValidateJobs (removeValidateJobRule FastCI . removeValidateJobRule FullCI)
 
 data NamedJob a = NamedJob { name :: String, jobInfo :: a } deriving (Show, Functor)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-darwin-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -66,6 +66,131 @@
       "TEST_ENV": "aarch64-darwin-validate"
     }
   },
+  "aarch64-linux-alpine3_18-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-alpine3_18-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-alpine3_18-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-alpine3_18:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-alpine3_18-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-alpine3_18-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-alpine3_18-validate"
+    }
+  },
+  "aarch64-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-deb10-validate"
+    }
+  },
   "aarch64-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -103,7 +228,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -165,7 +290,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\+llvm\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -190,6 +315,68 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-deb10-validate"
+    }
+  },
   "i386-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -227,7 +414,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4745,7 +4932,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-darwin-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4777,18 +4964,18 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-linux-alpine3_12-validate+fully_static": {
+  "x86_64-linux-alpine3_12-int_native-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": false,
+    "allow_failure": true,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4814,7 +5001,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-int_native-validate\\+fully_static\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4830,17 +5017,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static",
       "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
       "BUILD_FLAVOUR": "validate+fully_static",
       "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
+      "TEST_ENV": "x86_64-linux-alpine3_12-int_native-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4851,7 +5038,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4861,14 +5048,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4877,7 +5064,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4894,16 +5081,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4914,7 +5101,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4924,14 +5111,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4940,9 +5127,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\+fully_static\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -4957,17 +5143,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
+      "BUILD_FLAVOUR": "validate+fully_static",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4978,7 +5164,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5004,9 +5190,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5022,16 +5207,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
       "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
       "CROSS_TARGET": "wasm32-wasi",
       "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
+  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5042,7 +5227,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5052,14 +5237,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5068,8 +5253,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5084,18 +5270,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
-      "CROSS_TARGET": "aarch64-linux-gnu",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5106,7 +5291,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5116,14 +5301,78 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+    }
+  },
+  "x86_64-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5132,7 +5381,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5148,19 +5397,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CONFIGURE_WRAPPER": "emconfigure",
-      "CROSS_EMULATOR": "js-emulator",
-      "CROSS_TARGET": "javascript-unknown-ghcjs",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-validate"
     }
   },
-  "x86_64-linux-deb12-int_native-validate": {
+  "x86_64-linux-centos7-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5171,7 +5418,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
+        "ghc-x86_64-linux-centos7-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5181,14 +5428,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-centos7-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5197,7 +5444,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-centos7-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5213,16 +5460,18 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate",
+      "BROKEN_TESTS": "T22012",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=no-sphinx",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
+      "TEST_ENV": "x86_64-linux-centos7-validate"
     }
   },
-  "x86_64-linux-deb12-no_tntc-validate": {
+  "x86_64-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5233,7 +5482,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5243,14 +5492,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5259,9 +5508,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5277,15 +5525,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate"
     }
   },
-  "x86_64-linux-deb12-numa-slow-validate": {
+  "x86_64-linux-deb10-validate+debug_info": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5296,7 +5544,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate+debug_info.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5306,14 +5554,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5322,7 +5570,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\+debug_info\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5339,16 +5587,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
-      "BUILD_FLAVOUR": "slow-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate+debug_info"
     }
   },
-  "x86_64-linux-deb12-unreg-validate": {
+  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5359,7 +5606,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5369,14 +5616,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5385,7 +5632,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-cross_aarch64-linux-gnu-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5402,15 +5649,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
+      "CROSS_TARGET": "aarch64-linux-gnu",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb12-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5421,7 +5670,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5431,14 +5680,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5447,7 +5696,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5463,16 +5712,19 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_WRAPPER": "emconfigure",
+      "CROSS_EMULATOR": "js-emulator",
+      "CROSS_TARGET": "javascript-unknown-ghcjs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
-  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+  "x86_64-linux-deb11-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5483,7 +5735,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "ghc-x86_64-linux-deb11-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5493,14 +5745,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5509,7 +5761,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5526,15 +5778,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
-      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
-      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb11-validate"
     }
   },
-  "x86_64-linux-deb12-validate+llvm": {
+  "x86_64-linux-deb12-int_native-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5545,7 +5797,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5571,7 +5823,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-int_native-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5587,27 +5839,27 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
-      "BUILD_FLAVOUR": "validate+llvm",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
     }
   },
-  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+  "x86_64-linux-deb12-no_tntc-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": true,
+    "allow_failure": false,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5634,7 +5886,7 @@
     "rules": [
       {
         "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-no_tntc-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "manual"
       }
     ],
@@ -5651,17 +5903,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
     }
   },
-  "x86_64-linux-deb12-zstd-validate": {
+  "x86_64-linux-deb12-numa-slow-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5672,7 +5922,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5698,7 +5948,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-numa-slow-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5715,15 +5965,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
+      "BUILD_FLAVOUR": "slow-validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
-  "x86_64-linux-fedora33-release": {
+  "x86_64-linux-deb12-release-perf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5734,7 +5985,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "ghc-x86_64-linux-deb12-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5744,14 +5995,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "key": "x86_64-linux-deb12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5760,7 +6011,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-release\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5773,18 +6024,1018 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-linux"
+      "x86_64-linux-perf"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-release",
       "BUILD_FLAVOUR": "release",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "LLC": "/bin/false",
-      "OPT": "/bin/false",
-      "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-fedora33-release"
+      "RUNTEST_ARGS": " --config perf_path=perf",
+      "TEST_ENV": "x86_64-linux-deb12-release"
+    }
+  },
+  "x86_64-linux-deb12-unreg-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-unreg-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+boot_nonmoving_gc\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
+      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
+      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+    }
+  },
+  "x86_64-linux-deb12-validate+llvm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+llvm\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
+      "BUILD_FLAVOUR": "validate+llvm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+    }
+  },
+  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+thread_sanitizer_cmm\\b.*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=none",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+    }
+  },
+  "x86_64-linux-deb12-zstd-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-zstd-validate\\b.*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+    }
+  },
+  "x86_64-linux-deb9-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb9-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb9-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb9-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb9-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb9-validate"
+    }
+  },
+  "x86_64-linux-fedora33-release": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-release-hackage": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--haddock-for-hackage",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-validate+debug_info": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+    }
+  },
+  "x86_64-linux-fedora38-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora38-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora38-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora38-validate"
+    }
+  },
+  "x86_64-linux-rocky8-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-rocky8-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-rocky8-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-rocky8:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-rocky8-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-rocky8-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-rocky8-validate"
+    }
+  },
+  "x86_64-linux-ubuntu18_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu18_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu18_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu18_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu18_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu18_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu18_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu20_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu20_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu20_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu20_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu20_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu20_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu22_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu22_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu22_04-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu22_04-validate"
+    }
+  },
+  "x86_64-windows-int_native-validate": {
+    "after_script": [
+      "bash .gitlab/ci.sh save_cache",
+      "bash .gitlab/ci.sh save_test_output",
+      "bash .gitlab/ci.sh clean"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-windows-int_native-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "no-caching",
+      "paths": []
+    },
+    "dependencies": [],
+    "image": null,
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-int_native-validate\\b.*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "bash .gitlab/ci.sh setup",
+      "bash .gitlab/ci.sh configure",
+      "bash .gitlab/ci.sh build_hadrian",
+      "bash .gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "new-x86_64-windows"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CABAL_INSTALL_VERSION": "3.10.2.0",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "GHC_VERSION": "9.6.4",
+      "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LANG": "en_US.UTF-8",
+      "MSYSTEM": "CLANG64",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-windows-int_native-validate"
     }
   },
   "x86_64-windows-validate": {
@@ -5820,7 +7071,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-validate\\b.*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8db02d936c012dc3923716eb99b7cc0d97b1edc0

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 16:31:28 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Mon, 07 Oct 2024 12:31:28 -0400
Subject: [Git][ghc/ghc][wip/only_job] ci: Add support for ONLY_JOBS variable
 to trigger any validation pipeline
Message-ID: <67040ce038113_2eca231f34d41185f@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
653f25bd by Matthew Pickering at 2024-10-07T17:30:48+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -541,8 +541,8 @@ data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
                              }
 
 -- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
-emptyRules :: OnOffRules
-emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
+emptyRules :: String -> OnOffRules
+emptyRules jobName = OnOffRules (ValidateOnly jobName (S.fromList [FullCI])) OnSuccess
 
 -- When to run the job
 data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
@@ -559,10 +559,10 @@ onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
 onlyValidateRule r  = modifyValidateRules (const (S.singleton r))
 
 removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
-removeValidateRule r = modifyValidateRules (S.delete r)
+removeValidateRule v = modifyValidateRules (S.delete v)
 
 modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
-modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules f (OnOffRules (ValidateOnly s rs) m) = OnOffRules (ValidateOnly s (f rs)) m
 modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
 
 manualRule :: OnOffRules -> OnOffRules
@@ -575,13 +575,13 @@ enumRules :: OnOffRules -> [OnOffRule]
 enumRules (OnOffRules r _) = rulesList
   where
     rulesList = case r of
-                  ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+                  ValidateOnly s rs -> [OnOffRule On (ValidateOnly s rs)
                                     , OnOffRule Off ReleaseOnly
                                     , OnOffRule Off Nightly ]
-                  Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  Nightly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                              , OnOffRule Off ReleaseOnly
                              , OnOffRule On Nightly ]
-                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                                  , OnOffRule On ReleaseOnly
                                  , OnOffRule Off Nightly ]
 
@@ -619,11 +619,12 @@ or_all rs = intercalate " || " (map parens rs)
 -- run the job.
 data Rule = ReleaseOnly  -- ^ Only run this job in a release pipeline
           | Nightly      -- ^ Only run this job in the nightly pipeline
-          | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+          | ValidateOnly String (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
           deriving (Show, Ord, Eq)
 
 data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
+          | FastCI       -- ^ Run this job on every validation pipeline
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
@@ -631,7 +632,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
-          deriving (Show, Enum, Bounded, Ord, Eq)
+          deriving (Show, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
 -- expression language.
@@ -644,25 +645,43 @@ _false = "\"disabled\" != \"disabled\""
 
 -- Convert the state of the rule into a string that gitlab understand.
 ruleString :: OnOff -> Rule -> String
-ruleString On (ValidateOnly vs) =
-  case S.toList vs of
-    [] -> true
-    conds -> or_all (map validateRuleString conds)
+ruleString On (ValidateOnly only_job_name vs) =
+  let conds = S.toList vs
+      empty_only_job = envVarNull "ONLY_JOBS"
+      run_cond = case conds of
+                  [] -> _false
+                  cs -> or_all (map validateRuleString conds)
+      escape :: String -> String
+      escape = concatMap (\c -> if c == '+' then "\\+" else [c])
+
+  in
+    or_all  [
+    -- 1. Case when ONLY_JOBS is set
+      and_all [ "$ONLY_JOBS", "$ONLY_JOBS =~ /.*\\b" ++  escape only_job_name ++ "(\\s|$).*/" ]
+    -- 2. Case when ONLY_JOBS is null
+    , and_all [ empty_only_job, run_cond ]
+    ]
 ruleString Off (ValidateOnly {}) = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
-ruleString Off Nightly = "$NIGHTLY == null"
+ruleString Off Nightly = envVarNull "NIGHTLY"
 
 labelString :: String -> String
 labelString s =  "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
 
 branchStringExact :: String -> String
-branchStringExact s = "$CI_COMMIT_BRANCH == \"" ++ s ++ "\""
+branchStringExact s = envVarString "CI_COMMIT_BRANCH" s
 
 branchStringLike :: String -> String
 branchStringLike s = "$CI_COMMIT_BRANCH =~ /" ++ s ++ "/"
 
+envVarString :: String -> String -> String
+envVarString var s = "$" ++ var ++ " == \"" ++ s ++ "\""
+
+envVarNull :: String ->  String
+envVarNull var = "$" ++ var ++ " == null"
+
 
 validateRuleString :: ValidateRule -> String
 validateRuleString FullCI = or_all ([ labelString "full-ci"
@@ -670,6 +689,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
                                     , branchStringExact "master"
                                     , branchStringLike "ghc-[0-9]+\\.[0-9]+"
                                     ])
+validateRuleString FastCI = true
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
@@ -725,7 +745,7 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} }
   where
     jobPlatform = (arch, opsys)
 
-    jobRules = emptyRules
+    jobRules = emptyRules jobName
 
     jobName = testEnv arch opsys buildConfig
 
@@ -917,7 +937,7 @@ perfProfilingJobTag arch opsys j = j { jobTags = [ runnerPerfTag arch opsys ] }
 -- | Mark the validate job to run in fast-ci mode
 -- This is default way, to enable all jobs you have to apply the `full-ci` label.
 fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
+fastCI = onlyRule FastCI
 
 -- | Mark a group of jobs as allowed to fail.
 allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -934,8 +954,10 @@ onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
 
 -- | Don't run the validate job, normally used to alleviate CI load by marking
 -- jobs which are unlikely to fail (ie different linux distros)
+--
+-- These jobs can still be triggered by using the ONLY_JOBS environment variable
 disableValidate :: JobGroup Job -> JobGroup Job
-disableValidate st = st { v = Nothing }
+disableValidate = modifyValidateJobs (removeValidateJobRule FastCI . removeValidateJobRule FullCI)
 
 data NamedJob a = NamedJob { name :: String, jobInfo :: a } deriving (Show, Functor)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-darwin-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -66,6 +66,131 @@
       "TEST_ENV": "aarch64-darwin-validate"
     }
   },
+  "aarch64-linux-alpine3_18-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-alpine3_18-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-alpine3_18-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-alpine3_18:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-alpine3_18-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-alpine3_18-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-alpine3_18-validate"
+    }
+  },
+  "aarch64-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-deb10-validate"
+    }
+  },
   "aarch64-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -103,7 +228,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -165,7 +290,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\+llvm(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -190,6 +315,68 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-deb10-validate"
+    }
+  },
   "i386-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -227,7 +414,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4745,7 +4932,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-darwin-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4777,18 +4964,18 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-linux-alpine3_12-validate+fully_static": {
+  "x86_64-linux-alpine3_12-int_native-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": false,
+    "allow_failure": true,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4814,7 +5001,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-int_native-validate\\+fully_static(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4830,17 +5017,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static",
       "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
       "BUILD_FLAVOUR": "validate+fully_static",
       "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
+      "TEST_ENV": "x86_64-linux-alpine3_12-int_native-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4851,7 +5038,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4861,14 +5048,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4877,7 +5064,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4894,16 +5081,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4914,7 +5101,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4924,14 +5111,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4940,9 +5127,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\+fully_static(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -4957,17 +5143,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
+      "BUILD_FLAVOUR": "validate+fully_static",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4978,7 +5164,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5004,9 +5190,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5022,16 +5207,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf",
       "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
       "CROSS_TARGET": "wasm32-wasi",
       "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
+  "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5042,7 +5227,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5052,14 +5237,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5068,8 +5253,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5084,18 +5270,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
-      "CROSS_TARGET": "aarch64-linux-gnu",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5106,7 +5291,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5116,14 +5301,78 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_18-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_18-wasm:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release\\+fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf"
+    }
+  },
+  "x86_64-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5132,7 +5381,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5148,19 +5397,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CONFIGURE_WRAPPER": "emconfigure",
-      "CROSS_EMULATOR": "js-emulator",
-      "CROSS_TARGET": "javascript-unknown-ghcjs",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-validate"
     }
   },
-  "x86_64-linux-deb12-int_native-validate": {
+  "x86_64-linux-centos7-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5171,7 +5418,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
+        "ghc-x86_64-linux-centos7-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5181,14 +5428,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-centos7-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5197,7 +5444,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-centos7-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5213,16 +5460,18 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate",
+      "BROKEN_TESTS": "T22012",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=no-sphinx",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
+      "TEST_ENV": "x86_64-linux-centos7-validate"
     }
   },
-  "x86_64-linux-deb12-no_tntc-validate": {
+  "x86_64-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5233,7 +5482,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5243,14 +5492,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5259,9 +5508,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5277,15 +5525,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate"
     }
   },
-  "x86_64-linux-deb12-numa-slow-validate": {
+  "x86_64-linux-deb10-validate+debug_info": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5296,7 +5544,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate+debug_info.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5306,14 +5554,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5322,7 +5570,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5339,16 +5587,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
-      "BUILD_FLAVOUR": "slow-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate+debug_info"
     }
   },
-  "x86_64-linux-deb12-unreg-validate": {
+  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5359,7 +5606,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5369,14 +5616,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5385,7 +5632,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-cross_aarch64-linux-gnu-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5402,15 +5649,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
+      "CROSS_TARGET": "aarch64-linux-gnu",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb12-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5421,7 +5670,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5431,14 +5680,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5447,7 +5696,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5463,16 +5712,19 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_WRAPPER": "emconfigure",
+      "CROSS_EMULATOR": "js-emulator",
+      "CROSS_TARGET": "javascript-unknown-ghcjs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
-  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+  "x86_64-linux-deb11-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5483,7 +5735,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "ghc-x86_64-linux-deb11-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5493,14 +5745,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5509,7 +5761,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5526,15 +5778,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
-      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
-      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb11-validate"
     }
   },
-  "x86_64-linux-deb12-validate+llvm": {
+  "x86_64-linux-deb12-int_native-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5545,7 +5797,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5571,7 +5823,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-int_native-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5587,27 +5839,27 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
-      "BUILD_FLAVOUR": "validate+llvm",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
     }
   },
-  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+  "x86_64-linux-deb12-no_tntc-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": true,
+    "allow_failure": false,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5634,7 +5886,7 @@
     "rules": [
       {
         "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-no_tntc-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "manual"
       }
     ],
@@ -5651,17 +5903,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
     }
   },
-  "x86_64-linux-deb12-zstd-validate": {
+  "x86_64-linux-deb12-numa-slow-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5672,7 +5922,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5698,7 +5948,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-numa-slow-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5715,15 +5965,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
+      "BUILD_FLAVOUR": "slow-validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
-  "x86_64-linux-fedora33-release": {
+  "x86_64-linux-deb12-release-perf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5734,7 +5985,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "ghc-x86_64-linux-deb12-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5744,14 +5995,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "key": "x86_64-linux-deb12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5760,7 +6011,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5773,18 +6024,1018 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-linux"
+      "x86_64-linux-perf"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-release",
       "BUILD_FLAVOUR": "release",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "LLC": "/bin/false",
-      "OPT": "/bin/false",
-      "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-fedora33-release"
+      "RUNTEST_ARGS": " --config perf_path=perf",
+      "TEST_ENV": "x86_64-linux-deb12-release"
+    }
+  },
+  "x86_64-linux-deb12-unreg-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-unreg-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+boot_nonmoving_gc(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
+      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
+      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+    }
+  },
+  "x86_64-linux-deb12-validate+llvm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+llvm(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
+      "BUILD_FLAVOUR": "validate+llvm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+    }
+  },
+  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+thread_sanitizer_cmm(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=none",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+    }
+  },
+  "x86_64-linux-deb12-zstd-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-zstd-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+    }
+  },
+  "x86_64-linux-deb9-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb9-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb9-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb9-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb9-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb9-validate"
+    }
+  },
+  "x86_64-linux-fedora33-release": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-release-hackage": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--haddock-for-hackage",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-validate+debug_info": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+    }
+  },
+  "x86_64-linux-fedora38-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora38-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora38-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora38-validate"
+    }
+  },
+  "x86_64-linux-rocky8-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-rocky8-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-rocky8-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-rocky8:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-rocky8-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-rocky8-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-rocky8-validate"
+    }
+  },
+  "x86_64-linux-ubuntu18_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu18_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu18_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu18_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu18_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu18_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu18_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu20_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu20_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu20_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu20_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu20_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu20_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu22_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu22_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu22_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu22_04-validate"
+    }
+  },
+  "x86_64-windows-int_native-validate": {
+    "after_script": [
+      "bash .gitlab/ci.sh save_cache",
+      "bash .gitlab/ci.sh save_test_output",
+      "bash .gitlab/ci.sh clean"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-windows-int_native-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "no-caching",
+      "paths": []
+    },
+    "dependencies": [],
+    "image": null,
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-int_native-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "bash .gitlab/ci.sh setup",
+      "bash .gitlab/ci.sh configure",
+      "bash .gitlab/ci.sh build_hadrian",
+      "bash .gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "new-x86_64-windows"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CABAL_INSTALL_VERSION": "3.10.2.0",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "GHC_VERSION": "9.6.4",
+      "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LANG": "en_US.UTF-8",
+      "MSYSTEM": "CLANG64",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-windows-int_native-validate"
     }
   },
   "x86_64-windows-validate": {
@@ -5820,7 +7071,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/653f25bd90528f614e115a1d9de830afaa52d8bb

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 17:19:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 13:19:53 -0400
Subject: [Git][ghc/ghc][master] javascript: Read fields of ObjectBlock lazily
Message-ID: <670418391c1e4_2eca23450ec02093e@gitlab.mail>



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


Commits:
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -


2 changed files:

- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs


Changes:

=====================================
compiler/GHC/StgToJS/Object.hs
=====================================
@@ -255,23 +255,23 @@ instance Outputable ExportedFun where
 -- index
 putObjBlock :: WriteBinHandle -> ObjBlock -> IO ()
 putObjBlock bh (ObjBlock _syms b c d e f g) = do
-    put_ bh b
-    put_ bh c
+    lazyPut bh b
+    lazyPut bh c
     lazyPut bh d
-    put_ bh e
-    put_ bh f
-    put_ bh g
+    lazyPut bh e
+    lazyPut bh f
+    lazyPut bh g
 
 -- | Read an ObjBlock and associate it to the given symbols (that must have been
 -- read from the index)
 getObjBlock :: [FastString] -> ReadBinHandle -> IO ObjBlock
 getObjBlock syms bh = do
-    b <- get bh
-    c <- get bh
+    b <- lazyGet bh
+    c <- lazyGet bh
     d <- lazyGet bh
-    e <- get bh
-    f <- get bh
-    g <- get bh
+    e <- lazyGet bh
+    f <- lazyGet bh
+    g <- lazyGet bh
     pure $ ObjBlock
       { oiSymbols  = syms
       , oiClInfo   = b


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -312,13 +312,13 @@ data LinkableUnit = LinkableUnit
 
 -- | one toplevel block in the object file
 data ObjBlock = ObjBlock
-  { oiSymbols  :: ![FastString]   -- ^ toplevel symbols (stored in index)
-  , oiClInfo   :: ![ClosureInfo]  -- ^ closure information of all closures in block
-  , oiStatic   :: ![StaticInfo]   -- ^ static closure data
+  { oiSymbols  :: [FastString]   -- ^ toplevel symbols (stored in index)
+  , oiClInfo   :: [ClosureInfo]  -- ^ closure information of all closures in block
+  , oiStatic   :: [StaticInfo]   -- ^ static closure data
   , oiStat     :: Sat.JStat       -- ^ the code
-  , oiRaw      :: !BS.ByteString  -- ^ raw JS code
-  , oiFExports :: ![ExpFun]
-  , oiFImports :: ![ForeignJSRef]
+  , oiRaw      :: BS.ByteString  -- ^ raw JS code
+  , oiFExports :: [ExpFun]
+  , oiFImports :: [ForeignJSRef]
   }
 
 data ExpFun = ExpFun



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 17:21:17 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 13:21:17 -0400
Subject: [Git][ghc/ghc][master] ci: Run the i386 validation job when i386
 label is set
Message-ID: <6704188d66ead_2eca23538e6427913@gitlab.mail>



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


Commits:
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -631,6 +631,7 @@ data ValidateRule =
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
+          | I386Backend  -- ^ Run this job when the "i386" label is set
           deriving (Show, Enum, Bounded, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
@@ -678,6 +679,7 @@ validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
 validateRuleString IpeData      = labelString "IPE"
 validateRuleString TestPrimops  = labelString "test-primops"
+validateRuleString I386Backend  = labelString "i386"
 
 -- | A 'Job' is the description of a single job in a gitlab pipeline. The
 -- job contains all the information about how to do the build but can be further
@@ -1055,7 +1057,7 @@ debian_aarch64 =
 debian_i386 :: [JobGroup Job]
 debian_i386 =
   [ disableValidate (standardBuildsWithConfig I386 (Linux Debian10) (splitSectionsBroken vanilla))
-  , standardBuildsWithConfig I386 (Linux Debian12) (splitSectionsBroken vanilla)
+  , addValidateRule I386Backend (standardBuildsWithConfig I386 (Linux Debian12) (splitSectionsBroken vanilla))
   ]
 
 ubuntu_x86 :: [JobGroup Job]


=====================================
.gitlab/jobs.yaml
=====================================
@@ -227,7 +227,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*i386.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/571329df8a4cdbb98a1aae7113ad5fa5c22f1ff0

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 17:21:43 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 13:21:43 -0400
Subject: [Git][ghc/ghc][master] Rewrite partitionByWorkerSize to avoid pattern
 match checker bug
Message-ID: <670418a6d7350_2eca237e74942813a@gitlab.mail>



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


Commits:
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -


1 changed file:

- compiler/GHC/Core/Opt/SpecConstr.hs


Changes:

=====================================
compiler/GHC/Core/Opt/SpecConstr.hs
=====================================
@@ -2512,13 +2512,11 @@ callsToNewPats env fn spec_info@(SI { si_specs = done_specs }) bndr_occs calls
     partitionByWorkerSize worker_size pats = go pats [] []
       where
         go [] small warnings = (small, warnings)
-        go (p:ps) small warnings
-          | WorkerSmallEnough <- worker_size p
-          = go ps (p:small) warnings
-          | WorkerTooLarge <- worker_size p
-          = go ps small warnings
-          | WorkerTooLargeForced name <- worker_size p
-          = go ps small (SpecFailForcedArgCount name : warnings)
+        go (p:ps) small warnings =
+          case worker_size p of
+            WorkerSmallEnough -> go ps (p:small) warnings
+            WorkerTooLarge -> go ps small warnings
+            WorkerTooLargeForced name -> go ps small (SpecFailForcedArgCount name : warnings)
 
 
 trim_pats :: ScEnv -> Id -> SpecInfo -> [CallPat] -> (Bool, [CallPat])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 17:52:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 13:52:53 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: javascript:
 Read fields of ObjectBlock lazily
Message-ID: <67041ff51ea91_2eca23c1b13c45151@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
7c2ae5b5 by Arnaud Spiwack at 2024-10-07T13:52:28-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
3757c590 by Sven Tennie at 2024-10-07T13:52:29-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
4e52d603 by Mario Blažević at 2024-10-07T13:52:35-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
16572491 by ARATA Mizuki at 2024-10-07T13:52:41-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff9e4198 by Andreas Klebinger at 2024-10-07T13:52:42-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
f6af2d08 by Sven Tennie at 2024-10-07T13:52:43-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
d2b06154 by Cheng Shao at 2024-10-07T13:52:44-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
967c4928 by sheaf at 2024-10-07T13:52:44-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2eda0b22fd3ba08812a3f68e7e4fc4abe71d186...967c49286f2bcaefe6a68d086ebf03be11c21741

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2eda0b22fd3ba08812a3f68e7e4fc4abe71d186...967c49286f2bcaefe6a68d086ebf03be11c21741
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 19:53:29 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 07 Oct 2024 15:53:29 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann] 11 commits: driver: fix
 runWorkerLimit on wasm
Message-ID: <67043c39c39e2_f9bf651ab44565ec@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann at Glasgow Haskell Compiler / GHC


Commits:
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
7602d6ed by Alan Zimmerman at 2024-10-07T20:52:52+01:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Unit/Finder.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ecfc64d67184d31c332076022cc8650eba588a6...7602d6ed59fe5dd28046182837d82bcb07476b42

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ecfc64d67184d31c332076022cc8650eba588a6...7602d6ed59fe5dd28046182837d82bcb07476b42
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 21:07:09 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 07 Oct 2024 17:07:09 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 11 commits: driver: fix
 runWorkerLimit on wasm
Message-ID: <67044d7dc3280_1a40871b324489436@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
7515044f by Hassan Al-Awwadi at 2024-10-07T23:02:30+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, which was easy, and we parameterized it over
the ghcPass instead of over some arbitrary type. This part was quite annoying.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Unit/Finder.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/linear_types.rst
- libraries/base/changelog.md
- libraries/template-haskell/changelog.md
- rts/posix/Signals.c
- testsuite/tests/count-deps/CountDepsAst.stdout


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42effa949f9827d812ebc3a1dc78fed219748ca4...7515044fd4d4e685e2f4b181889082ecca4a68ee

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42effa949f9827d812ebc3a1dc78fed219748ca4...7515044fd4d4e685e2f4b181889082ecca4a68ee
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 21:30:02 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 07 Oct 2024 17:30:02 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] Refactored BooleanFormula to
 be in line with TTG (#21592)
Message-ID: <670452da5dc75_1a408727e624918c6@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
0b77bee8 by Hassan Al-Awwadi at 2024-10-07T23:28:55+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, which was easy, and we parameterized it over
the ghcPass instead of over some arbitrary type. This part was quite annoying.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -


21 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
+import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -35,7 +36,7 @@ import GHC.Utils.Panic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
 import GHC.Utils.Outputable
-import GHC.Data.BooleanFormula (BooleanFormula, mkTrue)
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula, mkTrue )
 
 import qualified Data.Data as Data
 
@@ -135,7 +136,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula Name -- Required methods
+type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,5 +1,5 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable  #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
 -- | Boolean formulas without quantifiers and without negation.
@@ -8,74 +8,45 @@
 -- This module is used to represent minimal complete definitions for classes.
 --
 module GHC.Data.BooleanFormula (
-        BooleanFormula(..), LBooleanFormula,
-        mkFalse, mkTrue, mkAnd, mkOr, mkVar,
+        module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
+        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
-        pprBooleanFormula, pprBooleanFormulaNice
+        pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
   ) where
 
-import GHC.Prelude hiding ( init, last )
-
-import Data.List ( nub, intersperse )
+import Data.List ( intersperse )
 import Data.List.NonEmpty ( NonEmpty (..), init, last )
-import Data.Data
 
-import GHC.Utils.Monad
-import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( LocatedL )
-import GHC.Types.SrcLoc
+import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
+import GHC.Types.SrcLoc (unLoc)
+import GHC.Utils.Outputable
+import GHC.Parser.Annotation ( SrcSpanAnnL )
+import GHC.Hs.Extension (GhcPass (..), GhcPs, GhcRn, OutputableBndrId)
+import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
+import Language.Haskell.Syntax.BooleanFormula
+
 
 ----------------------------------------------------------------------
 -- Boolean formula type and smart constructors
 ----------------------------------------------------------------------
 
-type LBooleanFormula a = LocatedL (BooleanFormula a)
-
-data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a]
-                      | Parens (LBooleanFormula a)
-  deriving (Eq, Data, Functor, Foldable, Traversable)
+type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
-mkVar :: a -> BooleanFormula a
-mkVar = Var
-
-mkFalse, mkTrue :: BooleanFormula a
-mkFalse = Or []
-mkTrue = And []
-
--- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula a
-mkBool False = mkFalse
-mkBool True  = mkTrue
-
--- Make a conjunction, and try to simplify
-mkAnd :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkAnd = maybe mkFalse (mkAnd' . nub) . concatMapM fromAnd
-  where
-  -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula a -> Maybe [LBooleanFormula a]
-  fromAnd (L _ (And xs)) = Just xs
-     -- assume that xs are already simplified
-     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
-  fromAnd (L _ (Or [])) = Nothing
-     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
-  fromAnd x = Just [x]
-  mkAnd' [x] = unLoc x
-  mkAnd' xs = And xs
-
-mkOr :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkOr = maybe mkTrue (mkOr' . nub) . concatMapM fromOr
-  where
-  -- See Note [Simplification of BooleanFormulas]
-  fromOr (L _ (Or xs)) = Just xs
-  fromOr (L _ (And [])) = Nothing
-  fromOr x = Just [x]
-  mkOr' [x] = unLoc x
-  mkOr' xs = Or xs
+-- the other part of jury rigging some fake instances for booleanformula
+-- using the genlocated instances of Functor and Traversable.
+bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
+      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
+bfMap f = bfExplMap fmap f
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (GhcPass p'))
+bfTraverse f = bfExplTraverse traverse f
 
 {-
 Note [Simplification of BooleanFormulas]
@@ -115,15 +86,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula a -> Bool
+isFalse :: BooleanFormula (GhcPass p) -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula a -> Bool
+isTrue :: BooleanFormula (GhcPass p) -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (a -> Bool) -> BooleanFormula a -> Bool
+eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
 eval f (Var x)  = f x
 eval f (And xs) = all (eval f . unLoc) xs
 eval f (Or xs)  = any (eval f . unLoc) xs
@@ -131,18 +102,24 @@ eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: Eq a => (a -> Maybe Bool) -> BooleanFormula a -> BooleanFormula a
+simplify :: forall p. Eq (LIdP (GhcPass p))
+          => (LIdP (GhcPass p) ->  Maybe Bool)
+          -> BooleanFormula (GhcPass p)
+          -> BooleanFormula (GhcPass p)
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (\(L l x) -> L l (simplify f x)) xs)
-simplify f (Or xs) = mkOr (map (\(L l x) -> L l (simplify f x)) xs)
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
 simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq a => (a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
+isUnsatisfied :: Eq (LIdP (GhcPass p))
+              => (LIdP (GhcPass p) -> Bool)
+              -> BooleanFormula (GhcPass p)
+              -> Maybe (BooleanFormula (GhcPass p))
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -155,42 +132,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq a => BooleanFormula a -> a -> Bool
-Var x  `impliesAtom` y = x == y
-And xs `impliesAtom` y = any (\x -> (unLoc x) `impliesAtom` y) xs
+impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
            -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> (unLoc x) `impliesAtom` y) xs
-Parens x `impliesAtom` y = (unLoc x) `impliesAtom` y
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
-implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
+implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable a => Clause a -> Clause a -> Bool
+    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms x r -> True
-                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms (unLoc x) r -> True
+                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
             And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms x l -> True
-                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
+            Var x | memberClauseAtoms (unLoc x) l -> True
+                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = unLoc con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause a = Clause {
-        clauseAtoms :: UniqSet a,
-        clauseExprs :: [BooleanFormula a]
+data Clause p = Clause {
+        clauseAtoms :: UniqSet (IdP p),
+        clauseExprs :: [BooleanFormula p]
     }
-extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
+extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
+memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -199,28 +176,29 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula' :: (Rational -> a -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
-  go p (And []) = cparen (p > 0) $ empty
+  go p (And []) = cparen (p > 0) empty
   go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
   go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
   go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
+pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -230,14 +208,15 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance (OutputableBndr a) => Outputable (BooleanFormula a) where
+instance Outputable (BooleanFormula GhcPs) where
+  ppr = pprBooleanFormulaNormal
+instance Outputable (BooleanFormula GhcRn) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: (OutputableBndr a)
-                        => BooleanFormula a -> SDoc
+pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc x
+    go (Var x)    = pprPrefixOcc (unLoc x)
     go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,6 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -47,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Var
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.Name.Reader
 import GHC.Types.Name
 
@@ -934,9 +934,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: (OutputableBndr name)
-              => LBooleanFormula (GenLocated l name) -> SDoc
-pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -103,6 +103,7 @@ module GHC.Hs.Decls (
 import GHC.Prelude
 
 import Language.Haskell.Syntax.Decls
+import Language.Haskell.Syntax.Extension
 
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprUntypedSplice )
         -- Because Expr imports Decls via HsBracket
@@ -112,7 +113,7 @@ import GHC.Hs.Type
 import GHC.Hs.Doc
 import GHC.Types.Basic
 import GHC.Core.Coercion
-import Language.Haskell.Syntax.Extension
+
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
 import GHC.Types.Name


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -33,6 +33,8 @@ import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
+import GHC.Data.BooleanFormula (BooleanFormula(..))
+import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -594,3 +596,6 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+
+deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -14,6 +14,10 @@ module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
    , toIfaceBooleanFormula
+
+   -- converting back
+   , fromIfaceBooleanFormula
+   , traverseIfaceBooleanFormula
    )
 where
 
@@ -33,7 +37,7 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-
+import GHC.Hs.Extension ( GhcPass )
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
@@ -42,6 +46,8 @@ import GHC.Types.Basic
 import GHC.Types.TyThing
 import GHC.Types.SrcLoc
 
+import GHC.Parser.Annotation (noLocA)
+
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
@@ -49,6 +55,7 @@ import GHC.Data.Maybe
 import GHC.Data.BooleanFormula
 
 import Data.List ( findIndex, mapAccumL )
+import Language.Haskell.Syntax.Extension (LIdP)
 
 {-
 ************************************************************************
@@ -287,7 +294,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula $ fmap (mkIfLclName . getOccFS) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (mkIfLclName . getOccFS . unLoc) (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -336,9 +343,29 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
 
-toIfaceBooleanFormula :: BooleanFormula IfLclName -> IfaceBooleanFormula
-toIfaceBooleanFormula = \case
-    Var nm    -> IfVar    nm
-    And bfs   -> IfAnd    (map (toIfaceBooleanFormula . unLoc) bfs)
-    Or bfs    -> IfOr     (map (toIfaceBooleanFormula . unLoc) bfs)
-    Parens bf -> IfParens (toIfaceBooleanFormula . unLoc $ bf)
+toIfaceBooleanFormula :: (LIdP (GhcPass p) -> IfLclName) ->  BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
+toIfaceBooleanFormula f = go
+  where
+    go (Var nm   ) = IfVar    (f nm)
+    go (And bfs  ) = IfAnd    (map (go . unLoc) bfs)
+    go (Or bfs   ) = IfOr     (map (go . unLoc) bfs)
+    go (Parens bf) = IfParens (go . unLoc $ bf)
+
+fromIfaceBooleanFormula :: (IfLclName -> LIdP (GhcPass p))  -> IfaceBooleanFormula -> BooleanFormula (GhcPass p)
+fromIfaceBooleanFormula f = go
+  where
+    go (IfVar nm    ) = Var    $ f nm
+    go (IfAnd ibfs  ) = And    $ map (noLocA . go) ibfs
+    go (IfOr ibfs   ) = Or     $ map (noLocA . go) ibfs
+    go (IfParens ibf) = Parens $ (noLocA . go) ibf
+
+traverseIfaceBooleanFormula :: Applicative f
+                            => (IfLclName -> f (LIdP (GhcPass p)))
+                            -> IfaceBooleanFormula
+                            -> f (BooleanFormula (GhcPass p))
+traverseIfaceBooleanFormula f = go
+  where
+    go (IfVar nm    ) = Var     <$> f nm
+    go (IfAnd ibfs  ) = And     <$> traverse (fmap noLocA . go) ibfs
+    go (IfOr ibfs   ) = Or      <$> traverse (fmap noLocA . go) ibfs
+    go (IfParens ibf) = Parens  <$> (fmap noLocA . go) ibf
\ No newline at end of file


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -35,7 +35,7 @@ import GHC.Core.Class             ( className, classSCSelIds )
 import GHC.Core.ConLike           ( conLikeName )
 import GHC.Core.FVs
 import GHC.Core.DataCon           ( dataConNonlinearType )
-import GHC.Types.FieldLabel
+import GHC.Types.FieldLabel ( FieldLabel(flSelector) )
 import GHC.Hs
 import GHC.Hs.Syn.Type
 import GHC.Utils.Monad            ( concatMapM, MonadIO(liftIO) )
@@ -2043,8 +2043,22 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance ToHie (LBooleanFormula (LocatedN Name)) where
-  toHie (L span form) = concatM $ makeNode form (locA span) : case form of
+instance HiePass p => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+  toHie (L span form) = case hiePass @p of
+    HieRn -> concatM $ makeNode form (locA span) : case form of
+      Var a ->
+        [ toHie $ C Use a
+        ]
+      And forms ->
+        [ toHie forms
+        ]
+      Or forms ->
+        [ toHie forms
+        ]
+      Parens f ->
+        [ toHie f
+        ]
+    HieTc -> concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -35,7 +35,6 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
-        fromIfaceBooleanFormula,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
 
@@ -75,7 +74,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
@@ -98,6 +96,7 @@ import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
 import Data.Proxy
+import Data.List ( intersperse )
 
 infixl 3 &&&
 
@@ -218,13 +217,7 @@ data IfaceBooleanFormula
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
-
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
-fromIfaceBooleanFormula = \case
-    IfVar nm     -> Var    nm
-    IfAnd ibfs   -> And    (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfOr ibfs    -> Or     (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfParens ibf -> Parens (noLocA . fromIfaceBooleanFormula $ ibf)
+  deriving Eq
 
 data IfaceTyConParent
   = IfNoParent
@@ -1022,7 +1015,7 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
          , pprClassStandaloneKindSig ss clas (mkIfaceTyConKind binders constraintIfaceKind)
          , text "class" <+> pprIfaceDeclHead suppress_bndr_sig context ss clas binders <+> pprFundeps fds <+> pp_where
          , nest 2 (vcat [ vcat asocs, vcat dsigs
-                        , ppShowAllSubs ss (pprMinDef $ fromIfaceBooleanFormula minDef)])]
+                        , ppShowAllSubs ss (pprMinDef minDef)])]
     where
       pp_where = ppShowRhs ss $ ppUnless (null sigs && null ats) (text "where")
 
@@ -1039,13 +1032,30 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | showSub ss sg = Just $  pprIfaceClassOp ss sg
         | otherwise     = Nothing
 
-      pprMinDef :: BooleanFormula IfLclName -> SDoc
-      pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
+      pprMinDef :: IfaceBooleanFormula -> SDoc
+      pprMinDef minDef = ppUnless (ifLclIsTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
-        pprBooleanFormula
-          (\_ def -> cparen (isLexSym def) (ppr def)) 0 (fmap ifLclNameFS minDef) <+>
+        pprifLclBooleanFormula
+          (\_ def -> let fs = ifLclNameFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+      ifLclIsTrue :: IfaceBooleanFormula -> Bool
+      ifLclIsTrue (IfAnd []) = True
+      ifLclIsTrue _          = False
+
+      pprifLclBooleanFormula  :: (Rational -> IfLclName -> SDoc)
+                              -> Rational -> IfaceBooleanFormula -> SDoc
+      pprifLclBooleanFormula pprVar = go
+        where
+        go p (IfVar x)  = pprVar p x
+        go p (IfAnd []) = cparen (p > 0) empty
+        go p (IfAnd xs) = pprAnd p (map (go 3) xs)
+        go _ (IfOr  []) = keyword $ text "FALSE"
+        go p (IfOr  xs) = pprOr p (map (go 2) xs)
+        go p (IfParens x) = go p x
+        pprAnd p = cparen (p > 3) . fsep . punctuate comma
+        pprOr  p = cparen (p > 2) . fsep . intersperse vbar
+
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -32,6 +32,7 @@ module GHC.IfaceToCore (
         hydrateCgBreakInfo
  ) where
 
+
 import GHC.Prelude
 
 import GHC.ByteCode.Types
@@ -43,7 +44,7 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (toIfaceBooleanFormula)
+import GHC.Iface.Decl (traverseIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -124,7 +125,6 @@ import GHC.Types.TyThing
 import GHC.Types.Error
 
 import GHC.Fingerprint
-import qualified GHC.Data.BooleanFormula as BF
 
 import Control.Monad
 import GHC.Parser.Annotation
@@ -133,6 +133,7 @@ import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List (nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
@@ -297,9 +298,21 @@ mergeIfaceDecl d1 d2
                   plusNameEnv_C mergeIfaceClassOp
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
+
+          -- specialized version of BooleanFormula's MkOr.
+          mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+          mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+            where
+            fromOr bf = case bf of
+              (IfOr xs)  -> Just xs
+              (IfAnd []) -> Nothing
+              _        -> Just [bf]
+            mkOr' [x] = x
+            mkOr' xs = IfOr xs
+
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . BF.mkOr . map (noLocA . fromIfaceBooleanFormula) $ [bf1, bf2]
+                ifMinDef = mkOr [bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -795,8 +808,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef_occ = fromIfaceBooleanFormula if_mindef
-    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) mindef_occ
+    ; mindef <- traverseIfaceBooleanFormula (fmap noLocA . lookupIfaceTop . mkVarOccFS . ifLclNameFS) if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -39,9 +39,9 @@ module GHC.Parser
 where
 
 -- base
-import Control.Monad    ( unless, liftM, when, (<=<) )
+import Control.Monad      ( unless, liftM, when, (<=<) )
 import GHC.Exts
-import Data.Maybe       ( maybeToList )
+import Data.Maybe         ( maybeToList )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
@@ -3700,27 +3700,27 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
         | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula :: { LBooleanFormula GhcPs }
         : name_boolformula_and                      { $1 }
         | name_boolformula_and '|' name_boolformula
                            {% do { h <- addTrailingVbarL $1 (gl $2)
                                  ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
         : name_boolformula_and_list
                   { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula (LocatedN RdrName)] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
         : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
             {% do { h <- addTrailingCommaL $1 (gl $2)
                   ; return (h : $3) } }
 
-name_boolformula_atom :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
         : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
                                       (AnnList Nothing (Just (mop $1)) (Just (mcp $3)) [] []) }
         | name_var                  { sL1a $1 (Var $1) }


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,6 +80,7 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
+import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1137,7 +1138,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
-  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just (fmap unLoc bf)
-    toMinimalDef _                               = Nothing
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef _                             = Nothing
 
 {-
 Note [Polymorphic methods]


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -28,6 +28,7 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   , GRHSs )
 import {-# SOURCE #-} Language.Haskell.Syntax.Pat
   ( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
@@ -35,7 +36,6 @@ import Language.Haskell.Syntax.Type
 import GHC.Types.Fixity (Fixity)
 import GHC.Types.Basic (InlinePragma)
 
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 
 import Data.Void
@@ -465,7 +465,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -0,0 +1,87 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+
+module Language.Haskell.Syntax.BooleanFormula(
+  BooleanFormula(..), LBooleanFormula,
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr,
+  bfExplMap, bfExplTraverse) where
+
+import Prelude hiding ( init, last )
+import Data.List ( nub )
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+
+
+-- types
+type LBooleanFormula p = XRec p (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
+
+-- instances
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+
+-- jury rigged map and traverse functions.
+-- if we had Functor/Traversable (LbooleanFormula p) we could use as a constraint
+-- we wouldn't neeed the first higher order argument, but because LBooleanformula
+-- is a type synonym that's no can do.
+bfExplMap :: ((BooleanFormula p -> BooleanFormula p') -> LBooleanFormula p -> LBooleanFormula p')
+          -> (LIdP p -> LIdP p')
+          -> BooleanFormula p -> BooleanFormula p'
+bfExplMap lbfMap f = go
+  where
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (lbfMap go) bfs
+    go (Or     bfs) = Or      $ map (lbfMap go) bfs
+    go (Parens bf ) = Parens  $ lbfMap go bf
+
+bfExplTraverse  :: Applicative f
+                => ((BooleanFormula p -> f (BooleanFormula p')) -> LBooleanFormula p -> f (LBooleanFormula p'))
+                -> (LIdP p -> f (LIdP p'))
+                -> BooleanFormula p -> f (BooleanFormula p')
+bfExplTraverse lbfTraverse f  = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (lbfTraverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (lbfTraverse go) bfs
+    go (Parens bf ) = Parens <$> lbfTraverse go bf
+
+-- smart constructors
+-- see note [Simplification of BooleanFormulas]
+mkVar :: LIdP p -> BooleanFormula p
+mkVar = Var
+
+mkFalse, mkTrue :: BooleanFormula p
+mkFalse = Or []
+mkTrue = And []
+
+-- Convert a Bool to a BooleanFormula
+mkBool :: Bool -> BooleanFormula p
+mkBool False = mkFalse
+mkBool True  = mkTrue
+
+-- Make a conjunction, and try to simplify
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
+    (And xs) -> Just xs
+     -- assume that xs are already simplified
+     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
+    (Or [])  -> Nothing
+     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
+    _        -> Just [bf]
+  mkAnd' [x] = unXRec @p x
+  mkAnd' xs = And xs
+
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromOr bf = case unXRec @p bf of
+    (Or xs)  -> Just xs
+    (And []) -> Nothing
+    _        -> Just [bf]
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
compiler/ghc.cabal.in
=====================================
@@ -989,6 +989,7 @@ Library
         Language.Haskell.Syntax
         Language.Haskell.Syntax.Basic
         Language.Haskell.Syntax.Binds
+        Language.Haskell.Syntax.BooleanFormula
         Language.Haskell.Syntax.Decls
         Language.Haskell.Syntax.Expr
         Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -234,6 +234,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2984,7 +2984,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4695,7 +4695,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -45,6 +45,7 @@ import GHC.Builtin.Types
   , promotedNilDataCon
   , unitTy
   )
+
 import GHC.Builtin.Types.Prim (alphaTyVars)
 import GHC.Core.Class
 import GHC.Core.Coercion.Axiom
@@ -176,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA . fmap noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -34,6 +34,7 @@ import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
 import Prelude hiding (mapM)
+import Language.Haskell.Syntax.BooleanFormula (bfExplTraverse)
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -770,7 +771,7 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- traverse (traverse lookupRn) s
+    s' <- bfExplTraverse traverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -52,6 +52,7 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 import GHC
 import qualified GHC.Data.Strict as Strict
+import GHC.Data.BooleanFormula (BooleanFormula)
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
@@ -818,6 +819,7 @@ type instance Anno (HsDecl DocNameI) = SrcSpanAnnA
 type instance Anno (FamilyResultSig DocNameI) = EpAnn NoEpAnns
 type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
+type instance Anno (BooleanFormula DocNameI) = SrcSpanAnnL
 
 type XRecCond a =
   ( XParTy a ~ AnnParen



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b77bee8d1cfd11c7fbbe74ca936efe4a3b945f9

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 22:05:28 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 07 Oct 2024 18:05:28 -0400
Subject: [Git][ghc/ghc][wip/T25281] More
Message-ID: <67045b28bc7de_1a40874902f09861c@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
cada7c27 by Simon Peyton Jones at 2024-10-07T22:38:04+01:00
More

- - - - -


2 changed files:

- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
=====================================
@@ -362,7 +362,7 @@ ppFamDecl
   -> Bool
   -- ^ unicode
   -> LaTeX
-ppFamDecl associated doc instances decl unicode =
+ppFamDecl associated doc instances decl@(FamDecl{}) unicode =
   declWithDoc
     (ppFamHeader (tcdFam decl) unicode associated <+> whereBit)
     (if null body then Nothing else Just (vcat body))
@@ -401,6 +401,9 @@ ppFamDecl associated doc instances decl unicode =
 
     instancesBit = ppDocInstances unicode instances
 
+ppFamDecl _ _ _ _ _ = error "ppFamDecl"
+  -- Should never be called on a non-FamDecl
+
 -- | Print the LHS of a type\/data family declaration.
 ppFamHeader
   :: FamilyDecl DocNameI
@@ -811,10 +814,11 @@ ppInstDecl :: Bool -> InstHead DocNameI -> LaTeX
 ppInstDecl unicode (InstHead{..}) = case ihdInstType of
   ClassInst ctx _ _ _ -> keyword "instance" <+> ppContextNoLocs ctx unicode <+> typ
   TypeInst rhs -> keyword "type" <+> keyword "instance" <+> typ <+> tibody rhs
-  DataInst dd ->
+  DataInst dd@(DataDecl {}) ->
     let cons = dd_cons (tcdDataDefn dd)
         pref = case cons of NewTypeCon _ -> keyword "newtype"; DataTypeCons _ _ -> keyword "data"
      in pref <+> keyword "instance" <+> typ
+  DataInst _ -> error "ppInstDecl"
   where
     typ = ppAppNameTypes ihdClsName ihdTypes unicode
     tibody = maybe empty (\t -> equals <+> ppType unicode t)
@@ -849,7 +853,7 @@ ppDataDecl
   -> Bool
   -- ^ unicode
   -> LaTeX
-ppDataDecl pats instances subdocs doc dataDecl unicode =
+ppDataDecl pats instances subdocs doc dataDecl@(DataDecl {}) unicode =
   declWithDoc
     (ppDataHeader dataDecl unicode <+> whereBit)
     (if null body then Nothing else Just (vcat body))
@@ -890,6 +894,8 @@ ppDataDecl pats instances subdocs doc dataDecl unicode =
               $$ text "\\end{tabulary}\\par"
 
     instancesBit = ppDocInstances unicode instances
+ppDataDecl _ _ _ _ _ _ = error "ppDataDecl"
+  -- Should never be called on a non-DataDecl
 
 -- ppConstrHdr is for (non-GADT) existentials constructors' syntax
 ppConstrHdr


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -886,7 +886,7 @@ type instance XBndrNoKind DocNameI = NoExtField
 type instance XXBndrKind DocNameI = DataConCantHappen
 
 type instance XCFieldOcc DocNameI = DocName
-type instance XXFieldOcc DocNameI = NoExtField
+type instance XXFieldOcc DocNameI = DataConCantHappen
 
 type instance XFixitySig DocNameI = NoExtField
 type instance XFixSig DocNameI = NoExtField
@@ -941,6 +941,7 @@ type instance XClassDecl DocNameI = NoExtField
 type instance XDataDecl DocNameI = NoExtField
 type instance XSynDecl DocNameI = NoExtField
 type instance XFamDecl DocNameI = NoExtField
+type instance XXHsDataDefn DocNameI = DataConCantHappen
 type instance XXFamilyDecl DocNameI = DataConCantHappen
 type instance XXTyClDecl DocNameI = DataConCantHappen
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 22:38:13 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 07 Oct 2024 18:38:13 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-pat
Message-ID: <670462d54e6b6_388a8214c29c328c0@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-pat at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-pat
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 22:38:41 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 07 Oct 2024 18:38:41 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] 13 commits: Deprecation for
 WarnCompatUnqualifiedImports
Message-ID: <670462f13cf7a_388a8210ae7833039@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
8e2e925f by Hassan Al-Awwadi at 2024-10-08T00:33:30+02:00
The main purpose of this commit is to rip RdrName out of FieldOcc, and
as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade <Jade512 at proton.me>
                @Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Gen/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e2d3926a2d547f7fa072fa52ee9de2b168a6e89...8e2e925f4d15858de046ad801f015af6c9cef159

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e2d3926a2d547f7fa072fa52ee9de2b168a6e89...8e2e925f4d15858de046ad801f015af6c9cef159
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:23:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:23:25 -0400
Subject: [Git][ghc/ghc][master] Remove the wrapper/coercion-passing logic for
 submultiplicity checks
Message-ID: <67046d6d30c53_388a8252a2244937a@gitlab.mail>



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


Commits:
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -


30 changed files:

- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcMType.hs-boot
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Utils/Unify.hs-boot
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/linear/should_fail/LinearLet7.stderr


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:24:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:24:02 -0400
Subject: [Git][ghc/ghc][master] AArch64: Implement switch/jump tables (#19912)
Message-ID: <67046d92955fb_388a825109a052824@gitlab.mail>



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


Commits:
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -


3 changed files:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
=====================================
@@ -23,7 +23,7 @@ import GHC.Cmm.DebugBlock
 import GHC.CmmToAsm.Monad
    ( NatM, getNewRegNat
    , getPicBaseMaybeNat, getPlatform, getConfig
-   , getDebugBlock, getFileId
+   , getDebugBlock, getFileId, getNewLabelNat
    )
 -- import GHC.CmmToAsm.Instr
 import GHC.CmmToAsm.PIC
@@ -50,7 +50,7 @@ import GHC.Types.Unique.DSM
 import GHC.Data.OrdList
 import GHC.Utils.Outputable
 
-import Control.Monad    ( mapAndUnzipM, foldM )
+import Control.Monad    ( mapAndUnzipM )
 import GHC.Float
 
 import GHC.Types.Basic
@@ -209,43 +209,79 @@ annExpr e instr {- debugIsOn -} = ANN (text . show $ e) instr
 -- -----------------------------------------------------------------------------
 -- Generating a table-branch
 
--- TODO jump tables would be a lot faster, but we'll use bare bones for now.
--- this is usually done by sticking the jump table ids into an instruction
--- and then have the @generateJumpTableForInstr@ callback produce the jump
--- table as a static.
+-- | Generate jump to jump table target
 --
--- See Ticket 19912
---
--- data SwitchTargets =
---    SwitchTargets
---        Bool                       -- Signed values
---        (Integer, Integer)         -- Range
---        (Maybe Label)              -- Default value
---        (M.Map Integer Label)      -- The branches
---
--- Non Jumptable plan:
--- xE <- expr
+-- The index into the jump table is calulated by evaluating @expr at . The
+-- corresponding table entry contains the relative address to jump to (relative
+-- to the jump table's first entry / the table's own label).
+genSwitch :: NCGConfig -> CmmExpr -> SwitchTargets -> NatM InstrBlock
+genSwitch config expr targets = do
+  (reg, fmt1, e_code) <- getSomeReg indexExpr
+  let fmt = II64
+  targetReg <- getNewRegNat fmt
+  lbl <- getNewLabelNat
+  dynRef <- cmmMakeDynamicReference config DataReference lbl
+  (tableReg, fmt2, t_code) <- getSomeReg dynRef
+  let code =
+        toOL
+          [ COMMENT (text "indexExpr" <+> (text . show) indexExpr),
+            COMMENT (text "dynRef" <+> (text . show) dynRef)
+          ]
+          `appOL` e_code
+          `appOL` t_code
+          `appOL` toOL
+            [ COMMENT (ftext "Jump table for switch"),
+              -- index to offset into the table (relative to tableReg)
+              annExpr expr (LSL (OpReg (formatToWidth fmt1) reg) (OpReg (formatToWidth fmt1) reg) (OpImm (ImmInt 3))),
+              -- calculate table entry address
+              ADD (OpReg W64 targetReg) (OpReg (formatToWidth fmt1) reg) (OpReg (formatToWidth fmt2) tableReg),
+              -- load table entry (relative offset from tableReg (first entry) to target label)
+              LDR II64 (OpReg W64 targetReg) (OpAddr (AddrRegImm targetReg (ImmInt 0))),
+              -- calculate absolute address of the target label
+              ADD (OpReg W64 targetReg) (OpReg W64 targetReg) (OpReg W64 tableReg),
+              -- prepare jump to target label
+              J_TBL ids (Just lbl) targetReg
+            ]
+  return code
+  where
+    -- See Note [Sub-word subtlety during jump-table indexing] in
+    -- GHC.CmmToAsm.X86.CodeGen for why we must first offset, then widen.
+    indexExpr0 = cmmOffset platform expr offset
+    -- We widen to a native-width register to sanitize the high bits
+    indexExpr =
+      CmmMachOp
+        (MO_UU_Conv expr_w (platformWordWidth platform))
+        [indexExpr0]
+    expr_w = cmmExprWidth platform expr
+    (offset, ids) = switchTargetsToTable targets
+    platform = ncgPlatform config
+
+-- | Generate jump table data (if required)
 --
-genSwitch :: CmmExpr -> SwitchTargets -> NatM InstrBlock
-genSwitch expr targets = do -- pprPanic "genSwitch" (ppr expr)
-  (reg, format, code) <- getSomeReg expr
-  let w = formatToWidth format
-  let mkbranch acc (key, bid) = do
-        (keyReg, _format, code) <- getSomeReg (CmmLit (CmmInt key w))
-        return $ code `appOL`
-                 toOL [ CMP (OpReg w reg) (OpReg w keyReg)
-                      , BCOND EQ (TBlock bid)
-                      ] `appOL` acc
-      def_code = case switchTargetsDefault targets of
-        Just bid -> unitOL (B (TBlock bid))
-        Nothing  -> nilOL
-
-  switch_code <- foldM mkbranch nilOL (switchTargetsCases targets)
-  return $ code `appOL` switch_code `appOL` def_code
-
--- We don't do jump tables for now, see Ticket 19912
-generateJumpTableForInstr :: NCGConfig -> Instr
-  -> Maybe (NatCmmDecl RawCmmStatics Instr)
+-- The idea is to emit one table entry per case. The entry is the relative
+-- address of the block to jump to (relative to the table's first entry /
+-- table's own label.) The calculation itself is done by the linker.
+generateJumpTableForInstr ::
+  NCGConfig ->
+  Instr ->
+  Maybe (NatCmmDecl RawCmmStatics Instr)
+generateJumpTableForInstr config (J_TBL ids (Just lbl) _) =
+  let jumpTable =
+        map jumpTableEntryRel ids
+        where
+          jumpTableEntryRel Nothing =
+            CmmStaticLit (CmmInt 0 (ncgWordWidth config))
+          jumpTableEntryRel (Just blockid) =
+            CmmStaticLit
+              ( CmmLabelDiffOff
+                  blockLabel
+                  lbl
+                  0
+                  (ncgWordWidth config)
+              )
+            where
+              blockLabel = blockLbl blockid
+   in Just (CmmData (Section ReadOnlyData lbl) (CmmStaticsRaw lbl jumpTable))
 generateJumpTableForInstr _ _ = Nothing
 
 -- -----------------------------------------------------------------------------
@@ -266,6 +302,7 @@ stmtToInstrs :: CmmNode e x -- ^ Cmm Statement
 stmtToInstrs stmt = do
   -- traceM $ "-- -------------------------- stmtToInstrs -------------------------- --\n"
   --     ++ showSDocUnsafe (ppr stmt)
+  config <- getConfig
   platform <- getPlatform
   case stmt of
     CmmUnsafeForeignCall target result_regs args
@@ -294,7 +331,7 @@ stmtToInstrs stmt = do
       CmmCondBranch arg true false _prediction ->
           genCondBranch true false arg
 
-      CmmSwitch arg ids -> genSwitch arg ids
+      CmmSwitch arg ids -> genSwitch config arg ids
 
       CmmCall { cml_target = arg } -> genJump arg
 
@@ -339,12 +376,6 @@ getRegisterReg platform (CmmGlobal reg@(GlobalRegUse mid _))
         -- ones which map to a real machine register on this
         -- platform.  Hence if it's not mapped to a registers something
         -- went wrong earlier in the pipeline.
--- | Convert a BlockId to some CmmStatic data
--- TODO: Add JumpTable Logic, see Ticket 19912
--- jumpTableEntry :: NCGConfig -> Maybe BlockId -> CmmStatic
--- jumpTableEntry config Nothing   = CmmStaticLit (CmmInt 0 (ncgWordWidth config))
--- jumpTableEntry _ (Just blockid) = CmmStaticLit (CmmLabel blockLabel)
---     where blockLabel = blockLbl blockid
 
 -- -----------------------------------------------------------------------------
 -- General things for putting together code sequences


=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -29,7 +29,7 @@ import GHC.Types.Unique.DSM
 
 import GHC.Utils.Panic
 
-import Data.Maybe (fromMaybe)
+import Data.Maybe (fromMaybe, catMaybes)
 
 import GHC.Stack
 
@@ -120,6 +120,7 @@ regUsageOfInstr platform instr = case instr of
   ORR dst src1 src2        -> usage (regOp src1 ++ regOp src2, regOp dst)
   -- 4. Branch Instructions ----------------------------------------------------
   J t                      -> usage (regTarget t, [])
+  J_TBL _ _ t              -> usage ([t], [])
   B t                      -> usage (regTarget t, [])
   BCOND _ t                -> usage (regTarget t, [])
   BL t ps                  -> usage (regTarget t ++ ps, callerSavedRegisters)
@@ -275,10 +276,11 @@ patchRegsOfInstr instr env = case instr of
     ORR o1 o2 o3   -> ORR  (patchOp o1) (patchOp o2) (patchOp o3)
 
     -- 4. Branch Instructions --------------------------------------------------
-    J t            -> J (patchTarget t)
-    B t            -> B (patchTarget t)
-    BL t rs        -> BL (patchTarget t) rs
-    BCOND c t      -> BCOND c (patchTarget t)
+    J t               -> J (patchTarget t)
+    J_TBL ids mbLbl t -> J_TBL ids mbLbl (env t)
+    B t               -> B (patchTarget t)
+    BL t rs           -> BL (patchTarget t) rs
+    BCOND c t         -> BCOND c (patchTarget t)
 
     -- 5. Atomic Instructions --------------------------------------------------
     -- 6. Conditional Instructions ---------------------------------------------
@@ -332,6 +334,7 @@ isJumpishInstr instr = case instr of
     CBZ{} -> True
     CBNZ{} -> True
     J{} -> True
+    J_TBL{} -> True
     B{} -> True
     BL{} -> True
     BCOND{} -> True
@@ -345,6 +348,7 @@ jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i
 jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]]
 jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]]
 jumpDestsOfInstr (J t) = [id | TBlock id <- [t]]
+jumpDestsOfInstr (J_TBL ids _mbLbl _r) = catMaybes ids
 jumpDestsOfInstr (B t) = [id | TBlock id <- [t]]
 jumpDestsOfInstr (BL t _) = [ id | TBlock id <- [t]]
 jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]]
@@ -353,6 +357,11 @@ jumpDestsOfInstr _ = []
 canFallthroughTo :: Instr -> BlockId -> Bool
 canFallthroughTo (ANN _ i) bid = canFallthroughTo i bid
 canFallthroughTo (J (TBlock target)) bid = bid == target
+canFallthroughTo (J_TBL targets _ _) bid = all isTargetBid targets
+  where
+    isTargetBid target = case target of
+      Nothing -> True
+      Just target -> target == bid
 canFallthroughTo (B (TBlock target)) bid = bid == target
 canFallthroughTo _ _ = False
 
@@ -366,6 +375,7 @@ patchJumpInstr instr patchF
         CBZ r (TBlock bid) -> CBZ r (TBlock (patchF bid))
         CBNZ r (TBlock bid) -> CBNZ r (TBlock (patchF bid))
         J (TBlock bid) -> J (TBlock (patchF bid))
+        J_TBL ids mbLbl r -> J_TBL (map (fmap patchF) ids) mbLbl r
         B (TBlock bid) -> B (TBlock (patchF bid))
         BL (TBlock bid) ps -> BL (TBlock (patchF bid)) ps
         BCOND c (TBlock bid) -> BCOND c (TBlock (patchF bid))
@@ -540,6 +550,7 @@ allocMoreStack platform slots proc@(CmmProc info lbl live (ListGraph code)) = do
 
       insert_dealloc insn r = case insn of
         J _ -> dealloc ++ (insn : r)
+        J_TBL {} -> dealloc ++ (insn : r)
         ANN _ (J _) -> dealloc ++ (insn : r)
         _other | jumpDestsOfInstr insn /= []
             -> patchJumpInstr insn retarget : r
@@ -668,6 +679,7 @@ data Instr
     | CBNZ Operand Target -- if op /= 0, then branch.
     -- Branching.
     | J Target            -- like B, but only generated from genJump. Used to distinguish genJumps from others.
+    | J_TBL [Maybe BlockId] (Maybe CLabel) Reg -- A jump instruction with data for switch/jump tables
     | B Target            -- unconditional branching b/br. (To a blockid, label or register)
     | BL Target [Reg] -- branch and link (e.g. set x30 to next pc, and branch)
     | BCOND Cond Target   -- branch with condition. b.
@@ -758,6 +770,7 @@ instrCon i =
       CBZ{} -> "CBZ"
       CBNZ{} -> "CBNZ"
       J{} -> "J"
+      J_TBL {} -> "J_TBL"
       B{} -> "B"
       BL{} -> "BL"
       BCOND{} -> "BCOND"


=====================================
compiler/GHC/CmmToAsm/AArch64/Ppr.hs
=====================================
@@ -425,6 +425,7 @@ pprInstr platform instr = case instr of
 
   -- 4. Branch Instructions ----------------------------------------------------
   J t            -> pprInstr platform (B t)
+  J_TBL _ _ r    -> pprInstr platform (B (TReg r))
   B (TBlock bid) -> line $ text "\tb" <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid))
   B (TLabel lbl) -> line $ text "\tb" <+> pprAsmLabel platform lbl
   B (TReg r)     -> line $ text "\tbr" <+> pprReg W64 r



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d22611665117131d1c7c3c0287696e8efcc88f2

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:24:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:24:53 -0400
Subject: [Git][ghc/ghc][master] Fixes #25256, missing parens inside TH-printed
 pattern type signature
Message-ID: <67046dc58c3a3_388a824c578457662@gitlab.mail>



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


Commits:
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -


4 changed files:

- libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs
- + testsuite/tests/th/T25256.hs
- + testsuite/tests/th/T25256.stdout
- testsuite/tests/th/all.T


Changes:

=====================================
libraries/ghc-boot-th/GHC/Internal/TH/Ppr.hs
=====================================
@@ -398,7 +398,8 @@ pprPat _ (RecP nm fs)
             <+> braces (sep $ punctuate comma $
                         map (\(s,p) -> pprName' Applied s <+> equals <+> ppr p) fs)
 pprPat _ (ListP ps) = brackets (commaSep ps)
-pprPat i (SigP p t) = parensIf (i > noPrec) $ ppr p <+> dcolon <+> ppr t
+pprPat i (SigP p t) = parensIf (i > noPrec) $ pprPat sigPrec p
+                                          <+> dcolon <+> pprType sigPrec t
 pprPat _ (ViewP e p) = parens $ pprExp noPrec e <+> text "->" <+> pprPat noPrec p
 pprPat _ (TypeP t) = parens $ text "type" <+> ppr t
 pprPat _ (InvisP t) = parens $ text "@" <+> ppr t


=====================================
testsuite/tests/th/T25256.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE Haskell2010, ScopedTypeVariables, TemplateHaskell #-}
+
+import Language.Haskell.TH (runQ, Type (UnboxedSumT, UnboxedTupleT))
+import Language.Haskell.TH.Ppr (pprint)
+
+main = runQ [d| f ((a :: [Char]) :: String) = (a :: [Char]) :: String |] >>= putStrLn . pprint


=====================================
testsuite/tests/th/T25256.stdout
=====================================
@@ -0,0 +1 @@
+f_0 ((a_1 :: [GHC.Types.Char]) :: GHC.Internal.Base.String) = (a_1 :: [GHC.Types.Char]) :: GHC.Internal.Base.String


=====================================
testsuite/tests/th/all.T
=====================================
@@ -618,6 +618,7 @@ test('T24837', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T24894', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T24911', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T24997', normal, compile_and_run, [''])
+test('T25256', normal, compile_and_run, [''])
 test('T24572a', normal, compile, [''])
 test('T24572b', normal, compile_fail, [''])
 test('T24572c', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fe621dd0e3209291b100e25909ef751ec9612f5

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:25:56 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:25:56 -0400
Subject: [Git][ghc/ghc][master] Better documentation for floatRange function
Message-ID: <67046e04a509b_388a824ce71c65297@gitlab.mail>



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


Commits:
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/Float.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Float.hs
=====================================
@@ -282,8 +282,10 @@ class  (RealFrac a, Floating a) => RealFloat a  where
     -- | a constant function, returning the number of digits of
     -- 'floatRadix' in the significand
     floatDigits         :: a -> Int
-    -- | a constant function, returning the lowest and highest values
-    -- the exponent may assume
+    -- | A constant function, returning the lowest and highest values
+    -- that @'exponent' x@ may assume for a normal @x at .
+    -- The relation to IEEE @emin@ and @emax@ is
+    -- @'floatRange' x = (emin + 1, emax + 1)@.
     floatRange          :: a -> (Int,Int)
     -- | The function 'decodeFloat' applied to a real floating-point
     -- number returns the significand expressed as an 'Integer' and an



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:27:05 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:27:05 -0400
Subject: [Git][ghc/ghc][master] Adjust progress message for hadrian to include
 cwd.
Message-ID: <67046e4941fb_388a82a7ec8469989@gitlab.mail>



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


Commits:
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -


3 changed files:

- hadrian/hadrian.cabal
- hadrian/src/Main.hs
- + hadrian/src/Progress.hs


Changes:

=====================================
hadrian/hadrian.cabal
=====================================
@@ -74,6 +74,7 @@ executable hadrian
                        , Oracles.ModuleFiles
                        , Oracles.TestSettings
                        , Packages
+                       , Progress
                        , Rules
                        , Rules.BinaryDist
                        , Rules.CabalReinstall


=====================================
hadrian/src/Main.hs
=====================================
@@ -27,6 +27,7 @@ import qualified Rules.Selftest
 import qualified Rules.SourceDist
 import qualified Rules.Test
 import qualified UserSettings
+import qualified Progress
 
 main :: IO ()
 main = do
@@ -56,7 +57,7 @@ main = do
         options = shakeOptions
             { shakeChange   = ChangeModtimeAndDigest
             , shakeFiles    = buildRoot -/- Base.shakeFilesDir
-            , shakeProgress = progressSimple
+            , shakeProgress = Progress.hadrianProgress cwd
             , shakeRebuild  = rebuild
             , shakeTimings  = False
             , shakeColor    = shakeColor


=====================================
hadrian/src/Progress.hs
=====================================
@@ -0,0 +1,12 @@
+module Progress (hadrianProgress) where
+
+import Development.Shake
+
+-- | A simple method for displaying progress messages, suitable for using as 'Development.Shake.shakeProgress'.
+--   This is the shakeProgress function hadrian uses. It writes the current progress to the titlebar every five seconds
+--   using 'progressTitlebar', and calls any @shake-progress@ program on the @$PATH@ using 'progressProgram'.
+hadrianProgress :: String -> IO Progress -> IO ()
+hadrianProgress cwd p = do
+    program <- progressProgram
+    progressDisplay 5 (\status -> let s = status<> "(" <> cwd <> ")" in progressTitlebar s >> program s) p
+



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:27:56 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:27:56 -0400
Subject: [Git][ghc/ghc][master] CCallConv test: Align argument types
Message-ID: <67046e7c79d41_388a824f49f8769e5@gitlab.mail>



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


Commits:
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -


3 changed files:

- testsuite/tests/codeGen/should_run/CCallConv.stdout
- testsuite/tests/codeGen/should_run/CCallConv_c.c
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
testsuite/tests/codeGen/should_run/CCallConv.stdout
=====================================
@@ -7,8 +7,8 @@ a4: 0xffffffff -1
 a5: 0xffffffff -1
 a6: 0xffffffff -1
 a7: 0xffffffff -1
-s0: 0xffffffff -1
-s1: 0xff 255
+s0: 0xff 255
+s1: 0xffffffff -1
 "fun8 result:502"
 fun16:
 a0: 0xffffffff -1
@@ -19,8 +19,8 @@ a4: 0xffffffff -1
 a5: 0xffffffff -1
 a6: 0xffffffff -1
 a7: 0xffffffff -1
-s0: 0xffffffff -1
-s1: 0xffff 65535
+s0: 0xffff 65535
+s1: 0xffffffff -1
 "fun16 result:131062"
 fun32:
 a0: 0xffffffff -1
@@ -31,8 +31,8 @@ a4: 0xffffffff -1
 a5: 0xffffffff -1
 a6: 0xffffffff -1
 a7: 0xffffffff -1
-s0: 0xffffffff -1
-s1: 0xffffffff 4294967295
+s0: 0xffffffff 4294967295
+s1: 0xffffffff -1
 "fun32 result:8589934582"
 funFloat:
 a0: 1.000000


=====================================
testsuite/tests/codeGen/should_run/CCallConv_c.c
=====================================
@@ -2,7 +2,7 @@
 #include 
 
 int64_t fun8(int8_t a0, uint8_t a1, int8_t a2, int8_t a3, int8_t a4, int8_t a5,
-             int8_t a6, int8_t a7, int8_t s0, uint8_t s1) {
+             int8_t a6, int8_t a7, uint8_t s0, int8_t s1) {
   printf("fun8:\n");
   printf("a0: %#x %hhd\n", a0, a0);
   printf("a1: %#x %hhu\n", a1, a1);
@@ -12,8 +12,8 @@ int64_t fun8(int8_t a0, uint8_t a1, int8_t a2, int8_t a3, int8_t a4, int8_t a5,
   printf("a5: %#x %hhd\n", a5, a5);
   printf("a6: %#x %hhd\n", a6, a6);
   printf("a7: %#x %hhd\n", a7, a7);
-  printf("s0: %#x %hhd\n", s0, s0);
-  printf("s1: %#x %hhu\n", s1, s1);
+  printf("s0: %#x %hhu\n", s0, s0);
+  printf("s1: %#x %hhd\n", s1, s1);
 
   fflush(stdout);
 
@@ -21,7 +21,7 @@ int64_t fun8(int8_t a0, uint8_t a1, int8_t a2, int8_t a3, int8_t a4, int8_t a5,
 }
 
 int64_t fun16(int16_t a0, uint16_t a1, int16_t a2, int16_t a3, int16_t a4,
-              int16_t a5, int16_t a6, int16_t a7, int16_t s0, uint16_t s1) {
+              int16_t a5, int16_t a6, int16_t a7, uint16_t s0, int16_t s1) {
   printf("fun16:\n");
   printf("a0: %#x %hd\n", a0, a0);
   printf("a1: %#x %hu\n", a1, a1);
@@ -31,8 +31,8 @@ int64_t fun16(int16_t a0, uint16_t a1, int16_t a2, int16_t a3, int16_t a4,
   printf("a5: %#x %hd\n", a5, a5);
   printf("a6: %#x %hd\n", a6, a6);
   printf("a7: %#x %hd\n", a7, a7);
-  printf("s0: %#x %hd\n", s0, s0);
-  printf("s1: %#x %hu\n", s1, s1);
+  printf("s0: %#x %hu\n", s0, s0);
+  printf("s1: %#x %hd\n", s1, s1);
 
   fflush(stdout);
 
@@ -40,7 +40,7 @@ int64_t fun16(int16_t a0, uint16_t a1, int16_t a2, int16_t a3, int16_t a4,
 }
 
 int64_t fun32(int32_t a0, uint32_t a1, int32_t a2, int32_t a3, int32_t a4,
-              int32_t a5, int32_t a6, int32_t a7, int32_t s0, uint32_t s1) {
+              int32_t a5, int32_t a6, int32_t a7, uint32_t s0, int32_t s1) {
   printf("fun32:\n");
   printf("a0: %#x %d\n", a0, a0);
   printf("a1: %#x %u\n", a1, a1);
@@ -50,8 +50,8 @@ int64_t fun32(int32_t a0, uint32_t a1, int32_t a2, int32_t a3, int32_t a4,
   printf("a5: %#x %d\n", a5, a5);
   printf("a6: %#x %d\n", a6, a6);
   printf("a7: %#x %d\n", a7, a7);
-  printf("s0: %#x %d\n", s0, s0);
-  printf("s1: %#x %u\n", s1, s1);
+  printf("s0: %#x %u\n", s0, s0);
+  printf("s1: %#x %d\n", s1, s1);
 
   fflush(stdout);
 


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -251,4 +251,4 @@ test('T23034', req_c, compile_and_run, ['-O2 T23034_c.c'])
 test('T24700', normal, compile_and_run, ['-O'])
 test('T24893', normal, compile_and_run, ['-O'])
 
-test('CCallConv', [req_c, when(arch('wasm32'), fragile(25249))], compile_and_run, ['CCallConv_c.c'])
+test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5fd320da57bb52458bb1e8c14c5311129d88a3a7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:28:18 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:28:18 -0400
Subject: [Git][ghc/ghc][master] hadrian: remove unused ghciWithDebugger field
 from flavour config
Message-ID: <67046e92d2ae7_388a8252a22477195@gitlab.mail>



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


Commits:
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -


3 changed files:

- hadrian/doc/user-settings.md
- hadrian/src/Flavour/Type.hs
- hadrian/src/Settings/Default.hs


Changes:

=====================================
hadrian/doc/user-settings.md
=====================================
@@ -33,9 +33,6 @@ data Flavour = Flavour {
     rtsWays :: Ways,
     -- | Build dynamic GHC programs.
     dynamicGhcPrograms :: Action Bool,
-    -- | Enable GHCi debugger.
-    ghciWithDebugger :: Stage -- ^ stage of the /built/ compiler
-                     -> Bool,
     -- | Build profiled GHC.
     ghcProfiled :: Stage -- ^ stage of the /built/ compiler
                 -> Bool,


=====================================
hadrian/src/Flavour/Type.hs
=====================================
@@ -32,9 +32,6 @@ data Flavour = Flavour {
     rtsWays :: Ways,
     -- | Build dynamic GHC programs.
     dynamicGhcPrograms :: Action Bool,
-    -- | Enable GHCi debugger.
-    ghciWithDebugger :: Stage -- ^ stage of the /built/ compiler
-                     -> Bool,
     -- | Build profiled GHC.
     ghcProfiled :: Stage -- ^ stage of the /built/ compiler
                 -> Bool,


=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -276,7 +276,6 @@ defaultFlavour = Flavour
     , libraryWays        = defaultLibraryWays
     , rtsWays            = defaultRtsWays
     , dynamicGhcPrograms = defaultDynamicGhcPrograms
-    , ghciWithDebugger   = const False
     , ghcProfiled        = const False
     , ghcDebugged        = const False
     , ghcThreaded        = const True



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct  7 23:28:41 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 07 Oct 2024 19:28:41 -0400
Subject: [Git][ghc/ghc][master] user's guide: update docs for X86 CPU flags
Message-ID: <67046ea910b8e_388a82ce5b08773d9@gitlab.mail>



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


Commits:
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -


1 changed file:

- docs/users_guide/using.rst


Changes:

=====================================
docs/users_guide/using.rst
=====================================
@@ -1590,78 +1590,48 @@ Some flags only make sense for particular target platforms.
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX instructions.
 
 .. ghc-flag:: -mavx2
     :shortdesc: (x86 only) Enable support for AVX2 SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX2 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX2 instructions.
 
 .. ghc-flag:: -mavx512cd
     :shortdesc: (x86 only) Enable support for AVX512-CD SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-CD instructions.
 
 .. ghc-flag:: -mavx512er
     :shortdesc: (x86 only) Enable support for AVX512-ER SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-ER instructions.
 
 .. ghc-flag:: -mavx512f
     :shortdesc: (x86 only) Enable support for AVX512-F SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-F instructions.
 
 .. ghc-flag:: -mavx512pf
     :shortdesc: (x86 only) Enable support for AVX512-PF SIMD extensions
     :type: dynamic
     :category: platform-options
 
-    (x86 only) These SIMD instructions are currently not supported by
-    the :ref:`native code generator `. Enabling this flag
-    has no effect and is only present for future extensions.
-
-    The :ref:`LLVM backend ` may use AVX512 if your
-    processor supports it, but detects this automatically, so no flag is
-    required.
+    (x86 only) This flag allows the code generator (whether the :ref:`native code generator `
+    or the :ref:`LLVM backend `) to emit x86_64 AVX512-PF instructions.
 
 .. ghc-flag:: -msse
     :shortdesc: (x86 only) Use SSE for floating-point operations
@@ -1706,15 +1676,9 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only) Use the SSE3 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `.
-
-    Note that the current version does not use SSE3 specific instructions
-    and only requires SSE2 processor support.
-
-    The :ref:`LLVM backend ` will also use
-    SSE3 if your processor supports it but detects this automatically
-    so no flag is required.
+    implement some floating point and bit operations
+    (whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `).
 
 .. ghc-flag:: -msse4
     :shortdesc: (x86 only) Use SSE4 for floating-point operations
@@ -1722,15 +1686,8 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only) Use the SSE4 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `.
-
-    Note that the current version does not use SSE4 specific instructions
-    and only requires SSE2 processor support.
-
-    The :ref:`LLVM backend ` will also use
-    SSE4 if your processor supports it but detects this automatically
-    so no flag is required.
+    implement some floating point and bit operations(whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `).
 
 .. ghc-flag:: -msse4.2
     :shortdesc: (x86 only) Use SSE4.2 for floating-point operations
@@ -1738,23 +1695,21 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only, added in GHC 7.4.1) Use the SSE4.2 instruction set to
-    implement some floating point and bit operations when using the
-    :ref:`native code generator `. The resulting compiled
+    implement some floating point and bit operations,
+    whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `. The resulting compiled
     code will only run on processors that support SSE4.2 (Intel Core i7
-    and later). The :ref:`LLVM backend ` will also use
-    SSE4.2 if your processor supports it but detects this automatically
-    so no flag is required.
+    and later).
 
 .. ghc-flag:: -mbmi
     :shortdesc: (x86 only) Use BMI1 for bit manipulation operations
     :type: dynamic
     :category: platform-options
 
-    (x86 only) Use the BMI1 instruction set to implement some bit operations
-    when using the :ref:`native code generator `.
+    (x86 only) Use the BMI1 instruction set to implement some bit operations.
 
-    Note that the current version does not use BMI specific instructions,
-    so using this flag has no effect.
+    Note that GHC currently does not use BMI specific instructions,
+    so this flag has no effect when used with the :ref:`native code generator `.
 
 .. ghc-flag:: -mbmi2
     :shortdesc: (x86 only) Use BMI2 for bit manipulation operations
@@ -1762,9 +1717,11 @@ Some flags only make sense for particular target platforms.
     :category: platform-options
 
     (x86 only, added in GHC 7.4.1) Use the BMI2 instruction set to
-    implement some bit operations when using the
-    :ref:`native code generator `. The resulting compiled
-    code will only run on processors that support BMI2 (Intel Haswell and newer, AMD Excavator, Zen and newer).
+    implement some bit operations, whether using the :ref:`native code generator `
+    or the :ref:`LLVM backend `.
+
+    The resulting compiled code will only run on processors that support BMI2
+    (Intel Haswell and newer, AMD Excavator, Zen and newer).
 
 .. ghc-flag:: -mfma
     :shortdesc: Use native FMA instructions for fused multiply-add floating-point operations



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c9c790dbca89722080f47158001ac3920f11606

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 12:06:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 08 Oct 2024 08:06:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: Remove the
 wrapper/coercion-passing logic for submultiplicity checks
Message-ID: <6705202a90842_3bf6b945bf8c104297@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
8eb4eadc by Sven Tennie at 2024-10-08T08:05:37-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d306c475 by Arnaud Spiwack at 2024-10-08T08:05:53-04:00
Remove unused accumulators in partition_errors

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcMType.hs-boot
- compiler/GHC/Tc/Utils/Unify.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/967c49286f2bcaefe6a68d086ebf03be11c21741...d306c475b47384fb71b5bf73b4a44c4fb231b3f2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/967c49286f2bcaefe6a68d086ebf03be11c21741...d306c475b47384fb71b5bf73b4a44c4fb231b3f2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 13:25:25 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Tue, 08 Oct 2024 09:25:25 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/sv/T25246-b
Message-ID: <670532c5840cb_3b56e533ece424515@gitlab.mail>



Sjoerd Visscher pushed new branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/sv/T25246-b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 13:58:00 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 08 Oct 2024 09:58:00 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 9 commits: Remove the
 wrapper/coercion-passing logic for submultiplicity checks
Message-ID: <67053a685dee2_3b56e54856342978b@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
3d8ae104 by Hassan Al-Awwadi at 2024-10-08T15:55:49+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, and we parameterized it over the ghcPass instead
of over some arbitrary type.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77bee8d1cfd11c7fbbe74ca936efe4a3b945f9...3d8ae1043867e6a8148abbb815f80990e388ba09

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77bee8d1cfd11c7fbbe74ca936efe4a3b945f9...3d8ae1043867e6a8148abbb815f80990e388ba09
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 14:00:37 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 08 Oct 2024 10:00:37 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] 9 commits: Remove the
 wrapper/coercion-passing logic for submultiplicity checks
Message-ID: <67053b051e9da_3b56e552bcdc30115@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
fd6bbf0e by Hassan Al-Awwadi at 2024-10-08T16:00:14+02:00
The main purpose of this commit is to rip RdrName out of FieldOcc, and
as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade <Jade512 at proton.me>
                @Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8e2e925f4d15858de046ad801f015af6c9cef159...fd6bbf0e8141572983b65af01b3eff6825865f2b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8e2e925f4d15858de046ad801f015af6c9cef159...fd6bbf0e8141572983b65af01b3eff6825865f2b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 14:40:22 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 08 Oct 2024 10:40:22 -0400
Subject: [Git][ghc/ghc][wip/T25281] 26 commits: EPA: Remove unused
 hsCaseAnnsRest
Message-ID: <6705445648e64_116d2f1c19c01002f8@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
f579ec01 by Sebastian Graf at 2024-10-08T12:29:10+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
13a38836 by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
e2130b2a by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
Yet more

- - - - -
17e68471 by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
One more

- - - - -
9209ca22 by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
More

- - - - -
4658168a by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
More

- - - - -
26035f4a by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
Wibble

- - - - -
4497402c by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
Wibble warning

- - - - -
4e99eebb by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
Try again

- - - - -
4f503bef by Simon Peyton Jones at 2024-10-08T12:29:10+01:00
More

- - - - -
cec48035 by Simon Peyton Jones at 2024-10-08T15:39:43+01:00
Wibble nospec

- - - - -
e81f2e72 by Simon Peyton Jones at 2024-10-08T15:39:52+01:00
Wibble record selectors

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cada7c27b8a6227999f586d877c2fe2e0730ef7a...e81f2e726dba3f28799e3aacd17f015c1ee2710d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cada7c27b8a6227999f586d877c2fe2e0730ef7a...e81f2e726dba3f28799e3aacd17f015c1ee2710d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 15:03:57 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 08 Oct 2024 11:03:57 -0400
Subject: [Git][ghc/ghc][wip/T25266] 46 commits: SpecConstr: Introduce a
 separate argument limit for forced specs.
Message-ID: <670549dd2e8a3_116d2f3fd06810458c@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a177f3e4 by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
92753361 by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Work in progress on #25266

- - - - -
d095e5d8 by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Better generalisation

- - - - -
2ccba13d by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Wibbles to short cuts

- - - - -
c520a355 by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Iterating in decideAndPromote

- - - - -
2072ec50 by Simon Peyton Jones at 2024-10-08T12:46:58+01:00
Wibble

- - - - -
2921f22b by Simon Peyton Jones at 2024-10-08T16:03:21+01:00
Wibble Solver

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Platform/Reg/Class.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0af764039011d433416d91fee6f444ba63acff1e...2921f22bb1d031969a7013ec9c30f12cee5f6688

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0af764039011d433416d91fee6f444ba63acff1e...2921f22bb1d031969a7013ec9c30f12cee5f6688
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 15:46:12 2024
From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits))
Date: Tue, 08 Oct 2024 11:46:12 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed]
 Link interface bytecode from package DBs if possible
Message-ID: <670553c4a2301_116d2f7ddc2814289b@gitlab.mail>



Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC


Commits:
3b151d9c by Torsten Schmits at 2024-10-08T17:45:54+02:00
Link interface bytecode from package DBs if possible

Part of #25090.

MR !?????

When splices are executed with `-fprefer-byte-code`, the loader will
compile Core bindings to bytecode if those are present in interfaces of
module dependencies.

So far, this only applied to local modules (i.e. home modules in make
mode and non-package deps in oneshot mode).

This patch extends support to interfaces loaded from a package DB.
In `getLinkDeps`, the dependencies chosen for recursion were restricted
to `dep_direct_mods`, which has been changed to include `mi_usages`.
In order to unify treatment of the different link variants across
make/oneshot mode, the algorithm's intermediate results have been
abstracted into the data types `LinkDep` and `LinkModule`.

At the moment, following package deps is only implemented for oneshot
mode.

- - - - -


22 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- docs/users_guide/phases.rst
- + testsuite/tests/bytecode/T25090/Dep.hs
- + testsuite/tests/bytecode/T25090/DepApi.hs
- + testsuite/tests/bytecode/T25090/Local.hs
- testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/Num.hs
- + testsuite/tests/bytecode/T25090/Num.hs-boot
- + testsuite/tests/bytecode/T25090/PkgBytecode.hs
- + testsuite/tests/bytecode/T25090/PkgBytecode.stdout
- testsuite/tests/bytecode/T25090/all.T
- + testsuite/tests/bytecode/T25090/dep.conf
- + testsuite/tests/bytecode/T25090/prep.bash
- + testsuite/tests/bytecode/T25090/run.bash
- + testsuite/tests/bytecode/T25090/unit1
- + testsuite/tests/bytecode/T25090/unit2


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -843,6 +843,7 @@ data GeneralFlag
    | Opt_BuildDynamicToo
    | Opt_WriteIfSimplifiedCore
    | Opt_UseBytecodeRatherThanObjects
+   | Opt_PackageDbBytecode
 
    -- safe haskell flags
    | Opt_DistrustAllPackages


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2540,6 +2540,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "package-db-byte-code"             Opt_PackageDbBytecode,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.Directory
 import GHC.Driver.Env.KnotVars
 import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
 import GHC.Iface.Errors.Types
+import GHC.Runtime.Context (emptyInteractiveContext)
 import Data.Function ((&))
 
 {-
@@ -533,12 +534,18 @@ loadInterface doc_str mod from
               --
               -- See Note [Interface Files with Core Definitions]
               add_bytecode old
-                | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls)
+                | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls)
                 = extendModuleEnv old mod action
                 -- Don't add an entry if the iface doesn't have 'extra_decls'
                 -- so 'get_link_deps' knows that it should load object code.
                 | otherwise
                 = old
+                where
+                  -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is
+                  -- accessed when the processed module is from a different
+                  -- package.
+                  hydration_env =
+                    purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)}
 
         ; warnPprTrace bad_boot "loadInterface" (ppr mod) $
           updateEps_  $ \ eps ->


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Linker.Deps
   ( LinkDepsOpts (..)
@@ -28,6 +29,7 @@ import GHC.Types.Unique.DSet
 import GHC.Types.Unique.DFM
 
 import GHC.Utils.Outputable
+import qualified GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Error
 
@@ -47,9 +49,11 @@ import GHC.Utils.Misc
 import GHC.Unit.Home
 import GHC.Data.Maybe
 
-import Control.Monad
 import Control.Applicative
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
 
+import Data.Foldable (traverse_)
 import qualified Data.Set as Set
 import qualified Data.Map as M
 import Data.List (isSuffixOf)
@@ -64,19 +68,21 @@ data LinkDepsOpts = LinkDepsOpts
   , ldUnitEnv     :: !UnitEnv
   , ldPprOpts     :: !SDocContext                   -- ^ Rendering options for error messages
   , ldUseByteCode :: !Bool                          -- ^ Use bytecode rather than objects
+  , ldPkgByteCode :: !Bool                          -- ^ Use bytecode for external packages
   , ldMsgOpts     :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics
   , ldWays        :: !Ways                          -- ^ Enabled ways
   , ldFinderCache :: !FinderCache
   , ldFinderOpts  :: !FinderOpts
-  , ldLoadIface   :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface))
-  , ldLoadByteCode :: !(Module -> IO (Maybe Linkable))
+  , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)))
+  , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable)))
+  , ldDebugTrace :: !(SDoc -> IO ())
   }
 
 data LinkDeps = LinkDeps
   { ldNeededLinkables :: [Linkable]
   , ldAllLinkables    :: [Linkable]
-  , ldUnits           :: [UnitId]
-  , ldNeededUnits     :: UniqDSet UnitId
+  , ldNeededUnits     :: [UnitId]
+  , ldAllUnits        :: UniqDSet UnitId
   }
 
 -- | Find all the packages and linkables that a set of modules depends on
@@ -102,7 +108,14 @@ getLinkDeps opts interp pls span mods = do
 
       get_link_deps opts pls maybe_normal_osuf span mods
 
-
+-- | Compute the linkables for the given module set's dependencies.
+--
+-- Home modules in make mode are treated separately in a preprocessing step,
+-- then all the remaining external deps are processed for both modes.
+-- If bytecode is available, transitive external deps are included, otherwise
+-- the module's library is linked and processing stops.
+--
+-- The results are split into sets of needed/loaded modules/packages.
 get_link_deps
   :: LinkDepsOpts
   -> LoaderState
@@ -111,46 +124,40 @@ get_link_deps
   -> [Module]
   -> IO LinkDeps
 get_link_deps opts pls maybe_normal_osuf span mods = do
-        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-        -- (omitting modules from the interactive package, which is already linked)
-      (mods_s, pkgs_s) <-
-          -- Why two code paths here? There is a significant amount of repeated work
-          -- performed calculating transitive dependencies
-          -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests)
-          if ldOneShotMode opts
-            then follow_deps (filterOut isInteractiveModule mods)
-                              emptyUniqDSet emptyUniqDSet;
-            else do
-              (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
-              return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-
-      let
-        -- 2.  Exclude ones already linked
-        --      Main reason: avoid findModule calls in get_linkable
-            (mods_needed, links_got) = partitionWith split_mods mods_s
-            pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls
-
-            split_mods mod =
-                let is_linked = lookupModuleEnv (objs_loaded pls) mod
-                                <|> lookupModuleEnv (bcos_loaded pls) mod
-                in case is_linked of
-                     Just linkable -> Right linkable
-                     Nothing -> Left mod
-
-        -- 3.  For each dependent module, find its linkable
-        --     This will either be in the HPT or (in the case of one-shot
-        --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
-
-      return $ LinkDeps
-        { ldNeededLinkables = lnks_needed
-        , ldAllLinkables    = links_got ++ lnks_needed
-        , ldUnits           = pkgs_needed
-        , ldNeededUnits     = pkgs_s
-        }
+  (link_deps_home, module_deps_external) <- separate_home_deps
+  link_deps_external <- external_deps opts module_deps_external
+  let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) =
+        classify_deps pls (link_deps_home ++ link_deps_external)
+  ldNeededLinkables <- mapM module_linkable needed_modules
+  pure LinkDeps {
+    ldNeededLinkables,
+    ldAllLinkables = loaded_modules ++ ldNeededLinkables,
+    ldNeededUnits,
+    ldAllUnits
+  }
   where
     mod_graph = ldModuleGraph opts
     unit_env  = ldUnitEnv     opts
+    noninteractive = filterOut isInteractiveModule mods
+
+    -- Preprocess the dependencies in make mode to remove all home modules,
+    -- since the transitive dependency closure is already cached for those in
+    -- the HUG (see MultiLayerModulesTH_* tests for the performance impact).
+    --
+    -- Returns the remaining, external, dependencies on the right, which is the
+    -- entire set for oneshot mode.
+    separate_home_deps =
+      if ldOneShotMode opts
+      then pure ([], noninteractive)
+      else make_deps
+
+    make_deps = do
+      (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods
+      let
+        link_mods =
+          listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods]
+        ext = uniqDSetToList (unionManyUniqDSets (init_ext : dep_ext))
+      pure ([LinkModules (LinkHomeModule <$> link_mods)], ext)
 
     -- This code is used in `--make` mode to calculate the home package and unit dependencies
     -- for a set of modules.
@@ -160,9 +167,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     -- It is also a matter of correctness to use the module graph so that dependencies between home units
     -- is resolved correctly.
-    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+    make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey)
     make_deps_loop found [] = found
-    make_deps_loop found@(found_units, found_mods) (nk:nexts)
+    make_deps_loop found@(external, found_mods) (nk:nexts)
       | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
       | otherwise =
         case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of
@@ -171,85 +178,26 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   -- See #936 and the ghci.prog007 test for why we have to continue traversing through
                   -- boot modules.
                   todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps]
-              in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
+              in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
             Nothing ->
-              let (ModNodeKeyWithUid _ uid) = nk
-              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+              let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk
+              in make_deps_loop (addOneToUniqDSet external (Module (RealUnit (Definite uid)) mod_name), found_mods) nexts
 
     mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
-    (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods)
+    (init_ext, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk noninteractive
 
     all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps]
 
     get_mod_info (ModNodeKeyWithUid gwib uid) =
       case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of
-        Just hmi ->
-          let iface = (hm_iface hmi)
-              mmod = case mi_hsc_src iface of
-                      HsBootFile -> link_boot_mod_error (mi_module iface)
-                      _          -> return $ Just (mi_module iface)
-
-          in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$>  mmod
+        Just hmi -> do
+          let iface = hm_iface hmi
+          case mi_hsc_src iface of
+            HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface)
+            _ -> pure (mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi)
         Nothing -> throwProgramError opts $
           text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
 
-
-       -- This code is used in one-shot mode to traverse downwards through the HPT
-       -- to find all link dependencies.
-       -- The ModIface contains the transitive closure of the module dependencies
-       -- within the current package, *except* for boot modules: if we encounter
-       -- a boot module, we have to find its real interface and discover the
-       -- dependencies of that.  Hence we need to traverse the dependency
-       -- tree recursively.  See bug #936, testcase ghci/prog007.
-    follow_deps :: [Module]             -- modules to follow
-                -> UniqDSet Module         -- accum. module dependencies
-                -> UniqDSet UnitId          -- accum. package dependencies
-                -> IO ([Module], UniqDSet UnitId) -- result
-    follow_deps []     acc_mods acc_pkgs
-        = return (uniqDSetToList acc_mods, acc_pkgs)
-    follow_deps (mod:mods) acc_mods acc_pkgs
-        = do
-          mb_iface <- ldLoadIface opts msg mod
-          iface <- case mb_iface of
-                    Failed err      -> throwProgramError opts $
-                      missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
-                    Succeeded iface -> return iface
-
-          when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
-
-          let
-            pkg = moduleUnit mod
-            deps  = mi_deps iface
-
-            pkg_deps = dep_direct_pkgs deps
-            (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $
-              \case
-                (_, GWIB m IsBoot)  -> Left m
-                (_, GWIB m NotBoot) -> Right m
-
-            mod_deps' = case ue_homeUnit unit_env of
-                          Nothing -> []
-                          Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps))
-            acc_mods'  = case ue_homeUnit unit_env of
-                          Nothing -> acc_mods
-                          Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps)
-            acc_pkgs'  = addListToUniqDSet acc_pkgs (Set.toList pkg_deps)
-
-          case ue_homeUnit unit_env of
-            Just home_unit | isHomeUnit home_unit pkg ->  follow_deps (mod_deps' ++ mods)
-                                                                      acc_mods' acc_pkgs'
-            _ ->  follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
-        where
-           msg = text "need to link module" <+> ppr mod <+>
-                  text "due to use of Template Haskell"
-
-
-
-    link_boot_mod_error :: Module -> IO a
-    link_boot_mod_error mod = throwProgramError opts $
-            text "module" <+> ppr mod <+>
-            text "cannot be linked; it is only available as a boot module"
-
     no_obj :: Outputable a => a -> IO b
     no_obj mod = dieWith opts span $
                      text "cannot find object file for module " <>
@@ -258,6 +206,20 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     while_linking_expr = text "while linking an interpreted expression"
 
+  -- Extract the 'Linkable's for unlinked modules from the intermediate
+  -- results.
+    module_linkable = \case
+      LinkHomeModule hmi ->
+        adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi))
+
+      LinkObjectModule iface loc -> do
+        let mod = mi_module iface
+        findObjectLinkableMaybe mod loc >>= \case
+          Nothing  -> no_obj mod
+          Just lnk -> adjust_linkable lnk
+
+      LinkByteCodeModule _ load_bytecode ->
+        load_bytecode
 
     -- See Note [Using Byte Code rather than Object Code for Template Haskell]
     homeModLinkable :: HomeModInfo -> Maybe Linkable
@@ -266,57 +228,257 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
-        | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
-        = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
-        | otherwise
-        = do    -- It's not in the HPT because we are in one shot mode,
-                -- so use the Finder to get a ModLocation...
-             case ue_homeUnit unit_env of
-              Nothing -> no_obj mod
-              Just home_unit -> do
-                from_bc <- ldLoadByteCode opts mod
-                maybe (fallback_no_bytecode home_unit mod) pure from_bc
-        where
-
-            fallback_no_bytecode home_unit mod = do
-              let fc = ldFinderCache opts
-              let fopts = ldFinderOpts opts
-              mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod)
-              case mb_stuff of
-                Found loc _ -> do
-                  mb_lnk <- findObjectLinkableMaybe mod loc
-                  case mb_lnk of
-                    Nothing  -> no_obj mod
-                    Just lnk -> adjust_linkable lnk
-                _ -> no_obj (moduleName mod)
-
-            adjust_linkable lnk
-                | Just new_osuf <- maybe_normal_osuf = do
-                        new_parts <- mapM (adjust_part new_osuf)
-                                        (linkableParts lnk)
-                        return lnk{ linkableParts=new_parts }
-                | otherwise =
-                        return lnk
-
-            adjust_part new_osuf part = case part of
-              DotO file ModuleObject -> do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
-                ok <- doesFileExist new_file
-                if (not ok)
-                   then dieWith opts span $
-                          text "cannot find object file "
-                                <> quotes (text new_file) $$ while_linking_expr
-                   else return (DotO new_file ModuleObject)
-              DotO file ForeignObject -> pure (DotO file ForeignObject)
-              DotA fp    -> panic ("adjust_ul DotA " ++ show fp)
-              DotDLL fp  -> panic ("adjust_ul DotDLL " ++ show fp)
-              BCOs {}    -> pure part
-              LazyBCOs{} -> pure part
-              CoreBindings WholeCoreBindings {wcb_module} ->
-                pprPanic "Unhydrated core bindings" (ppr wcb_module)
+    adjust_linkable lnk
+        | Just new_osuf <- maybe_normal_osuf = do
+                new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf)
+                                (linkableParts lnk)
+                return lnk {linkableParts = new_uls}
+        | otherwise =
+                return lnk
+
+    adjust_part osuf new_osuf part = case part of
+      DotO file ModuleObject -> do
+        massert (osuf `isSuffixOf` file)
+        let file_base = fromJust (stripExtension osuf file)
+            new_file = file_base <.> new_osuf
+        ok <- doesFileExist new_file
+        if (not ok)
+            then dieWith opts span $
+                  text "cannot find object file "
+                        <> quotes (text new_file) $$ while_linking_expr
+            else return (DotO new_file ModuleObject)
+      DotO file ForeignObject -> pure (DotO file ForeignObject)
+      DotA fp    -> panic ("adjust_part DotA " ++ show fp)
+      DotDLL fp  -> panic ("adjust_part DotDLL " ++ show fp)
+      BCOs {}    -> pure part
+      LazyBCOs{} -> pure part
+      CoreBindings WholeCoreBindings {wcb_module} ->
+        pprPanic "Unhydrated core bindings" (ppr wcb_module)
+
+data LinkModule =
+  LinkHomeModule !HomeModInfo
+  |
+  LinkObjectModule !ModIface !ModLocation
+  |
+  LinkByteCodeModule !ModIface !(IO Linkable)
+
+link_module_iface :: LinkModule -> ModIface
+link_module_iface = \case
+  LinkHomeModule hmi -> hm_iface hmi
+  LinkObjectModule iface _ -> iface
+  LinkByteCodeModule iface _ -> iface
+
+instance Outputable LinkModule where
+  ppr = \case
+    LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI")
+    LinkObjectModule iface _ -> ppr (mi_module iface)
+    LinkByteCodeModule iface _ -> ppr (mi_module iface) <+> brackets (text "BC")
+
+data LinkDep =
+  LinkModules !(UniqDFM ModuleName LinkModule)
+  |
+  LinkLibrary !UnitId
+
+instance Outputable LinkDep where
+  ppr = \case
+    LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods)
+    LinkLibrary uid -> text "library:" <+> ppr uid
+
+data OneshotError =
+  NoLocation !Module
+  |
+  NoInterface !MissingInterfaceError
+  |
+  LinkBootModule !Module
+
+-- Compute the transitive dependency closure of the given modules.
+--
+-- Used for all oneshot mode dependencies and for external dependencies of home
+-- modules in make mode.
+--
+-- TODO is the following still relevant?
+-- The ModIface contains the transitive closure of the module dependencies
+-- within the current package, *except* for boot modules: if we encounter
+-- a boot module, we have to find its real interface and discover the
+-- dependencies of that.  Hence we need to traverse the dependency
+-- tree recursively.  See bug #936, testcase ghci/prog007.
+external_deps ::
+  LinkDepsOpts ->
+  -- | Modules whose imports to follow
+  [Module] ->
+  IO [LinkDep]
+external_deps opts mods =
+  runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case
+    Right a -> pure (eltsUDFM a)
+    Left err -> throwProgramError opts (message err)
+  where
+    message = \case
+      NoLocation mod ->
+        pprPanic "found iface but no location" (ppr mod)
+      NoInterface err ->
+        missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
+      LinkBootModule mod ->
+        link_boot_mod_error mod
+
+external_deps_loop ::
+  LinkDepsOpts ->
+  [Module] ->
+  UniqDFM UnitId LinkDep ->
+  ExceptT OneshotError IO (UniqDFM UnitId LinkDep)
+external_deps_loop _ [] acc =
+  pure acc
+external_deps_loop opts (mod : mods) acc = do
+  (new_acc, new_mods, action) <- process_module
+  traverse_ debug_log action
+  external_deps_loop opts (new_mods ++ mods) new_acc
+  where
+    debug_log action =
+      liftIO $ ldDebugTrace opts $
+      text "TH dep" <+> ppr mod <+> brackets (sep [
+        if is_home then text "home" else Outputable.empty,
+        text action
+      ])
+
+    -- Decide how this module needs to be processed.
+    -- We only need an interface if we want to load bytecode or if we have to
+    -- link an object file (which happens for home unit modules, since those
+    -- have no libraries).
+    process_module
+      | already_seen = pure (acc, [], Nothing)
+      | is_home || prefer_bytecode = try_iface
+      | otherwise = add_library
+
+    -- Check whether the current module was processed before.
+    -- Since the accumulator is keyed by unit ID, we have to perform two
+    -- lookups.
+    -- If another module from this module's unit has been determined to be
+    -- linked as a library previously, we skip this module, assuming that no
+    -- bytecode is available for the entire package.
+    already_seen
+      | Just (LinkModules mods) <- mod_dep
+      = elemUDFM mod_name mods
+      | Just (LinkLibrary _) <- mod_dep
+      = True
+      | otherwise
+      = False
+
+    -- Load the iface and attempt to get bytecode from Core bindings.
+    try_iface =
+      liftIO (ldLoadIface opts load_reason mod) >>= \case
+        Failed err -> throwE (NoInterface err)
+        Succeeded (iface, loc) -> do
+          mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface))
+          with_iface loc iface mb_load_bc
+
+    -- Decide how to link this module.
+    -- If bytecode or an object file is available, use those in that order.
+    -- Otherwise fall back to linking a library.
+    with_iface loc iface mb_load_bc
+      | IsBoot <- mi_boot iface
+      = throwE (LinkBootModule mod)
+
+      | prefer_bytecode
+      , Just load_bc <- mb_load_bc
+      = pure (add_module iface (LinkByteCodeModule iface load_bc) "bytecode")
+
+      | is_home
+      = pure (add_module iface (LinkObjectModule iface loc) "object")
+
+      | otherwise
+      = add_library
+
+    add_library =
+      pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library")
+
+    add_module iface lmod action =
+      (addListToUDFM with_mod (direct_pkgs iface), new_deps iface, Just action)
+      where
+        with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id
+
+    add_package_module lmod = \case
+      Just (LinkLibrary u) -> Just (LinkLibrary u)
+      Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod))
+      Nothing -> Just (LinkModules (unitUDFM mod_name lmod))
+
+    direct_pkgs iface
+      | prefer_bytecode
+      = []
+      | otherwise
+      = [(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))]
+
+    new_deps iface
+      | prefer_bytecode
+      -- TODO How can we better determine the external deps?
+      -- OTOH, we probably don't want to link unused dependencies anyway.
+      = [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface] ++ local
+      | is_home
+      = local
+      | otherwise
+      = []
+      where
+        local =
+          [
+            mkModule mod_unit m
+            -- TODO Somehow this just works, no idea what the deal was in the
+            -- old code with boot modules.
+            | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface))
+          ]
+
+    is_home
+      | Just home <- mb_home
+      = homeUnitAsUnit home == mod_unit
+      | otherwise
+      = False
+
+    mod_dep = lookupUDFM acc mod_unit_id
+    mod_name = moduleName mod
+    mod_unit_id = moduleUnitId mod
+    mod_unit = moduleUnit mod
+    load_reason =
+      text "need to link module" <+> ppr mod <+>
+      text "due to use of Template Haskell"
+
+    prefer_bytecode = ldUseByteCode opts && (is_home || ldPkgByteCode opts)
+    mb_home = ue_homeUnit (ldUnitEnv opts)
+
+link_boot_mod_error :: Module -> SDoc
+link_boot_mod_error mod =
+  text "module" <+> ppr mod <+>
+  text "cannot be linked; it is only available as a boot module"
+
+-- | Split link dependencies into the sets of modules and packages that have
+-- been linked previously and those that need to be linked now by checking for
+-- their presence in the 'LoaderState':
+--
+-- - For module dependencies, in the sets of loaded objects and BCOs
+--   ('objs_loaded' and 'bcos_loaded')
+-- - For package dependencies, in the set of loaded packages ('pkgs_loaded')
+classify_deps ::
+  LoaderState ->
+  [LinkDep] ->
+  ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId])
+classify_deps pls deps =
+  (loaded_modules, needed_modules, all_packages, needed_packages)
+  where
+    (loaded_modules, needed_modules) =
+      partitionWith loaded_or_needed_module (concatMap eltsUDFM modules)
+
+    needed_packages =
+      eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls)
+
+    all_packages = mkUniqDSet packages
+
+    (modules, packages) = flip partitionWith deps $ \case
+      LinkModules mods -> Left mods
+      LinkLibrary lib -> Right lib
+
+    loaded_or_needed_module lm =
+      maybe (Right lm) Left (loaded_module (mi_module (link_module_iface lm)))
+
+    loaded_module mod =
+      lookupModuleEnv (objs_loaded pls) mod
+      <|>
+      lookupModuleEnv (bcos_loaded pls) mod
 
 {-
 Note [Using Byte Code rather than Object Code for Template Haskell]


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -77,11 +77,13 @@ import GHC.Utils.TmpFs
 
 import GHC.Unit.Env
 import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
+import GHC.Unit.Finder
 import GHC.Unit.Module
 import GHC.Unit.State as Packages
 
 import qualified GHC.Data.ShortText as ST
 import GHC.Data.FastString
+import qualified GHC.Data.Maybe as Maybe
 
 import GHC.Linker.Deps
 import GHC.Linker.MacOS
@@ -94,6 +96,7 @@ import Control.Monad
 import qualified Data.Set as Set
 import Data.Char (isSpace)
 import qualified Data.Foldable as Foldable
+import Data.Functor ((<&>))
 import Data.IORef
 import Data.List (intercalate, isPrefixOf, nub, partition)
 import Data.Maybe
@@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do
    -- Find what packages and linkables are required
    deps <- getLinkDeps opts interp pls span needed_mods
 
-   let this_pkgs_needed = ldNeededUnits deps
+   let this_pkgs_needed = ldAllUnits deps
 
    -- Link the packages and modules required
-   pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
+   pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls
    (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
    let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
        all_pkgs_loaded = pkgs_loaded pls2
@@ -646,18 +649,39 @@ initLinkDepsOpts hsc_env = opts
             , ldFinderCache = hsc_FC hsc_env
             , ldFinderOpts  = initFinderOpts dflags
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
+            , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
             , ldLoadIface
             , ldLoadByteCode
+            , ldDebugTrace = debugTraceMsg (hsc_logger hsc_env) 3
             }
     dflags = hsc_dflags hsc_env
-    ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env
-                          $ loadInterface msg mod (ImportByUser NotBoot)
+
+    ldLoadIface msg mod =
+      initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case
+        Maybe.Failed err -> pure (Maybe.Failed err)
+        Maybe.Succeeded iface ->
+          find_location mod <&> \case
+            InstalledFound loc _ -> Maybe.Succeeded (iface, loc)
+            err -> Maybe.Failed $
+                   cannotFindInterface unit_state home_unit
+                   (targetProfile dflags) (moduleName mod) err
+
+    find_location mod =
+      liftIO $
+      findExactModule (hsc_FC hsc_env) (initFinderOpts dflags)
+      (initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env)
+      unit_state home_unit
+      (toUnitId <$> mod)
+
+    unit_state = hsc_units hsc_env
+
+    home_unit = ue_homeUnit (hsc_unit_env hsc_env)
 
     ldLoadByteCode mod = do
       EPS {eps_iface_bytecode} <- hscEPS hsc_env
-      sequence (lookupModuleEnv eps_iface_bytecode mod)
+      pure (lookupModuleEnv eps_iface_bytecode mod)
 
 
 


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -734,7 +734,7 @@ mkStubPaths fopts mod location = do
     src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
 
 -- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
+-- findObjectLinkable isn't related to the other stuff in here,
 -- but there's no other obvious place for it
 
 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)


=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed
 build artifacts, which can be objects or bytecode, depending on the build
 settings.
 
-1. In make mode, all eligible modules are part of the dependency graph.
+1. In make mode, all eligible home modules are part of the dependency graph.
    Their interfaces are loaded unconditionally and in dependency order by the
    compilation manager, and each module's bytecode is prepared before its
    dependents are compiled, in one of two ways:
@@ -88,9 +88,10 @@ settings.
 2. In oneshot mode, which compiles individual modules without a shared home unit
    graph, a previously compiled module is not reprocessed as described for make
    mode above.
-   When 'get_link_deps' encounters a dependency on a local module, it requests
-   its bytecode from the External Package State, who loads the interface
-   on-demand.
+   'get_link_deps' requests the bytecode of dependencies from the External
+   Package State, who loads the interface on-demand.
+   This works for modules in local directories (via @-i@ and @-hidir@) as well
+   as those exposed from a package DB.
 
    Since the EPS stores interfaces for all package dependencies in addition to
    local modules in oneshot mode, it has a substantial memory footprint.
@@ -109,6 +110,18 @@ settings.
    storing the intermediate representation as rehydrated Core bindings, since
    the latter have a significantly greater memory footprint.
 
+3. In both of the above modes, whenever a module from an external package
+   (loaded from a package DB) is encountered, the workflow is the same as for
+   oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object
+   code is loaded.
+   Interfaces for external modules are stored together with local oneshot mode
+   modules, so almost no special treatment is necessary, with the exception of:
+   - When external package modules are compiled, the @InteractiveContext@ in
+     @HscEnv@ is accessed, which is not available due to its impact on retention
+     of outdated build products.
+     This is solved by writing an empty @InteractiveContext@ to the env used for
+     compilation.
+
 Note [Size of Interface Files with Core Definitions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op.
 Otherwise, the stub objects from the interface are compiled to objects in
 'generateByteCode' and added to the 'HomeModLinkable' as well.
 
-Case 3 is not implemented yet (!13042).
+In case 3, Core bindings are loaded from the EPS, where stubs only exist in
+their serialized form in the interface, so they must be regenerated like in case
+2.
 
 Problem 3:
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -826,6 +826,17 @@ Options affecting code generation
     will generate byte-code rather than object code.
 
 
+.. ghc-flag:: -fpackage-db-byte-code
+    :shortdesc: Use byte-code from package DB dependencies
+    :type: dynamic
+    :category: codegen
+
+    GHC normally only considers local modules to be eligible for loading
+    bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`.
+    When this flag is specified additionally, bytecode will be loaded from
+    interfaces for all external package dependencies that provide it.
+
+
 .. _options-linker:
 
 Options affecting linking


=====================================
testsuite/tests/bytecode/T25090/Dep.hs
=====================================
@@ -0,0 +1,15 @@
+module Dep where
+
+data A = A Int
+
+used :: Int
+used = 9681
+
+dep :: A
+dep = A used
+
+unused1 :: A
+unused1 = A 1
+
+unused2 :: A
+unused2 = unused1


=====================================
testsuite/tests/bytecode/T25090/DepApi.hs
=====================================
@@ -0,0 +1,7 @@
+module DepApi (A (A), dep) where
+
+import Dep (A (A))
+import qualified Dep
+
+dep :: A
+dep = Dep.dep


=====================================
testsuite/tests/bytecode/T25090/Local.hs
=====================================
@@ -0,0 +1,15 @@
+{-# language PackageImports #-}
+
+module Local where
+
+import GHC.Prim
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+-- just to be sure that the file isn't accidentally picked up locally
+import "dep" DepApi (dep, A (A))
+import {-# source #-} Num (num)
+
+splc :: ExpQ
+splc = lift @_ @Int (num + d)
+  where
+    A d = dep


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -19,3 +19,35 @@ T25090a:
 T25090b:
 	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe
+
+DB := -package-db db -package dep
+BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0
+BC := -fprefer-byte-code -fbyte-code-and-object-code
+ARGS := $(BASIC) $(BC)
+
+T25090_pkg:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_empty:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_nolib:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none"
+	./run.bash "$(TEST_HC)" "$(ARGS)"
+
+T25090_pkg_obj_code:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code"
+
+T25090_pkg_multi_unit:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	mkdir -p unit2-src/
+	mv Local.hs Num.hs Num.hs-boot unit2-src/
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -dynamic -unit @unit1 -unit @unit2
+	./PkgBytecode
+
+T25090_pkg_archive:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive"
+	./run.bash "$(TEST_HC)" "$(ARGS)"


=====================================
testsuite/tests/bytecode/T25090/Num.hs
=====================================
@@ -0,0 +1,4 @@
+module Num where
+
+num :: Int
+num = 48332


=====================================
testsuite/tests/bytecode/T25090/Num.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module Num where
+
+num :: Int


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.hs
=====================================
@@ -0,0 +1,12 @@
+{-# language TemplateHaskell #-}
+
+module Main where
+
+import GHC.Prim
+import Local (splc)
+
+a :: Int
+a = $(splc)
+
+main :: IO ()
+main = putStrLn (show a)


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.stdout
=====================================
@@ -0,0 +1 @@
+58013


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -16,3 +16,33 @@ def test_T25090(name):
 
 test_T25090('T25090a')
 test_T25090('T25090b')
+
+def test_pkg(name, files = []):
+    test(
+        name,
+        [
+            extra_files([
+                'PkgBytecode.hs',
+                'Local.hs',
+                'Dep.hs',
+                'DepApi.hs',
+                'Num.hs',
+                'Num.hs-boot',
+                'dep.conf',
+                'prep.bash',
+                'run.bash',
+            ] + files),
+            use_specs({'stdout': 'PkgBytecode.stdout'}),
+        ],
+        makefile_test,
+        [],
+    )
+
+test_pkg('T25090_pkg')
+test_pkg('T25090_pkg_empty')
+test_pkg('T25090_pkg_nolib')
+test_pkg('T25090_pkg_obj_code')
+test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2'])
+# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a
+# comment says "search for .so libraries _first_" (rather than "only").
+# test_pkg('T25090_pkg_archive')


=====================================
testsuite/tests/bytecode/T25090/dep.conf
=====================================
@@ -0,0 +1,8 @@
+name: dep
+version: 1.0
+id: dep-1.0
+key: dep-1.0
+exposed: True
+exposed-modules: DepApi
+import-dirs: ${pkgroot}/dep
+library-dirs: ${pkgroot}/dep


=====================================
testsuite/tests/bytecode/T25090/prep.bash
=====================================
@@ -0,0 +1,57 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+ghc_pkg_cmd="$3"
+library="$4"
+
+base="$PWD"
+db="$base/db"
+dep="$base/dep"
+conf_dep="${dep}/dep.conf"
+
+mkdir -p "$dep" "$db"
+mv Dep.hs DepApi.hs "$dep/"
+cp dep.conf "$dep/"
+
+ghc_pkg()
+{
+  eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@"
+}
+
+ghc()
+{
+  eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@"
+}
+
+version=$(ghc "--numeric-version")
+
+ghc_pkg recache
+
+ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+
+if [[ "$library" == 'shared' ]]
+then
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'shared-empty' ]]
+then
+  echo 'module Dummy where' > Dummy.hs
+  ghc "-dynamic-too -c Dummy.hs"
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'archive' ]]
+then
+  $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'none' ]]
+then
+  :
+else
+  echo "Invalid argument for 'library': $library"
+  exit 1
+fi
+
+ghc_pkg -v0 register "${conf_dep at Q}"


=====================================
testsuite/tests/bytecode/T25090/run.bash
=====================================
@@ -0,0 +1,16 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+
+ghc()
+{
+  eval "${ghc_cmd at Q} $ghc_opts $@"
+}
+
+ghc -c Num.hs-boot Num.hs Local.hs
+ghc -fpackage-db-byte-code -c PkgBytecode.hs
+ghc PkgBytecode.o -o PkgBytecode
+./PkgBytecode


=====================================
testsuite/tests/bytecode/T25090/unit1
=====================================
@@ -0,0 +1 @@
+-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2


=====================================
testsuite/tests/bytecode/T25090/unit2
=====================================
@@ -0,0 +1 @@
+-i -i./unit2-src Local Num -this-unit-id unit2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b151d9c970be271081f725835c1584f6fa7cfb7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 16:34:23 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 08 Oct 2024 12:34:23 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] Don't log GHC invocation in abi-test
Message-ID: <67055f0faef71_116d2fbbc3bc176716@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
2fcfee20 by Rodrigo Mesquita at 2024-10-08T17:34:01+01:00
Don't log GHC invocation in abi-test

The two abi test invocations would differ because of -dinitial-unique
and -dunique-increment

- - - - -


1 changed file:

- .gitlab/ci.sh


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -712,7 +712,7 @@ function cabal_abi_test() {
 
   start_section "Cabal test: $OUT"
   mkdir -p "$OUT"
-  run "$HC" \
+  "$HC" \
     -hidir tmp -odir tmp -fforce-recomp -haddock \
     -iCabal/Cabal/src -XNoPolyKinds Distribution.Simple -j"$cores" \
     -fobject-determinism \



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2fcfee207d3c7d2856028479067e27d3690ff701

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:07:37 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 08 Oct 2024 13:07:37 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.8-2
Message-ID: <670566d964cf1_116d2fd39f00184567@gitlab.mail>



Ben Gamari deleted branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:07:39 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 08 Oct 2024 13:07:39 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 10 commits: rts: only collect live words in
 nonmoving census when non-concurrent
Message-ID: <670566db4f290_116d2fd9d1681847c2@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
fede0d99 by Teo Camarasu at 2024-10-04T16:05:22-04:00
rts: only collect live words in nonmoving census when non-concurrent

This avoids segfaults when the mutator modifies closures as we examine
them.

Resolves #24393

(cherry picked from commit 84357d1143fe4f9076253160f78fac6c2acc8e5b)

- - - - -
47182b77 by Andreas Klebinger at 2024-10-04T16:05:22-04:00
Fix ffi callbacks with >6 args and non-64bit args.

Check for ptr/int arguments rather than 64-bit width arguments when counting
integer register arguments.
The old approach broke when we stopped using exclusively W64-sized types to represent
sub-word sized integers.

Fixes #24314

(cherry picked from commit de589554386fc173a9019922851c05bb727e3450)

- - - - -
72c537ce by Teo Camarasu at 2024-10-04T16:05:22-04:00
nonmoving: Add support for heap profiling

Add support for heap profiling while using the nonmoving collector.

We greatly simply the implementation by disabling concurrent collection for
GCs when heap profiling is enabled. This entails that the marked objects on
the nonmoving heap are exactly the live objects.

Note that we match the behaviour for live bytes accounting by taking the size
of objects on the nonmoving heap to be that of the segment's block
rather than the object itself.

Resolves #22221

(cherry picked from commit bedb4f0de102936099bda4e995cc83f1c344366c)

- - - - -
b2712f69 by Teo Camarasu at 2024-10-04T16:05:22-04:00
docs: move -xn flag beside --nonmoving-gc

It makes sense to have these beside each other as they are aliases.

(cherry picked from commit 98166389e166d4ab7cc2ddbc044261e508859de1)

- - - - -
60f97ccb by Teo Camarasu at 2024-10-04T16:05:22-04:00
nonmoving: introduce a family of dense allocators

Supplement the existing power 2 sized nonmoving allocators with a family
of dense allocators up to a configurable threshold.

This should reduce waste from rounding up block sizes while keeping the
amount of allocator sizes manageable.

This patch:
  - Adds a new configuration option `--nonmoving-dense-allocator-count`
    to control the amount of these new dense allocators.
  - Adds some constants to `NonmovingAllocator` in order to keep
    marking fast with the new allocators.

Resolves #23340

(cherry picked from commit f830d5a34c4c972cced73b6dc25954cedf336747)
(cherry picked from commit 47e02c2ae0ea4713a2f22edf21b9a4eb5fe635be)

- - - - -
8031ebaa by Teo Camarasu at 2024-10-04T16:05:22-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

(cherry picked from commit 35ef8dc83428f5405e092b12eb8cfc440b6504d8)
(cherry picked from commit 7991656954a2ba7d66fd75a8202af7d86327f279)

- - - - -
c71191f7 by Ben Gamari at 2024-10-04T16:05:22-04:00
Add changelog entry for #23340

(cherry picked from commit 2b07bf2e8bcb24520fe78b469c3550b9f4099526)

- - - - -
3ff6bbbe by Simon Peyton Jones at 2024-10-04T16:05:22-04:00
Update the unification count in wrapUnifierX

Omitting this caused type inference to fail in #24146.
This was an accidental omision in my refactoring of the
equality solver.

- - - - -
7e5f2ac0 by Fendor at 2024-10-04T16:05:22-04:00
Escape multiple arguments in the settings file

Uses responseFile syntax.

The issue arises when GHC is installed on windows into a location that
has a space, for example the user name is 'Fake User'.
The $topdir will also contain a space, consequentially.
When we resolve the top dir in the string `-I$topdir/mingw/include`,
then `words` will turn this single argument into `-I/C/Users/Fake` and
`User/.../mingw/include` which trips up the flag argument parser of
various tools such as gcc or clang.
We avoid this by escaping the $topdir before replacing it in
`initSettngs`.
Additionally, we allow to escape spaces and quotation marks for
arguments in `settings` file.

Add regression test case to count the number of options after variable
expansion and argument escaping took place.
Additionally, we check that escaped spaces and double quotation marks are
correctly parsed.

(cherry picked from commit 31bf85ee49fe2ca0b17eaee0774e395f017a9373)
(cherry picked from commit d74ffbbb93cb377e64c557f777089b81710ef873)

- - - - -
3d90849d by Ben Gamari at 2024-10-04T16:05:44-04:00
Accept performance shifts

The metrics of MultiLayerModulesTH_Make are remarkably unstable but
bizarrely only on Darwin.

Metric Decrease:
    MultiLayerModulesTH_Make

- - - - -


30 changed files:

- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Tc/Solver/Monad.hs
- docs/users_guide/9.8.3-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/runtime_control.rst
- hadrian/src/Rules/Generate.hs
- rts/Capability.h
- rts/ProfHeap.c
- rts/RtsFlags.c
- rts/Trace.c
- rts/Trace.h
- rts/eventlog/EventLog.c
- rts/eventlog/EventLog.h
- rts/gen_event_types.py
- rts/include/rts/Flags.h
- rts/include/rts/storage/Block.h
- rts/sm/GC.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/NonMovingCensus.c
- rts/sm/Sanity.c
- rts/sm/Storage.c
- rts/sm/Storage.h
- + testsuite/tests/ffi/should_run/T24314.hs
- + testsuite/tests/ffi/should_run/T24314.stdout
- + testsuite/tests/ffi/should_run/T24314_c.c
- testsuite/tests/ffi/should_run/all.T
- + testsuite/tests/ghc-api/settings-escape/T11938.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bd62051db8abee470e4b5481a6a110c319d21cc...3d90849d00871853c68dbb7b9b4e97349a999459

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bd62051db8abee470e4b5481a6a110c319d21cc...3d90849d00871853c68dbb7b9b4e97349a999459
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:11:29 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 08 Oct 2024 13:11:29 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/drop-libffi
Message-ID: <670567c195315_116d2fd154c018494b@gitlab.mail>



Cheng Shao pushed new branch wip/drop-libffi at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/drop-libffi
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:21:12 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 08 Oct 2024 13:21:12 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ttg/lits
Message-ID: <67056a07f3c5f_116d2ff93d6418673b@gitlab.mail>



Hassan Al-Awwadi pushed new branch wip/ttg/lits at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ttg/lits
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:36:28 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 08 Oct 2024 13:36:28 -0400
Subject: [Git][ghc/ghc][master] ci: RISCV64 cross-compile testing
Message-ID: <67056d9c6f650_116d2ffa279c195926@gitlab.mail>



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


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -106,6 +106,7 @@ data Opsys
 
 data LinuxDistro
   = Debian12
+  | Debian12Riscv
   | Debian11
   | Debian11Js
   | Debian10
@@ -303,6 +304,7 @@ distroName :: LinuxDistro -> String
 distroName Debian12   = "deb12"
 distroName Debian11   = "deb11"
 distroName Debian11Js = "deb11-emsdk-closure"
+distroName Debian12Riscv = "deb12-riscv"
 distroName Debian10   = "deb10"
 distroName Debian9    = "deb9"
 distroName Fedora33   = "fedora33"
@@ -626,6 +628,7 @@ data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
+          | RiscV        -- ^ Run this job when the "RISC-V" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
           | FreeBSDLabel -- ^ Run this job when the "FreeBSD" label is set.
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
@@ -674,6 +677,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
+validateRuleString RiscV        = labelString "RISC-V"
 validateRuleString WasmBackend  = labelString "wasm"
 validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
@@ -1125,6 +1129,9 @@ cross_jobs = [
   -- x86 -> aarch64
     validateBuilds Amd64 (Linux Debian11) (crossConfig "aarch64-linux-gnu" (Emulator "qemu-aarch64 -L /usr/aarch64-linux-gnu") Nothing)
 
+  -- x86_64 -> riscv
+  , addValidateRule RiscV (validateBuilds Amd64 (Linux Debian12Riscv) (crossConfig "riscv64-linux-gnu" (Emulator "qemu-riscv64 -L /usr/riscv64-linux-gnu") Nothing))
+
   -- Javascript
   , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11Js) javascriptConfig)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1854,6 +1854,71 @@
       "XZ_OPT": "-9"
     }
   },
+  "nightly-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "8 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "XZ_OPT": "-9"
+    }
+  },
   "nightly-x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -5348,6 +5413,70 @@
       "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
+  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+    }
+  },
   "x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:37:07 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 08 Oct 2024 13:37:07 -0400
Subject: [Git][ghc/ghc][master] Remove unused accumulators in partition_errors
Message-ID: <67056dc392fd7_116d2ffa5ce41990e0@gitlab.mail>



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


Commits:
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -


1 changed file:

- compiler/GHC/Tc/Errors.hs


Changes:

=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -580,22 +580,20 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
     tidy_errs = bagToList (mapBag (tidyDelayedError env) errs)
 
     partition_errors :: [DelayedError] -> ([Hole], [Hole], [NotConcreteError], [(TcCoercion, CtLoc)])
-    partition_errors = go [] [] [] []
-      where
-        go out_of_scope other_holes syn_eqs mult_co_errs []
-          = (out_of_scope, other_holes, syn_eqs, mult_co_errs)
-        go es1 es2 es3 es4 (err:errs)
-          | (es1, es2, es3, es4) <- go es1 es2 es3 es4 errs
-          = case err of
-              DE_Hole hole
-                | isOutOfScopeHole hole
-                -> (hole : es1, es2, es3, es4)
-                | otherwise
-                -> (es1, hole : es2, es3, es4)
-              DE_NotConcrete err
-                -> (es1, es2, err : es3, es4)
-              DE_Multiplicity mult_co loc
-                -> (es1, es2, es3, (mult_co, loc):es4)
+    partition_errors []
+      = ([], [], [], [])
+    partition_errors (err:errs)
+      | (es1, es2, es3, es4) <- partition_errors errs
+      = case err of
+          DE_Hole hole
+            | isOutOfScopeHole hole
+            -> (hole : es1, es2, es3, es4)
+            | otherwise
+            -> (es1, hole : es2, es3, es4)
+          DE_NotConcrete err
+            -> (es1, es2, err : es3, es4)
+          DE_Multiplicity mult_co loc
+            -> (es1, es2, es3, (mult_co, loc):es4)
 
       -- See Note [Suppressing confusing errors]
     suppress :: ErrorItem -> Bool



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:57:07 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Tue, 08 Oct 2024 13:57:07 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann] 11 commits: Remove the
 wrapper/coercion-passing logic for submultiplicity checks
Message-ID: <670572736b9bb_2df11525e888598be@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann at Glasgow Haskell Compiler / GHC


Commits:
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
14f4daf4 by Alan Zimmerman at 2024-10-08T18:44:55+01:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7602d6ed59fe5dd28046182837d82bcb07476b42...14f4daf4aa0c2bb7a53e75b45c0f8a0ab5d1e837

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7602d6ed59fe5dd28046182837d82bcb07476b42...14f4daf4aa0c2bb7a53e75b45c0f8a0ab5d1e837
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 17:59:20 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 08 Oct 2024 13:59:20 -0400
Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass]
 Cleaned up leftover StringLiteral
Message-ID: <670572f832528_2df115159f28605c0@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC


Commits:
e5a7e02f by Hassan Al-Awwadi at 2024-10-08T19:59:04+02:00
Cleaned up leftover StringLiteral

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1842,7 +1842,7 @@ instance ExactPrint (ImportDecl GhcPs) where
         _ -> return ann1
     ann3 <-
       case mpkg of
-       RawPkgQual (StringLiteral src' v _) ->
+       RawPkgQual (SL src' v _) ->
          printStringAtMLocL ann2 limportDeclAnnPackage (sourceTextToString src' (show v))
        _ -> return ann2
     modname' <- markAnnotated modname
@@ -2175,14 +2175,14 @@ exactNsSpec (DataNamespaceSpecifier data_) = do
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint StringLiteral where
+instance ExactPrint StringLit where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StringLiteral src fs mcomma) = do
+  exact (SL src fs mcomma) = do
     printSourceTextAA src (show (unpackFS fs))
     mcomma' <- mapM (\r -> printStringAtNC r ",") mcomma
-    return (StringLiteral src fs mcomma')
+    return (SL src fs mcomma')
 
 -- ---------------------------------------------------------------------
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 18:44:12 2024
From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits))
Date: Tue, 08 Oct 2024 14:44:12 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed]
 Link interface bytecode from package DBs if possible
Message-ID: <67057d7cc14aa_2df115529d2476652@gitlab.mail>



Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC


Commits:
196dbea3 by Torsten Schmits at 2024-10-08T20:42:30+02:00
Link interface bytecode from package DBs if possible

Part of #25090.

MR !13068

When splices are executed with `-fprefer-byte-code`, the loader will
compile Core bindings to bytecode if those are present in interfaces of
module dependencies.

So far, this only applied to local modules (i.e. home modules in make
mode and non-package deps in oneshot mode).

This patch extends support to interfaces loaded from a package DB.
In `getLinkDeps`, the dependencies chosen for recursion were restricted
to `dep_direct_mods`, which has been changed to include `mi_usages`.
In order to unify treatment of the different link variants across
make/oneshot mode, the algorithm's intermediate results have been
abstracted into the data types `LinkDep` and `LinkModule`.

- - - - -


22 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- docs/users_guide/phases.rst
- + testsuite/tests/bytecode/T25090/Dep.hs
- + testsuite/tests/bytecode/T25090/DepApi.hs
- + testsuite/tests/bytecode/T25090/Local.hs
- testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/Num.hs
- + testsuite/tests/bytecode/T25090/Num.hs-boot
- + testsuite/tests/bytecode/T25090/PkgBytecode.hs
- + testsuite/tests/bytecode/T25090/PkgBytecode.stdout
- testsuite/tests/bytecode/T25090/all.T
- + testsuite/tests/bytecode/T25090/dep.conf
- + testsuite/tests/bytecode/T25090/prep.bash
- + testsuite/tests/bytecode/T25090/run.bash
- + testsuite/tests/bytecode/T25090/unit1
- + testsuite/tests/bytecode/T25090/unit2


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -843,6 +843,7 @@ data GeneralFlag
    | Opt_BuildDynamicToo
    | Opt_WriteIfSimplifiedCore
    | Opt_UseBytecodeRatherThanObjects
+   | Opt_PackageDbBytecode
 
    -- safe haskell flags
    | Opt_DistrustAllPackages


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2540,6 +2540,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "package-db-byte-code"             Opt_PackageDbBytecode,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.Directory
 import GHC.Driver.Env.KnotVars
 import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
 import GHC.Iface.Errors.Types
+import GHC.Runtime.Context (emptyInteractiveContext)
 import Data.Function ((&))
 
 {-
@@ -533,12 +534,18 @@ loadInterface doc_str mod from
               --
               -- See Note [Interface Files with Core Definitions]
               add_bytecode old
-                | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls)
+                | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls)
                 = extendModuleEnv old mod action
                 -- Don't add an entry if the iface doesn't have 'extra_decls'
                 -- so 'get_link_deps' knows that it should load object code.
                 | otherwise
                 = old
+                where
+                  -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is
+                  -- accessed when the processed module is from a different
+                  -- package.
+                  hydration_env =
+                    purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)}
 
         ; warnPprTrace bad_boot "loadInterface" (ppr mod) $
           updateEps_  $ \ eps ->


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Linker.Deps
   ( LinkDepsOpts (..)
@@ -28,6 +29,7 @@ import GHC.Types.Unique.DSet
 import GHC.Types.Unique.DFM
 
 import GHC.Utils.Outputable
+import qualified GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Error
 
@@ -47,9 +49,11 @@ import GHC.Utils.Misc
 import GHC.Unit.Home
 import GHC.Data.Maybe
 
-import Control.Monad
 import Control.Applicative
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
 
+import Data.Foldable (traverse_)
 import qualified Data.Set as Set
 import qualified Data.Map as M
 import Data.List (isSuffixOf)
@@ -64,19 +68,21 @@ data LinkDepsOpts = LinkDepsOpts
   , ldUnitEnv     :: !UnitEnv
   , ldPprOpts     :: !SDocContext                   -- ^ Rendering options for error messages
   , ldUseByteCode :: !Bool                          -- ^ Use bytecode rather than objects
+  , ldPkgByteCode :: !Bool                          -- ^ Use bytecode for external packages
   , ldMsgOpts     :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics
   , ldWays        :: !Ways                          -- ^ Enabled ways
   , ldFinderCache :: !FinderCache
   , ldFinderOpts  :: !FinderOpts
-  , ldLoadIface   :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface))
-  , ldLoadByteCode :: !(Module -> IO (Maybe Linkable))
+  , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)))
+  , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable)))
+  , ldDebugTrace :: !(SDoc -> IO ())
   }
 
 data LinkDeps = LinkDeps
   { ldNeededLinkables :: [Linkable]
   , ldAllLinkables    :: [Linkable]
-  , ldUnits           :: [UnitId]
-  , ldNeededUnits     :: UniqDSet UnitId
+  , ldNeededUnits     :: [UnitId]
+  , ldAllUnits        :: UniqDSet UnitId
   }
 
 -- | Find all the packages and linkables that a set of modules depends on
@@ -102,7 +108,14 @@ getLinkDeps opts interp pls span mods = do
 
       get_link_deps opts pls maybe_normal_osuf span mods
 
-
+-- | Compute the linkables for the given module set's dependencies.
+--
+-- Home modules in make mode are treated separately in a preprocessing step,
+-- then all the remaining external deps are processed for both modes.
+-- If bytecode is available, transitive external deps are included, otherwise
+-- the module's library is linked and processing stops.
+--
+-- The results are split into sets of needed/loaded modules/packages.
 get_link_deps
   :: LinkDepsOpts
   -> LoaderState
@@ -111,46 +124,40 @@ get_link_deps
   -> [Module]
   -> IO LinkDeps
 get_link_deps opts pls maybe_normal_osuf span mods = do
-        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-        -- (omitting modules from the interactive package, which is already linked)
-      (mods_s, pkgs_s) <-
-          -- Why two code paths here? There is a significant amount of repeated work
-          -- performed calculating transitive dependencies
-          -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests)
-          if ldOneShotMode opts
-            then follow_deps (filterOut isInteractiveModule mods)
-                              emptyUniqDSet emptyUniqDSet;
-            else do
-              (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
-              return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-
-      let
-        -- 2.  Exclude ones already linked
-        --      Main reason: avoid findModule calls in get_linkable
-            (mods_needed, links_got) = partitionWith split_mods mods_s
-            pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls
-
-            split_mods mod =
-                let is_linked = lookupModuleEnv (objs_loaded pls) mod
-                                <|> lookupModuleEnv (bcos_loaded pls) mod
-                in case is_linked of
-                     Just linkable -> Right linkable
-                     Nothing -> Left mod
-
-        -- 3.  For each dependent module, find its linkable
-        --     This will either be in the HPT or (in the case of one-shot
-        --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
-
-      return $ LinkDeps
-        { ldNeededLinkables = lnks_needed
-        , ldAllLinkables    = links_got ++ lnks_needed
-        , ldUnits           = pkgs_needed
-        , ldNeededUnits     = pkgs_s
-        }
+  (link_deps_home, module_deps_external) <- separate_home_deps
+  link_deps_external <- external_deps opts module_deps_external
+  let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) =
+        classify_deps pls (link_deps_home ++ link_deps_external)
+  ldNeededLinkables <- mapM module_linkable needed_modules
+  pure LinkDeps {
+    ldNeededLinkables,
+    ldAllLinkables = loaded_modules ++ ldNeededLinkables,
+    ldNeededUnits,
+    ldAllUnits
+  }
   where
     mod_graph = ldModuleGraph opts
     unit_env  = ldUnitEnv     opts
+    noninteractive = filterOut isInteractiveModule mods
+
+    -- Preprocess the dependencies in make mode to remove all home modules,
+    -- since the transitive dependency closure is already cached for those in
+    -- the HUG (see MultiLayerModulesTH_* tests for the performance impact).
+    --
+    -- Returns the remaining, external, dependencies on the right, which is the
+    -- entire set for oneshot mode.
+    separate_home_deps =
+      if ldOneShotMode opts
+      then pure ([], noninteractive)
+      else make_deps
+
+    make_deps = do
+      (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods
+      let
+        link_mods =
+          listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods]
+        ext = uniqDSetToList (unionManyUniqDSets (init_ext : dep_ext))
+      pure ([LinkModules (LinkHomeModule <$> link_mods)], ext)
 
     -- This code is used in `--make` mode to calculate the home package and unit dependencies
     -- for a set of modules.
@@ -160,9 +167,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     -- It is also a matter of correctness to use the module graph so that dependencies between home units
     -- is resolved correctly.
-    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+    make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey)
     make_deps_loop found [] = found
-    make_deps_loop found@(found_units, found_mods) (nk:nexts)
+    make_deps_loop found@(external, found_mods) (nk:nexts)
       | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
       | otherwise =
         case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of
@@ -171,85 +178,26 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   -- See #936 and the ghci.prog007 test for why we have to continue traversing through
                   -- boot modules.
                   todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps]
-              in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
+              in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
             Nothing ->
-              let (ModNodeKeyWithUid _ uid) = nk
-              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+              let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk
+              in make_deps_loop (addOneToUniqDSet external (Module (RealUnit (Definite uid)) mod_name), found_mods) nexts
 
     mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
-    (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods)
+    (init_ext, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk noninteractive
 
     all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps]
 
     get_mod_info (ModNodeKeyWithUid gwib uid) =
       case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of
-        Just hmi ->
-          let iface = (hm_iface hmi)
-              mmod = case mi_hsc_src iface of
-                      HsBootFile -> link_boot_mod_error (mi_module iface)
-                      _          -> return $ Just (mi_module iface)
-
-          in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$>  mmod
+        Just hmi -> do
+          let iface = hm_iface hmi
+          case mi_hsc_src iface of
+            HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface)
+            _ -> pure (mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi)
         Nothing -> throwProgramError opts $
           text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
 
-
-       -- This code is used in one-shot mode to traverse downwards through the HPT
-       -- to find all link dependencies.
-       -- The ModIface contains the transitive closure of the module dependencies
-       -- within the current package, *except* for boot modules: if we encounter
-       -- a boot module, we have to find its real interface and discover the
-       -- dependencies of that.  Hence we need to traverse the dependency
-       -- tree recursively.  See bug #936, testcase ghci/prog007.
-    follow_deps :: [Module]             -- modules to follow
-                -> UniqDSet Module         -- accum. module dependencies
-                -> UniqDSet UnitId          -- accum. package dependencies
-                -> IO ([Module], UniqDSet UnitId) -- result
-    follow_deps []     acc_mods acc_pkgs
-        = return (uniqDSetToList acc_mods, acc_pkgs)
-    follow_deps (mod:mods) acc_mods acc_pkgs
-        = do
-          mb_iface <- ldLoadIface opts msg mod
-          iface <- case mb_iface of
-                    Failed err      -> throwProgramError opts $
-                      missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
-                    Succeeded iface -> return iface
-
-          when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
-
-          let
-            pkg = moduleUnit mod
-            deps  = mi_deps iface
-
-            pkg_deps = dep_direct_pkgs deps
-            (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $
-              \case
-                (_, GWIB m IsBoot)  -> Left m
-                (_, GWIB m NotBoot) -> Right m
-
-            mod_deps' = case ue_homeUnit unit_env of
-                          Nothing -> []
-                          Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps))
-            acc_mods'  = case ue_homeUnit unit_env of
-                          Nothing -> acc_mods
-                          Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps)
-            acc_pkgs'  = addListToUniqDSet acc_pkgs (Set.toList pkg_deps)
-
-          case ue_homeUnit unit_env of
-            Just home_unit | isHomeUnit home_unit pkg ->  follow_deps (mod_deps' ++ mods)
-                                                                      acc_mods' acc_pkgs'
-            _ ->  follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
-        where
-           msg = text "need to link module" <+> ppr mod <+>
-                  text "due to use of Template Haskell"
-
-
-
-    link_boot_mod_error :: Module -> IO a
-    link_boot_mod_error mod = throwProgramError opts $
-            text "module" <+> ppr mod <+>
-            text "cannot be linked; it is only available as a boot module"
-
     no_obj :: Outputable a => a -> IO b
     no_obj mod = dieWith opts span $
                      text "cannot find object file for module " <>
@@ -258,6 +206,20 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     while_linking_expr = text "while linking an interpreted expression"
 
+  -- Extract the 'Linkable's for unlinked modules from the intermediate
+  -- results.
+    module_linkable = \case
+      LinkHomeModule hmi ->
+        adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi))
+
+      LinkObjectModule iface loc -> do
+        let mod = mi_module iface
+        findObjectLinkableMaybe mod loc >>= \case
+          Nothing  -> no_obj mod
+          Just lnk -> adjust_linkable lnk
+
+      LinkByteCodeModule _ load_bytecode ->
+        load_bytecode
 
     -- See Note [Using Byte Code rather than Object Code for Template Haskell]
     homeModLinkable :: HomeModInfo -> Maybe Linkable
@@ -266,57 +228,257 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
-        | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
-        = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
-        | otherwise
-        = do    -- It's not in the HPT because we are in one shot mode,
-                -- so use the Finder to get a ModLocation...
-             case ue_homeUnit unit_env of
-              Nothing -> no_obj mod
-              Just home_unit -> do
-                from_bc <- ldLoadByteCode opts mod
-                maybe (fallback_no_bytecode home_unit mod) pure from_bc
-        where
-
-            fallback_no_bytecode home_unit mod = do
-              let fc = ldFinderCache opts
-              let fopts = ldFinderOpts opts
-              mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod)
-              case mb_stuff of
-                Found loc _ -> do
-                  mb_lnk <- findObjectLinkableMaybe mod loc
-                  case mb_lnk of
-                    Nothing  -> no_obj mod
-                    Just lnk -> adjust_linkable lnk
-                _ -> no_obj (moduleName mod)
-
-            adjust_linkable lnk
-                | Just new_osuf <- maybe_normal_osuf = do
-                        new_parts <- mapM (adjust_part new_osuf)
-                                        (linkableParts lnk)
-                        return lnk{ linkableParts=new_parts }
-                | otherwise =
-                        return lnk
-
-            adjust_part new_osuf part = case part of
-              DotO file ModuleObject -> do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
-                ok <- doesFileExist new_file
-                if (not ok)
-                   then dieWith opts span $
-                          text "cannot find object file "
-                                <> quotes (text new_file) $$ while_linking_expr
-                   else return (DotO new_file ModuleObject)
-              DotO file ForeignObject -> pure (DotO file ForeignObject)
-              DotA fp    -> panic ("adjust_ul DotA " ++ show fp)
-              DotDLL fp  -> panic ("adjust_ul DotDLL " ++ show fp)
-              BCOs {}    -> pure part
-              LazyBCOs{} -> pure part
-              CoreBindings WholeCoreBindings {wcb_module} ->
-                pprPanic "Unhydrated core bindings" (ppr wcb_module)
+    adjust_linkable lnk
+        | Just new_osuf <- maybe_normal_osuf = do
+                new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf)
+                                (linkableParts lnk)
+                return lnk {linkableParts = new_uls}
+        | otherwise =
+                return lnk
+
+    adjust_part osuf new_osuf part = case part of
+      DotO file ModuleObject -> do
+        massert (osuf `isSuffixOf` file)
+        let file_base = fromJust (stripExtension osuf file)
+            new_file = file_base <.> new_osuf
+        ok <- doesFileExist new_file
+        if (not ok)
+            then dieWith opts span $
+                  text "cannot find object file "
+                        <> quotes (text new_file) $$ while_linking_expr
+            else return (DotO new_file ModuleObject)
+      DotO file ForeignObject -> pure (DotO file ForeignObject)
+      DotA fp    -> panic ("adjust_part DotA " ++ show fp)
+      DotDLL fp  -> panic ("adjust_part DotDLL " ++ show fp)
+      BCOs {}    -> pure part
+      LazyBCOs{} -> pure part
+      CoreBindings WholeCoreBindings {wcb_module} ->
+        pprPanic "Unhydrated core bindings" (ppr wcb_module)
+
+data LinkModule =
+  LinkHomeModule !HomeModInfo
+  |
+  LinkObjectModule !ModIface !ModLocation
+  |
+  LinkByteCodeModule !ModIface !(IO Linkable)
+
+link_module_iface :: LinkModule -> ModIface
+link_module_iface = \case
+  LinkHomeModule hmi -> hm_iface hmi
+  LinkObjectModule iface _ -> iface
+  LinkByteCodeModule iface _ -> iface
+
+instance Outputable LinkModule where
+  ppr = \case
+    LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI")
+    LinkObjectModule iface _ -> ppr (mi_module iface)
+    LinkByteCodeModule iface _ -> ppr (mi_module iface) <+> brackets (text "BC")
+
+data LinkDep =
+  LinkModules !(UniqDFM ModuleName LinkModule)
+  |
+  LinkLibrary !UnitId
+
+instance Outputable LinkDep where
+  ppr = \case
+    LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods)
+    LinkLibrary uid -> text "library:" <+> ppr uid
+
+data OneshotError =
+  NoLocation !Module
+  |
+  NoInterface !MissingInterfaceError
+  |
+  LinkBootModule !Module
+
+-- Compute the transitive dependency closure of the given modules.
+--
+-- Used for all oneshot mode dependencies and for external dependencies of home
+-- modules in make mode.
+--
+-- TODO is the following still relevant?
+-- The ModIface contains the transitive closure of the module dependencies
+-- within the current package, *except* for boot modules: if we encounter
+-- a boot module, we have to find its real interface and discover the
+-- dependencies of that.  Hence we need to traverse the dependency
+-- tree recursively.  See bug #936, testcase ghci/prog007.
+external_deps ::
+  LinkDepsOpts ->
+  -- | Modules whose imports to follow
+  [Module] ->
+  IO [LinkDep]
+external_deps opts mods =
+  runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case
+    Right a -> pure (eltsUDFM a)
+    Left err -> throwProgramError opts (message err)
+  where
+    message = \case
+      NoLocation mod ->
+        pprPanic "found iface but no location" (ppr mod)
+      NoInterface err ->
+        missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
+      LinkBootModule mod ->
+        link_boot_mod_error mod
+
+external_deps_loop ::
+  LinkDepsOpts ->
+  [Module] ->
+  UniqDFM UnitId LinkDep ->
+  ExceptT OneshotError IO (UniqDFM UnitId LinkDep)
+external_deps_loop _ [] acc =
+  pure acc
+external_deps_loop opts (mod : mods) acc = do
+  (new_acc, new_mods, action) <- process_module
+  traverse_ debug_log action
+  external_deps_loop opts (new_mods ++ mods) new_acc
+  where
+    debug_log action =
+      liftIO $ ldDebugTrace opts $
+      text "TH dep" <+> ppr mod <+> brackets (sep [
+        if is_home then text "home" else Outputable.empty,
+        text action
+      ])
+
+    -- Decide how this module needs to be processed.
+    -- We only need an interface if we want to load bytecode or if we have to
+    -- link an object file (which happens for home unit modules, since those
+    -- have no libraries).
+    process_module
+      | already_seen = pure (acc, [], Nothing)
+      | is_home || prefer_bytecode = try_iface
+      | otherwise = add_library
+
+    -- Check whether the current module was processed before.
+    -- Since the accumulator is keyed by unit ID, we have to perform two
+    -- lookups.
+    -- If another module from this module's unit has been determined to be
+    -- linked as a library previously, we skip this module, assuming that no
+    -- bytecode is available for the entire package.
+    already_seen
+      | Just (LinkModules mods) <- mod_dep
+      = elemUDFM mod_name mods
+      | Just (LinkLibrary _) <- mod_dep
+      = True
+      | otherwise
+      = False
+
+    -- Load the iface and attempt to get bytecode from Core bindings.
+    try_iface =
+      liftIO (ldLoadIface opts load_reason mod) >>= \case
+        Failed err -> throwE (NoInterface err)
+        Succeeded (iface, loc) -> do
+          mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface))
+          with_iface loc iface mb_load_bc
+
+    -- Decide how to link this module.
+    -- If bytecode or an object file is available, use those in that order.
+    -- Otherwise fall back to linking a library.
+    with_iface loc iface mb_load_bc
+      | IsBoot <- mi_boot iface
+      = throwE (LinkBootModule mod)
+
+      | prefer_bytecode
+      , Just load_bc <- mb_load_bc
+      = pure (add_module iface (LinkByteCodeModule iface load_bc) "bytecode")
+
+      | is_home
+      = pure (add_module iface (LinkObjectModule iface loc) "object")
+
+      | otherwise
+      = add_library
+
+    add_library =
+      pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library")
+
+    add_module iface lmod action =
+      (addListToUDFM with_mod (direct_pkgs iface), new_deps iface, Just action)
+      where
+        with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id
+
+    add_package_module lmod = \case
+      Just (LinkLibrary u) -> Just (LinkLibrary u)
+      Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod))
+      Nothing -> Just (LinkModules (unitUDFM mod_name lmod))
+
+    direct_pkgs iface
+      | prefer_bytecode
+      = []
+      | otherwise
+      = [(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))]
+
+    new_deps iface
+      | prefer_bytecode
+      -- TODO How can we better determine the external deps?
+      -- OTOH, we probably don't want to link unused dependencies anyway.
+      = [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface] ++ local
+      | is_home
+      = local
+      | otherwise
+      = []
+      where
+        local =
+          [
+            mkModule mod_unit m
+            -- TODO Somehow this just works, no idea what the deal was in the
+            -- old code with boot modules.
+            | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface))
+          ]
+
+    is_home
+      | Just home <- mb_home
+      = homeUnitAsUnit home == mod_unit
+      | otherwise
+      = False
+
+    mod_dep = lookupUDFM acc mod_unit_id
+    mod_name = moduleName mod
+    mod_unit_id = moduleUnitId mod
+    mod_unit = moduleUnit mod
+    load_reason =
+      text "need to link module" <+> ppr mod <+>
+      text "due to use of Template Haskell"
+
+    prefer_bytecode = ldUseByteCode opts && (is_home || ldPkgByteCode opts)
+    mb_home = ue_homeUnit (ldUnitEnv opts)
+
+link_boot_mod_error :: Module -> SDoc
+link_boot_mod_error mod =
+  text "module" <+> ppr mod <+>
+  text "cannot be linked; it is only available as a boot module"
+
+-- | Split link dependencies into the sets of modules and packages that have
+-- been linked previously and those that need to be linked now by checking for
+-- their presence in the 'LoaderState':
+--
+-- - For module dependencies, in the sets of loaded objects and BCOs
+--   ('objs_loaded' and 'bcos_loaded')
+-- - For package dependencies, in the set of loaded packages ('pkgs_loaded')
+classify_deps ::
+  LoaderState ->
+  [LinkDep] ->
+  ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId])
+classify_deps pls deps =
+  (loaded_modules, needed_modules, all_packages, needed_packages)
+  where
+    (loaded_modules, needed_modules) =
+      partitionWith loaded_or_needed_module (concatMap eltsUDFM modules)
+
+    needed_packages =
+      eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls)
+
+    all_packages = mkUniqDSet packages
+
+    (modules, packages) = flip partitionWith deps $ \case
+      LinkModules mods -> Left mods
+      LinkLibrary lib -> Right lib
+
+    loaded_or_needed_module lm =
+      maybe (Right lm) Left (loaded_module (mi_module (link_module_iface lm)))
+
+    loaded_module mod =
+      lookupModuleEnv (objs_loaded pls) mod
+      <|>
+      lookupModuleEnv (bcos_loaded pls) mod
 
 {-
 Note [Using Byte Code rather than Object Code for Template Haskell]


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -77,11 +77,13 @@ import GHC.Utils.TmpFs
 
 import GHC.Unit.Env
 import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
+import GHC.Unit.Finder
 import GHC.Unit.Module
 import GHC.Unit.State as Packages
 
 import qualified GHC.Data.ShortText as ST
 import GHC.Data.FastString
+import qualified GHC.Data.Maybe as Maybe
 
 import GHC.Linker.Deps
 import GHC.Linker.MacOS
@@ -94,6 +96,7 @@ import Control.Monad
 import qualified Data.Set as Set
 import Data.Char (isSpace)
 import qualified Data.Foldable as Foldable
+import Data.Functor ((<&>))
 import Data.IORef
 import Data.List (intercalate, isPrefixOf, nub, partition)
 import Data.Maybe
@@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do
    -- Find what packages and linkables are required
    deps <- getLinkDeps opts interp pls span needed_mods
 
-   let this_pkgs_needed = ldNeededUnits deps
+   let this_pkgs_needed = ldAllUnits deps
 
    -- Link the packages and modules required
-   pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
+   pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls
    (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
    let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
        all_pkgs_loaded = pkgs_loaded pls2
@@ -646,18 +649,39 @@ initLinkDepsOpts hsc_env = opts
             , ldFinderCache = hsc_FC hsc_env
             , ldFinderOpts  = initFinderOpts dflags
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
+            , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
             , ldLoadIface
             , ldLoadByteCode
+            , ldDebugTrace = debugTraceMsg (hsc_logger hsc_env) 3
             }
     dflags = hsc_dflags hsc_env
-    ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env
-                          $ loadInterface msg mod (ImportByUser NotBoot)
+
+    ldLoadIface msg mod =
+      initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case
+        Maybe.Failed err -> pure (Maybe.Failed err)
+        Maybe.Succeeded iface ->
+          find_location mod <&> \case
+            InstalledFound loc _ -> Maybe.Succeeded (iface, loc)
+            err -> Maybe.Failed $
+                   cannotFindInterface unit_state home_unit
+                   (targetProfile dflags) (moduleName mod) err
+
+    find_location mod =
+      liftIO $
+      findExactModule (hsc_FC hsc_env) (initFinderOpts dflags)
+      (initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env)
+      unit_state home_unit
+      (toUnitId <$> mod)
+
+    unit_state = hsc_units hsc_env
+
+    home_unit = ue_homeUnit (hsc_unit_env hsc_env)
 
     ldLoadByteCode mod = do
       EPS {eps_iface_bytecode} <- hscEPS hsc_env
-      sequence (lookupModuleEnv eps_iface_bytecode mod)
+      pure (lookupModuleEnv eps_iface_bytecode mod)
 
 
 


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -734,7 +734,7 @@ mkStubPaths fopts mod location = do
     src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
 
 -- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
+-- findObjectLinkable isn't related to the other stuff in here,
 -- but there's no other obvious place for it
 
 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)


=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed
 build artifacts, which can be objects or bytecode, depending on the build
 settings.
 
-1. In make mode, all eligible modules are part of the dependency graph.
+1. In make mode, all eligible home modules are part of the dependency graph.
    Their interfaces are loaded unconditionally and in dependency order by the
    compilation manager, and each module's bytecode is prepared before its
    dependents are compiled, in one of two ways:
@@ -88,9 +88,10 @@ settings.
 2. In oneshot mode, which compiles individual modules without a shared home unit
    graph, a previously compiled module is not reprocessed as described for make
    mode above.
-   When 'get_link_deps' encounters a dependency on a local module, it requests
-   its bytecode from the External Package State, who loads the interface
-   on-demand.
+   'get_link_deps' requests the bytecode of dependencies from the External
+   Package State, who loads the interface on-demand.
+   This works for modules in local directories (via @-i@ and @-hidir@) as well
+   as those exposed from a package DB.
 
    Since the EPS stores interfaces for all package dependencies in addition to
    local modules in oneshot mode, it has a substantial memory footprint.
@@ -109,6 +110,18 @@ settings.
    storing the intermediate representation as rehydrated Core bindings, since
    the latter have a significantly greater memory footprint.
 
+3. In both of the above modes, whenever a module from an external package
+   (loaded from a package DB) is encountered, the workflow is the same as for
+   oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object
+   code is loaded.
+   Interfaces for external modules are stored together with local oneshot mode
+   modules, so almost no special treatment is necessary, with the exception of:
+   - When external package modules are compiled, the @InteractiveContext@ in
+     @HscEnv@ is accessed, which is not available due to its impact on retention
+     of outdated build products.
+     This is solved by writing an empty @InteractiveContext@ to the env used for
+     compilation.
+
 Note [Size of Interface Files with Core Definitions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op.
 Otherwise, the stub objects from the interface are compiled to objects in
 'generateByteCode' and added to the 'HomeModLinkable' as well.
 
-Case 3 is not implemented yet (!13042).
+In case 3, Core bindings are loaded from the EPS, where stubs only exist in
+their serialized form in the interface, so they must be regenerated like in case
+2.
 
 Problem 3:
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -826,6 +826,17 @@ Options affecting code generation
     will generate byte-code rather than object code.
 
 
+.. ghc-flag:: -fpackage-db-byte-code
+    :shortdesc: Use byte-code from package DB dependencies
+    :type: dynamic
+    :category: codegen
+
+    GHC normally only considers local modules to be eligible for loading
+    bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`.
+    When this flag is specified additionally, bytecode will be loaded from
+    interfaces for all external package dependencies that provide it.
+
+
 .. _options-linker:
 
 Options affecting linking


=====================================
testsuite/tests/bytecode/T25090/Dep.hs
=====================================
@@ -0,0 +1,15 @@
+module Dep where
+
+data A = A Int
+
+used :: Int
+used = 9681
+
+dep :: A
+dep = A used
+
+unused1 :: A
+unused1 = A 1
+
+unused2 :: A
+unused2 = unused1


=====================================
testsuite/tests/bytecode/T25090/DepApi.hs
=====================================
@@ -0,0 +1,7 @@
+module DepApi (A (A), dep) where
+
+import Dep (A (A))
+import qualified Dep
+
+dep :: A
+dep = Dep.dep


=====================================
testsuite/tests/bytecode/T25090/Local.hs
=====================================
@@ -0,0 +1,15 @@
+{-# language PackageImports #-}
+
+module Local where
+
+import GHC.Prim
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+-- just to be sure that the file isn't accidentally picked up locally
+import "dep" DepApi (dep, A (A))
+import {-# source #-} Num (num)
+
+splc :: ExpQ
+splc = lift @_ @Int (num + d)
+  where
+    A d = dep


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -19,3 +19,35 @@ T25090a:
 T25090b:
 	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe
+
+DB := -package-db db -package dep
+BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0
+BC := -fprefer-byte-code -fbyte-code-and-object-code
+ARGS := $(BASIC) $(BC)
+
+T25090_pkg:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_empty:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_nolib:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none"
+	./run.bash "$(TEST_HC)" "$(ARGS)"
+
+T25090_pkg_obj_code:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code"
+
+T25090_pkg_multi_unit:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared"
+	mkdir -p unit2-src/
+	mv Local.hs Num.hs Num.hs-boot unit2-src/
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -dynamic -unit @unit1 -unit @unit2
+	./PkgBytecode
+
+T25090_pkg_archive:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive"
+	./run.bash "$(TEST_HC)" "$(ARGS)"


=====================================
testsuite/tests/bytecode/T25090/Num.hs
=====================================
@@ -0,0 +1,4 @@
+module Num where
+
+num :: Int
+num = 48332


=====================================
testsuite/tests/bytecode/T25090/Num.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module Num where
+
+num :: Int


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.hs
=====================================
@@ -0,0 +1,12 @@
+{-# language TemplateHaskell #-}
+
+module Main where
+
+import GHC.Prim
+import Local (splc)
+
+a :: Int
+a = $(splc)
+
+main :: IO ()
+main = putStrLn (show a)


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.stdout
=====================================
@@ -0,0 +1 @@
+58013


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -16,3 +16,33 @@ def test_T25090(name):
 
 test_T25090('T25090a')
 test_T25090('T25090b')
+
+def test_pkg(name, files = []):
+    test(
+        name,
+        [
+            extra_files([
+                'PkgBytecode.hs',
+                'Local.hs',
+                'Dep.hs',
+                'DepApi.hs',
+                'Num.hs',
+                'Num.hs-boot',
+                'dep.conf',
+                'prep.bash',
+                'run.bash',
+            ] + files),
+            use_specs({'stdout': 'PkgBytecode.stdout'}),
+        ],
+        makefile_test,
+        [],
+    )
+
+test_pkg('T25090_pkg')
+test_pkg('T25090_pkg_empty')
+test_pkg('T25090_pkg_nolib')
+test_pkg('T25090_pkg_obj_code')
+test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2'])
+# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a
+# comment says "search for .so libraries _first_" (rather than "only").
+# test_pkg('T25090_pkg_archive')


=====================================
testsuite/tests/bytecode/T25090/dep.conf
=====================================
@@ -0,0 +1,8 @@
+name: dep
+version: 1.0
+id: dep-1.0
+key: dep-1.0
+exposed: True
+exposed-modules: DepApi
+import-dirs: ${pkgroot}/dep
+library-dirs: ${pkgroot}/dep


=====================================
testsuite/tests/bytecode/T25090/prep.bash
=====================================
@@ -0,0 +1,57 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+ghc_pkg_cmd="$3"
+library="$4"
+
+base="$PWD"
+db="$base/db"
+dep="$base/dep"
+conf_dep="${dep}/dep.conf"
+
+mkdir -p "$dep" "$db"
+mv Dep.hs DepApi.hs "$dep/"
+cp dep.conf "$dep/"
+
+ghc_pkg()
+{
+  eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@"
+}
+
+ghc()
+{
+  eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@"
+}
+
+version=$(ghc "--numeric-version")
+
+ghc_pkg recache
+
+ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+
+if [[ "$library" == 'shared' ]]
+then
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'shared-empty' ]]
+then
+  echo 'module Dummy where' > Dummy.hs
+  ghc "-dynamic-too -c Dummy.hs"
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'archive' ]]
+then
+  $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'none' ]]
+then
+  :
+else
+  echo "Invalid argument for 'library': $library"
+  exit 1
+fi
+
+ghc_pkg -v0 register "${conf_dep at Q}"


=====================================
testsuite/tests/bytecode/T25090/run.bash
=====================================
@@ -0,0 +1,16 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+
+ghc()
+{
+  eval "${ghc_cmd at Q} $ghc_opts $@"
+}
+
+ghc -c Num.hs-boot Num.hs Local.hs
+ghc -fpackage-db-byte-code -c PkgBytecode.hs
+ghc PkgBytecode.o -o PkgBytecode
+./PkgBytecode


=====================================
testsuite/tests/bytecode/T25090/unit1
=====================================
@@ -0,0 +1 @@
+-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2


=====================================
testsuite/tests/bytecode/T25090/unit2
=====================================
@@ -0,0 +1 @@
+-i -i./unit2-src Local Num -this-unit-id unit2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/196dbea3920369a3f6141c09f9a66b4452189675

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 22:04:29 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 08 Oct 2024 18:04:29 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.8-2
Message-ID: <6705ac6dd97b9_36fafb5f8d04713a@gitlab.mail>



Ben Gamari pushed new branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.8-2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 22:07:26 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 08 Oct 2024 18:07:26 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 2 commits: linker: Avoid linear
 search when looking up Haskell symbols via dlsym
Message-ID: <6705ad1e9a660_36fafb5f3bb0744fa@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
5a9a1757 by Alexis King at 2024-10-08T18:07:01-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
4973098d by Ben Gamari at 2024-10-08T18:07:01-04:00
hadrian: Update bootstrap plans

- - - - -


14 changed files:

- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- hadrian/bootstrap/generate_bootstrap_plans
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- rts/Linker.c
- rts/RtsSymbols.c
- rts/include/rts/Linker.h
- testsuite/tests/rts/linker/T2615.hs


Changes:

=====================================
compiler/GHC/ByteCode/Linker.hs
=====================================
@@ -25,6 +25,7 @@ import GHCi.ResolvedBCO
 import GHCi.BreakArray
 
 import GHC.Builtin.PrimOps
+import GHC.Builtin.PrimOps.Ids
 import GHC.Builtin.Names
 
 import GHC.Unit.Types
@@ -40,6 +41,8 @@ import GHC.Utils.Outputable
 
 import GHC.Types.Name
 import GHC.Types.Name.Env
+import qualified GHC.Types.Id as Id
+import GHC.Types.Unique.DFM
 
 import Language.Haskell.Syntax.Module.Name
 
@@ -54,32 +57,33 @@ import GHC.Exts
 
 linkBCO
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> UnlinkedBCO
   -> IO ResolvedBCO
-linkBCO interp le bco_ix breakarray
+linkBCO interp pkgs_loaded le bco_ix breakarray
            (UnlinkedBCO _ arity insns bitmap lits0 ptrs0) = do
   -- fromIntegral Word -> Word64 should be a no op if Word is Word64
   -- otherwise it will result in a cast to longlong on 32bit systems.
-  lits <- mapM (fmap fromIntegral . lookupLiteral interp le) (ssElts lits0)
-  ptrs <- mapM (resolvePtr interp le bco_ix breakarray) (ssElts ptrs0)
+  lits <- mapM (fmap fromIntegral . lookupLiteral interp pkgs_loaded le) (ssElts lits0)
+  ptrs <- mapM (resolvePtr interp pkgs_loaded le bco_ix breakarray) (ssElts ptrs0)
   return (ResolvedBCO isLittleEndian arity insns bitmap
               (listArray (0, fromIntegral (sizeSS lits0)-1) lits)
               (addListToSS emptySS ptrs))
 
-lookupLiteral :: Interp -> LinkerEnv -> BCONPtr -> IO Word
-lookupLiteral interp le ptr = case ptr of
+lookupLiteral :: Interp -> PkgsLoaded -> LinkerEnv -> BCONPtr -> IO Word
+lookupLiteral interp pkgs_loaded le ptr = case ptr of
   BCONPtrWord lit -> return lit
   BCONPtrLbl  sym -> do
     Ptr a# <- lookupStaticPtr interp sym
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrItbl nm -> do
-    Ptr a# <- lookupIE interp (itbl_env le) nm
+    Ptr a# <- lookupIE interp pkgs_loaded (itbl_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrAddr nm -> do
-    Ptr a# <- lookupAddr interp (addr_env le) nm
+    Ptr a# <- lookupAddr interp pkgs_loaded (addr_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrStr _ ->
     -- should be eliminated during assembleBCOs
@@ -93,19 +97,19 @@ lookupStaticPtr interp addr_of_label_string = do
     Nothing  -> linkFail "GHC.ByteCode.Linker: can't find label"
                   (unpackFS addr_of_label_string)
 
-lookupIE :: Interp -> ItblEnv -> Name -> IO (Ptr ())
-lookupIE interp ie con_nm =
+lookupIE :: Interp -> PkgsLoaded -> ItblEnv -> Name -> IO (Ptr ())
+lookupIE interp pkgs_loaded ie con_nm =
   case lookupNameEnv ie con_nm of
     Just (_, ItblPtr a) -> return (fromRemotePtr (castRemotePtr a))
     Nothing -> do -- try looking up in the object files.
        let sym_to_find1 = nameToCLabel con_nm "con_info"
-       m <- lookupSymbol interp sym_to_find1
+       m <- lookupHsSymbol interp pkgs_loaded con_nm "con_info"
        case m of
           Just addr -> return addr
           Nothing
              -> do -- perhaps a nullary constructor?
                    let sym_to_find2 = nameToCLabel con_nm "static_info"
-                   n <- lookupSymbol interp sym_to_find2
+                   n <- lookupHsSymbol interp pkgs_loaded con_nm "static_info"
                    case n of
                       Just addr -> return addr
                       Nothing   -> linkFail "GHC.ByteCode.Linker.lookupIE"
@@ -113,35 +117,36 @@ lookupIE interp ie con_nm =
                                        unpackFS sym_to_find2)
 
 -- see Note [Generating code for top-level string literal bindings] in GHC.StgToByteCode
-lookupAddr :: Interp -> AddrEnv -> Name -> IO (Ptr ())
-lookupAddr interp ae addr_nm = do
+lookupAddr :: Interp -> PkgsLoaded -> AddrEnv -> Name -> IO (Ptr ())
+lookupAddr interp pkgs_loaded ae addr_nm = do
   case lookupNameEnv ae addr_nm of
     Just (_, AddrPtr ptr) -> return (fromRemotePtr ptr)
     Nothing -> do -- try looking up in the object files.
       let sym_to_find = nameToCLabel addr_nm "bytes"
                           -- see Note [Bytes label] in GHC.Cmm.CLabel
-      m <- lookupSymbol interp sym_to_find
+      m <- lookupHsSymbol interp pkgs_loaded addr_nm "bytes"
       case m of
         Just ptr -> return ptr
         Nothing -> linkFail "GHC.ByteCode.Linker.lookupAddr"
                      (unpackFS sym_to_find)
 
-lookupPrimOp :: Interp -> PrimOp -> IO (RemotePtr ())
-lookupPrimOp interp primop = do
+lookupPrimOp :: Interp -> PkgsLoaded -> PrimOp -> IO (RemotePtr ())
+lookupPrimOp interp pkgs_loaded primop = do
   let sym_to_find = primopToCLabel primop "closure"
-  m <- lookupSymbol interp (mkFastString sym_to_find)
+  m <- lookupHsSymbol interp pkgs_loaded (Id.idName $ primOpId primop) "closure"
   case m of
     Just p -> return (toRemotePtr p)
     Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE(primop)" sym_to_find
 
 resolvePtr
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> BCOPtr
   -> IO ResolvedBCOPtr
-resolvePtr interp le bco_ix breakarray ptr = case ptr of
+resolvePtr interp pkgs_loaded le bco_ix breakarray ptr = case ptr of
   BCOPtrName nm
     | Just ix <- lookupNameEnv bco_ix nm
     -> return (ResolvedBCORef ix) -- ref to another BCO in this group
@@ -153,20 +158,42 @@ resolvePtr interp le bco_ix breakarray ptr = case ptr of
     -> assertPpr (isExternalName nm) (ppr nm) $
        do
           let sym_to_find = nameToCLabel nm "closure"
-          m <- lookupSymbol interp sym_to_find
+          m <- lookupHsSymbol interp pkgs_loaded nm "closure"
           case m of
             Just p -> return (ResolvedBCOStaticPtr (toRemotePtr p))
             Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE" (unpackFS sym_to_find)
 
   BCOPtrPrimOp op
-    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp op
+    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp pkgs_loaded op
 
   BCOPtrBCO bco
-    -> ResolvedBCOPtrBCO <$> linkBCO interp le bco_ix breakarray bco
+    -> ResolvedBCOPtrBCO <$> linkBCO interp pkgs_loaded le bco_ix breakarray bco
 
   BCOPtrBreakArray
     -> return (ResolvedBCOPtrBreakArray breakarray)
 
+-- | Look up the address of a Haskell symbol in the currently
+-- loaded units.
+--
+-- See Note [Looking up symbols in the relevant objects].
+lookupHsSymbol :: Interp -> PkgsLoaded -> Name -> String -> IO (Maybe (Ptr ()))
+lookupHsSymbol interp pkgs_loaded nm sym_suffix = do
+  massertPpr (isExternalName nm) (ppr nm)
+  let sym_to_find = nameToCLabel nm sym_suffix
+      pkg_id = moduleUnitId $ nameModule nm
+      loaded_dlls = maybe [] loaded_pkg_hs_dlls $ lookupUDFM pkgs_loaded pkg_id
+
+      go (dll:dlls) = do
+        mb_ptr <- lookupSymbolInDLL interp dll sym_to_find
+        case mb_ptr of
+          Just ptr -> pure (Just ptr)
+          Nothing -> go dlls
+      go [] =
+        -- See Note [Symbols may not be found in pkgs_loaded] in GHC.Linker.Types
+        lookupSymbol interp sym_to_find
+
+  go loaded_dlls
+
 linkFail :: String -> String -> IO a
 linkFail who what
    = throwGhcExceptionIO (ProgramError $


=====================================
compiler/GHC/Driver/Plugins.hs
=====================================
@@ -405,12 +405,12 @@ loadExternalPluginLib :: FilePath -> IO ()
 loadExternalPluginLib path = do
   -- load library
   loadDLL path >>= \case
-    Just errmsg -> pprPanic "loadExternalPluginLib"
-                    (vcat [ text "Can't load plugin library"
-                          , text "  Library path: " <> text path
-                          , text "  Error       : " <> text errmsg
-                          ])
-    Nothing -> do
+    Left errmsg -> pprPanic "loadExternalPluginLib"
+                     (vcat [ text "Can't load plugin library"
+                           , text "  Library path: " <> text path
+                           , text "  Error       : " <> text errmsg
+                           ])
+    Right _ -> do
       -- resolve objects
       resolveObjs >>= \case
         True -> return ()


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -56,6 +56,7 @@ import GHC.Tc.Utils.Monad
 import GHC.Runtime.Interpreter
 import GHCi.RemoteTypes
 import GHC.Iface.Load
+import GHCi.Message (LoadedDLL)
 
 import GHC.ByteCode.Linker
 import GHC.ByteCode.Asm
@@ -145,7 +146,7 @@ emptyLoaderState = LoaderState
   --
   -- The linker's symbol table is populated with RTS symbols using an
   -- explicit list.  See rts/Linker.c for details.
-  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] emptyUniqDSet)
+  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] [] emptyUniqDSet)
 
 extendLoadedEnv :: Interp -> [(Name,ForeignHValue)] -> IO ()
 extendLoadedEnv interp new_bindings =
@@ -194,8 +195,8 @@ loadDependencies
   -> SrcSpan
   -> [Module]
   -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) -- ^ returns the set of linkables required
+-- When called, the loader state must have been initialized (see `initLoaderState`)
 loadDependencies interp hsc_env pls span needed_mods = do
---   initLoaderState (hsc_dflags hsc_env) dl
    let opts = initLinkDepsOpts hsc_env
 
    -- Find what packages and linkables are required
@@ -485,25 +486,25 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
     DLL dll_unadorned -> do
       maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
       case maybe_errstr of
-         Nothing -> maybePutStrLn logger "done"
-         Just mm | platformOS platform /= OSDarwin ->
+         Right _ -> maybePutStrLn logger "done"
+         Left mm | platformOS platform /= OSDarwin ->
            preloadFailed mm lib_paths lib_spec
-         Just mm | otherwise -> do
+         Left mm | otherwise -> do
            -- As a backup, on Darwin, try to also load a .so file
            -- since (apparently) some things install that way - see
            -- ticket #8770.
            let libfile = ("lib" ++ dll_unadorned) <.> "so"
            err2 <- loadDLL interp libfile
            case err2 of
-             Nothing -> maybePutStrLn logger "done"
-             Just _  -> preloadFailed mm lib_paths lib_spec
+             Right _ -> maybePutStrLn logger "done"
+             Left _  -> preloadFailed mm lib_paths lib_spec
       return pls
 
     DLLPath dll_path -> do
       do maybe_errstr <- loadDLL interp dll_path
          case maybe_errstr of
-            Nothing -> maybePutStrLn logger "done"
-            Just mm -> preloadFailed mm lib_paths lib_spec
+            Right _ -> maybePutStrLn logger "done"
+            Left mm -> preloadFailed mm lib_paths lib_spec
          return pls
 
     Framework framework ->
@@ -588,7 +589,7 @@ loadExpr interp hsc_env span root_ul_bco = do
         let le = linker_env pls
             nobreakarray = error "no break array"
             bco_ix = mkNameEnv [(unlinkedBCOName root_ul_bco, 0)]
-        resolved <- linkBCO interp le bco_ix nobreakarray root_ul_bco
+        resolved <- linkBCO interp (pkgs_loaded pls) le bco_ix nobreakarray root_ul_bco
         [root_hvref] <- createBCOs interp [resolved]
         fhv <- mkFinalizedHValue interp root_hvref
         return (pls, fhv)
@@ -651,7 +652,7 @@ loadDecls interp hsc_env span cbc at CompiledByteCode{..} = do
                        , addr_env = plusNameEnv (addr_env le) bc_strs }
 
           -- Link the necessary packages and linkables
-          new_bindings <- linkSomeBCOs interp le2 [cbc]
+          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 [cbc]
           nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
           let ce2  = extendClosureEnv (closure_env le2) nms_fhvs
               !pls2 = pls { linker_env = le2 { closure_env = ce2 } }
@@ -832,8 +833,8 @@ dynLoadObjs interp hsc_env pls at LoaderState{..} objs = do
     changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
     m <- loadDLL interp soFile
     case m of
-        Nothing -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
-        Just err -> linkFail msg err
+      Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
+      Left err -> linkFail msg err
   where
     msg = "GHC.Linker.Loader.dynLoadObjs: Loading temp shared object failed"
 
@@ -873,7 +874,7 @@ dynLinkBCOs interp pls bcos = do
             ae2 = foldr plusNameEnv (addr_env le1) (map bc_strs cbcs)
             le2 = le1 { itbl_env = ie2, addr_env = ae2 }
 
-        names_and_refs <- linkSomeBCOs interp le2 cbcs
+        names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
 
         -- We only want to add the external ones to the ClosureEnv
         let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
@@ -888,6 +889,7 @@ dynLinkBCOs interp pls bcos = do
 
 -- Link a bunch of BCOs and return references to their values
 linkSomeBCOs :: Interp
+             -> PkgsLoaded
              -> LinkerEnv
              -> [CompiledByteCode]
              -> IO [(Name,HValueRef)]
@@ -895,7 +897,7 @@ linkSomeBCOs :: Interp
                         -- the incoming unlinked BCOs.  Each gives the
                         -- value of the corresponding unlinked BCO
 
-linkSomeBCOs interp le mods = foldr fun do_link mods []
+linkSomeBCOs interp pkgs_loaded le mods = foldr fun do_link mods []
  where
   fun CompiledByteCode{..} inner accum =
     case bc_breaks of
@@ -908,7 +910,7 @@ linkSomeBCOs interp le mods = foldr fun do_link mods []
     let flat = [ (breakarray, bco) | (breakarray, bcos) <- mods, bco <- bcos ]
         names = map (unlinkedBCOName . snd) flat
         bco_ix = mkNameEnv (zip names [0..])
-    resolved <- sequence [ linkBCO interp le bco_ix breakarray bco
+    resolved <- sequence [ linkBCO interp pkgs_loaded le bco_ix breakarray bco
                          | (breakarray, bco) <- flat ]
     hvrefs <- createBCOs interp resolved
     return (zip names hvrefs)
@@ -1071,18 +1073,18 @@ loadPackages' interp hsc_env new_pks pls = do
                -- Link dependents first
              ; pkgs' <- link pkgs deps
                 -- Now link the package itself
-             ; (hs_cls, extra_cls) <- loadPackage interp hsc_env pkg_cfg
+             ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
              ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
                                                    | dep_pkg <- deps
                                                    , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
                                                    ]
-             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls trans_deps)) }
+             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
 
         | otherwise
         = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
 
 
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec])
+loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
 loadPackage interp hsc_env pkg
    = do
         let dflags    = hsc_dflags hsc_env
@@ -1124,7 +1126,9 @@ loadPackage interp hsc_env pkg
         let classifieds = hs_classifieds ++ extra_classifieds
 
         -- Complication: all the .so's must be loaded before any of the .o's.
-        let known_dlls = [ dll  | DLLPath dll    <- classifieds ]
+        let known_hs_dlls    = [ dll | DLLPath dll <- hs_classifieds ]
+            known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
+            known_dlls       = known_hs_dlls ++ known_extra_dlls
 #if defined(CAN_LOAD_DLL)
             dlls       = [ dll  | DLL dll        <- classifieds ]
 #endif
@@ -1145,10 +1149,13 @@ loadPackage interp hsc_env pkg
         loadFrameworks interp platform pkg
         -- See Note [Crash early load_dyn and locateLib]
         -- Crash early if can't load any of `known_dlls`
-        mapM_ (load_dyn interp hsc_env True) known_dlls
+        mapM_ (load_dyn interp hsc_env True) known_extra_dlls
+        loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
         -- For remaining `dlls` crash early only when there is surely
         -- no package's DLL around ... (not is_dyn)
         mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+#else
+        let loaded_dlls = []
 #endif
         -- After loading all the DLLs, we can load the static objects.
         -- Ordering isn't important here, because we do one final link
@@ -1168,7 +1175,7 @@ loadPackage interp hsc_env pkg
         if succeeded ok
            then do
              maybePutStrLn logger "done."
-             return (hs_classifieds, extra_classifieds)
+             return (hs_classifieds, extra_classifieds, loaded_dlls)
            else let errmsg = text "unable to load unit `"
                              <> pprUnitInfoForUser pkg <> text "'"
                  in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
@@ -1221,19 +1228,20 @@ restriction very easily.
 -- can be passed directly to loadDLL.  They are either fully-qualified
 -- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so").  In the latter case,
 -- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO ()
+load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
 load_dyn interp hsc_env crash_early dll = do
   r <- loadDLL interp dll
   case r of
-    Nothing  -> return ()
-    Just err ->
+    Right loaded_dll -> pure (Just loaded_dll)
+    Left err ->
       if crash_early
         then cmdLineErrorIO err
-        else
+        else do
           when (diag_wopt Opt_WarnMissedExtraSharedLib diag_opts)
             $ logMsg logger
                 (mkMCDiagnostic diag_opts (WarningWithFlag Opt_WarnMissedExtraSharedLib) Nothing)
                   noSrcSpan $ withPprStyle defaultUserStyle (note err)
+          pure Nothing
   where
     diag_opts = initDiagOpts (hsc_dflags hsc_env)
     logger = hsc_logger hsc_env


=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -172,6 +172,6 @@ loadFramework interp extraPaths rootname
      findLoadDLL (p:ps) errs =
        do { dll <- loadDLL interp (p  fwk_file)
           ; case dll of
-              Nothing  -> return Nothing
-              Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
+              Right _  -> return Nothing
+              Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
           }


=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -40,7 +40,8 @@ import GHC.Prelude
 import GHC.Unit                ( UnitId, Module )
 import GHC.ByteCode.Types      ( ItblEnv, AddrEnv, CompiledByteCode )
 import GHC.Fingerprint.Type    ( Fingerprint )
-import GHCi.RemoteTypes        ( ForeignHValue )
+import GHCi.RemoteTypes        ( ForeignHValue, RemotePtr )
+import GHCi.Message            ( LoadedDLL )
 
 import GHC.Types.Var           ( Id )
 import GHC.Types.Name.Env      ( NameEnv, emptyNameEnv, extendNameEnvList, filterNameEnv )
@@ -75,6 +76,53 @@ initialised.
 
 The LinkerEnv maps Names to actual closures (for interpreted code only), for
 use during linking.
+
+Note [Looking up symbols in the relevant objects]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In #23415, we determined that a lot of time (>10s, or even up to >35s!) was
+being spent on dynamically loading symbols before actually interpreting code
+when `:main` was run in GHCi. The root cause was that for each symbol we wanted
+to lookup, we would traverse the list of loaded objects and try find the symbol
+in each of them with dlsym (i.e. looking up a symbol was, worst case, linear in
+the amount of loaded objects).
+
+To drastically improve load time (from +-38 seconds down to +-2s), we now:
+
+1. For every of the native objects loaded for a given unit, store the handles returned by `dlopen`.
+  - In `pkgs_loaded` of the `LoaderState`, which maps `UnitId`s to
+    `LoadedPkgInfo`s, where the handles live in its field `loaded_pkg_hs_dlls`.
+
+2. When looking up a Name (e.g. `lookupHsSymbol`), find that name's `UnitId` in
+    the `pkgs_loaded` mapping,
+
+3. And only look for the symbol (with `dlsym`) on the /handles relevant to that
+    unit/, rather than in every loaded object.
+
+Note [Symbols may not be found in pkgs_loaded]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Currently the `pkgs_loaded` mapping only contains the dynamic objects
+associated with loaded units. Symbols defined in a static object (e.g. from a
+statically-linked Haskell library) are found via the generic `lookupSymbol`
+function call by `lookupHsSymbol` when the symbol is not found in any of the
+dynamic objects of `pkgs_loaded`.
+
+The rationale here is two-fold:
+
+ * we have only observed major link-time issues in dynamic linking; lookups in
+ the RTS linker's static symbol table seem to be fast enough
+
+ * allowing symbol lookups restricted to a single ObjectCode would require the
+ maintenance of a symbol table per `ObjectCode`, which would introduce time and
+ space overhead
+
+This fallback is further needed because we don't look in the haskell objects
+loaded for the home units (see the call to `loadModuleLinkables` in
+`loadDependencies`, as opposed to the call to `loadPackages'` in the same
+function which updates `pkgs_loaded`). We should ultimately keep track of the
+objects loaded (probably in `objs_loaded`, for which `LinkableSet` is a bit
+unsatisfactory, see a suggestion in 51c5c4eb1f2a33e4dc88e6a37b7b7c135234ce9b)
+and be able to lookup symbols specifically in them too (similarly to
+`lookupSymbolInDLL`).
 -}
 
 newtype Loader = Loader { loader_state :: MVar (Maybe LoaderState) }
@@ -146,11 +194,13 @@ data LoadedPkgInfo
   { loaded_pkg_uid         :: !UnitId
   , loaded_pkg_hs_objs     :: ![LibrarySpec]
   , loaded_pkg_non_hs_objs :: ![LibrarySpec]
+  , loaded_pkg_hs_dlls     :: ![RemotePtr LoadedDLL]
+    -- ^ See Note [Looking up symbols in the relevant objects]
   , loaded_pkg_trans_deps  :: UniqDSet UnitId
   }
 
 instance Outputable LoadedPkgInfo where
-  ppr (LoadedPkgInfo uid hs_objs non_hs_objs trans_deps) =
+  ppr (LoadedPkgInfo uid hs_objs non_hs_objs _ trans_deps) =
     vcat [ppr uid
          , ppr hs_objs
          , ppr non_hs_objs
@@ -159,10 +209,10 @@ instance Outputable LoadedPkgInfo where
 
 -- | Information we can use to dynamically link modules into the compiler
 data Linkable = LM {
-  linkableTime     :: !UTCTime,          -- ^ Time at which this linkable was built
+  linkableTime     :: !UTCTime,         -- ^ Time at which this linkable was built
                                         -- (i.e. when the bytecodes were produced,
                                         --       or the mod date on the files)
-  linkableModule   :: !Module,           -- ^ The linkable module itself
+  linkableModule   :: !Module,          -- ^ The linkable module itself
   linkableUnlinked :: [Unlinked]
     -- ^ Those files and chunks of code we have yet to link.
     --


=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -37,6 +37,7 @@ module GHC.Runtime.Interpreter
   -- * The object-code linker
   , initObjLinker
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , loadDLL
   , loadArchive
@@ -478,6 +479,13 @@ lookupSymbol interp str = case interpInstance interp of
 
     ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str)
 
+lookupSymbolInDLL :: Interp -> RemotePtr LoadedDLL -> FastString -> IO (Maybe (Ptr ()))
+lookupSymbolInDLL interp dll str = case interpInstance interp of
+#if defined(HAVE_INTERNAL_INTERPRETER)
+  InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL dll (unpackFS str))
+#endif
+  ExternalInterp _ -> panic "lookupSymbolInDLL: not implemented for external interpreter" -- FIXME
+
 lookupClosure :: Interp -> String -> IO (Maybe HValueRef)
 lookupClosure interp str =
   interpCmd interp (LookupClosure str)
@@ -496,12 +504,7 @@ purgeLookupSymbolCache interp = case interpInstance interp of
 -- an absolute pathname to the file, or a relative filename
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
---
--- Returns:
---
--- Nothing      => success
--- Just err_msg => failure
-loadDLL :: Interp -> String -> IO (Maybe String)
+loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
 loadDLL interp str = interpCmd interp (LoadDLL str)
 
 loadArchive :: Interp -> String -> IO ()


=====================================
hadrian/bootstrap/generate_bootstrap_plans
=====================================
@@ -23,6 +23,11 @@ run_all() {
     run "9_4_4"
     run "9_6_1"
     run "9_6_2"
+    run "9_6_3"
+    run "9_6_4"
+    run "9_6_5"
+    run "9_8_1"
+    run "9_8_2"
 }
 
 if (( $# == 0 )); then


=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -21,6 +21,7 @@ module GHCi.Message
   , QState(..)
   , getMessage, putMessage, getTHMessage, putTHMessage
   , Pipe(..), remoteCall, remoteTHCall, readPipe, writePipe
+  , LoadedDLL
   ) where
 
 import Prelude -- See note [Why do we import Prelude here?]
@@ -69,8 +70,9 @@ data Message a where
   -- These all invoke the corresponding functions in the RTS Linker API.
   InitLinker :: Message ()
   LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
+  LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
   LookupClosure :: String -> Message (Maybe HValueRef)
-  LoadDLL :: String -> Message (Maybe String)
+  LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
   LoadArchive :: String -> Message () -- error?
   LoadObj :: String -> Message () -- error?
   UnloadObj :: String -> Message () -- error?
@@ -394,6 +396,9 @@ data EvalResult a
 
 instance Binary a => Binary (EvalResult a)
 
+-- | A dummy type that tags pointers returned by 'LoadDLL'.
+data LoadedDLL
+
 -- SomeException can't be serialized because it contains dynamic
 -- types.  However, we do very limited things with the exceptions that
 -- are thrown by interpreted computations:
@@ -521,6 +526,7 @@ getMessage = do
       36 -> Msg <$> (Seq <$> get)
       37 -> Msg <$> return RtsRevertCAFs
       38 -> Msg <$> (ResumeSeq <$> get)
+      40 -> Msg <$> (LookupSymbolInDLL <$> get <*> get)
       _  -> error $ "Unknown Message code " ++ (show b)
 
 putMessage :: Message a -> Put
@@ -564,6 +570,7 @@ putMessage m = case m of
   Seq a                       -> putWord8 36 >> put a
   RtsRevertCAFs               -> putWord8 37
   ResumeSeq a                 -> putWord8 38 >> put a
+  LookupSymbolInDLL dll str   -> putWord8 40 >> put dll >> put str
 
 -- -----------------------------------------------------------------------------
 -- Reading/writing messages


=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -18,6 +18,7 @@ module GHCi.ObjLink
   , unloadObj
   , purgeObj
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , resolveObjs
   , addLibrarySearchPath
@@ -27,18 +28,17 @@ module GHCi.ObjLink
 
 import Prelude -- See note [Why do we import Prelude here?]
 import GHCi.RemoteTypes
+import GHCi.Message (LoadedDLL)
 import Control.Exception (throwIO, ErrorCall(..))
 import Control.Monad    ( when )
 import Foreign.C
-import Foreign.Marshal.Alloc ( free )
-import Foreign          ( nullPtr )
+import Foreign.Marshal.Alloc ( alloca, free )
+import Foreign          ( nullPtr, peek )
 import GHC.Exts
 import System.Posix.Internals ( CFilePath, withFilePath, peekFilePath )
 import System.FilePath  ( dropExtension, normalise )
 
 
-
-
 -- ---------------------------------------------------------------------------
 -- RTS Linker Interface
 -- ---------------------------------------------------------------------------
@@ -70,6 +70,15 @@ lookupSymbol str_in = do
         then return Nothing
         else return (Just addr)
 
+lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
+lookupSymbolInDLL dll str_in = do
+   let str = prefixUnderscore str_in
+   withCAString str $ \c_str -> do
+     addr <- c_lookupSymbolInDLL dll c_str
+     if addr == nullPtr
+       then return Nothing
+       else return (Just addr)
+
 lookupClosure :: String -> IO (Maybe HValueRef)
 lookupClosure str = do
   m <- lookupSymbol str
@@ -89,7 +98,7 @@ prefixUnderscore
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
 --
-loadDLL :: String -> IO (Maybe String)
+loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
 -- Nothing      => success
 -- Just err_msg => failure
 loadDLL str0 = do
@@ -101,12 +110,16 @@ loadDLL str0 = do
      str | isWindowsHost = dropExtension str0
          | otherwise     = str0
   --
-  maybe_errmsg <- withFilePath (normalise str) $ \dll -> c_addDLL dll
-  if maybe_errmsg == nullPtr
-        then return Nothing
-        else do str <- peekCString maybe_errmsg
-                free maybe_errmsg
-                return (Just str)
+  (maybe_handle, maybe_errmsg) <- withFilePath (normalise str) $ \dll ->
+    alloca $ \errmsg_ptr -> (,)
+      <$> c_addDLL dll errmsg_ptr
+      <*> peek errmsg_ptr
+
+  if maybe_handle == nullPtr
+    then do str <- peekCString maybe_errmsg
+            free maybe_errmsg
+            return (Left str)
+    else return (Right maybe_handle)
 
 loadArchive :: String -> IO ()
 loadArchive str = do
@@ -163,7 +176,8 @@ resolveObjs = do
 -- Foreign declarations to RTS entry points which does the real work;
 -- ---------------------------------------------------------------------------
 
-foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> IO CString
+foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL)
+foreign import ccall unsafe "lookupSymbolInDLL"       c_lookupSymbolInDLL       :: Ptr LoadedDLL -> CString -> IO (Ptr a)
 foreign import ccall unsafe "initLinker_"             c_initLinker_             :: CInt -> IO ()
 foreign import ccall unsafe "lookupSymbol"            c_lookupSymbol            :: CString -> IO (Ptr a)
 foreign import ccall unsafe "loadArchive"             c_loadArchive             :: CFilePath -> IO Int


=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -68,7 +68,7 @@ run m = case m of
   LookupClosure str           -> lookupJSClosure str
 #else
   InitLinker -> initObjLinker RetainCAFs
-  LoadDLL str -> loadDLL str
+  LoadDLL str -> fmap toRemotePtr <$> loadDLL str
   LoadArchive str -> loadArchive str
   LoadObj str -> loadObj str
   UnloadObj str -> unloadObj str
@@ -83,6 +83,8 @@ run m = case m of
 #endif
   RtsRevertCAFs -> rts_revertCAFs
   LookupSymbol str -> fmap toRemotePtr <$> lookupSymbol str
+  LookupSymbolInDLL dll str ->
+    fmap toRemotePtr <$> lookupSymbolInDLL (fromRemotePtr dll) str
   FreeHValueRefs rs -> mapM_ freeRemoteRef rs
   AddSptEntry fpr r -> localRef r >>= sptAddEntry fpr
   EvalStmt opts r -> evalStmt opts r


=====================================
rts/Linker.c
=====================================
@@ -578,13 +578,11 @@ typedef
 /* A list thereof. */
 static OpenedSO* openedSOs = NULL;
 
-static const char *
-internal_dlopen(const char *dll_name)
+static void *
+internal_dlopen(const char *dll_name, const char **errmsg_ptr)
 {
    OpenedSO* o_so;
    void *hdl;
-   const char *errmsg;
-   char *errmsg_copy;
 
    // omitted: RTLD_NOW
    // see http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html
@@ -619,14 +617,13 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&ccs_mutex);
 #endif
 
-   errmsg = NULL;
    if (hdl == NULL) {
       /* dlopen failed; return a ptr to the error msg. */
-      errmsg = dlerror();
+      char *errmsg = dlerror();
       if (errmsg == NULL) errmsg = "addDLL: unknown error";
-      errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
+      char *errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
       strcpy(errmsg_copy, errmsg);
-      errmsg = errmsg_copy;
+      *errmsg_ptr = errmsg_copy;
    } else {
       o_so = stgMallocBytes(sizeof(OpenedSO), "addDLL");
       o_so->handle = hdl;
@@ -637,7 +634,7 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&dl_mutex);
    //--------------- End critical section -------------------
 
-   return errmsg;
+   return hdl;
 }
 
 /*
@@ -725,16 +722,29 @@ internal_dlsym(const char *symbol) {
     // we failed to find the symbol
     return NULL;
 }
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name)
+{
+#if defined(OBJFORMAT_MACHO)
+    CHECK(symbol_name[0] == '_');
+    symbol_name = symbol_name+1;
+#endif
+
+    ACQUIRE_LOCK(&dl_mutex); // dlsym alters dlerror
+    void *result = dlsym(handle, symbol_name);
+    RELEASE_LOCK(&dl_mutex);
+    return result;
+}
 #  endif
 
-const char *
-addDLL( pathchar *dll_name )
+void *addDLL(pathchar* dll_name, const char **errmsg_ptr)
 {
 #  if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
    /* ------------------- ELF DLL loader ------------------- */
 
 #define NMATCH 5
    regmatch_t match[NMATCH];
+   void *handle;
    const char *errmsg;
    FILE* fp;
    size_t match_length;
@@ -743,10 +753,10 @@ addDLL( pathchar *dll_name )
    int result;
 
    IF_DEBUG(linker, debugBelch("addDLL: dll_name = '%s'\n", dll_name));
-   errmsg = internal_dlopen(dll_name);
+   handle = internal_dlopen(dll_name, &errmsg);
 
-   if (errmsg == NULL) {
-      return NULL;
+   if (handle != NULL) {
+      return handle;
    }
 
    // GHC #2615
@@ -775,7 +785,8 @@ addDLL( pathchar *dll_name )
       line[match_length] = '\0'; // make sure string is null-terminated
       IF_DEBUG(linker, debugBelch("file name = '%s'\n", line));
       if ((fp = __rts_fopen(line, "r")) == NULL) {
-         return errmsg; // return original error if open fails
+         *errmsg_ptr = errmsg; // return original error if open fails
+         return NULL;
       }
       // try to find a GROUP or INPUT ( ... ) command
       while (fgets(line, MAXLINE, fp) != NULL) {
@@ -785,7 +796,7 @@ addDLL( pathchar *dll_name )
             IF_DEBUG(linker, debugBelch("match%s\n",""));
             line[match[2].rm_eo] = '\0';
             stgFree((void*)errmsg); // Free old message before creating new one
-            errmsg = internal_dlopen(line+match[2].rm_so);
+            handle = internal_dlopen(line+match[2].rm_so, errmsg_ptr);
             break;
          }
          // if control reaches here, no GROUP or INPUT ( ... ) directive
@@ -794,9 +805,10 @@ addDLL( pathchar *dll_name )
       }
       fclose(fp);
    }
-   return errmsg;
+   return handle;
 
 #  elif defined(OBJFORMAT_PEi386)
+   // FIXME
    return addDLL_PEi386(dll_name, NULL);
 
 #  else


=====================================
rts/RtsSymbols.c
=====================================
@@ -618,6 +618,7 @@ extern char **environ;
       SymI_HasProto(purgeObj)                                           \
       SymI_HasProto(insertSymbol)                                       \
       SymI_HasProto(lookupSymbol)                                       \
+      SymI_HasProto(lookupSymbolInDLL)                                  \
       SymI_HasDataProto(stg_makeStablePtrzh)                                \
       SymI_HasDataProto(stg_mkApUpd0zh)                                     \
       SymI_HasDataProto(stg_labelThreadzh)                                  \


=====================================
rts/include/rts/Linker.h
=====================================
@@ -91,7 +91,9 @@ void *loadNativeObj( pathchar *path, char **errmsg );
 HsInt unloadNativeObj( void *handle );
 
 /* load a dynamic library */
-const char *addDLL( pathchar* dll_name );
+void *addDLL(pathchar* dll_name, const char **errmsg);
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name);
 
 /* add a path to the library search path */
 HsPtr addLibrarySearchPath(pathchar* dll_path);


=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -6,5 +6,5 @@ main = do
   initObjLinker RetainCAFs
   result <- loadDLL library_name
   case result of
-    Nothing -> putStrLn (library_name ++ " loaded successfully")
-    Just x  -> putStrLn ("error: " ++ x)
+    Right _ -> putStrLn (library_name ++ " loaded successfully")
+    Left x  -> putStrLn ("error: " ++ x)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a26873ce7a324f85106d410e7b1d88bc03985aa4...4973098ded1679d76b4f3766240a75a116a57bf4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a26873ce7a324f85106d410e7b1d88bc03985aa4...4973098ded1679d76b4f3766240a75a116a57bf4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 22:13:38 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 08 Oct 2024 18:13:38 -0400
Subject: [Git][ghc/ghc][wip/T25281] Avoid incomplete rec sel
Message-ID: <6705ae92aed5e_36fafb5f6b9479454@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
a7716a59 by Simon Peyton Jones at 2024-10-08T23:13:07+01:00
Avoid incomplete rec sel

- - - - -


2 changed files:

- utils/check-exact/Transform.hs
- utils/check-exact/Utils.hs


Changes:

=====================================
utils/check-exact/Transform.hs
=====================================
@@ -563,7 +563,7 @@ priorCommentsDeltas r cs = go r (sortEpaComments cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (deltaLine dp, la) : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
     go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -389,7 +389,7 @@ priorCommentsDeltas' r cs = go r (reverse cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (deltaLine dp, la) : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
     go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct  8 23:10:03 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 08 Oct 2024 19:10:03 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: ci: RISCV64
 cross-compile testing
Message-ID: <6705bbcbc12c1_2b9ece1b401821286@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
7d8ff63e by Andrzej Rybczak at 2024-10-08T19:09:55-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef20f6c2 by Alan Zimmerman at 2024-10-08T19:09:56-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d306c475b47384fb71b5bf73b4a44c4fb231b3f2...ef20f6c222d4bfc63525a99724b51682dc70b6b7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d306c475b47384fb71b5bf73b4a44c4fb231b3f2...ef20f6c222d4bfc63525a99724b51682dc70b6b7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 04:51:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 09 Oct 2024 00:51:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Fix typo in
 the @since annotation of annotateIO
Message-ID: <67060bb6bd0ba_2268f53b6c1c13941@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
5d338b1d by Andrzej Rybczak at 2024-10-09T00:50:57-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
c28d4929 by Alan Zimmerman at 2024-10-09T00:50:58-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef20f6c222d4bfc63525a99724b51682dc70b6b7...c28d4929e15d60049422576d508f9d17cb6c6498

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef20f6c222d4bfc63525a99724b51682dc70b6b7...c28d4929e15d60049422576d508f9d17cb6c6498
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 07:24:04 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 09 Oct 2024 03:24:04 -0400
Subject: [Git][ghc/ghc][wip/T25281] Missing record selectors in
 GHC.Internal.IO.Windows.Handle
Message-ID: <67062f94a3169_3ead80157fd411916@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
0c68c409 by Simon Peyton Jones at 2024-10-09T08:23:48+01:00
Missing record selectors in GHC.Internal.IO.Windows.Handle

This look genuinely wrong.  These two fixes need auditing;
but they are better than the status quo.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
=====================================
@@ -468,7 +468,10 @@ hwndReadNonBlocking hwnd ptr offset bytes
        val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
                                (isAsynchronous hwnd) offset (startCB ptr)
                                completionCB
-       return $ ioValue val
+       return $ case val of
+                   IOSuccess mb_v  -> mb_v
+                   IOFailed mb_err -> error ("hwndReadNonBlocking " ++ show mb_err)
+                       -- ToDo: this unhandled errror case seems bad
   where
     startCB inputBuf lpOverlapped = do
       debugIO ":: hwndReadNonBlocking"
@@ -514,7 +517,11 @@ hwndWriteNonBlocking hwnd ptr offset bytes
        val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
                                (isAsynchronous hwnd) offset (startCB ptr)
                                completionCB
-       return $ fromIntegral $ ioValue val
+       return $ fromIntegral $
+         case val of
+            IOSuccess val   -> val
+            IOFailed mb_err -> error ("hwndWriteNonBlocking " ++ show mb_err)
+                -- ToDo: this unhandled errror case seems bad
   where
     startCB :: Ptr a -> LPOVERLAPPED -> IO (Mgr.CbResult a1)
     startCB outBuf lpOverlapped = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0c68c409aacdd5db52fec96535033bd28fbd2215

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 08:53:10 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 09 Oct 2024 04:53:10 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] Bump Cabal submodule to 3.14
Message-ID: <67064476c54bc_3ead805c57b02165b@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
516661c8 by Zubin Duggal at 2024-10-09T14:22:33+05:30
Bump Cabal submodule to 3.14

- - - - -


1 changed file:

- libraries/Cabal


Changes:

=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/516661c82fbf9e3798cc6eb3405c56a3bc99c984

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 08:59:43 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Wed, 09 Oct 2024 04:59:43 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] Revert "ci: Allow abi-test to fail."
Message-ID: <670645ff350b6_1ba9411054c8920cc@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
80539878 by Rodrigo Mesquita at 2024-10-09T09:58:33+01:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -


1 changed file:

- .gitlab-ci.yml


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1007,8 +1007,6 @@ perf:
 ############################################################
 
 abi-test:
-  # see #12935 for remaining work
-  allow_failure: true
   stage: testing
   needs:
     - job: x86_64-linux-fedora33-release



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80539878902aa787c36d542b19b323793c09db36

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 09:21:34 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 09 Oct 2024 05:21:34 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Fix typo in
 the @since annotation of annotateIO
Message-ID: <67064b1ed547_1ba941290978965cb@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
5558bf1d by Andrzej Rybczak at 2024-10-09T05:21:29-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
83a661df by Alan Zimmerman at 2024-10-09T05:21:29-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- libraries/ghc-internal/src/GHC/Internal/IO.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c28d4929e15d60049422576d508f9d17cb6c6498...83a661dffa899c5d6bd9f2e908512ef021b64d04

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c28d4929e15d60049422576d508f9d17cb6c6498...83a661dffa899c5d6bd9f2e908512ef021b64d04
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 10:11:32 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 09 Oct 2024 06:11:32 -0400
Subject: [Git][ghc/ghc][wip/T25281] Wibble to Windows.Handle fix
Message-ID: <670656d4369be_1ba9415231cc111260@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
b64b0ef5 by Simon Peyton Jones at 2024-10-09T11:11:15+01:00
Wibble to Windows.Handle fix

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
=====================================
@@ -519,7 +519,7 @@ hwndWriteNonBlocking hwnd ptr offset bytes
                                completionCB
        return $ fromIntegral $
          case val of
-            IOSuccess val   -> val
+            IOSuccess res   -> res
             IOFailed mb_err -> error ("hwndWriteNonBlocking " ++ show mb_err)
                 -- ToDo: this unhandled errror case seems bad
   where



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 10:18:53 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 06:18:53 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] 3 commits: ci: RISCV64 cross-compile
 testing
Message-ID: <6706588d4eeb2_1ba94176dc841138a3@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
494d7064 by Hassan Al-Awwadi at 2024-10-09T10:18:50+00:00
The main purpose of this commit is to rip RdrName out of FieldOcc, and
as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade <Jade512 at proton.me>
                @Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fd6bbf0e8141572983b65af01b3eff6825865f2b...494d7064e9a5d3929660a5910fc3c14d0119ce8a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fd6bbf0e8141572983b65af01b3eff6825865f2b...494d7064e9a5d3929660a5910fc3c14d0119ce8a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 10:19:39 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 06:19:39 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 3 commits: ci: RISCV64
 cross-compile testing
Message-ID: <670658bb7e514_1ba94172a18c1145dd@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
bca81cf0 by Hassan Al-Awwadi at 2024-10-09T10:19:14+00:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, and we parameterized it over the ghcPass instead
of over some arbitrary type.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -


25 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Core/Class.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -106,6 +106,7 @@ data Opsys
 
 data LinuxDistro
   = Debian12
+  | Debian12Riscv
   | Debian11
   | Debian11Js
   | Debian10
@@ -303,6 +304,7 @@ distroName :: LinuxDistro -> String
 distroName Debian12   = "deb12"
 distroName Debian11   = "deb11"
 distroName Debian11Js = "deb11-emsdk-closure"
+distroName Debian12Riscv = "deb12-riscv"
 distroName Debian10   = "deb10"
 distroName Debian9    = "deb9"
 distroName Fedora33   = "fedora33"
@@ -626,6 +628,7 @@ data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
+          | RiscV        -- ^ Run this job when the "RISC-V" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
           | FreeBSDLabel -- ^ Run this job when the "FreeBSD" label is set.
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
@@ -674,6 +677,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
+validateRuleString RiscV        = labelString "RISC-V"
 validateRuleString WasmBackend  = labelString "wasm"
 validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
@@ -1125,6 +1129,9 @@ cross_jobs = [
   -- x86 -> aarch64
     validateBuilds Amd64 (Linux Debian11) (crossConfig "aarch64-linux-gnu" (Emulator "qemu-aarch64 -L /usr/aarch64-linux-gnu") Nothing)
 
+  -- x86_64 -> riscv
+  , addValidateRule RiscV (validateBuilds Amd64 (Linux Debian12Riscv) (crossConfig "riscv64-linux-gnu" (Emulator "qemu-riscv64 -L /usr/riscv64-linux-gnu") Nothing))
+
   -- Javascript
   , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11Js) javascriptConfig)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1854,6 +1854,71 @@
       "XZ_OPT": "-9"
     }
   },
+  "nightly-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "8 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "XZ_OPT": "-9"
+    }
+  },
   "nightly-x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -5348,6 +5413,70 @@
       "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
+  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+    }
+  },
   "x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",


=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
+import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -35,7 +36,7 @@ import GHC.Utils.Panic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
 import GHC.Utils.Outputable
-import GHC.Data.BooleanFormula (BooleanFormula, mkTrue)
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula, mkTrue )
 
 import qualified Data.Data as Data
 
@@ -135,7 +136,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula Name -- Required methods
+type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,5 +1,5 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable  #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
 -- | Boolean formulas without quantifiers and without negation.
@@ -8,74 +8,45 @@
 -- This module is used to represent minimal complete definitions for classes.
 --
 module GHC.Data.BooleanFormula (
-        BooleanFormula(..), LBooleanFormula,
-        mkFalse, mkTrue, mkAnd, mkOr, mkVar,
+        module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
+        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
-        pprBooleanFormula, pprBooleanFormulaNice
+        pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
   ) where
 
-import GHC.Prelude hiding ( init, last )
-
-import Data.List ( nub, intersperse )
+import Data.List ( intersperse )
 import Data.List.NonEmpty ( NonEmpty (..), init, last )
-import Data.Data
 
-import GHC.Utils.Monad
-import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( LocatedL )
-import GHC.Types.SrcLoc
+import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
+import GHC.Types.SrcLoc (unLoc)
+import GHC.Utils.Outputable
+import GHC.Parser.Annotation ( SrcSpanAnnL )
+import GHC.Hs.Extension (GhcPass (..), GhcPs, GhcRn, OutputableBndrId)
+import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
+import Language.Haskell.Syntax.BooleanFormula
+
 
 ----------------------------------------------------------------------
 -- Boolean formula type and smart constructors
 ----------------------------------------------------------------------
 
-type LBooleanFormula a = LocatedL (BooleanFormula a)
-
-data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a]
-                      | Parens (LBooleanFormula a)
-  deriving (Eq, Data, Functor, Foldable, Traversable)
+type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
-mkVar :: a -> BooleanFormula a
-mkVar = Var
-
-mkFalse, mkTrue :: BooleanFormula a
-mkFalse = Or []
-mkTrue = And []
-
--- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula a
-mkBool False = mkFalse
-mkBool True  = mkTrue
-
--- Make a conjunction, and try to simplify
-mkAnd :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkAnd = maybe mkFalse (mkAnd' . nub) . concatMapM fromAnd
-  where
-  -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula a -> Maybe [LBooleanFormula a]
-  fromAnd (L _ (And xs)) = Just xs
-     -- assume that xs are already simplified
-     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
-  fromAnd (L _ (Or [])) = Nothing
-     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
-  fromAnd x = Just [x]
-  mkAnd' [x] = unLoc x
-  mkAnd' xs = And xs
-
-mkOr :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkOr = maybe mkTrue (mkOr' . nub) . concatMapM fromOr
-  where
-  -- See Note [Simplification of BooleanFormulas]
-  fromOr (L _ (Or xs)) = Just xs
-  fromOr (L _ (And [])) = Nothing
-  fromOr x = Just [x]
-  mkOr' [x] = unLoc x
-  mkOr' xs = Or xs
+-- the other part of jury rigging some fake instances for booleanformula
+-- using the genlocated instances of Functor and Traversable.
+bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
+      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
+bfMap f = bfExplMap fmap f
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (GhcPass p'))
+bfTraverse f = bfExplTraverse traverse f
 
 {-
 Note [Simplification of BooleanFormulas]
@@ -115,15 +86,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula a -> Bool
+isFalse :: BooleanFormula (GhcPass p) -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula a -> Bool
+isTrue :: BooleanFormula (GhcPass p) -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (a -> Bool) -> BooleanFormula a -> Bool
+eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
 eval f (Var x)  = f x
 eval f (And xs) = all (eval f . unLoc) xs
 eval f (Or xs)  = any (eval f . unLoc) xs
@@ -131,18 +102,24 @@ eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: Eq a => (a -> Maybe Bool) -> BooleanFormula a -> BooleanFormula a
+simplify :: forall p. Eq (LIdP (GhcPass p))
+          => (LIdP (GhcPass p) ->  Maybe Bool)
+          -> BooleanFormula (GhcPass p)
+          -> BooleanFormula (GhcPass p)
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (\(L l x) -> L l (simplify f x)) xs)
-simplify f (Or xs) = mkOr (map (\(L l x) -> L l (simplify f x)) xs)
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
 simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq a => (a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
+isUnsatisfied :: Eq (LIdP (GhcPass p))
+              => (LIdP (GhcPass p) -> Bool)
+              -> BooleanFormula (GhcPass p)
+              -> Maybe (BooleanFormula (GhcPass p))
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -155,42 +132,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq a => BooleanFormula a -> a -> Bool
-Var x  `impliesAtom` y = x == y
-And xs `impliesAtom` y = any (\x -> (unLoc x) `impliesAtom` y) xs
+impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
            -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> (unLoc x) `impliesAtom` y) xs
-Parens x `impliesAtom` y = (unLoc x) `impliesAtom` y
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
-implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
+implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable a => Clause a -> Clause a -> Bool
+    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms x r -> True
-                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms (unLoc x) r -> True
+                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
             And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms x l -> True
-                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
+            Var x | memberClauseAtoms (unLoc x) l -> True
+                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = unLoc con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause a = Clause {
-        clauseAtoms :: UniqSet a,
-        clauseExprs :: [BooleanFormula a]
+data Clause p = Clause {
+        clauseAtoms :: UniqSet (IdP p),
+        clauseExprs :: [BooleanFormula p]
     }
-extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
+extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
+memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -199,28 +176,29 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula' :: (Rational -> a -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
-  go p (And []) = cparen (p > 0) $ empty
+  go p (And []) = cparen (p > 0) empty
   go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
   go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
   go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
+pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -230,14 +208,15 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance (OutputableBndr a) => Outputable (BooleanFormula a) where
+instance Outputable (BooleanFormula GhcPs) where
+  ppr = pprBooleanFormulaNormal
+instance Outputable (BooleanFormula GhcRn) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: (OutputableBndr a)
-                        => BooleanFormula a -> SDoc
+pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc x
+    go (Var x)    = pprPrefixOcc (unLoc x)
     go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,6 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -47,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Var
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.Name.Reader
 import GHC.Types.Name
 
@@ -934,9 +934,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: (OutputableBndr name)
-              => LBooleanFormula (GenLocated l name) -> SDoc
-pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -103,6 +103,7 @@ module GHC.Hs.Decls (
 import GHC.Prelude
 
 import Language.Haskell.Syntax.Decls
+import Language.Haskell.Syntax.Extension
 
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprUntypedSplice )
         -- Because Expr imports Decls via HsBracket
@@ -112,7 +113,7 @@ import GHC.Hs.Type
 import GHC.Hs.Doc
 import GHC.Types.Basic
 import GHC.Core.Coercion
-import Language.Haskell.Syntax.Extension
+
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
 import GHC.Types.Name


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -33,6 +33,8 @@ import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
+import GHC.Data.BooleanFormula (BooleanFormula(..))
+import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -594,3 +596,6 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+
+deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -14,6 +14,10 @@ module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
    , toIfaceBooleanFormula
+
+   -- converting back
+   , fromIfaceBooleanFormula
+   , traverseIfaceBooleanFormula
    )
 where
 
@@ -33,7 +37,7 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-
+import GHC.Hs.Extension ( GhcPass )
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
@@ -42,6 +46,8 @@ import GHC.Types.Basic
 import GHC.Types.TyThing
 import GHC.Types.SrcLoc
 
+import GHC.Parser.Annotation (noLocA)
+
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
@@ -49,6 +55,7 @@ import GHC.Data.Maybe
 import GHC.Data.BooleanFormula
 
 import Data.List ( findIndex, mapAccumL )
+import Language.Haskell.Syntax.Extension (LIdP)
 
 {-
 ************************************************************************
@@ -287,7 +294,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula $ fmap (mkIfLclName . getOccFS) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (mkIfLclName . getOccFS . unLoc) (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -336,9 +343,29 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
 
-toIfaceBooleanFormula :: BooleanFormula IfLclName -> IfaceBooleanFormula
-toIfaceBooleanFormula = \case
-    Var nm    -> IfVar    nm
-    And bfs   -> IfAnd    (map (toIfaceBooleanFormula . unLoc) bfs)
-    Or bfs    -> IfOr     (map (toIfaceBooleanFormula . unLoc) bfs)
-    Parens bf -> IfParens (toIfaceBooleanFormula . unLoc $ bf)
+toIfaceBooleanFormula :: (LIdP (GhcPass p) -> IfLclName) ->  BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
+toIfaceBooleanFormula f = go
+  where
+    go (Var nm   ) = IfVar    (f nm)
+    go (And bfs  ) = IfAnd    (map (go . unLoc) bfs)
+    go (Or bfs   ) = IfOr     (map (go . unLoc) bfs)
+    go (Parens bf) = IfParens (go . unLoc $ bf)
+
+fromIfaceBooleanFormula :: (IfLclName -> LIdP (GhcPass p))  -> IfaceBooleanFormula -> BooleanFormula (GhcPass p)
+fromIfaceBooleanFormula f = go
+  where
+    go (IfVar nm    ) = Var    $ f nm
+    go (IfAnd ibfs  ) = And    $ map (noLocA . go) ibfs
+    go (IfOr ibfs   ) = Or     $ map (noLocA . go) ibfs
+    go (IfParens ibf) = Parens $ (noLocA . go) ibf
+
+traverseIfaceBooleanFormula :: Applicative f
+                            => (IfLclName -> f (LIdP (GhcPass p)))
+                            -> IfaceBooleanFormula
+                            -> f (BooleanFormula (GhcPass p))
+traverseIfaceBooleanFormula f = go
+  where
+    go (IfVar nm    ) = Var     <$> f nm
+    go (IfAnd ibfs  ) = And     <$> traverse (fmap noLocA . go) ibfs
+    go (IfOr ibfs   ) = Or      <$> traverse (fmap noLocA . go) ibfs
+    go (IfParens ibf) = Parens  <$> (fmap noLocA . go) ibf
\ No newline at end of file


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -35,7 +35,7 @@ import GHC.Core.Class             ( className, classSCSelIds )
 import GHC.Core.ConLike           ( conLikeName )
 import GHC.Core.FVs
 import GHC.Core.DataCon           ( dataConNonlinearType )
-import GHC.Types.FieldLabel
+import GHC.Types.FieldLabel ( FieldLabel(flSelector) )
 import GHC.Hs
 import GHC.Hs.Syn.Type
 import GHC.Utils.Monad            ( concatMapM, MonadIO(liftIO) )
@@ -2043,8 +2043,22 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance ToHie (LBooleanFormula (LocatedN Name)) where
-  toHie (L span form) = concatM $ makeNode form (locA span) : case form of
+instance HiePass p => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+  toHie (L span form) = case hiePass @p of
+    HieRn -> concatM $ makeNode form (locA span) : case form of
+      Var a ->
+        [ toHie $ C Use a
+        ]
+      And forms ->
+        [ toHie forms
+        ]
+      Or forms ->
+        [ toHie forms
+        ]
+      Parens f ->
+        [ toHie f
+        ]
+    HieTc -> concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -35,7 +35,6 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
-        fromIfaceBooleanFormula,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
 
@@ -75,7 +74,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
@@ -98,6 +96,7 @@ import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
 import Data.Proxy
+import Data.List ( intersperse )
 
 infixl 3 &&&
 
@@ -218,13 +217,7 @@ data IfaceBooleanFormula
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
-
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
-fromIfaceBooleanFormula = \case
-    IfVar nm     -> Var    nm
-    IfAnd ibfs   -> And    (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfOr ibfs    -> Or     (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfParens ibf -> Parens (noLocA . fromIfaceBooleanFormula $ ibf)
+  deriving Eq
 
 data IfaceTyConParent
   = IfNoParent
@@ -1022,7 +1015,7 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
          , pprClassStandaloneKindSig ss clas (mkIfaceTyConKind binders constraintIfaceKind)
          , text "class" <+> pprIfaceDeclHead suppress_bndr_sig context ss clas binders <+> pprFundeps fds <+> pp_where
          , nest 2 (vcat [ vcat asocs, vcat dsigs
-                        , ppShowAllSubs ss (pprMinDef $ fromIfaceBooleanFormula minDef)])]
+                        , ppShowAllSubs ss (pprMinDef minDef)])]
     where
       pp_where = ppShowRhs ss $ ppUnless (null sigs && null ats) (text "where")
 
@@ -1039,13 +1032,30 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | showSub ss sg = Just $  pprIfaceClassOp ss sg
         | otherwise     = Nothing
 
-      pprMinDef :: BooleanFormula IfLclName -> SDoc
-      pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
+      pprMinDef :: IfaceBooleanFormula -> SDoc
+      pprMinDef minDef = ppUnless (ifLclIsTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
-        pprBooleanFormula
-          (\_ def -> cparen (isLexSym def) (ppr def)) 0 (fmap ifLclNameFS minDef) <+>
+        pprifLclBooleanFormula
+          (\_ def -> let fs = ifLclNameFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+      ifLclIsTrue :: IfaceBooleanFormula -> Bool
+      ifLclIsTrue (IfAnd []) = True
+      ifLclIsTrue _          = False
+
+      pprifLclBooleanFormula  :: (Rational -> IfLclName -> SDoc)
+                              -> Rational -> IfaceBooleanFormula -> SDoc
+      pprifLclBooleanFormula pprVar = go
+        where
+        go p (IfVar x)  = pprVar p x
+        go p (IfAnd []) = cparen (p > 0) empty
+        go p (IfAnd xs) = pprAnd p (map (go 3) xs)
+        go _ (IfOr  []) = keyword $ text "FALSE"
+        go p (IfOr  xs) = pprOr p (map (go 2) xs)
+        go p (IfParens x) = go p x
+        pprAnd p = cparen (p > 3) . fsep . punctuate comma
+        pprOr  p = cparen (p > 2) . fsep . intersperse vbar
+
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -32,6 +32,7 @@ module GHC.IfaceToCore (
         hydrateCgBreakInfo
  ) where
 
+
 import GHC.Prelude
 
 import GHC.ByteCode.Types
@@ -43,7 +44,7 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (toIfaceBooleanFormula)
+import GHC.Iface.Decl (traverseIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -124,7 +125,6 @@ import GHC.Types.TyThing
 import GHC.Types.Error
 
 import GHC.Fingerprint
-import qualified GHC.Data.BooleanFormula as BF
 
 import Control.Monad
 import GHC.Parser.Annotation
@@ -133,6 +133,7 @@ import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List (nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
@@ -297,9 +298,21 @@ mergeIfaceDecl d1 d2
                   plusNameEnv_C mergeIfaceClassOp
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
+
+          -- specialized version of BooleanFormula's MkOr.
+          mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+          mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+            where
+            fromOr bf = case bf of
+              (IfOr xs)  -> Just xs
+              (IfAnd []) -> Nothing
+              _        -> Just [bf]
+            mkOr' [x] = x
+            mkOr' xs = IfOr xs
+
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . BF.mkOr . map (noLocA . fromIfaceBooleanFormula) $ [bf1, bf2]
+                ifMinDef = mkOr [bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -795,8 +808,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef_occ = fromIfaceBooleanFormula if_mindef
-    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) mindef_occ
+    ; mindef <- traverseIfaceBooleanFormula (fmap noLocA . lookupIfaceTop . mkVarOccFS . ifLclNameFS) if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -39,9 +39,9 @@ module GHC.Parser
 where
 
 -- base
-import Control.Monad    ( unless, liftM, when, (<=<) )
+import Control.Monad      ( unless, liftM, when, (<=<) )
 import GHC.Exts
-import Data.Maybe       ( maybeToList )
+import Data.Maybe         ( maybeToList )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
@@ -3700,27 +3700,27 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
         | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula :: { LBooleanFormula GhcPs }
         : name_boolformula_and                      { $1 }
         | name_boolformula_and '|' name_boolformula
                            {% do { h <- addTrailingVbarL $1 (gl $2)
                                  ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
         : name_boolformula_and_list
                   { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula (LocatedN RdrName)] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
         : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
             {% do { h <- addTrailingCommaL $1 (gl $2)
                   ; return (h : $3) } }
 
-name_boolformula_atom :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
         : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
                                       (AnnList Nothing (Just (mop $1)) (Just (mcp $3)) [] []) }
         | name_var                  { sL1a $1 (Var $1) }


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,6 +80,7 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
+import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1137,7 +1138,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
-  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -580,22 +580,20 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
     tidy_errs = bagToList (mapBag (tidyDelayedError env) errs)
 
     partition_errors :: [DelayedError] -> ([Hole], [Hole], [NotConcreteError], [(TcCoercion, CtLoc)])
-    partition_errors = go [] [] [] []
-      where
-        go out_of_scope other_holes syn_eqs mult_co_errs []
-          = (out_of_scope, other_holes, syn_eqs, mult_co_errs)
-        go es1 es2 es3 es4 (err:errs)
-          | (es1, es2, es3, es4) <- go es1 es2 es3 es4 errs
-          = case err of
-              DE_Hole hole
-                | isOutOfScopeHole hole
-                -> (hole : es1, es2, es3, es4)
-                | otherwise
-                -> (es1, hole : es2, es3, es4)
-              DE_NotConcrete err
-                -> (es1, es2, err : es3, es4)
-              DE_Multiplicity mult_co loc
-                -> (es1, es2, es3, (mult_co, loc):es4)
+    partition_errors []
+      = ([], [], [], [])
+    partition_errors (err:errs)
+      | (es1, es2, es3, es4) <- partition_errors errs
+      = case err of
+          DE_Hole hole
+            | isOutOfScopeHole hole
+            -> (hole : es1, es2, es3, es4)
+            | otherwise
+            -> (es1, hole : es2, es3, es4)
+          DE_NotConcrete err
+            -> (es1, es2, err : es3, es4)
+          DE_Multiplicity mult_co loc
+            -> (es1, es2, es3, (mult_co, loc):es4)
 
       -- See Note [Suppressing confusing errors]
     suppress :: ErrorItem -> Bool


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just (fmap unLoc bf)
-    toMinimalDef _                               = Nothing
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef _                             = Nothing
 
 {-
 Note [Polymorphic methods]


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -28,6 +28,7 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   , GRHSs )
 import {-# SOURCE #-} Language.Haskell.Syntax.Pat
   ( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
@@ -35,7 +36,6 @@ import Language.Haskell.Syntax.Type
 import GHC.Types.Fixity (Fixity)
 import GHC.Types.Basic (InlinePragma)
 
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 
 import Data.Void
@@ -465,7 +465,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -0,0 +1,87 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+
+module Language.Haskell.Syntax.BooleanFormula(
+  BooleanFormula(..), LBooleanFormula,
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr,
+  bfExplMap, bfExplTraverse) where
+
+import Prelude hiding ( init, last )
+import Data.List ( nub )
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+
+
+-- types
+type LBooleanFormula p = XRec p (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
+
+-- instances
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+
+-- jury rigged map and traverse functions.
+-- if we had Functor/Traversable (LbooleanFormula p) we could use as a constraint
+-- we wouldn't neeed the first higher order argument, but because LBooleanformula
+-- is a type synonym that's no can do.
+bfExplMap :: ((BooleanFormula p -> BooleanFormula p') -> LBooleanFormula p -> LBooleanFormula p')
+          -> (LIdP p -> LIdP p')
+          -> BooleanFormula p -> BooleanFormula p'
+bfExplMap lbfMap f = go
+  where
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (lbfMap go) bfs
+    go (Or     bfs) = Or      $ map (lbfMap go) bfs
+    go (Parens bf ) = Parens  $ lbfMap go bf
+
+bfExplTraverse  :: Applicative f
+                => ((BooleanFormula p -> f (BooleanFormula p')) -> LBooleanFormula p -> f (LBooleanFormula p'))
+                -> (LIdP p -> f (LIdP p'))
+                -> BooleanFormula p -> f (BooleanFormula p')
+bfExplTraverse lbfTraverse f  = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (lbfTraverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (lbfTraverse go) bfs
+    go (Parens bf ) = Parens <$> lbfTraverse go bf
+
+-- smart constructors
+-- see note [Simplification of BooleanFormulas]
+mkVar :: LIdP p -> BooleanFormula p
+mkVar = Var
+
+mkFalse, mkTrue :: BooleanFormula p
+mkFalse = Or []
+mkTrue = And []
+
+-- Convert a Bool to a BooleanFormula
+mkBool :: Bool -> BooleanFormula p
+mkBool False = mkFalse
+mkBool True  = mkTrue
+
+-- Make a conjunction, and try to simplify
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
+    (And xs) -> Just xs
+     -- assume that xs are already simplified
+     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
+    (Or [])  -> Nothing
+     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
+    _        -> Just [bf]
+  mkAnd' [x] = unXRec @p x
+  mkAnd' xs = And xs
+
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromOr bf = case unXRec @p bf of
+    (Or xs)  -> Just xs
+    (And []) -> Nothing
+    _        -> Just [bf]
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
compiler/ghc.cabal.in
=====================================
@@ -989,6 +989,7 @@ Library
         Language.Haskell.Syntax
         Language.Haskell.Syntax.Basic
         Language.Haskell.Syntax.Binds
+        Language.Haskell.Syntax.BooleanFormula
         Language.Haskell.Syntax.Decls
         Language.Haskell.Syntax.Expr
         Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -234,6 +234,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -258,6 +258,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2984,7 +2984,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4695,7 +4695,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -45,6 +45,7 @@ import GHC.Builtin.Types
   , promotedNilDataCon
   , unitTy
   )
+
 import GHC.Builtin.Types.Prim (alphaTyVars)
 import GHC.Core.Class
 import GHC.Core.Coercion.Axiom
@@ -176,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA . fmap noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -34,6 +34,7 @@ import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
 import Prelude hiding (mapM)
+import Language.Haskell.Syntax.BooleanFormula (bfExplTraverse)
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -770,7 +771,7 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- traverse (traverse lookupRn) s
+    s' <- bfExplTraverse traverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -52,6 +52,7 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 import GHC
 import qualified GHC.Data.Strict as Strict
+import GHC.Data.BooleanFormula (BooleanFormula)
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
@@ -818,6 +819,7 @@ type instance Anno (HsDecl DocNameI) = SrcSpanAnnA
 type instance Anno (FamilyResultSig DocNameI) = EpAnn NoEpAnns
 type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
+type instance Anno (BooleanFormula DocNameI) = SrcSpanAnnL
 
 type XRecCond a =
   ( XParTy a ~ AnnParen



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d8ae1043867e6a8148abbb815f80990e388ba09...bca81cf0145793749722524af7ac4f9984b0f1cc

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d8ae1043867e6a8148abbb815f80990e388ba09...bca81cf0145793749722524af7ac4f9984b0f1cc
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 10:20:03 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 06:20:03 -0400
Subject: [Git][ghc/ghc][wip/ttg/lits] 3 commits: ci: RISCV64 cross-compile
 testing
Message-ID: <670658d34d469_1ba9416c318011494c@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/lits at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
a12ea597 by Hassan Al-Awwadi at 2024-10-09T10:19:28+00:00
Move HsInteger and HsRat to an extension constructor

- - - - -


21 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -106,6 +106,7 @@ data Opsys
 
 data LinuxDistro
   = Debian12
+  | Debian12Riscv
   | Debian11
   | Debian11Js
   | Debian10
@@ -303,6 +304,7 @@ distroName :: LinuxDistro -> String
 distroName Debian12   = "deb12"
 distroName Debian11   = "deb11"
 distroName Debian11Js = "deb11-emsdk-closure"
+distroName Debian12Riscv = "deb12-riscv"
 distroName Debian10   = "deb10"
 distroName Debian9    = "deb9"
 distroName Fedora33   = "fedora33"
@@ -626,6 +628,7 @@ data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
+          | RiscV        -- ^ Run this job when the "RISC-V" label is present
           | WasmBackend  -- ^ Run this job when the "wasm" label is present
           | FreeBSDLabel -- ^ Run this job when the "FreeBSD" label is set.
           | NonmovingGc  -- ^ Run this job when the "non-moving GC" label is set.
@@ -674,6 +677,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
+validateRuleString RiscV        = labelString "RISC-V"
 validateRuleString WasmBackend  = labelString "wasm"
 validateRuleString FreeBSDLabel = labelString "FreeBSD"
 validateRuleString NonmovingGc  = labelString "non-moving GC"
@@ -1125,6 +1129,9 @@ cross_jobs = [
   -- x86 -> aarch64
     validateBuilds Amd64 (Linux Debian11) (crossConfig "aarch64-linux-gnu" (Emulator "qemu-aarch64 -L /usr/aarch64-linux-gnu") Nothing)
 
+  -- x86_64 -> riscv
+  , addValidateRule RiscV (validateBuilds Amd64 (Linux Debian12Riscv) (crossConfig "riscv64-linux-gnu" (Emulator "qemu-riscv64 -L /usr/riscv64-linux-gnu") Nothing))
+
   -- Javascript
   , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11Js) javascriptConfig)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1854,6 +1854,71 @@
       "XZ_OPT": "-9"
     }
   },
+  "nightly-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "8 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "XZ_OPT": "-9"
+    }
+  },
   "nightly-x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -5348,6 +5413,70 @@
       "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
+  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+    }
+  },
   "x86_64-linux-deb12-unreg-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -432,6 +432,8 @@ deriving instance Data XBindStmtTc
 -- deriving instance (DataId p) => Data (HsLit p)
 deriving instance Data (HsLit GhcPs)
 deriving instance Data (HsLit GhcRn)
+
+deriving instance Data HsLitTc
 deriving instance Data (HsLit GhcTc)
 
 -- deriving instance (DataIdLR p p) => Data (HsOverLit p)


=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -62,11 +62,26 @@ type instance XHsWord8Prim  (GhcPass _) = SourceText
 type instance XHsWord16Prim (GhcPass _) = SourceText
 type instance XHsWord32Prim (GhcPass _) = SourceText
 type instance XHsWord64Prim (GhcPass _) = SourceText
-type instance XHsInteger    (GhcPass _) = SourceText
-type instance XHsRat        (GhcPass _) = NoExtField
 type instance XHsFloatPrim  (GhcPass _) = NoExtField
 type instance XHsDoublePrim (GhcPass _) = NoExtField
-type instance XXLit         (GhcPass _) = DataConCantHappen
+
+type instance XXLit         GhcPs = DataConCantHappen
+type instance XXLit         GhcRn = DataConCantHappen
+type instance XXLit         GhcTc = HsLitTc
+
+data HsLitTc
+  = HsInteger SourceText Integer Type
+      -- ^ Genuinely an integer; arises only
+      -- from TRANSLATION (overloaded
+      -- literals are done with HsOverLit)
+  | HsRat FractionalLit Type
+      -- ^ Genuinely a rational; arises only from
+      -- TRANSLATION (overloaded literals are
+      -- done with HsOverLit)
+instance Eq HsLitTc where
+  (HsInteger _ x _) == (HsInteger _ y _) = x==y
+  (HsRat x _)       == (HsRat y _)       = x==y
+  _                 == _                 = False
 
 data OverLitRn
   = OverLitRn {
@@ -130,7 +145,7 @@ hsOverLitNeedsParens _ (XOverLit { }) = False
 --
 -- See Note [Printing of literals in Core] in GHC.Types.Literal
 -- for the reasoning.
-hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
+hsLitNeedsParens :: forall x. IsPass x => PprPrec -> HsLit (GhcPass x) -> Bool
 hsLitNeedsParens p = go
   where
     go (HsChar {})        = False
@@ -139,8 +154,6 @@ hsLitNeedsParens p = go
     go (HsMultilineString {}) = False
     go (HsStringPrim {})  = False
     go (HsInt _ x)        = p > topPrec && il_neg x
-    go (HsInteger _ x _)  = p > topPrec && x < 0
-    go (HsRat _ x _)      = p > topPrec && fl_neg x
     go (HsFloatPrim {})   = False
     go (HsDoublePrim {})  = False
     go (HsIntPrim {})     = False
@@ -153,30 +166,72 @@ hsLitNeedsParens p = go
     go (HsWord16Prim {})  = False
     go (HsWord64Prim {})  = False
     go (HsWord32Prim {})  = False
-    go (XLit _)           = False
+    go (XLit x)           = case ghcPass @x of
+      GhcTc -> case x of
+         (HsInteger _ x _) -> p > topPrec && x < 0
+         (HsRat  x _)      -> p > topPrec && fl_neg x
+
 
 -- | Convert a literal from one index type to another
-convertLit :: HsLit (GhcPass p1) -> HsLit (GhcPass p2)
-convertLit (HsChar a x)       = HsChar a x
-convertLit (HsCharPrim a x)   = HsCharPrim a x
-convertLit (HsString a x)     = HsString a x
-convertLit (HsMultilineString a x) = HsMultilineString a x
-convertLit (HsStringPrim a x) = HsStringPrim a x
-convertLit (HsInt a x)        = HsInt a x
-convertLit (HsIntPrim a x)    = HsIntPrim a x
-convertLit (HsWordPrim a x)   = HsWordPrim a x
-convertLit (HsInt8Prim a x)   = HsInt8Prim a x
-convertLit (HsInt16Prim a x)  = HsInt16Prim a x
-convertLit (HsInt32Prim a x)  = HsInt32Prim a x
-convertLit (HsInt64Prim a x)  = HsInt64Prim a x
-convertLit (HsWord8Prim a x)  = HsWord8Prim a x
-convertLit (HsWord16Prim a x) = HsWord16Prim a x
-convertLit (HsWord32Prim a x) = HsWord32Prim a x
-convertLit (HsWord64Prim a x) = HsWord64Prim a x
-convertLit (HsInteger a x b)  = HsInteger a x b
-convertLit (HsRat a x b)      = HsRat a x b
-convertLit (HsFloatPrim a x)  = HsFloatPrim a x
-convertLit (HsDoublePrim a x) = HsDoublePrim a x
+convertLitPsRn :: HsLit GhcPs -> HsLit GhcRn
+convertLitPsRn (HsChar a x)       = HsChar a x
+convertLitPsRn (HsCharPrim a x)   = HsCharPrim a x
+convertLitPsRn (HsString a x)     = HsString a x
+convertLitPsRn (HsMultilineString a x) = HsMultilineString a x
+convertLitPsRn (HsStringPrim a x) = HsStringPrim a x
+convertLitPsRn (HsInt a x)        = HsInt a x
+convertLitPsRn (HsIntPrim a x)    = HsIntPrim a x
+convertLitPsRn (HsWordPrim a x)   = HsWordPrim a x
+convertLitPsRn (HsInt8Prim a x)   = HsInt8Prim a x
+convertLitPsRn (HsInt16Prim a x)  = HsInt16Prim a x
+convertLitPsRn (HsInt32Prim a x)  = HsInt32Prim a x
+convertLitPsRn (HsInt64Prim a x)  = HsInt64Prim a x
+convertLitPsRn (HsWord8Prim a x)  = HsWord8Prim a x
+convertLitPsRn (HsWord16Prim a x) = HsWord16Prim a x
+convertLitPsRn (HsWord32Prim a x) = HsWord32Prim a x
+convertLitPsRn (HsWord64Prim a x) = HsWord64Prim a x
+convertLitPsRn (HsFloatPrim a x)  = HsFloatPrim a x
+convertLitPsRn (HsDoublePrim a x) = HsDoublePrim a x
+
+convertLitPsTc :: HsLit GhcPs -> HsLit GhcTc
+convertLitPsTc (HsChar a x)       = HsChar a x
+convertLitPsTc (HsCharPrim a x)   = HsCharPrim a x
+convertLitPsTc (HsString a x)     = HsString a x
+convertLitPsTc (HsMultilineString a x) = HsMultilineString a x
+convertLitPsTc (HsStringPrim a x) = HsStringPrim a x
+convertLitPsTc (HsInt a x)        = HsInt a x
+convertLitPsTc (HsIntPrim a x)    = HsIntPrim a x
+convertLitPsTc (HsWordPrim a x)   = HsWordPrim a x
+convertLitPsTc (HsInt8Prim a x)   = HsInt8Prim a x
+convertLitPsTc (HsInt16Prim a x)  = HsInt16Prim a x
+convertLitPsTc (HsInt32Prim a x)  = HsInt32Prim a x
+convertLitPsTc (HsInt64Prim a x)  = HsInt64Prim a x
+convertLitPsTc (HsWord8Prim a x)  = HsWord8Prim a x
+convertLitPsTc (HsWord16Prim a x) = HsWord16Prim a x
+convertLitPsTc (HsWord32Prim a x) = HsWord32Prim a x
+convertLitPsTc (HsWord64Prim a x) = HsWord64Prim a x
+convertLitPsTc (HsFloatPrim a x)  = HsFloatPrim a x
+convertLitPsTc (HsDoublePrim a x) = HsDoublePrim a x
+
+convertLitRnTc :: HsLit GhcRn -> HsLit GhcTc
+convertLitRnTc (HsChar a x)       = HsChar a x
+convertLitRnTc (HsCharPrim a x)   = HsCharPrim a x
+convertLitRnTc (HsString a x)     = HsString a x
+convertLitRnTc (HsMultilineString a x) = HsMultilineString a x
+convertLitRnTc (HsStringPrim a x) = HsStringPrim a x
+convertLitRnTc (HsInt a x)        = HsInt a x
+convertLitRnTc (HsIntPrim a x)    = HsIntPrim a x
+convertLitRnTc (HsWordPrim a x)   = HsWordPrim a x
+convertLitRnTc (HsInt8Prim a x)   = HsInt8Prim a x
+convertLitRnTc (HsInt16Prim a x)  = HsInt16Prim a x
+convertLitRnTc (HsInt32Prim a x)  = HsInt32Prim a x
+convertLitRnTc (HsInt64Prim a x)  = HsInt64Prim a x
+convertLitRnTc (HsWord8Prim a x)  = HsWord8Prim a x
+convertLitRnTc (HsWord16Prim a x) = HsWord16Prim a x
+convertLitRnTc (HsWord32Prim a x) = HsWord32Prim a x
+convertLitRnTc (HsWord64Prim a x) = HsWord64Prim a x
+convertLitRnTc (HsFloatPrim a x)  = HsFloatPrim a x
+convertLitRnTc (HsDoublePrim a x) = HsDoublePrim a x
 
 {-
 Note [ol_rebindable]
@@ -194,7 +249,7 @@ Equivalently it's True if
 -}
 
 -- Instance specific to GhcPs, need the SourceText
-instance Outputable (HsLit (GhcPass p)) where
+instance IsPass p => Outputable (HsLit (GhcPass p)) where
     ppr (HsChar st c)       = pprWithSourceText st (pprHsChar c)
     ppr (HsCharPrim st c)   = pprWithSourceText st (pprPrimChar c)
     ppr (HsString st s)     = pprWithSourceText st (pprHsString s)
@@ -205,8 +260,6 @@ instance Outputable (HsLit (GhcPass p)) where
     ppr (HsStringPrim st s) = pprWithSourceText st (pprHsBytes s)
     ppr (HsInt _ i)
       = pprWithSourceText (il_text i) (integer (il_value i))
-    ppr (HsInteger st i _)  = pprWithSourceText st (integer i)
-    ppr (HsRat _ f _)       = ppr f
     ppr (HsFloatPrim _ f)   = ppr f <> primFloatSuffix
     ppr (HsDoublePrim _ d)  = ppr d <> primDoubleSuffix
     ppr (HsIntPrim st i)    = pprWithSourceText st (pprPrimInt i)
@@ -219,6 +272,10 @@ instance Outputable (HsLit (GhcPass p)) where
     ppr (HsWord16Prim st w) = pprWithSourceText st (pprPrimWord16 w)
     ppr (HsWord32Prim st w) = pprWithSourceText st (pprPrimWord32 w)
     ppr (HsWord64Prim st w) = pprWithSourceText st (pprPrimWord64 w)
+    ppr (XLit x)            = case ghcPass @p of
+      GhcTc -> case x of
+         (HsInteger st i _) -> pprWithSourceText st (integer i)
+         (HsRat  f _)       -> ppr f
 
 -- in debug mode, print the expression that it's resolved to, too
 instance OutputableBndrId p
@@ -237,7 +294,7 @@ instance Outputable OverLitVal where
 -- mainly for too reasons:
 --  * We do not want to expose their internal representation
 --  * The warnings become too messy
-pmPprHsLit :: HsLit (GhcPass x) -> SDoc
+pmPprHsLit :: forall p. IsPass p => HsLit (GhcPass p) -> SDoc
 pmPprHsLit (HsChar _ c)       = pprHsChar c
 pmPprHsLit (HsCharPrim _ c)   = pprHsChar c
 pmPprHsLit (HsString st s)    = pprWithSourceText st (pprHsString s)
@@ -254,10 +311,12 @@ pmPprHsLit (HsWord8Prim _ w)  = integer w
 pmPprHsLit (HsWord16Prim _ w) = integer w
 pmPprHsLit (HsWord32Prim _ w) = integer w
 pmPprHsLit (HsWord64Prim _ w) = integer w
-pmPprHsLit (HsInteger _ i _)  = integer i
-pmPprHsLit (HsRat _ f _)      = ppr f
 pmPprHsLit (HsFloatPrim _ f)  = ppr f
 pmPprHsLit (HsDoublePrim _ d) = ppr d
+pmPprHsLit (XLit x)           = case ghcPass @p of
+  GhcTc -> case x of
+   (HsInteger _ i _)  -> integer i
+   (HsRat f _)        -> ppr f
 
 negateOverLitVal :: OverLitVal -> OverLitVal
 negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i)


=====================================
compiler/GHC/Hs/Syn/Type.hs
=====================================
@@ -7,8 +7,7 @@ module GHC.Hs.Syn.Type (
     -- * Extracting types from HsExpr
     lhsExprType, hsExprType, hsWrapperType,
     -- * Extracting types from HsSyn
-    hsLitType, hsPatType, hsLPatType
-
+    hsLitType, hsPatType, hsLPatType,
   ) where
 
 import GHC.Prelude
@@ -72,7 +71,7 @@ hsPatType (XPat ext) =
     ExpansionPat _ pat -> hsPatType pat
 hsPatType (SplicePat v _)               = dataConCantHappen v
 
-hsLitType :: HsLit (GhcPass p) -> Type
+hsLitType :: forall p. IsPass p => HsLit (GhcPass p) -> Type
 hsLitType (HsChar _ _)       = charTy
 hsLitType (HsCharPrim _ _)   = charPrimTy
 hsLitType (HsString _ _)     = stringTy
@@ -89,10 +88,12 @@ hsLitType (HsWord8Prim _ _)  = word8PrimTy
 hsLitType (HsWord16Prim _ _) = word16PrimTy
 hsLitType (HsWord32Prim _ _) = word32PrimTy
 hsLitType (HsWord64Prim _ _) = word64PrimTy
-hsLitType (HsInteger _ _ ty) = ty
-hsLitType (HsRat _ _ ty)     = ty
 hsLitType (HsFloatPrim _ _)  = floatPrimTy
 hsLitType (HsDoublePrim _ _) = doublePrimTy
+hsLitType (XLit x)           = case ghcPass @p of
+      GhcTc -> case x of
+         (HsInteger _ _ ty) -> ty
+         (HsRat  _ ty)      -> ty
 
 
 -- | Compute the 'Type' of an @'LHsExpr' 'GhcTc'@ in a pure fashion.


=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -305,7 +305,7 @@ dsExpr (HsProjection x _)     = dataConCantHappen x
 
 dsExpr (HsLit _ lit)
   = do { warnAboutOverflowedLit lit
-       ; dsLit (convertLit lit) }
+       ; dsLit lit }
 
 dsExpr (HsOverLit _ lit)
   = do { warnAboutOverflowedOverLit lit


=====================================
compiler/GHC/HsToCore/Match/Literal.hs
=====================================
@@ -97,7 +97,7 @@ For numeric literals, we try to detect there use at a standard type
 See also below where we look for @DictApps@ for \tr{plusInt}, etc.
 -}
 
-dsLit :: HsLit GhcRn -> DsM CoreExpr
+dsLit :: forall p. IsPass p => HsLit (GhcPass p) -> DsM CoreExpr
 dsLit l = do
   dflags <- getDynFlags
   let platform = targetPlatform dflags
@@ -122,9 +122,11 @@ dsLit l = do
     HsChar _ c       -> return (mkCharExpr c)
     HsString _ str   -> mkStringExprFS str
     HsMultilineString _ str -> mkStringExprFS str
-    HsInteger _ i _  -> return (mkIntegerExpr platform i)
     HsInt _ i        -> return (mkIntExpr platform (il_value i))
-    HsRat _ fl ty    -> dsFractionalLitToRational fl ty
+    XLit x           -> case ghcPass @p of
+      GhcTc          -> case x of
+        HsInteger _ i _  -> return (mkIntegerExpr platform i)
+        HsRat fl ty      -> dsFractionalLitToRational fl ty
 
 {-
 Note [FractionalLit representation]
@@ -460,24 +462,24 @@ getIntegralLit _ = Nothing
 -- | If 'Integral', extract the value and type of the non-overloaded literal.
 getSimpleIntegralLit :: HsLit GhcTc -> Maybe (Integer, Type)
 getSimpleIntegralLit (HsInt _ IL{ il_value = i }) = Just (i, intTy)
-getSimpleIntegralLit (HsIntPrim _ i)    = Just (i, intPrimTy)
-getSimpleIntegralLit (HsWordPrim _ i)   = Just (i, wordPrimTy)
-getSimpleIntegralLit (HsInt8Prim _ i)   = Just (i, int8PrimTy)
-getSimpleIntegralLit (HsInt16Prim _ i)  = Just (i, int16PrimTy)
-getSimpleIntegralLit (HsInt32Prim _ i)  = Just (i, int32PrimTy)
-getSimpleIntegralLit (HsInt64Prim _ i)  = Just (i, int64PrimTy)
-getSimpleIntegralLit (HsWord8Prim _ i)  = Just (i, word8PrimTy)
-getSimpleIntegralLit (HsWord16Prim _ i) = Just (i, word16PrimTy)
-getSimpleIntegralLit (HsWord32Prim _ i) = Just (i, word32PrimTy)
-getSimpleIntegralLit (HsWord64Prim _ i) = Just (i, word64PrimTy)
-getSimpleIntegralLit (HsInteger _ i ty) = Just (i, ty)
+getSimpleIntegralLit (HsIntPrim _ i)            = Just (i, intPrimTy)
+getSimpleIntegralLit (HsWordPrim _ i)           = Just (i, wordPrimTy)
+getSimpleIntegralLit (HsInt8Prim _ i)           = Just (i, int8PrimTy)
+getSimpleIntegralLit (HsInt16Prim _ i)          = Just (i, int16PrimTy)
+getSimpleIntegralLit (HsInt32Prim _ i)          = Just (i, int32PrimTy)
+getSimpleIntegralLit (HsInt64Prim _ i)          = Just (i, int64PrimTy)
+getSimpleIntegralLit (HsWord8Prim _ i)          = Just (i, word8PrimTy)
+getSimpleIntegralLit (HsWord16Prim _ i)         = Just (i, word16PrimTy)
+getSimpleIntegralLit (HsWord32Prim _ i)         = Just (i, word32PrimTy)
+getSimpleIntegralLit (HsWord64Prim _ i)         = Just (i, word64PrimTy)
+getSimpleIntegralLit (XLit (HsInteger _ i ty))  = Just (i, ty)
 
 getSimpleIntegralLit HsChar{}           = Nothing
 getSimpleIntegralLit HsCharPrim{}       = Nothing
 getSimpleIntegralLit HsString{}         = Nothing
 getSimpleIntegralLit HsMultilineString{} = Nothing
 getSimpleIntegralLit HsStringPrim{}     = Nothing
-getSimpleIntegralLit HsRat{}            = Nothing
+getSimpleIntegralLit (XLit (HsRat{}))   = Nothing
 getSimpleIntegralLit HsFloatPrim{}      = Nothing
 getSimpleIntegralLit HsDoublePrim{}     = Nothing
 


=====================================
compiler/GHC/HsToCore/Pmc/Desugar.hs
=====================================
@@ -225,7 +225,7 @@ desugarPat x pat = case pat of
     mkPmLitGrds x lit'
 
   LitPat _ lit -> do
-    core_expr <- dsLit (convertLit lit)
+    core_expr <- dsLit lit
     let lit = expectJust "failed to detect Lit" (coreExprAsPmLit core_expr)
     mkPmLitGrds x lit
 


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -3001,7 +3001,7 @@ repTyVarSig (MkC bndr) = rep2 tyVarSigName [bndr]
 ----------------------------------------------------------
 --              Literals
 
-repLiteral :: HsLit GhcRn -> MetaM (Core TH.Lit)
+repLiteral ::  HsLit GhcRn -> MetaM (Core TH.Lit)
 repLiteral (HsStringPrim _ bs)
   = do word8_ty <- lookupType word8TyConName
        let w8s = unpack bs
@@ -3010,20 +3010,19 @@ repLiteral (HsStringPrim _ bs)
        rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr]
 repLiteral lit
   = do lit' <- case lit of
-                   HsIntPrim _ i    -> mk_integer i
-                   HsWordPrim _ w   -> mk_integer w
-                   HsInt _ i        -> mk_integer (il_value i)
-                   HsFloatPrim _ r  -> mk_rational r
-                   HsDoublePrim _ r -> mk_rational r
-                   HsCharPrim _ c   -> mk_char c
-                   _ -> return lit
-       lit_expr <- lift $ dsLit lit'
+                   HsIntPrim _ i    -> dsLit <$> mk_integer i
+                   HsWordPrim _ w   -> dsLit <$> mk_integer w
+                   HsInt _ i        -> dsLit <$> mk_integer (il_value i)
+                   HsFloatPrim _ r  -> dsLit <$> mk_rational r
+                   HsDoublePrim _ r -> dsLit <$> mk_rational r
+                   HsCharPrim _ c   -> dsLit <$> mk_char c
+                   _                -> return $ dsLit lit
+       lit_expr <- lift lit'
        case mb_lit_name of
           Just lit_name -> rep2_nw lit_name [lit_expr]
           Nothing -> notHandled (ThExoticLiteral lit)
   where
     mb_lit_name = case lit of
-                 HsInteger _ _ _  -> Just integerLName
                  HsInt _ _        -> Just integerLName
                  HsIntPrim _ _    -> Just intPrimLName
                  HsWordPrim _ _   -> Just wordPrimLName
@@ -3033,32 +3032,41 @@ repLiteral lit
                  HsCharPrim _ _   -> Just charPrimLName
                  HsString _ _     -> Just stringLName
                  HsMultilineString _ _ -> Just stringLName
-                 HsRat _ _ _      -> Just rationalLName
                  _                -> Nothing
 
-mk_integer :: Integer -> MetaM (HsLit GhcRn)
-mk_integer  i = return $ HsInteger NoSourceText i integerTy
+mk_integer :: Integer -> MetaM (HsLit GhcTc)
+mk_integer  i = return $ XLit $ HsInteger NoSourceText i integerTy
 
-mk_rational :: FractionalLit -> MetaM (HsLit GhcRn)
+mk_rational :: FractionalLit -> MetaM (HsLit GhcTc)
 mk_rational r = do rat_ty <- lookupType rationalTyConName
-                   return $ HsRat noExtField r rat_ty
-mk_string :: FastString -> MetaM (HsLit GhcRn)
+                   return $ XLit $ HsRat r rat_ty
+mk_string :: FastString -> MetaM (HsLit GhcTc)
 mk_string s = return $ HsString NoSourceText s
 
-mk_char :: Char -> MetaM (HsLit GhcRn)
+mk_char :: Char -> MetaM (HsLit GhcTc)
 mk_char c = return $ HsChar NoSourceText c
 
 repOverloadedLiteral :: HsOverLit GhcRn -> MetaM (Core TH.Lit)
 repOverloadedLiteral (OverLit { ol_val = val})
-  = do { lit <- mk_lit val; repLiteral lit }
-        -- The type Rational will be in the environment, because
-        -- the smart constructor 'TH.Syntax.rationalL' uses it in its type,
-        -- and rationalL is sucked in when any TH stuff is used
-
-mk_lit :: OverLitVal -> MetaM (HsLit GhcRn)
-mk_lit (HsIntegral i)     = mk_integer  (il_value i)
-mk_lit (HsFractional f)   = mk_rational f
-mk_lit (HsIsString _ s)   = mk_string   s
+  = repOverLiteralVal val
+    -- The type Rational will be in the environment, because
+    -- the smart constructor 'TH.Syntax.rationalL' uses it in its type,
+    -- and rationalL is sucked in when any TH stuff is used
+
+repOverLiteralVal ::  OverLitVal -> MetaM (Core TH.Lit)
+repOverLiteralVal lit = do
+  lit' <- case lit of
+        (HsIntegral i)   -> mk_integer  (il_value i)
+        (HsFractional f) -> mk_rational f
+        (HsIsString _ s) -> mk_string   s
+  lit_expr <- lift $ dsLit  lit'
+
+  let lit_name = case lit of
+        (HsIntegral _  ) -> integerLName
+        (HsFractional _) -> rationalLName
+        (HsIsString _ _) -> stringLName
+
+  rep2_nw lit_name [lit_expr]
 
 repRdrName :: RdrName -> MetaM (Core TH.Name)
 repRdrName rdr_name = do


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -374,7 +374,7 @@ rnExpr (HsLit x lit) | Just (src, s) <- stringLike lit
             rnExpr (HsOverLit x (mkHsIsString src s))
          else do {
             ; rnLit lit
-            ; return (HsLit x (convertLit lit), emptyFVs) } }
+            ; return (HsLit x (convertLitPsRn lit), emptyFVs) } }
   where
     stringLike = \case
       HsString src s -> Just (src, s)
@@ -383,7 +383,7 @@ rnExpr (HsLit x lit) | Just (src, s) <- stringLike lit
 
 rnExpr (HsLit x lit)
   = do { rnLit lit
-       ; return (HsLit x(convertLit lit), emptyFVs) }
+       ; return (HsLit x(convertLitPsRn lit), emptyFVs) }
 
 rnExpr (HsOverLit x lit)
   = do { ((lit', mb_neg), fvs) <- rnOverLit lit -- See Note [Negative zero]


=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -572,7 +572,7 @@ rnPatAndThen mk (LitPat x lit)
          else normal_lit }
   | otherwise = normal_lit
   where
-    normal_lit = do { liftCps (rnLit lit); return (LitPat x (convertLit lit)) }
+    normal_lit = do { liftCps (rnLit lit); return (LitPat x (convertLitPsRn lit)) }
 
 rnPatAndThen _ (NPat x (L l lit) mb_neg _eq)
   = do { (lit', mb_neg') <- liftCpsFV $ rnOverLit lit


=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -580,22 +580,20 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
     tidy_errs = bagToList (mapBag (tidyDelayedError env) errs)
 
     partition_errors :: [DelayedError] -> ([Hole], [Hole], [NotConcreteError], [(TcCoercion, CtLoc)])
-    partition_errors = go [] [] [] []
-      where
-        go out_of_scope other_holes syn_eqs mult_co_errs []
-          = (out_of_scope, other_holes, syn_eqs, mult_co_errs)
-        go es1 es2 es3 es4 (err:errs)
-          | (es1, es2, es3, es4) <- go es1 es2 es3 es4 errs
-          = case err of
-              DE_Hole hole
-                | isOutOfScopeHole hole
-                -> (hole : es1, es2, es3, es4)
-                | otherwise
-                -> (es1, hole : es2, es3, es4)
-              DE_NotConcrete err
-                -> (es1, es2, err : es3, es4)
-              DE_Multiplicity mult_co loc
-                -> (es1, es2, es3, (mult_co, loc):es4)
+    partition_errors []
+      = ([], [], [], [])
+    partition_errors (err:errs)
+      | (es1, es2, es3, es4) <- partition_errors errs
+      = case err of
+          DE_Hole hole
+            | isOutOfScopeHole hole
+            -> (hole : es1, es2, es3, es4)
+            | otherwise
+            -> (es1, hole : es2, es3, es4)
+          DE_NotConcrete err
+            -> (es1, es2, err : es3, es4)
+          DE_Multiplicity mult_co loc
+            -> (es1, es2, es3, (mult_co, loc):es4)
 
       -- See Note [Suppressing confusing errors]
     suppress :: ErrorItem -> Bool


=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -317,7 +317,7 @@ tcExpr (HsUnboundVar _ occ) res_ty
 
 tcExpr e@(HsLit x lit) res_ty
   = do { let lit_ty = hsLitType lit
-       ; tcWrapResult e (HsLit x (convertLit lit)) lit_ty res_ty }
+       ; tcWrapResult e (HsLit x (convertLitRnTc lit)) lit_ty res_ty }
 
 tcExpr (HsPar x expr) res_ty
   = do { expr' <- tcMonoExprNC expr res_ty


=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -829,7 +829,7 @@ Fortunately that's what matchActualFunTy returns anyway.
         ; wrap   <- tc_sub_type penv (scaledThing pat_ty) lit_ty
         ; res    <- thing_inside
         ; pat_ty <- readExpType (scaledThing pat_ty)
-        ; return ( mkHsWrapPat wrap (LitPat x (convertLit simple_lit)) pat_ty
+        ; return ( mkHsWrapPat wrap (LitPat x (convertLitRnTc simple_lit)) pat_ty
                  , res) }
 
 ------------------------


=====================================
compiler/GHC/Tc/Utils/Instantiate.hs
=====================================
@@ -807,15 +807,14 @@ newNonTrivialOverloadedLit
     orig = LiteralOrigin lit
 
 ------------
-mkOverLit :: OverLitVal -> TcM (HsLit (GhcPass p))
+mkOverLit :: OverLitVal -> TcM (HsLit GhcTc)
 mkOverLit (HsIntegral i)
   = do  { integer_ty <- tcMetaTy integerTyConName
-        ; return (HsInteger (il_text i)
-                            (il_value i) integer_ty) }
+        ; return (XLit $ HsInteger  (il_text i) (il_value i) integer_ty) }
 
 mkOverLit (HsFractional r)
   = do  { rat_ty <- tcMetaTy rationalTyConName
-        ; return (HsRat noExtField r rat_ty) }
+        ; return (XLit $ HsRat r rat_ty) }
 
 mkOverLit (HsIsString src s) = return (HsString src s)
 


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -2368,7 +2368,7 @@ shortCutLit platform val res_ty
       | isWordTy res_ty && platformInWordRange platform i
       = Just (mkLit wordDataCon (HsWordPrim src i))
       | isIntegerTy res_ty
-      = Just (HsLit noExtField (HsInteger src i res_ty))
+      = Just (HsLit noExtField (XLit $ HsInteger src i res_ty))
       | otherwise
       = go_fractional (integralFractionalLit neg i)
         -- The 'otherwise' case is important


=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -943,9 +943,9 @@ zonkExpr (HsIPVar x _) = dataConCantHappen x
 
 zonkExpr (HsOverLabel x _) = dataConCantHappen x
 
-zonkExpr (HsLit x (HsRat e f ty))
+zonkExpr (HsLit x (XLit (HsRat f ty)))
   = do new_ty <- zonkTcTypeToTypeX ty
-       return (HsLit x (HsRat e f new_ty))
+       return (HsLit x (XLit $ HsRat f new_ty))
 
 zonkExpr (HsLit x lit)
   = return (HsLit x lit)


=====================================
compiler/Language/Haskell/Syntax/Extension.hs
=====================================
@@ -569,8 +569,6 @@ type family XHsWord8Prim x
 type family XHsWord16Prim x
 type family XHsWord32Prim x
 type family XHsWord64Prim x
-type family XHsInteger x
-type family XHsRat x
 type family XHsFloatPrim x
 type family XHsDoublePrim x
 type family XXLit x


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -21,7 +21,6 @@ module Language.Haskell.Syntax.Lit where
 import Language.Haskell.Syntax.Extension
 
 import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText)
-import GHC.Core.Type (Type)
 
 import GHC.Data.FastString (FastString, lexicalCompareFS)
 
@@ -80,22 +79,13 @@ data HsLit x
       -- ^ literal @Word32#@
   | HsWord64Prim (XHsWord64Prim x) {- SourceText -} Integer
       -- ^ literal @Word64#@
-  | HsInteger (XHsInteger x) {- SourceText -} Integer Type
-      -- ^ Genuinely an integer; arises only
-      -- from TRANSLATION (overloaded
-      -- literals are done with HsOverLit)
-  | HsRat (XHsRat x)  FractionalLit Type
-      -- ^ Genuinely a rational; arises only from
-      -- TRANSLATION (overloaded literals are
-      -- done with HsOverLit)
   | HsFloatPrim (XHsFloatPrim x)   FractionalLit
       -- ^ Unboxed Float
   | HsDoublePrim (XHsDoublePrim x) FractionalLit
       -- ^ Unboxed Double
-
   | XLit !(XXLit x)
 
-instance Eq (HsLit x) where
+instance (Eq (XXLit x)) => Eq (HsLit x) where
   (HsChar _ x1)       == (HsChar _ x2)       = x1==x2
   (HsCharPrim _ x1)   == (HsCharPrim _ x2)   = x1==x2
   (HsString _ x1)     == (HsString _ x2)     = x1==x2
@@ -105,10 +95,9 @@ instance Eq (HsLit x) where
   (HsWordPrim _ x1)   == (HsWordPrim _ x2)   = x1==x2
   (HsInt64Prim _ x1)  == (HsInt64Prim _ x2)  = x1==x2
   (HsWord64Prim _ x1) == (HsWord64Prim _ x2) = x1==x2
-  (HsInteger _ x1 _)  == (HsInteger _ x2 _)  = x1==x2
-  (HsRat _ x1 _)      == (HsRat _ x2 _)      = x1==x2
   (HsFloatPrim _ x1)  == (HsFloatPrim _ x2)  = x1==x2
   (HsDoublePrim _ x1) == (HsDoublePrim _ x2) = x1==x2
+  (XLit x1)           == (XLit x2)           = x1==x2
   _                   == _                   = False
 
 -- | Haskell Overloaded Literal


=====================================
testsuite/tests/ghc-api/annotations-literals/parsed.hs
=====================================
@@ -64,8 +64,6 @@ testOneFile libdir fileName = do
        = ["HsInt64Prim [" ++ unpackFS src ++ "] " ++ show c]
      doHsLit (HsWord64Prim (SourceText src) c)
        = ["HsWord64Prim [" ++ unpackFS src ++ "] " ++ show c]
-     doHsLit (HsInteger  (SourceText src) c _)
-       = ["HsInteger [" ++ unpackFS src ++ "] " ++ show c]
      doHsLit _ = []
 
      doOverLit :: OverLitVal -> [String]


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -4948,8 +4948,6 @@ hsLit2String lit =
     HsWord16Prim src v   -> toSourceTextWithSuffix src v ""
     HsWord32Prim src v   -> toSourceTextWithSuffix src v ""
     HsWord64Prim src v   -> toSourceTextWithSuffix src v ""
-    HsInteger    src v _ -> toSourceTextWithSuffix src v ""
-    HsRat        _ fl@(FL{fl_text = src }) _ -> toSourceTextWithSuffix src fl ""
     HsFloatPrim  _ fl@(FL{fl_text = src })   -> toSourceTextWithSuffix src fl "#"
     HsDoublePrim _ fl@(FL{fl_text = src })   -> toSourceTextWithSuffix src fl "##"
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65d7019b7137c6851b3b2ea76d6c9dccd0ccfb43...a12ea597f3876dcdcabecc12aa21ca732832949f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65d7019b7137c6851b3b2ea76d6c9dccd0ccfb43...a12ea597f3876dcdcabecc12aa21ca732832949f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 11:33:56 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 09 Oct 2024 07:33:56 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] Bump Cabal submodule to 3.14
Message-ID: <67066a24e03d8_26d7fabc96c8936b@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
e5d48ed9 by Zubin Duggal at 2024-10-09T17:03:50+05:30
Bump Cabal submodule to 3.14

- - - - -


3 changed files:

- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 12:15:21 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 08:15:21 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25362
Message-ID: <670673d93b73d_26d7fa2f86909732e@gitlab.mail>



Ben Gamari pushed new branch wip/T25362 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25362
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 12:22:38 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 08:22:38 -0400
Subject: [Git][ghc/ghc][wip/bump-process] Bump process submodule to v1.6.25.0
Message-ID: <6706758ee1bd1_26d7fa476eb81023be@gitlab.mail>



Ben Gamari pushed to branch wip/bump-process at Glasgow Haskell Compiler / GHC


Commits:
faaf8b79 by Ben Gamari at 2024-10-09T08:22:29-04:00
Bump process submodule to v1.6.25.0

- - - - -


3 changed files:

- libraries/process
- testsuite/tests/process/process004.hs
- testsuite/tests/process/process004.stdout


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b
+Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e


=====================================
testsuite/tests/process/process004.hs
=====================================
@@ -4,8 +4,13 @@ import System.IO.Error
 import System.Process
 
 main :: IO ()
-main = do test1 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
-          test2 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
+main = do
+  -- N.B. Only show the error type since the exact error text
+  -- may depend upon precise system call which @process@ decided
+  -- to use.
+  let printError e = putStrLn ("Exc: " ++ show (ioeGetErrorType e))
+  test1 `catchIOError` printError
+  test2 `catchIOError` printError
 
 test1 :: IO ()
 test1 = do


=====================================
testsuite/tests/process/process004.stdout
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: chdir: invalid argument (Bad file descriptor)
+Exc: true: runInteractiveProcess: chdir: does not exist (No such file or directory)
 Exc: true: runProcess: chdir: does not exist (No such file or directory)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 12:44:19 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 08:44:19 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 2 commits: linker: Avoid linear
 search when looking up Haskell symbols via dlsym
Message-ID: <67067aa38541b_26d7fa5c533c1119cf@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
c9db9806 by Alexis King at 2024-10-09T08:44:02-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
8362bd5c by Ben Gamari at 2024-10-09T08:44:02-04:00
hadrian: Update bootstrap plans

- - - - -


14 changed files:

- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- hadrian/bootstrap/generate_bootstrap_plans
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- rts/Linker.c
- rts/RtsSymbols.c
- rts/include/rts/Linker.h
- testsuite/tests/rts/linker/T2615.hs


Changes:

=====================================
compiler/GHC/ByteCode/Linker.hs
=====================================
@@ -25,6 +25,7 @@ import GHCi.ResolvedBCO
 import GHCi.BreakArray
 
 import GHC.Builtin.PrimOps
+import GHC.Builtin.PrimOps.Ids
 import GHC.Builtin.Names
 
 import GHC.Unit.Types
@@ -40,6 +41,8 @@ import GHC.Utils.Outputable
 
 import GHC.Types.Name
 import GHC.Types.Name.Env
+import qualified GHC.Types.Id as Id
+import GHC.Types.Unique.DFM
 
 import Language.Haskell.Syntax.Module.Name
 
@@ -54,32 +57,33 @@ import GHC.Exts
 
 linkBCO
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> UnlinkedBCO
   -> IO ResolvedBCO
-linkBCO interp le bco_ix breakarray
+linkBCO interp pkgs_loaded le bco_ix breakarray
            (UnlinkedBCO _ arity insns bitmap lits0 ptrs0) = do
   -- fromIntegral Word -> Word64 should be a no op if Word is Word64
   -- otherwise it will result in a cast to longlong on 32bit systems.
-  lits <- mapM (fmap fromIntegral . lookupLiteral interp le) (ssElts lits0)
-  ptrs <- mapM (resolvePtr interp le bco_ix breakarray) (ssElts ptrs0)
+  lits <- mapM (fmap fromIntegral . lookupLiteral interp pkgs_loaded le) (ssElts lits0)
+  ptrs <- mapM (resolvePtr interp pkgs_loaded le bco_ix breakarray) (ssElts ptrs0)
   return (ResolvedBCO isLittleEndian arity insns bitmap
               (listArray (0, fromIntegral (sizeSS lits0)-1) lits)
               (addListToSS emptySS ptrs))
 
-lookupLiteral :: Interp -> LinkerEnv -> BCONPtr -> IO Word
-lookupLiteral interp le ptr = case ptr of
+lookupLiteral :: Interp -> PkgsLoaded -> LinkerEnv -> BCONPtr -> IO Word
+lookupLiteral interp pkgs_loaded le ptr = case ptr of
   BCONPtrWord lit -> return lit
   BCONPtrLbl  sym -> do
     Ptr a# <- lookupStaticPtr interp sym
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrItbl nm -> do
-    Ptr a# <- lookupIE interp (itbl_env le) nm
+    Ptr a# <- lookupIE interp pkgs_loaded (itbl_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrAddr nm -> do
-    Ptr a# <- lookupAddr interp (addr_env le) nm
+    Ptr a# <- lookupAddr interp pkgs_loaded (addr_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrStr _ ->
     -- should be eliminated during assembleBCOs
@@ -93,19 +97,19 @@ lookupStaticPtr interp addr_of_label_string = do
     Nothing  -> linkFail "GHC.ByteCode.Linker: can't find label"
                   (unpackFS addr_of_label_string)
 
-lookupIE :: Interp -> ItblEnv -> Name -> IO (Ptr ())
-lookupIE interp ie con_nm =
+lookupIE :: Interp -> PkgsLoaded -> ItblEnv -> Name -> IO (Ptr ())
+lookupIE interp pkgs_loaded ie con_nm =
   case lookupNameEnv ie con_nm of
     Just (_, ItblPtr a) -> return (fromRemotePtr (castRemotePtr a))
     Nothing -> do -- try looking up in the object files.
        let sym_to_find1 = nameToCLabel con_nm "con_info"
-       m <- lookupSymbol interp sym_to_find1
+       m <- lookupHsSymbol interp pkgs_loaded con_nm "con_info"
        case m of
           Just addr -> return addr
           Nothing
              -> do -- perhaps a nullary constructor?
                    let sym_to_find2 = nameToCLabel con_nm "static_info"
-                   n <- lookupSymbol interp sym_to_find2
+                   n <- lookupHsSymbol interp pkgs_loaded con_nm "static_info"
                    case n of
                       Just addr -> return addr
                       Nothing   -> linkFail "GHC.ByteCode.Linker.lookupIE"
@@ -113,35 +117,36 @@ lookupIE interp ie con_nm =
                                        unpackFS sym_to_find2)
 
 -- see Note [Generating code for top-level string literal bindings] in GHC.StgToByteCode
-lookupAddr :: Interp -> AddrEnv -> Name -> IO (Ptr ())
-lookupAddr interp ae addr_nm = do
+lookupAddr :: Interp -> PkgsLoaded -> AddrEnv -> Name -> IO (Ptr ())
+lookupAddr interp pkgs_loaded ae addr_nm = do
   case lookupNameEnv ae addr_nm of
     Just (_, AddrPtr ptr) -> return (fromRemotePtr ptr)
     Nothing -> do -- try looking up in the object files.
       let sym_to_find = nameToCLabel addr_nm "bytes"
                           -- see Note [Bytes label] in GHC.Cmm.CLabel
-      m <- lookupSymbol interp sym_to_find
+      m <- lookupHsSymbol interp pkgs_loaded addr_nm "bytes"
       case m of
         Just ptr -> return ptr
         Nothing -> linkFail "GHC.ByteCode.Linker.lookupAddr"
                      (unpackFS sym_to_find)
 
-lookupPrimOp :: Interp -> PrimOp -> IO (RemotePtr ())
-lookupPrimOp interp primop = do
+lookupPrimOp :: Interp -> PkgsLoaded -> PrimOp -> IO (RemotePtr ())
+lookupPrimOp interp pkgs_loaded primop = do
   let sym_to_find = primopToCLabel primop "closure"
-  m <- lookupSymbol interp (mkFastString sym_to_find)
+  m <- lookupHsSymbol interp pkgs_loaded (Id.idName $ primOpId primop) "closure"
   case m of
     Just p -> return (toRemotePtr p)
     Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE(primop)" sym_to_find
 
 resolvePtr
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> BCOPtr
   -> IO ResolvedBCOPtr
-resolvePtr interp le bco_ix breakarray ptr = case ptr of
+resolvePtr interp pkgs_loaded le bco_ix breakarray ptr = case ptr of
   BCOPtrName nm
     | Just ix <- lookupNameEnv bco_ix nm
     -> return (ResolvedBCORef ix) -- ref to another BCO in this group
@@ -153,20 +158,42 @@ resolvePtr interp le bco_ix breakarray ptr = case ptr of
     -> assertPpr (isExternalName nm) (ppr nm) $
        do
           let sym_to_find = nameToCLabel nm "closure"
-          m <- lookupSymbol interp sym_to_find
+          m <- lookupHsSymbol interp pkgs_loaded nm "closure"
           case m of
             Just p -> return (ResolvedBCOStaticPtr (toRemotePtr p))
             Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE" (unpackFS sym_to_find)
 
   BCOPtrPrimOp op
-    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp op
+    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp pkgs_loaded op
 
   BCOPtrBCO bco
-    -> ResolvedBCOPtrBCO <$> linkBCO interp le bco_ix breakarray bco
+    -> ResolvedBCOPtrBCO <$> linkBCO interp pkgs_loaded le bco_ix breakarray bco
 
   BCOPtrBreakArray
     -> return (ResolvedBCOPtrBreakArray breakarray)
 
+-- | Look up the address of a Haskell symbol in the currently
+-- loaded units.
+--
+-- See Note [Looking up symbols in the relevant objects].
+lookupHsSymbol :: Interp -> PkgsLoaded -> Name -> String -> IO (Maybe (Ptr ()))
+lookupHsSymbol interp pkgs_loaded nm sym_suffix = do
+  massertPpr (isExternalName nm) (ppr nm)
+  let sym_to_find = nameToCLabel nm sym_suffix
+      pkg_id = moduleUnitId $ nameModule nm
+      loaded_dlls = maybe [] loaded_pkg_hs_dlls $ lookupUDFM pkgs_loaded pkg_id
+
+      go (dll:dlls) = do
+        mb_ptr <- lookupSymbolInDLL interp dll sym_to_find
+        case mb_ptr of
+          Just ptr -> pure (Just ptr)
+          Nothing -> go dlls
+      go [] =
+        -- See Note [Symbols may not be found in pkgs_loaded] in GHC.Linker.Types
+        lookupSymbol interp sym_to_find
+
+  go loaded_dlls
+
 linkFail :: String -> String -> IO a
 linkFail who what
    = throwGhcExceptionIO (ProgramError $


=====================================
compiler/GHC/Driver/Plugins.hs
=====================================
@@ -405,12 +405,12 @@ loadExternalPluginLib :: FilePath -> IO ()
 loadExternalPluginLib path = do
   -- load library
   loadDLL path >>= \case
-    Just errmsg -> pprPanic "loadExternalPluginLib"
-                    (vcat [ text "Can't load plugin library"
-                          , text "  Library path: " <> text path
-                          , text "  Error       : " <> text errmsg
-                          ])
-    Nothing -> do
+    Left errmsg -> pprPanic "loadExternalPluginLib"
+                     (vcat [ text "Can't load plugin library"
+                           , text "  Library path: " <> text path
+                           , text "  Error       : " <> text errmsg
+                           ])
+    Right _ -> do
       -- resolve objects
       resolveObjs >>= \case
         True -> return ()


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -56,6 +56,7 @@ import GHC.Tc.Utils.Monad
 import GHC.Runtime.Interpreter
 import GHCi.RemoteTypes
 import GHC.Iface.Load
+import GHCi.Message (LoadedDLL)
 
 import GHC.ByteCode.Linker
 import GHC.ByteCode.Asm
@@ -145,7 +146,7 @@ emptyLoaderState = LoaderState
   --
   -- The linker's symbol table is populated with RTS symbols using an
   -- explicit list.  See rts/Linker.c for details.
-  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] emptyUniqDSet)
+  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] [] emptyUniqDSet)
 
 extendLoadedEnv :: Interp -> [(Name,ForeignHValue)] -> IO ()
 extendLoadedEnv interp new_bindings =
@@ -194,8 +195,8 @@ loadDependencies
   -> SrcSpan
   -> [Module]
   -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) -- ^ returns the set of linkables required
+-- When called, the loader state must have been initialized (see `initLoaderState`)
 loadDependencies interp hsc_env pls span needed_mods = do
---   initLoaderState (hsc_dflags hsc_env) dl
    let opts = initLinkDepsOpts hsc_env
 
    -- Find what packages and linkables are required
@@ -485,25 +486,25 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
     DLL dll_unadorned -> do
       maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
       case maybe_errstr of
-         Nothing -> maybePutStrLn logger "done"
-         Just mm | platformOS platform /= OSDarwin ->
+         Right _ -> maybePutStrLn logger "done"
+         Left mm | platformOS platform /= OSDarwin ->
            preloadFailed mm lib_paths lib_spec
-         Just mm | otherwise -> do
+         Left mm | otherwise -> do
            -- As a backup, on Darwin, try to also load a .so file
            -- since (apparently) some things install that way - see
            -- ticket #8770.
            let libfile = ("lib" ++ dll_unadorned) <.> "so"
            err2 <- loadDLL interp libfile
            case err2 of
-             Nothing -> maybePutStrLn logger "done"
-             Just _  -> preloadFailed mm lib_paths lib_spec
+             Right _ -> maybePutStrLn logger "done"
+             Left _  -> preloadFailed mm lib_paths lib_spec
       return pls
 
     DLLPath dll_path -> do
       do maybe_errstr <- loadDLL interp dll_path
          case maybe_errstr of
-            Nothing -> maybePutStrLn logger "done"
-            Just mm -> preloadFailed mm lib_paths lib_spec
+            Right _ -> maybePutStrLn logger "done"
+            Left mm -> preloadFailed mm lib_paths lib_spec
          return pls
 
     Framework framework ->
@@ -588,7 +589,7 @@ loadExpr interp hsc_env span root_ul_bco = do
         let le = linker_env pls
             nobreakarray = error "no break array"
             bco_ix = mkNameEnv [(unlinkedBCOName root_ul_bco, 0)]
-        resolved <- linkBCO interp le bco_ix nobreakarray root_ul_bco
+        resolved <- linkBCO interp (pkgs_loaded pls) le bco_ix nobreakarray root_ul_bco
         [root_hvref] <- createBCOs interp [resolved]
         fhv <- mkFinalizedHValue interp root_hvref
         return (pls, fhv)
@@ -651,7 +652,7 @@ loadDecls interp hsc_env span cbc at CompiledByteCode{..} = do
                        , addr_env = plusNameEnv (addr_env le) bc_strs }
 
           -- Link the necessary packages and linkables
-          new_bindings <- linkSomeBCOs interp le2 [cbc]
+          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 [cbc]
           nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
           let ce2  = extendClosureEnv (closure_env le2) nms_fhvs
               !pls2 = pls { linker_env = le2 { closure_env = ce2 } }
@@ -832,8 +833,8 @@ dynLoadObjs interp hsc_env pls at LoaderState{..} objs = do
     changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
     m <- loadDLL interp soFile
     case m of
-        Nothing -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
-        Just err -> linkFail msg err
+      Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
+      Left err -> linkFail msg err
   where
     msg = "GHC.Linker.Loader.dynLoadObjs: Loading temp shared object failed"
 
@@ -873,7 +874,7 @@ dynLinkBCOs interp pls bcos = do
             ae2 = foldr plusNameEnv (addr_env le1) (map bc_strs cbcs)
             le2 = le1 { itbl_env = ie2, addr_env = ae2 }
 
-        names_and_refs <- linkSomeBCOs interp le2 cbcs
+        names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
 
         -- We only want to add the external ones to the ClosureEnv
         let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
@@ -888,6 +889,7 @@ dynLinkBCOs interp pls bcos = do
 
 -- Link a bunch of BCOs and return references to their values
 linkSomeBCOs :: Interp
+             -> PkgsLoaded
              -> LinkerEnv
              -> [CompiledByteCode]
              -> IO [(Name,HValueRef)]
@@ -895,7 +897,7 @@ linkSomeBCOs :: Interp
                         -- the incoming unlinked BCOs.  Each gives the
                         -- value of the corresponding unlinked BCO
 
-linkSomeBCOs interp le mods = foldr fun do_link mods []
+linkSomeBCOs interp pkgs_loaded le mods = foldr fun do_link mods []
  where
   fun CompiledByteCode{..} inner accum =
     case bc_breaks of
@@ -908,7 +910,7 @@ linkSomeBCOs interp le mods = foldr fun do_link mods []
     let flat = [ (breakarray, bco) | (breakarray, bcos) <- mods, bco <- bcos ]
         names = map (unlinkedBCOName . snd) flat
         bco_ix = mkNameEnv (zip names [0..])
-    resolved <- sequence [ linkBCO interp le bco_ix breakarray bco
+    resolved <- sequence [ linkBCO interp pkgs_loaded le bco_ix breakarray bco
                          | (breakarray, bco) <- flat ]
     hvrefs <- createBCOs interp resolved
     return (zip names hvrefs)
@@ -1071,18 +1073,18 @@ loadPackages' interp hsc_env new_pks pls = do
                -- Link dependents first
              ; pkgs' <- link pkgs deps
                 -- Now link the package itself
-             ; (hs_cls, extra_cls) <- loadPackage interp hsc_env pkg_cfg
+             ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
              ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
                                                    | dep_pkg <- deps
                                                    , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
                                                    ]
-             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls trans_deps)) }
+             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
 
         | otherwise
         = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
 
 
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec])
+loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
 loadPackage interp hsc_env pkg
    = do
         let dflags    = hsc_dflags hsc_env
@@ -1124,7 +1126,9 @@ loadPackage interp hsc_env pkg
         let classifieds = hs_classifieds ++ extra_classifieds
 
         -- Complication: all the .so's must be loaded before any of the .o's.
-        let known_dlls = [ dll  | DLLPath dll    <- classifieds ]
+        let known_hs_dlls    = [ dll | DLLPath dll <- hs_classifieds ]
+            known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
+            known_dlls       = known_hs_dlls ++ known_extra_dlls
 #if defined(CAN_LOAD_DLL)
             dlls       = [ dll  | DLL dll        <- classifieds ]
 #endif
@@ -1145,10 +1149,13 @@ loadPackage interp hsc_env pkg
         loadFrameworks interp platform pkg
         -- See Note [Crash early load_dyn and locateLib]
         -- Crash early if can't load any of `known_dlls`
-        mapM_ (load_dyn interp hsc_env True) known_dlls
+        mapM_ (load_dyn interp hsc_env True) known_extra_dlls
+        loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
         -- For remaining `dlls` crash early only when there is surely
         -- no package's DLL around ... (not is_dyn)
         mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+#else
+        let loaded_dlls = []
 #endif
         -- After loading all the DLLs, we can load the static objects.
         -- Ordering isn't important here, because we do one final link
@@ -1168,7 +1175,7 @@ loadPackage interp hsc_env pkg
         if succeeded ok
            then do
              maybePutStrLn logger "done."
-             return (hs_classifieds, extra_classifieds)
+             return (hs_classifieds, extra_classifieds, loaded_dlls)
            else let errmsg = text "unable to load unit `"
                              <> pprUnitInfoForUser pkg <> text "'"
                  in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
@@ -1221,19 +1228,20 @@ restriction very easily.
 -- can be passed directly to loadDLL.  They are either fully-qualified
 -- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so").  In the latter case,
 -- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO ()
+load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
 load_dyn interp hsc_env crash_early dll = do
   r <- loadDLL interp dll
   case r of
-    Nothing  -> return ()
-    Just err ->
+    Right loaded_dll -> pure (Just loaded_dll)
+    Left err ->
       if crash_early
         then cmdLineErrorIO err
-        else
+        else do
           when (diag_wopt Opt_WarnMissedExtraSharedLib diag_opts)
             $ logMsg logger
                 (mkMCDiagnostic diag_opts (WarningWithFlag Opt_WarnMissedExtraSharedLib) Nothing)
                   noSrcSpan $ withPprStyle defaultUserStyle (note err)
+          pure Nothing
   where
     diag_opts = initDiagOpts (hsc_dflags hsc_env)
     logger = hsc_logger hsc_env


=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -172,6 +172,6 @@ loadFramework interp extraPaths rootname
      findLoadDLL (p:ps) errs =
        do { dll <- loadDLL interp (p  fwk_file)
           ; case dll of
-              Nothing  -> return Nothing
-              Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
+              Right _  -> return Nothing
+              Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
           }


=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -40,7 +40,8 @@ import GHC.Prelude
 import GHC.Unit                ( UnitId, Module )
 import GHC.ByteCode.Types      ( ItblEnv, AddrEnv, CompiledByteCode )
 import GHC.Fingerprint.Type    ( Fingerprint )
-import GHCi.RemoteTypes        ( ForeignHValue )
+import GHCi.RemoteTypes        ( ForeignHValue, RemotePtr )
+import GHCi.Message            ( LoadedDLL )
 
 import GHC.Types.Var           ( Id )
 import GHC.Types.Name.Env      ( NameEnv, emptyNameEnv, extendNameEnvList, filterNameEnv )
@@ -75,6 +76,53 @@ initialised.
 
 The LinkerEnv maps Names to actual closures (for interpreted code only), for
 use during linking.
+
+Note [Looking up symbols in the relevant objects]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In #23415, we determined that a lot of time (>10s, or even up to >35s!) was
+being spent on dynamically loading symbols before actually interpreting code
+when `:main` was run in GHCi. The root cause was that for each symbol we wanted
+to lookup, we would traverse the list of loaded objects and try find the symbol
+in each of them with dlsym (i.e. looking up a symbol was, worst case, linear in
+the amount of loaded objects).
+
+To drastically improve load time (from +-38 seconds down to +-2s), we now:
+
+1. For every of the native objects loaded for a given unit, store the handles returned by `dlopen`.
+  - In `pkgs_loaded` of the `LoaderState`, which maps `UnitId`s to
+    `LoadedPkgInfo`s, where the handles live in its field `loaded_pkg_hs_dlls`.
+
+2. When looking up a Name (e.g. `lookupHsSymbol`), find that name's `UnitId` in
+    the `pkgs_loaded` mapping,
+
+3. And only look for the symbol (with `dlsym`) on the /handles relevant to that
+    unit/, rather than in every loaded object.
+
+Note [Symbols may not be found in pkgs_loaded]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Currently the `pkgs_loaded` mapping only contains the dynamic objects
+associated with loaded units. Symbols defined in a static object (e.g. from a
+statically-linked Haskell library) are found via the generic `lookupSymbol`
+function call by `lookupHsSymbol` when the symbol is not found in any of the
+dynamic objects of `pkgs_loaded`.
+
+The rationale here is two-fold:
+
+ * we have only observed major link-time issues in dynamic linking; lookups in
+ the RTS linker's static symbol table seem to be fast enough
+
+ * allowing symbol lookups restricted to a single ObjectCode would require the
+ maintenance of a symbol table per `ObjectCode`, which would introduce time and
+ space overhead
+
+This fallback is further needed because we don't look in the haskell objects
+loaded for the home units (see the call to `loadModuleLinkables` in
+`loadDependencies`, as opposed to the call to `loadPackages'` in the same
+function which updates `pkgs_loaded`). We should ultimately keep track of the
+objects loaded (probably in `objs_loaded`, for which `LinkableSet` is a bit
+unsatisfactory, see a suggestion in 51c5c4eb1f2a33e4dc88e6a37b7b7c135234ce9b)
+and be able to lookup symbols specifically in them too (similarly to
+`lookupSymbolInDLL`).
 -}
 
 newtype Loader = Loader { loader_state :: MVar (Maybe LoaderState) }
@@ -146,11 +194,13 @@ data LoadedPkgInfo
   { loaded_pkg_uid         :: !UnitId
   , loaded_pkg_hs_objs     :: ![LibrarySpec]
   , loaded_pkg_non_hs_objs :: ![LibrarySpec]
+  , loaded_pkg_hs_dlls     :: ![RemotePtr LoadedDLL]
+    -- ^ See Note [Looking up symbols in the relevant objects]
   , loaded_pkg_trans_deps  :: UniqDSet UnitId
   }
 
 instance Outputable LoadedPkgInfo where
-  ppr (LoadedPkgInfo uid hs_objs non_hs_objs trans_deps) =
+  ppr (LoadedPkgInfo uid hs_objs non_hs_objs _ trans_deps) =
     vcat [ppr uid
          , ppr hs_objs
          , ppr non_hs_objs
@@ -159,10 +209,10 @@ instance Outputable LoadedPkgInfo where
 
 -- | Information we can use to dynamically link modules into the compiler
 data Linkable = LM {
-  linkableTime     :: !UTCTime,          -- ^ Time at which this linkable was built
+  linkableTime     :: !UTCTime,         -- ^ Time at which this linkable was built
                                         -- (i.e. when the bytecodes were produced,
                                         --       or the mod date on the files)
-  linkableModule   :: !Module,           -- ^ The linkable module itself
+  linkableModule   :: !Module,          -- ^ The linkable module itself
   linkableUnlinked :: [Unlinked]
     -- ^ Those files and chunks of code we have yet to link.
     --


=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -37,6 +37,7 @@ module GHC.Runtime.Interpreter
   -- * The object-code linker
   , initObjLinker
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , loadDLL
   , loadArchive
@@ -478,6 +479,13 @@ lookupSymbol interp str = case interpInstance interp of
 
     ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str)
 
+lookupSymbolInDLL :: Interp -> RemotePtr LoadedDLL -> FastString -> IO (Maybe (Ptr ()))
+lookupSymbolInDLL interp _dll str = case interpInstance interp of
+#if defined(HAVE_INTERNAL_INTERPRETER)
+  InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL _dll (unpackFS str))
+#endif
+  ExternalInterp _ -> panic "lookupSymbolInDLL: not implemented for external interpreter" -- FIXME
+
 lookupClosure :: Interp -> String -> IO (Maybe HValueRef)
 lookupClosure interp str =
   interpCmd interp (LookupClosure str)
@@ -496,12 +504,7 @@ purgeLookupSymbolCache interp = case interpInstance interp of
 -- an absolute pathname to the file, or a relative filename
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
---
--- Returns:
---
--- Nothing      => success
--- Just err_msg => failure
-loadDLL :: Interp -> String -> IO (Maybe String)
+loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
 loadDLL interp str = interpCmd interp (LoadDLL str)
 
 loadArchive :: Interp -> String -> IO ()


=====================================
hadrian/bootstrap/generate_bootstrap_plans
=====================================
@@ -23,6 +23,11 @@ run_all() {
     run "9_4_4"
     run "9_6_1"
     run "9_6_2"
+    run "9_6_3"
+    run "9_6_4"
+    run "9_6_5"
+    run "9_8_1"
+    run "9_8_2"
 }
 
 if (( $# == 0 )); then


=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -21,6 +21,7 @@ module GHCi.Message
   , QState(..)
   , getMessage, putMessage, getTHMessage, putTHMessage
   , Pipe(..), remoteCall, remoteTHCall, readPipe, writePipe
+  , LoadedDLL
   ) where
 
 import Prelude -- See note [Why do we import Prelude here?]
@@ -69,8 +70,9 @@ data Message a where
   -- These all invoke the corresponding functions in the RTS Linker API.
   InitLinker :: Message ()
   LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
+  LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
   LookupClosure :: String -> Message (Maybe HValueRef)
-  LoadDLL :: String -> Message (Maybe String)
+  LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
   LoadArchive :: String -> Message () -- error?
   LoadObj :: String -> Message () -- error?
   UnloadObj :: String -> Message () -- error?
@@ -394,6 +396,9 @@ data EvalResult a
 
 instance Binary a => Binary (EvalResult a)
 
+-- | A dummy type that tags pointers returned by 'LoadDLL'.
+data LoadedDLL
+
 -- SomeException can't be serialized because it contains dynamic
 -- types.  However, we do very limited things with the exceptions that
 -- are thrown by interpreted computations:
@@ -521,6 +526,7 @@ getMessage = do
       36 -> Msg <$> (Seq <$> get)
       37 -> Msg <$> return RtsRevertCAFs
       38 -> Msg <$> (ResumeSeq <$> get)
+      40 -> Msg <$> (LookupSymbolInDLL <$> get <*> get)
       _  -> error $ "Unknown Message code " ++ (show b)
 
 putMessage :: Message a -> Put
@@ -564,6 +570,7 @@ putMessage m = case m of
   Seq a                       -> putWord8 36 >> put a
   RtsRevertCAFs               -> putWord8 37
   ResumeSeq a                 -> putWord8 38 >> put a
+  LookupSymbolInDLL dll str   -> putWord8 40 >> put dll >> put str
 
 -- -----------------------------------------------------------------------------
 -- Reading/writing messages


=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -18,6 +18,7 @@ module GHCi.ObjLink
   , unloadObj
   , purgeObj
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , resolveObjs
   , addLibrarySearchPath
@@ -27,18 +28,17 @@ module GHCi.ObjLink
 
 import Prelude -- See note [Why do we import Prelude here?]
 import GHCi.RemoteTypes
+import GHCi.Message (LoadedDLL)
 import Control.Exception (throwIO, ErrorCall(..))
 import Control.Monad    ( when )
 import Foreign.C
-import Foreign.Marshal.Alloc ( free )
-import Foreign          ( nullPtr )
+import Foreign.Marshal.Alloc ( alloca, free )
+import Foreign          ( nullPtr, peek )
 import GHC.Exts
 import System.Posix.Internals ( CFilePath, withFilePath, peekFilePath )
 import System.FilePath  ( dropExtension, normalise )
 
 
-
-
 -- ---------------------------------------------------------------------------
 -- RTS Linker Interface
 -- ---------------------------------------------------------------------------
@@ -70,6 +70,15 @@ lookupSymbol str_in = do
         then return Nothing
         else return (Just addr)
 
+lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
+lookupSymbolInDLL dll str_in = do
+   let str = prefixUnderscore str_in
+   withCAString str $ \c_str -> do
+     addr <- c_lookupSymbolInDLL dll c_str
+     if addr == nullPtr
+       then return Nothing
+       else return (Just addr)
+
 lookupClosure :: String -> IO (Maybe HValueRef)
 lookupClosure str = do
   m <- lookupSymbol str
@@ -89,7 +98,7 @@ prefixUnderscore
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
 --
-loadDLL :: String -> IO (Maybe String)
+loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
 -- Nothing      => success
 -- Just err_msg => failure
 loadDLL str0 = do
@@ -101,12 +110,16 @@ loadDLL str0 = do
      str | isWindowsHost = dropExtension str0
          | otherwise     = str0
   --
-  maybe_errmsg <- withFilePath (normalise str) $ \dll -> c_addDLL dll
-  if maybe_errmsg == nullPtr
-        then return Nothing
-        else do str <- peekCString maybe_errmsg
-                free maybe_errmsg
-                return (Just str)
+  (maybe_handle, maybe_errmsg) <- withFilePath (normalise str) $ \dll ->
+    alloca $ \errmsg_ptr -> (,)
+      <$> c_addDLL dll errmsg_ptr
+      <*> peek errmsg_ptr
+
+  if maybe_handle == nullPtr
+    then do str <- peekCString maybe_errmsg
+            free maybe_errmsg
+            return (Left str)
+    else return (Right maybe_handle)
 
 loadArchive :: String -> IO ()
 loadArchive str = do
@@ -163,7 +176,8 @@ resolveObjs = do
 -- Foreign declarations to RTS entry points which does the real work;
 -- ---------------------------------------------------------------------------
 
-foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> IO CString
+foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL)
+foreign import ccall unsafe "lookupSymbolInDLL"       c_lookupSymbolInDLL       :: Ptr LoadedDLL -> CString -> IO (Ptr a)
 foreign import ccall unsafe "initLinker_"             c_initLinker_             :: CInt -> IO ()
 foreign import ccall unsafe "lookupSymbol"            c_lookupSymbol            :: CString -> IO (Ptr a)
 foreign import ccall unsafe "loadArchive"             c_loadArchive             :: CFilePath -> IO Int


=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -68,7 +68,7 @@ run m = case m of
   LookupClosure str           -> lookupJSClosure str
 #else
   InitLinker -> initObjLinker RetainCAFs
-  LoadDLL str -> loadDLL str
+  LoadDLL str -> fmap toRemotePtr <$> loadDLL str
   LoadArchive str -> loadArchive str
   LoadObj str -> loadObj str
   UnloadObj str -> unloadObj str
@@ -83,6 +83,8 @@ run m = case m of
 #endif
   RtsRevertCAFs -> rts_revertCAFs
   LookupSymbol str -> fmap toRemotePtr <$> lookupSymbol str
+  LookupSymbolInDLL dll str ->
+    fmap toRemotePtr <$> lookupSymbolInDLL (fromRemotePtr dll) str
   FreeHValueRefs rs -> mapM_ freeRemoteRef rs
   AddSptEntry fpr r -> localRef r >>= sptAddEntry fpr
   EvalStmt opts r -> evalStmt opts r


=====================================
rts/Linker.c
=====================================
@@ -578,13 +578,11 @@ typedef
 /* A list thereof. */
 static OpenedSO* openedSOs = NULL;
 
-static const char *
-internal_dlopen(const char *dll_name)
+static void *
+internal_dlopen(const char *dll_name, const char **errmsg_ptr)
 {
    OpenedSO* o_so;
    void *hdl;
-   const char *errmsg;
-   char *errmsg_copy;
 
    // omitted: RTLD_NOW
    // see http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html
@@ -619,14 +617,13 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&ccs_mutex);
 #endif
 
-   errmsg = NULL;
    if (hdl == NULL) {
       /* dlopen failed; return a ptr to the error msg. */
-      errmsg = dlerror();
+      char *errmsg = dlerror();
       if (errmsg == NULL) errmsg = "addDLL: unknown error";
-      errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
+      char *errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
       strcpy(errmsg_copy, errmsg);
-      errmsg = errmsg_copy;
+      *errmsg_ptr = errmsg_copy;
    } else {
       o_so = stgMallocBytes(sizeof(OpenedSO), "addDLL");
       o_so->handle = hdl;
@@ -637,7 +634,7 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&dl_mutex);
    //--------------- End critical section -------------------
 
-   return errmsg;
+   return hdl;
 }
 
 /*
@@ -725,16 +722,29 @@ internal_dlsym(const char *symbol) {
     // we failed to find the symbol
     return NULL;
 }
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name)
+{
+#if defined(OBJFORMAT_MACHO)
+    CHECK(symbol_name[0] == '_');
+    symbol_name = symbol_name+1;
+#endif
+
+    ACQUIRE_LOCK(&dl_mutex); // dlsym alters dlerror
+    void *result = dlsym(handle, symbol_name);
+    RELEASE_LOCK(&dl_mutex);
+    return result;
+}
 #  endif
 
-const char *
-addDLL( pathchar *dll_name )
+void *addDLL(pathchar* dll_name, const char **errmsg_ptr)
 {
 #  if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
    /* ------------------- ELF DLL loader ------------------- */
 
 #define NMATCH 5
    regmatch_t match[NMATCH];
+   void *handle;
    const char *errmsg;
    FILE* fp;
    size_t match_length;
@@ -743,10 +753,10 @@ addDLL( pathchar *dll_name )
    int result;
 
    IF_DEBUG(linker, debugBelch("addDLL: dll_name = '%s'\n", dll_name));
-   errmsg = internal_dlopen(dll_name);
+   handle = internal_dlopen(dll_name, &errmsg);
 
-   if (errmsg == NULL) {
-      return NULL;
+   if (handle != NULL) {
+      return handle;
    }
 
    // GHC #2615
@@ -775,7 +785,8 @@ addDLL( pathchar *dll_name )
       line[match_length] = '\0'; // make sure string is null-terminated
       IF_DEBUG(linker, debugBelch("file name = '%s'\n", line));
       if ((fp = __rts_fopen(line, "r")) == NULL) {
-         return errmsg; // return original error if open fails
+         *errmsg_ptr = errmsg; // return original error if open fails
+         return NULL;
       }
       // try to find a GROUP or INPUT ( ... ) command
       while (fgets(line, MAXLINE, fp) != NULL) {
@@ -785,7 +796,7 @@ addDLL( pathchar *dll_name )
             IF_DEBUG(linker, debugBelch("match%s\n",""));
             line[match[2].rm_eo] = '\0';
             stgFree((void*)errmsg); // Free old message before creating new one
-            errmsg = internal_dlopen(line+match[2].rm_so);
+            handle = internal_dlopen(line+match[2].rm_so, errmsg_ptr);
             break;
          }
          // if control reaches here, no GROUP or INPUT ( ... ) directive
@@ -794,9 +805,10 @@ addDLL( pathchar *dll_name )
       }
       fclose(fp);
    }
-   return errmsg;
+   return handle;
 
 #  elif defined(OBJFORMAT_PEi386)
+   // FIXME
    return addDLL_PEi386(dll_name, NULL);
 
 #  else


=====================================
rts/RtsSymbols.c
=====================================
@@ -618,6 +618,7 @@ extern char **environ;
       SymI_HasProto(purgeObj)                                           \
       SymI_HasProto(insertSymbol)                                       \
       SymI_HasProto(lookupSymbol)                                       \
+      SymI_HasProto(lookupSymbolInDLL)                                  \
       SymI_HasDataProto(stg_makeStablePtrzh)                                \
       SymI_HasDataProto(stg_mkApUpd0zh)                                     \
       SymI_HasDataProto(stg_labelThreadzh)                                  \


=====================================
rts/include/rts/Linker.h
=====================================
@@ -91,7 +91,9 @@ void *loadNativeObj( pathchar *path, char **errmsg );
 HsInt unloadNativeObj( void *handle );
 
 /* load a dynamic library */
-const char *addDLL( pathchar* dll_name );
+void *addDLL(pathchar* dll_name, const char **errmsg);
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name);
 
 /* add a path to the library search path */
 HsPtr addLibrarySearchPath(pathchar* dll_path);


=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -6,5 +6,5 @@ main = do
   initObjLinker RetainCAFs
   result <- loadDLL library_name
   case result of
-    Nothing -> putStrLn (library_name ++ " loaded successfully")
-    Just x  -> putStrLn ("error: " ++ x)
+    Right _ -> putStrLn (library_name ++ " loaded successfully")
+    Left x  -> putStrLn ("error: " ++ x)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4973098ded1679d76b4f3766240a75a116a57bf4...8362bd5cb0bf523312df3d6eefb223232a34d6bd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4973098ded1679d76b4f3766240a75a116a57bf4...8362bd5cb0bf523312df3d6eefb223232a34d6bd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 13:21:09 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 09:21:09 -0400
Subject: [Git][ghc/ghc][wip/ttg/lits] Implemented review comments for HsLit
 changes
Message-ID: <67068344f3ffd_26d7fa9ddc1c1332a5@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/lits at Glasgow Haskell Compiler / GHC


Commits:
460d9a83 by Hassan Al-Awwadi at 2024-10-09T15:20:21+02:00
Implemented review comments for HsLit changes

fused the various `convertLit`s together.
moved `lift` into the branches like I did `dsLit`

- - - - -


6 changed files:

- compiler/GHC/Hs/Lit.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs


Changes:

=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -173,65 +173,25 @@ hsLitNeedsParens p = go
 
 
 -- | Convert a literal from one index type to another
-convertLitPsRn :: HsLit GhcPs -> HsLit GhcRn
-convertLitPsRn (HsChar a x)       = HsChar a x
-convertLitPsRn (HsCharPrim a x)   = HsCharPrim a x
-convertLitPsRn (HsString a x)     = HsString a x
-convertLitPsRn (HsMultilineString a x) = HsMultilineString a x
-convertLitPsRn (HsStringPrim a x) = HsStringPrim a x
-convertLitPsRn (HsInt a x)        = HsInt a x
-convertLitPsRn (HsIntPrim a x)    = HsIntPrim a x
-convertLitPsRn (HsWordPrim a x)   = HsWordPrim a x
-convertLitPsRn (HsInt8Prim a x)   = HsInt8Prim a x
-convertLitPsRn (HsInt16Prim a x)  = HsInt16Prim a x
-convertLitPsRn (HsInt32Prim a x)  = HsInt32Prim a x
-convertLitPsRn (HsInt64Prim a x)  = HsInt64Prim a x
-convertLitPsRn (HsWord8Prim a x)  = HsWord8Prim a x
-convertLitPsRn (HsWord16Prim a x) = HsWord16Prim a x
-convertLitPsRn (HsWord32Prim a x) = HsWord32Prim a x
-convertLitPsRn (HsWord64Prim a x) = HsWord64Prim a x
-convertLitPsRn (HsFloatPrim a x)  = HsFloatPrim a x
-convertLitPsRn (HsDoublePrim a x) = HsDoublePrim a x
-
-convertLitPsTc :: HsLit GhcPs -> HsLit GhcTc
-convertLitPsTc (HsChar a x)       = HsChar a x
-convertLitPsTc (HsCharPrim a x)   = HsCharPrim a x
-convertLitPsTc (HsString a x)     = HsString a x
-convertLitPsTc (HsMultilineString a x) = HsMultilineString a x
-convertLitPsTc (HsStringPrim a x) = HsStringPrim a x
-convertLitPsTc (HsInt a x)        = HsInt a x
-convertLitPsTc (HsIntPrim a x)    = HsIntPrim a x
-convertLitPsTc (HsWordPrim a x)   = HsWordPrim a x
-convertLitPsTc (HsInt8Prim a x)   = HsInt8Prim a x
-convertLitPsTc (HsInt16Prim a x)  = HsInt16Prim a x
-convertLitPsTc (HsInt32Prim a x)  = HsInt32Prim a x
-convertLitPsTc (HsInt64Prim a x)  = HsInt64Prim a x
-convertLitPsTc (HsWord8Prim a x)  = HsWord8Prim a x
-convertLitPsTc (HsWord16Prim a x) = HsWord16Prim a x
-convertLitPsTc (HsWord32Prim a x) = HsWord32Prim a x
-convertLitPsTc (HsWord64Prim a x) = HsWord64Prim a x
-convertLitPsTc (HsFloatPrim a x)  = HsFloatPrim a x
-convertLitPsTc (HsDoublePrim a x) = HsDoublePrim a x
-
-convertLitRnTc :: HsLit GhcRn -> HsLit GhcTc
-convertLitRnTc (HsChar a x)       = HsChar a x
-convertLitRnTc (HsCharPrim a x)   = HsCharPrim a x
-convertLitRnTc (HsString a x)     = HsString a x
-convertLitRnTc (HsMultilineString a x) = HsMultilineString a x
-convertLitRnTc (HsStringPrim a x) = HsStringPrim a x
-convertLitRnTc (HsInt a x)        = HsInt a x
-convertLitRnTc (HsIntPrim a x)    = HsIntPrim a x
-convertLitRnTc (HsWordPrim a x)   = HsWordPrim a x
-convertLitRnTc (HsInt8Prim a x)   = HsInt8Prim a x
-convertLitRnTc (HsInt16Prim a x)  = HsInt16Prim a x
-convertLitRnTc (HsInt32Prim a x)  = HsInt32Prim a x
-convertLitRnTc (HsInt64Prim a x)  = HsInt64Prim a x
-convertLitRnTc (HsWord8Prim a x)  = HsWord8Prim a x
-convertLitRnTc (HsWord16Prim a x) = HsWord16Prim a x
-convertLitRnTc (HsWord32Prim a x) = HsWord32Prim a x
-convertLitRnTc (HsWord64Prim a x) = HsWord64Prim a x
-convertLitRnTc (HsFloatPrim a x)  = HsFloatPrim a x
-convertLitRnTc (HsDoublePrim a x) = HsDoublePrim a x
+convertLit :: XXLit (GhcPass p)~DataConCantHappen => HsLit (GhcPass p) -> HsLit (GhcPass p')
+convertLit (HsChar a x)       = HsChar a x
+convertLit (HsCharPrim a x)   = HsCharPrim a x
+convertLit (HsString a x)     = HsString a x
+convertLit (HsMultilineString a x) = HsMultilineString a x
+convertLit (HsStringPrim a x) = HsStringPrim a x
+convertLit (HsInt a x)        = HsInt a x
+convertLit (HsIntPrim a x)    = HsIntPrim a x
+convertLit (HsWordPrim a x)   = HsWordPrim a x
+convertLit (HsInt8Prim a x)   = HsInt8Prim a x
+convertLit (HsInt16Prim a x)  = HsInt16Prim a x
+convertLit (HsInt32Prim a x)  = HsInt32Prim a x
+convertLit (HsInt64Prim a x)  = HsInt64Prim a x
+convertLit (HsWord8Prim a x)  = HsWord8Prim a x
+convertLit (HsWord16Prim a x) = HsWord16Prim a x
+convertLit (HsWord32Prim a x) = HsWord32Prim a x
+convertLit (HsWord64Prim a x) = HsWord64Prim a x
+convertLit (HsFloatPrim a x)  = HsFloatPrim a x
+convertLit (HsDoublePrim a x) = HsDoublePrim a x
 
 {-
 Note [ol_rebindable]


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -3010,14 +3010,14 @@ repLiteral (HsStringPrim _ bs)
        rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr]
 repLiteral lit
   = do lit' <- case lit of
-                   HsIntPrim _ i    -> dsLit <$> mk_integer i
-                   HsWordPrim _ w   -> dsLit <$> mk_integer w
-                   HsInt _ i        -> dsLit <$> mk_integer (il_value i)
-                   HsFloatPrim _ r  -> dsLit <$> mk_rational r
-                   HsDoublePrim _ r -> dsLit <$> mk_rational r
-                   HsCharPrim _ c   -> dsLit <$> mk_char c
-                   _                -> return $ dsLit lit
-       lit_expr <- lift lit'
+                   HsIntPrim _ i    -> lift . dsLit <$> mk_integer i
+                   HsWordPrim _ w   -> lift . dsLit <$> mk_integer w
+                   HsInt _ i        -> lift . dsLit <$> mk_integer (il_value i)
+                   HsFloatPrim _ r  -> lift . dsLit <$> mk_rational r
+                   HsDoublePrim _ r -> lift . dsLit <$> mk_rational r
+                   HsCharPrim _ c   -> lift . dsLit <$> mk_char c
+                   _                -> return . lift . dsLit $ lit
+       lit_expr <- lit'
        case mb_lit_name of
           Just lit_name -> rep2_nw lit_name [lit_expr]
           Nothing -> notHandled (ThExoticLiteral lit)
@@ -3040,10 +3040,11 @@ mk_integer  i = return $ XLit $ HsInteger NoSourceText i integerTy
 mk_rational :: FractionalLit -> MetaM (HsLit GhcTc)
 mk_rational r = do rat_ty <- lookupType rationalTyConName
                    return $ XLit $ HsRat r rat_ty
-mk_string :: FastString -> MetaM (HsLit GhcTc)
+
+mk_string :: FastString -> MetaM (HsLit GhcRn)
 mk_string s = return $ HsString NoSourceText s
 
-mk_char :: Char -> MetaM (HsLit GhcTc)
+mk_char :: Char -> MetaM (HsLit GhcRn)
 mk_char c = return $ HsChar NoSourceText c
 
 repOverloadedLiteral :: HsOverLit GhcRn -> MetaM (Core TH.Lit)
@@ -3056,10 +3057,10 @@ repOverloadedLiteral (OverLit { ol_val = val})
 repOverLiteralVal ::  OverLitVal -> MetaM (Core TH.Lit)
 repOverLiteralVal lit = do
   lit' <- case lit of
-        (HsIntegral i)   -> mk_integer  (il_value i)
-        (HsFractional f) -> mk_rational f
-        (HsIsString _ s) -> mk_string   s
-  lit_expr <- lift $ dsLit  lit'
+        (HsIntegral i)   -> lift . dsLit <$> mk_integer  (il_value i)
+        (HsFractional f) -> lift . dsLit <$> mk_rational f
+        (HsIsString _ s) -> lift . dsLit <$> mk_string   s
+  lit_expr <- lit'
 
   let lit_name = case lit of
         (HsIntegral _  ) -> integerLName


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -374,7 +374,7 @@ rnExpr (HsLit x lit) | Just (src, s) <- stringLike lit
             rnExpr (HsOverLit x (mkHsIsString src s))
          else do {
             ; rnLit lit
-            ; return (HsLit x (convertLitPsRn lit), emptyFVs) } }
+            ; return (HsLit x (convertLit lit), emptyFVs) } }
   where
     stringLike = \case
       HsString src s -> Just (src, s)
@@ -383,7 +383,7 @@ rnExpr (HsLit x lit) | Just (src, s) <- stringLike lit
 
 rnExpr (HsLit x lit)
   = do { rnLit lit
-       ; return (HsLit x(convertLitPsRn lit), emptyFVs) }
+       ; return (HsLit x (convertLit lit), emptyFVs) }
 
 rnExpr (HsOverLit x lit)
   = do { ((lit', mb_neg), fvs) <- rnOverLit lit -- See Note [Negative zero]


=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -572,7 +572,7 @@ rnPatAndThen mk (LitPat x lit)
          else normal_lit }
   | otherwise = normal_lit
   where
-    normal_lit = do { liftCps (rnLit lit); return (LitPat x (convertLitPsRn lit)) }
+    normal_lit = do { liftCps (rnLit lit); return (LitPat x (convertLit lit)) }
 
 rnPatAndThen _ (NPat x (L l lit) mb_neg _eq)
   = do { (lit', mb_neg') <- liftCpsFV $ rnOverLit lit


=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -317,7 +317,7 @@ tcExpr (HsUnboundVar _ occ) res_ty
 
 tcExpr e@(HsLit x lit) res_ty
   = do { let lit_ty = hsLitType lit
-       ; tcWrapResult e (HsLit x (convertLitRnTc lit)) lit_ty res_ty }
+       ; tcWrapResult e (HsLit x (convertLit lit)) lit_ty res_ty }
 
 tcExpr (HsPar x expr) res_ty
   = do { expr' <- tcMonoExprNC expr res_ty


=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -829,7 +829,7 @@ Fortunately that's what matchActualFunTy returns anyway.
         ; wrap   <- tc_sub_type penv (scaledThing pat_ty) lit_ty
         ; res    <- thing_inside
         ; pat_ty <- readExpType (scaledThing pat_ty)
-        ; return ( mkHsWrapPat wrap (LitPat x (convertLitRnTc simple_lit)) pat_ty
+        ; return ( mkHsWrapPat wrap (LitPat x (convertLit simple_lit)) pat_ty
                  , res) }
 
 ------------------------



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/460d9a83cdb06ac3cbc06ea171b024e3c87d9a28

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 14:16:16 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 09 Oct 2024 10:16:16 -0400
Subject: [Git][ghc/ghc][wip/T25281] 5 commits: ci: RISCV64 cross-compile
 testing
Message-ID: <67069030778fe_1943b82500947794@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
fbbe8f28 by Sebastian Graf at 2024-10-09T15:12:39+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
f229d1fc by Simon Peyton Jones at 2024-10-09T15:12:40+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
ee8bcb06 by Simon Peyton Jones at 2024-10-09T15:13:16+01:00
Missing record selectors in GHC.Internal.IO.Windows.Handle

This look genuinely wrong: see #25362.  These two fixes need auditing;
but they are better than the status quo.

Actually Ben has fixed this in !13394, so this patch will be
obseleted once !13394 lands.

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b64b0ef57b6f5c016a0be948390c2e09b03fa62d...ee8bcb0657e8bf1d91664083a3cd9ff2b611a58a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b64b0ef57b6f5c016a0be948390c2e09b03fa62d...ee8bcb0657e8bf1d91664083a3cd9ff2b611a58a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 14:36:33 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 10:36:33 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/doc-unpack
Message-ID: <670694f1be0cb_1943b83e81cc860fc@gitlab.mail>



Ben Gamari pushed new branch wip/doc-unpack at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/doc-unpack
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 14:59:09 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 10:59:09 -0400
Subject: [Git][ghc/ghc][wip/doc-unpack] users-guide: Document field coalescence
Message-ID: <67069a3d831d0_1943b86146809213@gitlab.mail>



Ben Gamari pushed to branch wip/doc-unpack at Glasgow Haskell Compiler / GHC


Commits:
b380ddad by Ben Gamari at 2024-10-09T10:59:02-04:00
users-guide: Document field coalescence

- - - - -


1 changed file:

- docs/users_guide/exts/pragmas.rst


Changes:

=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -959,6 +959,35 @@ effect of adding ``{-# UNPACK #-}`` to every strict constructor field which is
 of a single-constructor data type. Sum types won't be unpacked automatically
 by this though, only with the explicit pragma.
 
+Also note that GHC will coalesce adjacent sub-word size fields into
+words. For instance, consider ::
+
+    data T = T {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
+
+As ``Word16`` is represented by the unlifted 32-bit ``Word32#`` type, the ``T``
+constructor will be represent its two ``Word32`` fields using only a single
+64-bit word.
+
+Note that during coalescence padding will be inserted to ensure that each field
+remains naturally aligned. For instance, on a 32-bit platform ::
+
+    data T = T {-# UNPACK #-} !Word16
+               {-# UNPACK #-} !Word8
+               {-# UNPACK #-} !Word16
+
+will require two words since padding is necessary after the ``Word8`` to
+ensure that the subsequent ``Word32`` is naturally aligned:
+
+.. code-block:: none
+
+     ┌───────────────────────────────────┐
+     │ Header                            │
+     ├─────────────────┬────────┬────────┤
+     │ Word16          │ Word8  │ padding│
+     ├─────────────────┴────────┴────────┤
+     │ Word16                            │
+     └───────────────────────────────────┘
+
 .. [1]
    In fact, :pragma:`UNPACK` has no effect without :ghc-flag:`-O`, for technical
    reasons (see :ghc-ticket:`5252`).



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 15:11:50 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 09 Oct 2024 11:11:50 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] Bump Cabal submodule to 3.14
Message-ID: <67069d3636b7_1943b863b834102726@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
9c05cd1e by Zubin Duggal at 2024-10-09T20:41:37+05:30
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -


3 changed files:

- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c05cd1e1e9daffb708285fcc03b0ffd13f5cbb0

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 15:24:13 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 11:24:13 -0400
Subject: [Git][ghc/ghc][wip/bump-process] Bump process submodule to v1.6.25.0
Message-ID: <6706a01d9ce3c_1943b8aab2ac1178b1@gitlab.mail>



Ben Gamari pushed to branch wip/bump-process at Glasgow Haskell Compiler / GHC


Commits:
55e47a32 by Ben Gamari at 2024-10-09T11:24:06-04:00
Bump process submodule to v1.6.25.0

- - - - -


5 changed files:

- libraries/process
- testsuite/tests/process/process004.hs
- testsuite/tests/process/process004.stdout
- testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
- testsuite/tests/process/process004.stdout-mingw32


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b
+Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e


=====================================
testsuite/tests/process/process004.hs
=====================================
@@ -4,8 +4,13 @@ import System.IO.Error
 import System.Process
 
 main :: IO ()
-main = do test1 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
-          test2 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
+main = do
+  -- N.B. Only show the error type since the exact error text
+  -- may depend upon precise system call which @process@ decided
+  -- to use.
+  let printError e = putStrLn ("Exc: " ++ show (ioeGetErrorType e))
+  test1 `catchIOError` printError
+  test2 `catchIOError` printError
 
 test1 :: IO ()
 test1 = do


=====================================
testsuite/tests/process/process004.stdout
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: chdir: invalid argument (Bad file descriptor)
-Exc: true: runProcess: chdir: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: does not exist (No such file or directory)
-Exc: true: runProcess: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-mingw32
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: invalid argument (Invalid argument)
-Exc: true: runProcess: invalid argument (Invalid argument)
+Exc: does not exist
+Exc: does not exist



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55e47a32fd43b0c794df6c137b262eb711a618c9

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 15:54:36 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 11:54:36 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] review changes for
 BooleanFormula
Message-ID: <6706a73c7d250_188b7bbc53444723@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
9f34aa08 by Hassan Al-Awwadi at 2024-10-09T17:53:19+02:00
review changes for BooleanFormula

* Removed bfExprMap, instead bfMap is fully defined inside Ghc.Data.BooleanFormula
* Cleaned up some classes for BooleanFormula
* Simplified toIfaceBooleanFormula to no longer be a higher order function
* And removed fromIfaceBooleanFormula completely

- - - - -


6 changed files:

- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/IfaceToCore.hs
- compiler/Language/Haskell/Syntax/BooleanFormula.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


Changes:

=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,4 +1,5 @@
 {-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
@@ -36,17 +37,35 @@ import Language.Haskell.Syntax.BooleanFormula
 
 type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
--- the other part of jury rigging some fake instances for booleanformula
--- using the genlocated instances of Functor and Traversable.
+-- if we had Functor/Traversable (LbooleanFormula p) we could use that
+-- as a constraint and we wouldn't need to specialize to just GhcPass p,
+-- but becuase LBooleanFormula is a type synonym such a constraint is
+-- impossible.
+
+-- BooleanFormula can't be an instance of functor because it can't lift
+-- arbitrary functions `a -> b`, only functions of type `LIdP a -> LIdP b`
+-- ditto for Traversable.
 bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
       -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
-bfMap f = bfExplMap fmap f
+bfMap f = go
+  where
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (fmap go) bfs
+    go (Or     bfs) = Or      $ map (fmap go) bfs
+    go (Parens bf ) = Parens  $ fmap go bf
 
 bfTraverse  :: Applicative f
             => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
             -> BooleanFormula (GhcPass p)
             -> f (BooleanFormula (GhcPass p'))
-bfTraverse f = bfExplTraverse traverse f
+bfTraverse f = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
+
 
 {-
 Note [Simplification of BooleanFormulas]
@@ -208,9 +227,7 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance Outputable (BooleanFormula GhcPs) where
-  ppr = pprBooleanFormulaNormal
-instance Outputable (BooleanFormula GhcRn) where
+instance OutputableBndrId p => Outputable (BooleanFormula (GhcPass p)) where
   ppr = pprBooleanFormulaNormal
 
 pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -16,7 +16,6 @@ module GHC.Iface.Decl
    , toIfaceBooleanFormula
 
    -- converting back
-   , fromIfaceBooleanFormula
    , traverseIfaceBooleanFormula
    )
 where
@@ -55,7 +54,7 @@ import GHC.Data.Maybe
 import GHC.Data.BooleanFormula
 
 import Data.List ( findIndex, mapAccumL )
-import Language.Haskell.Syntax.Extension (LIdP)
+import Language.Haskell.Syntax.Extension (IdP, LIdP)
 
 {-
 ************************************************************************
@@ -294,7 +293,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula (mkIfLclName . getOccFS . unLoc) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -343,21 +342,13 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
 
-toIfaceBooleanFormula :: (LIdP (GhcPass p) -> IfLclName) ->  BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
-toIfaceBooleanFormula f = go
+toIfaceBooleanFormula ::  NamedThing (IdP (GhcPass p)) => BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
+toIfaceBooleanFormula = go
   where
-    go (Var nm   ) = IfVar    (f nm)
-    go (And bfs  ) = IfAnd    (map (go . unLoc) bfs)
-    go (Or bfs   ) = IfOr     (map (go . unLoc) bfs)
-    go (Parens bf) = IfParens (go . unLoc $ bf)
-
-fromIfaceBooleanFormula :: (IfLclName -> LIdP (GhcPass p))  -> IfaceBooleanFormula -> BooleanFormula (GhcPass p)
-fromIfaceBooleanFormula f = go
-  where
-    go (IfVar nm    ) = Var    $ f nm
-    go (IfAnd ibfs  ) = And    $ map (noLocA . go) ibfs
-    go (IfOr ibfs   ) = Or     $ map (noLocA . go) ibfs
-    go (IfParens ibf) = Parens $ (noLocA . go) ibf
+    go (Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $ nm
+    go (And bfs  ) = IfAnd    $ map (go . unLoc) bfs
+    go (Or bfs   ) = IfOr     $ map (go . unLoc) bfs
+    go (Parens bf) = IfParens $ go . unLoc $ bf
 
 traverseIfaceBooleanFormula :: Applicative f
                             => (IfLclName -> f (LIdP (GhcPass p)))


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2043,22 +2043,9 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance HiePass p => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
-  toHie (L span form) = case hiePass @p of
-    HieRn -> concatM $ makeNode form (locA span) : case form of
-      Var a ->
-        [ toHie $ C Use a
-        ]
-      And forms ->
-        [ toHie forms
-        ]
-      Or forms ->
-        [ toHie forms
-        ]
-      Parens f ->
-        [ toHie f
-        ]
-    HieTc -> concatM $ makeNode form (locA span) : case form of
+instance (HiePass p, Data (IdGhcP p))
+  => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -299,20 +299,23 @@ mergeIfaceDecl d1 d2
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
 
-          -- specialized version of BooleanFormula's MkOr.
-          mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
-          mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+          -- same as BooleanFormula's mkOr, but specialized to IfaceBooleanFormula,
+          -- which can be taught of as being (BooleanFormula IfacePass) morally.
+          -- In practice, however, its a seperate type so it needs its own function
+          -- It makes an Or and does some super basic simplification.
+          mkIfaceOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+          mkIfaceOr = maybe (IfAnd []) (mkIfaceOr' . nub . concat) . mapM fromOr
             where
             fromOr bf = case bf of
               (IfOr xs)  -> Just xs
               (IfAnd []) -> Nothing
               _        -> Just [bf]
-            mkOr' [x] = x
-            mkOr' xs = IfOr xs
+            mkIfaceOr' [x] = x
+            mkIfaceOr' xs = IfOr xs
 
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = mkOr [bf1, bf2]
+                ifMinDef = mkIfaceOr [bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -4,8 +4,8 @@
 
 module Language.Haskell.Syntax.BooleanFormula(
   BooleanFormula(..), LBooleanFormula,
-  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr,
-  bfExplMap, bfExplTraverse) where
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr
+  ) where
 
 import Prelude hiding ( init, last )
 import Data.List ( nub )
@@ -20,31 +20,6 @@ data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFor
 -- instances
 deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
 
--- jury rigged map and traverse functions.
--- if we had Functor/Traversable (LbooleanFormula p) we could use as a constraint
--- we wouldn't neeed the first higher order argument, but because LBooleanformula
--- is a type synonym that's no can do.
-bfExplMap :: ((BooleanFormula p -> BooleanFormula p') -> LBooleanFormula p -> LBooleanFormula p')
-          -> (LIdP p -> LIdP p')
-          -> BooleanFormula p -> BooleanFormula p'
-bfExplMap lbfMap f = go
-  where
-    go (Var    a  ) = Var     $ f a
-    go (And    bfs) = And     $ map (lbfMap go) bfs
-    go (Or     bfs) = Or      $ map (lbfMap go) bfs
-    go (Parens bf ) = Parens  $ lbfMap go bf
-
-bfExplTraverse  :: Applicative f
-                => ((BooleanFormula p -> f (BooleanFormula p')) -> LBooleanFormula p -> f (LBooleanFormula p'))
-                -> (LIdP p -> f (LIdP p'))
-                -> BooleanFormula p -> f (BooleanFormula p')
-bfExplTraverse lbfTraverse f  = go
-  where
-    go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] (lbfTraverse go) bfs
-    go (Or     bfs) = Or     <$> traverse @[] (lbfTraverse go) bfs
-    go (Parens bf ) = Parens <$> lbfTraverse go bf
-
 -- smart constructors
 -- see note [Simplification of BooleanFormulas]
 mkVar :: LIdP p -> BooleanFormula p


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -19,6 +19,8 @@
 -- Portability :  portable
 module Haddock.Interface.Rename (renameInterface) where
 
+import Prelude hiding (mapM)
+
 import Control.Applicative ()
 import Control.DeepSeq (force)
 import Control.Monad hiding (mapM)
@@ -28,13 +30,13 @@ import Data.Foldable (traverse_)
 import qualified Data.Map.Strict as Map
 import qualified Data.Set as Set
 import Data.Traversable (mapM)
+
 import GHC hiding (NoLink)
 import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName)
 import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
-import Prelude hiding (mapM)
-import Language.Haskell.Syntax.BooleanFormula (bfExplTraverse)
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -771,11 +773,22 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- bfExplTraverse traverse (traverse lookupRn) s
+    s' <- bfTraverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP DocNameI))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (DocNameI))
+bfTraverse f = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do
   lname' <- renameNameL lname



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f34aa0884e755d4c6ebbb6f10e142bee245e78a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 16:28:25 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Wed, 09 Oct 2024 12:28:25 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] removed unused import
Message-ID: <6706af29e4e10_188b7b31a5c4563b1@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
3131d245 by Hassan Al-Awwadi at 2024-10-09T18:28:09+02:00
removed unused import

- - - - -


1 changed file:

- compiler/GHC/Data/BooleanFormula.hs


Changes:

=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -26,7 +26,7 @@ import GHC.Types.Unique.Set
 import GHC.Types.SrcLoc (unLoc)
 import GHC.Utils.Outputable
 import GHC.Parser.Annotation ( SrcSpanAnnL )
-import GHC.Hs.Extension (GhcPass (..), GhcPs, GhcRn, OutputableBndrId)
+import GHC.Hs.Extension (GhcPass (..), OutputableBndrId)
 import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
 import Language.Haskell.Syntax.BooleanFormula
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3131d24529ef8acb004e9a552130f18a03098b3e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 17:30:22 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 13:30:22 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25296
Message-ID: <6706bdaeeb0e3_188b7b5a66bc60663@gitlab.mail>



Ben Gamari pushed new branch wip/T25296 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25296
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 18:01:58 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 14:01:58 -0400
Subject: [Git][ghc/ghc][wip/T25362] ghc-internal: Fix incomplete matches on
 IOError
Message-ID: <6706c516dea8f_2e79881f749452098@gitlab.mail>



Ben Gamari pushed to branch wip/T25362 at Glasgow Haskell Compiler / GHC


Commits:
ac20ee9d by Ben Gamari at 2024-10-09T14:01:52-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
=====================================
@@ -77,7 +77,7 @@ import GHC.Internal.IO.Windows.Encoding (withGhcInternalToUTF16, withUTF16ToGhcI
 import GHC.Internal.IO.Windows.Paths (getDevicePath)
 import GHC.Internal.IO.Handle.Internals (debugIO)
 import GHC.Internal.IORef
-import GHC.Internal.Event.Windows (LPOVERLAPPED, withOverlappedEx, IOResult(..))
+import GHC.Internal.Event.Windows (LPOVERLAPPED, withOverlappedEx)
 import GHC.Internal.Foreign.Ptr
 import GHC.Internal.Foreign.C.Types
 import GHC.Internal.Foreign.C.Error
@@ -465,10 +465,10 @@ hwndReadNonBlocking :: Io NativeHandle -> Ptr Word8 -> Word64 -> Int
                     -> IO (Maybe Int)
 hwndReadNonBlocking hwnd ptr offset bytes
   = do mngr <- Mgr.getSystemManager
-       val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
+       Mgr.withException "hwndReadNonBlocking" $
+              withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
                                (isAsynchronous hwnd) offset (startCB ptr)
                                completionCB
-       return $ ioValue val
   where
     startCB inputBuf lpOverlapped = do
       debugIO ":: hwndReadNonBlocking"
@@ -511,10 +511,11 @@ hwndWrite hwnd ptr offset bytes
 hwndWriteNonBlocking :: Io NativeHandle -> Ptr Word8 -> Word64 -> Int -> IO Int
 hwndWriteNonBlocking hwnd ptr offset bytes
   = do mngr <- Mgr.getSystemManager
-       val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
-                               (isAsynchronous hwnd) offset (startCB ptr)
-                               completionCB
-       return $ fromIntegral $ ioValue val
+       fmap fromIntegral $
+           Mgr.withException "hwndWriteNonBlocking" $
+           withOverlappedEx mngr "hwndWriteNonBlocking" (toHANDLE hwnd)
+                            (isAsynchronous hwnd) offset (startCB ptr)
+                            completionCB
   where
     startCB :: Ptr a -> LPOVERLAPPED -> IO (Mgr.CbResult a1)
     startCB outBuf lpOverlapped = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 18:10:24 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 09 Oct 2024 14:10:24 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T24509
Message-ID: <6706c7107aab9_2e798831f52456013@gitlab.mail>



Ben Gamari pushed new branch wip/T24509 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24509
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 20:42:12 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 09 Oct 2024 16:42:12 -0400
Subject: [Git][ghc/ghc][master] Fix typo in the @since annotation of annotateIO
Message-ID: <6706eaa4d30cf_3e62d934f92c91541@gitlab.mail>



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


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/IO.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/IO.hs
=====================================
@@ -234,7 +234,7 @@ catchAny !(IO io) handler = IO $ catch# io handler'
 -- | Execute an 'IO' action, adding the given 'ExceptionContext'
 -- to any thrown synchronous exceptions.
 --
--- @since base-2.20.0.0
+-- @since base-4.20.0.0
 annotateIO :: forall e a. ExceptionAnnotation e => e -> IO a -> IO a
 annotateIO ann (IO io) = IO (catch# io handler)
   where



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55609880c3eeda2c13859c10c157d7df05496288

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 20:42:51 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 09 Oct 2024 16:42:51 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove [AddEpAnn] from (most of) HsExpr
Message-ID: <6706eacbd0ae_3e62d935bfb095063@gitlab.mail>



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


Commits:
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -


30 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 20:54:10 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 09 Oct 2024 16:54:10 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-pat] 52 commits: driver:
 fix runWorkerLimit on wasm
Message-ID: <6706ed72e4223_3e62d96359d495494@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-pat at Glasgow Haskell Compiler / GHC


Commits:
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
c0b075f6 by Alan Zimmerman at 2024-10-08T18:58:39+01:00
EPA: introduce EpAnnLam for lambda annotations

And remove `glAA` from `Parser.y`, it is the same as `glR`

- - - - -
e8ecb5de by Alan Zimmerman at 2024-10-08T18:58:39+01:00
EPA: Remove unused annotation from XOpApp

- - - - -
29ca35e5 by Alan Zimmerman at 2024-10-08T18:58:39+01:00
EPA: Use EpToken for XNPat and XNegApp

- - - - -
ec4df22c by Alan Zimmerman at 2024-10-08T18:58:39+01:00
EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

More removing [AddEpAnn] in favour of specific versions instead.

- - - - -
b8f6ba49 by Alan Zimmerman at 2024-10-08T18:58:39+01:00
EPA: Use specific annotation for MultiIf

Instead of [AddEpAnn]

- - - - -
4a9e2701 by Alan Zimmerman at 2024-10-08T18:59:38+01:00
EPA: Move annotations into FunRhs

- - - - -
49feb20f by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

- - - - -
53d0faf5 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from ArithSeq

- - - - -
51e23ba5 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from HsProc

- - - - -
4ad33ea7 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from HsStatic

- - - - -
e5359370 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from BindStmt

- - - - -
6ee0a7a6 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from TransStmt

- - - - -
1657f05f by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from HsTypedSplice

- - - - -
0b5fdf2e by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
ebf9683c by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from LazyPat

- - - - -
e34e6271 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

- - - - -
4c55ab1c by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from HsFieldBind

- - - - -
b7b71dc3 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from PatSynBind

- - - - -
72d3fdce by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from IPBind

- - - - -
05504c43 by Alan Zimmerman at 2024-10-08T18:59:41+01:00
EPA: Remove [AddEpAnn] from FixSig

- - - - -
a28a708b by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from activation rules

- - - - -
06ac81c2 by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpann] from SpecInstSig

- - - - -
4bcfc373 by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from MinimalSig

- - - - -
af2f742a by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from SCCFunSig

- - - - -
473a9014 by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from CompleteMatchSig

- - - - -
aaead9fd by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from AnnSig

As used in PatSynSig, ClassOpSig, TypeSig

- - - - -
7383e529 by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from IEThingAbs

- - - - -
4a46995d by Alan Zimmerman at 2024-10-08T18:59:42+01:00
EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

- - - - -
a3915584 by Alan Zimmerman at 2024-10-08T19:51:12+01:00
EPA: Remove [AddEpAnn] from IEModuleContents

- - - - -
7c73c371 by Alan Zimmerman at 2024-10-09T21:14:40+01:00
EPA: Remove [AddEpAnn] from HsOpTy

- - - - -
603ee523 by Alan Zimmerman at 2024-10-09T21:17:19+01:00
EPA: Remove [AddEpAnn] for various binders

- - - - -
c2356993 by Alan Zimmerman at 2024-10-09T21:53:30+01:00
EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


27 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/86fde81222b2f4dbfc0240d378cb9cba3460c68d...c2356993e32da823db815cf909b3b3fd92dfe11c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/86fde81222b2f4dbfc0240d378cb9cba3460c68d...c2356993e32da823db815cf909b3b3fd92dfe11c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 21:14:45 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 09 Oct 2024 17:14:45 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Fix typo in
 the @since annotation of annotateIO
Message-ID: <6706f24517530_3e62d980b5749702c@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
bd59c995 by Cheng Shao at 2024-10-09T17:14:20-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
7a20bca8 by Cristiano Moraes at 2024-10-09T17:14:25-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
d1174440 by Zubin Duggal at 2024-10-09T17:14:25-04:00
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -
d5761262 by sheaf at 2024-10-09T17:14:35-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
334aa722 by sheaf at 2024-10-09T17:14:35-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
9c3c9ddd by Cheng Shao at 2024-10-09T17:14:35-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- − libffi/Makefile


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83a661dffa899c5d6bd9f2e908512ef021b64d04...9c3c9ddd28376021d1f9b848155e95e8b114e670

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83a661dffa899c5d6bd9f2e908512ef021b64d04...9c3c9ddd28376021d1f9b848155e95e8b114e670
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 21:47:11 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 09 Oct 2024 17:47:11 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-pat] 20 commits: Fix typo
 in the @since annotation of annotateIO
Message-ID: <6706f9df3f558_3e62d9d43b54109734@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-pat at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
edf2a960 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from LazyPat

- - - - -
24a30c6f by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

- - - - -
4366f764 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from HsFieldBind

- - - - -
bb86b002 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from PatSynBind

- - - - -
6be25f52 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from IPBind

- - - - -
3f6a6bf3 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from FixSig

- - - - -
4fedf97f by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from activation rules

- - - - -
d56feeca by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpann] from SpecInstSig

- - - - -
14727496 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from MinimalSig

- - - - -
c8715302 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from SCCFunSig

- - - - -
721d2c30 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from CompleteMatchSig

- - - - -
d3e7bdd3 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from AnnSig

As used in PatSynSig, ClassOpSig, TypeSig

- - - - -
db7b2e82 by Alan Zimmerman at 2024-10-09T22:02:24+01:00
EPA: Remove [AddEpAnn] from IEThingAbs

- - - - -
017c2c8d by Alan Zimmerman at 2024-10-09T22:02:25+01:00
EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

- - - - -
06ec9747 by Alan Zimmerman at 2024-10-09T22:02:25+01:00
EPA: Remove [AddEpAnn] from IEModuleContents

- - - - -
b0b5700a by Alan Zimmerman at 2024-10-09T22:02:25+01:00
EPA: Remove [AddEpAnn] from HsOpTy

- - - - -
73eda997 by Alan Zimmerman at 2024-10-09T22:02:25+01:00
EPA: Remove [AddEpAnn] for various binders

- - - - -
fabc3919 by Alan Zimmerman at 2024-10-09T22:02:25+01:00
EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2356993e32da823db815cf909b3b3fd92dfe11c...fabc3919650f8d29586603e7a0ecc5289095ded1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2356993e32da823db815cf909b3b3fd92dfe11c...fabc3919650f8d29586603e7a0ecc5289095ded1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 21:50:25 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 09 Oct 2024 17:50:25 -0400
Subject: [Git][ghc/ghc][wip/T25281] 5 commits: Fix typo in the @since
 annotation of annotateIO
Message-ID: <6706faa13f8e6_3e62d9c7e37c1146d@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
3a45b51b by Sebastian Graf at 2024-10-09T22:50:03+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
602a65bc by Simon Peyton Jones at 2024-10-09T22:50:04+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
de030c0b by Simon Peyton Jones at 2024-10-09T22:50:04+01:00
Missing record selectors in GHC.Internal.IO.Windows.Handle

This look genuinely wrong: see #25362.  These two fixes need auditing;
but they are better than the status quo.

Actually Ben has fixed this in !13394, so this patch will be
obseleted once !13394 lands.

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ee8bcb0657e8bf1d91664083a3cd9ff2b611a58a...de030c0b6096a2696f863d1b07151c607ee7a4e0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ee8bcb0657e8bf1d91664083a3cd9ff2b611a58a...de030c0b6096a2696f863d1b07151c607ee7a4e0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct  9 22:42:49 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 09 Oct 2024 18:42:49 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-pat] EPA: Remove [AddEpAnn]
 from IE, Pat and some Tys
Message-ID: <670706e9cc0a5_30bcac21ff7085180@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-pat at Glasgow Haskell Compiler / GHC


Commits:
244b8c7c by Alan Zimmerman at 2024-10-09T23:40:39+01:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_compile/T20846.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/244b8c7c2d9acbd8a00e5d9d4d8f15b288f01568

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 05:06:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 10 Oct 2024 01:06:25 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: driver:
 bail out when -fllvm is passed to GHC not configured with LLVM
Message-ID: <670760d160709_30bcac105386c1381b0@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
ce36045a by Cheng Shao at 2024-10-10T01:05:42-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
ec36c7cb by Sebastian Graf at 2024-10-10T01:05:43-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
5982191b by Simon Peyton Jones at 2024-10-10T01:05:43-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
a943ab2c by Simon Peyton Jones at 2024-10-10T01:05:43-04:00
Missing record selectors in GHC.Internal.IO.Windows.Handle

This look genuinely wrong: see #25362.  These two fixes need auditing;
but they are better than the status quo.

Actually Ben has fixed this in !13394, so this patch will be
obseleted once !13394 lands.

- - - - -
f5aea95f by Cristiano Moraes at 2024-10-10T01:05:47-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
548e5ffa by Zubin Duggal at 2024-10-10T01:05:48-04:00
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -
8893beaa by sheaf at 2024-10-10T01:05:53-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
245493b1 by sheaf at 2024-10-10T01:05:53-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
4e3387c6 by Cheng Shao at 2024-10-10T01:05:54-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
98226a34 by Artem Pelenitsyn at 2024-10-10T01:06:00-04:00
Docs: Linear types: link Strict Patterns subsection
- - - - -
0b49f0f8 by Artem Pelenitsyn at 2024-10-10T01:06:00-04:00
Apply 2 suggestion(s) to 1 file(s)

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>
- - - - -
8bda61de by Alan Zimmerman at 2024-10-10T01:06:01-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c3c9ddd28376021d1f9b848155e95e8b114e670...8bda61dec4067cc5c0e6f6fa68e8ae067d781330

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c3c9ddd28376021d1f9b848155e95e8b114e670...8bda61dec4067cc5c0e6f6fa68e8ae067d781330
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 08:12:17 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Thu, 10 Oct 2024 04:12:17 -0400
Subject: [Git][ghc/ghc][wip/T23479] 19 commits: EPA: Remove unused
 hsCaseAnnsRest
Message-ID: <67078c611c466_74a063949f0514c3@gitlab.mail>



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


Commits:
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
cb30639d by Serge S. Gulin at 2024-10-10T11:12:04+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/48af9822ce106d5880d449ea938a6a076ff34bb1...cb30639d3bbee725aa29073b80833d8caa81f442

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/48af9822ce106d5880d449ea938a6a076ff34bb1...cb30639d3bbee725aa29073b80833d8caa81f442
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 09:47:07 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 10 Oct 2024 05:47:07 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: driver:
 bail out when -fllvm is passed to GHC not configured with LLVM
Message-ID: <6707a29b31cf7_2f95e8be66811438@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
f784364c by Cheng Shao at 2024-10-10T05:46:37-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
4cbbf06a by Sebastian Graf at 2024-10-10T05:46:38-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
3d682e7c by Simon Peyton Jones at 2024-10-10T05:46:38-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
b9d7e96b by Simon Peyton Jones at 2024-10-10T05:46:38-04:00
Missing record selectors in GHC.Internal.IO.Windows.Handle

This look genuinely wrong: see #25362.  These two fixes need auditing;
but they are better than the status quo.

Actually Ben has fixed this in !13394, so this patch will be
obseleted once !13394 lands.

- - - - -
5d327726 by Cristiano Moraes at 2024-10-10T05:46:41-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
06db7b46 by sheaf at 2024-10-10T05:46:45-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
9816761c by sheaf at 2024-10-10T05:46:45-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
a0f0761e by Cheng Shao at 2024-10-10T05:46:46-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
5aa42b73 by Artem Pelenitsyn at 2024-10-10T05:46:49-04:00
Docs: Linear types: link Strict Patterns subsection
- - - - -
753c5d34 by Artem Pelenitsyn at 2024-10-10T05:46:49-04:00
Apply 2 suggestion(s) to 1 file(s)

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>
- - - - -
ffdcebec by Alan Zimmerman at 2024-10-10T05:46:50-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bda61dec4067cc5c0e6f6fa68e8ae067d781330...ffdcebecb1fdd6431071fb7cae4ce0500164f62c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bda61dec4067cc5c0e6f6fa68e8ae067d781330...ffdcebecb1fdd6431071fb7cae4ce0500164f62c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 09:53:11 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 10 Oct 2024 05:53:11 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 3 commits: hadrian: Handle broken
 symlinks properly when creating source dist directories
Message-ID: <6707a40764352_2f95e81701b0269f7@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
407694e8 by Zubin Duggal at 2024-10-10T15:22:52+05:30
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
2d64fd7a by Zubin Duggal at 2024-10-10T15:22:52+05:30
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
4e74bf73 by Zubin Duggal at 2024-10-10T15:22:52+05:30
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -


4 changed files:

- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -55,8 +55,8 @@ archiveSourceTree prepare fname = do
   runBuilderWithCmdOptions
       [Cwd $ sourceDistRoot -/- dirName]
       (Tar Create)
-      ["chJf", ".." -/- tarName,  baseName]
-      ["chJf", ".." -/- tarName] [baseName]
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName,  baseName]
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName] [baseName]
 
 
 -- | This creates a symlink to the 'source' at 'target'
@@ -74,7 +74,9 @@ copyFileSourceDist source target = do
       error ("source-dist: tried to create non-relative symlink in source dist: " ++ show link_target)
     putProgressInfo =<< renderAction ("Create symlink (" ++ link_target ++ ")") source target
     isDirectory <- liftIO $ IO.doesDirectoryExist source
-    when (not isDirectory) $
+    -- We don't want to call `need` on broken symlinks
+    linkTargetExists <- liftIO $ IO.doesPathExist link_target
+    when (not isDirectory && linkTargetExists) $
       need [source]
     let createLink src tgt
           | isDirectory = liftIO $ IO.createDirectoryLink src tgt


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c05cd1e1e9daffb708285fcc03b0ffd13f5cbb0...4e74bf73c04104cf885828ef7611813fac7c2efb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c05cd1e1e9daffb708285fcc03b0ffd13f5cbb0...4e74bf73c04104cf885828ef7611813fac7c2efb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 10:06:35 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 10 Oct 2024 06:06:35 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 2 commits: hadrian: exclude
 cabal.project.symlink.broken from source archives
Message-ID: <6707a72bd7d22_2f95e844c208292e3@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
9de4b498 by Zubin Duggal at 2024-10-10T15:36:28+05:30
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
4d6e5afa by Zubin Duggal at 2024-10-10T15:36:28+05:30
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -


4 changed files:

- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -55,8 +55,9 @@ archiveSourceTree prepare fname = do
   runBuilderWithCmdOptions
       [Cwd $ sourceDistRoot -/- dirName]
       (Tar Create)
-      ["chJf", ".." -/- tarName,  baseName]
-      ["chJf", ".." -/- tarName] [baseName]
+      -- See https://github.com/haskell/cabal/issues/10442 for why we exclude this file.
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName,  baseName]
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName] [baseName]
 
 
 -- | This creates a symlink to the 'source' at 'target'


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e74bf73c04104cf885828ef7611813fac7c2efb...4d6e5afab00367324d2eb98062fc6dd7b34915fb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e74bf73c04104cf885828ef7611813fac7c2efb...4d6e5afab00367324d2eb98062fc6dd7b34915fb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 10:42:47 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Thu, 10 Oct 2024 06:42:47 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] 3 commits: Fix typo in the @since
 annotation of annotateIO
Message-ID: <6707afa7cf001_1568c8115a4410412a@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
5794e6e3 by Hassan Al-Awwadi at 2024-10-10T12:42:21+02:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc,
and as a side note it has simplified the method we use to deal with ambiguity
somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/494d7064e9a5d3929660a5910fc3c14d0119ce8a...5794e6e31cacc41ea3f897d594352913d8b11f99

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/494d7064e9a5d3929660a5910fc3c14d0119ce8a...5794e6e31cacc41ea3f897d594352913d8b11f99
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 10:54:25 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Thu, 10 Oct 2024 06:54:25 -0400
Subject: [Git][ghc/ghc][wip/ttg/lits] 3 commits: Fix typo in the @since
 annotation of annotateIO
Message-ID: <6707b2613eb03_1568c82e3420107355@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/lits at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
cf1a60fd by Hassan Al-Awwadi at 2024-10-10T12:53:38+02:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -


30 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/460d9a83cdb06ac3cbc06ea171b024e3c87d9a28...cf1a60fd9c9308cc4a97f4de273f1570170a50b9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/460d9a83cdb06ac3cbc06ea171b024e3c87d9a28...cf1a60fd9c9308cc4a97f4de273f1570170a50b9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 10:57:25 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Thu, 10 Oct 2024 06:57:25 -0400
Subject: [Git][ghc/ghc][wip/jade/ast] Put RdrName in the foExt field of
 FieldOcc
Message-ID: <6707b315a9f6f_1568c82e32b8107999@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC


Commits:
bba6167b by Hassan Al-Awwadi at 2024-10-10T12:55:57+02:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 11:03:23 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 10 Oct 2024 07:03:23 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-boot-orientation
Message-ID: <6707b47b994d_1568c854da80112197@gitlab.mail>



Matthew Pickering pushed new branch wip/fix-boot-orientation at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-boot-orientation
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 11:49:16 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 10 Oct 2024 07:49:16 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 46 commits: SpecConstr: Introduce a
 separate argument limit for forced specs.
Message-ID: <6707bf3c99919_1568c883203413116a@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
14d80f78 by Zubin Duggal at 2024-10-10T11:49:11+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
60f97025 by Zubin Duggal at 2024-10-10T11:49:11+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
50ec8c4a by Zubin Duggal at 2024-10-10T11:49:11+00:00
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d6e5afab00367324d2eb98062fc6dd7b34915fb...50ec8c4ab9db8d0bec202b44a5075790bb45e9eb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d6e5afab00367324d2eb98062fc6dd7b34915fb...50ec8c4ab9db8d0bec202b44a5075790bb45e9eb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 12:09:43 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 10 Oct 2024 08:09:43 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] More boot-file awareness in Finder
Message-ID: <6707c40771615_213d38145ed852983@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
49532ac1 by Sjoerd Visscher at 2024-10-10T14:09:30+02:00
More boot-file awareness in Finder

Finishes work started in fff55592

Adds findImportedModuleWithIsBoot and findHomeModuleWithIsBoot so that callers don't have to call addBootSuffix on the result.

Removes InstalledModule field from InstalledFound constructor since it's already part of the key that was searched for.

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Location.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -771,7 +771,7 @@ summariseRequirement pn mod_name = do
     let fopts = initFinderOpts dflags
 
     let PackageName pn_fs = pn
-    let location = mkHomeModLocation2 fopts mod_name
+    let location = mkHomeModLocation2 fopts (notBoot mod_name)
                     (unsafeEncodeUtf $ unpackFS pn_fs  moduleNameSlashes mod_name) (os "hsig")
 
     env <- getBkpEnv
@@ -848,23 +848,20 @@ hsModuleToModSummary home_keys pn hsc_src modname
     let PackageName unit_fs = pn
         dflags = hsc_dflags hsc_env
         fopts = initFinderOpts dflags
+        modWithIsBoot = GWIB modname (hscSourceToIsBoot hsc_src)
     -- Unfortunately, we have to define a "fake" location in
     -- order to appease the various code which uses the file
     -- name to figure out where to put, e.g. object files.
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation2 fopts modWithIsBoot
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
                               (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
@@ -893,7 +890,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modWithIsBoot location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2126,31 +2126,21 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
               ".lhs-boot" -> IsBoot
               _ -> NotBoot
 
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            modWithIsBoot = GWIB pi_mod_name is_boot
+
+            hsc_src
+              | IsBoot <- is_boot = HsBootFile
+              | isHaskellSigFilename src_fn = HsigFile
+              | otherwise = HsSrcFile
+
+            location = mkHomeModLocation fopts modWithIsBoot src_path
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit modWithIsBoot location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2180,14 +2170,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
            _ <- do
               let fc = hsc_FC hsc_env
                   gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+              addModuleToFinder fc gwib location
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
@@ -2239,7 +2225,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env (GWIB wanted_mod is_boot) mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2243,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2253,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env (GWIB imp is_boot) pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,19 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+        modWithIsBoot = GWIB mod_name (hscSourceToIsBoot src_flavour)
+    let location1 = mkHomeModLocation2 fopts modWithIsBoot (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -804,15 +799,15 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     -- above
     let expl_o_file = outputFile_ dflags
         expl_dyn_o_file  = dynOutputFile_ dflags
-        location5 | Just ofile <- expl_o_file
+        location4 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
-    return location5
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
+    return location4
     where
       fopts = initFinderOpts dflags
 


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -317,7 +317,7 @@ loadSrcInterface_maybe doc mod want_boot maybe_pkg
   -- interface; it will call the Finder again, but the ModLocation will be
   -- cached from the first search.
   = do hsc_env <- getTopEnv
-       res <- liftIO $ findImportedModule hsc_env mod maybe_pkg
+       res <- liftIO $ findImportedModuleWithIsBoot hsc_env (GWIB mod want_boot) maybe_pkg
        case res of
            Found _ mod -> initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
            -- TODO: Make sure this error message is good
@@ -895,9 +895,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit (GWIB mod hi_boot_file))
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,9 +15,11 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
+    findHomeModuleWithIsBoot,
     findExposedPackageModule,
     mkHomeModLocation,
     mkHomeModLocation2,
@@ -148,7 +150,10 @@ initFinderCache = do
 -- that package is searched for the module.
 
 findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult
-findImportedModule hsc_env mod pkg_qual =
+findImportedModule hsc_env = findImportedModuleWithIsBoot hsc_env . notBoot
+
+findImportedModuleWithIsBoot :: HscEnv -> ModuleNameWithIsBoot -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod pkg_qual =
   let fc        = hsc_FC hsc_env
       mhome_unit = hsc_home_unit_maybe hsc_env
       dflags    = hsc_dflags hsc_env
@@ -161,10 +166,10 @@ findImportedModuleNoHsc
   -> FinderOpts
   -> UnitEnv
   -> Maybe HomeUnit
-  -> ModuleName
+  -> ModuleNameWithIsBoot
   -> PkgQual
   -> IO FindResult
-findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
+findImportedModuleNoHsc fc fopts ue mhome_unit gwib at GWIB { gwib_mod = mod_name } mb_pkg =
   case mb_pkg of
     NoPkgQual  -> unqual_import
     ThisPkg uid | (homeUnitId <$> mhome_unit) == Just uid -> home_import
@@ -178,7 +183,7 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
 
 
     home_import = case mhome_unit of
-                   Just home_unit -> findHomeModule fc fopts home_unit mod_name
+                   Just home_unit -> findHomeModuleWithIsBoot fc fopts home_unit gwib
                    Nothing -> pure $ NoPackage (panic "findImportedModule: no home-unit")
 
 
@@ -186,11 +191,11 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
       -- If the module is reexported, then look for it as if it was from the perspective
       -- of that package which reexports it.
       | Just real_mod_name <- mod_name `M.lookup` finder_reexportedModules opts =
-        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) real_mod_name NoPkgQual
+        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) gwib{ gwib_mod = real_mod_name } NoPkgQual
       | mod_name `Set.member` finder_hiddenModules opts =
         return (mkHomeHidden uid)
       | otherwise =
-        findHomePackageModule fc opts uid mod_name
+        findHomePackageModule fc opts uid gwib
 
     -- Do not be smart and change this to `foldr orIfNotFound home_import hs` as
     -- that is not the same!! home_import is first because we need to look within ourselves
@@ -228,15 +233,15 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModuleWithIsBoot -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit gwib at GWIB { gwib_mod = mod } = do
   case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
-        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
+        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName <$> gwib)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
-        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
-    _ -> findPackageModule fc unit_state fopts mod
+        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName <$> gwib)
+    _ -> findPackageModule fc unit_state fopts gwib
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -271,10 +276,10 @@ orIfNotFound this or_this = do
 -- been done.  Otherwise, do the lookup (with the IO action) and save
 -- the result in the finder cache and the module location cache (if it
 -- was successful.)
-homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
+homeSearchCache :: FinderCache -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
-  let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  let mod = mkModule home_unit <$> mod_name
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -290,13 +295,13 @@ findLookupResult :: FinderCache -> FinderOpts -> LookupResult -> IO FindResult
 findLookupResult fc fopts r = case r of
      LookupFound m pkg_conf -> do
        let im = fst (getModuleInstantiation m)
-       r' <- findPackageModule_ fc fopts im (fst pkg_conf)
+       r' <- findPackageModule_ fc fopts (notBoot im) (fst pkg_conf)
        case r' of
         -- TODO: ghc -M is unlikely to do the right thing
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -344,24 +349,27 @@ modLocationCache fc mod do_this = do
 addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
   let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
 addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
   let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
+  addToFinderCache fc mod (InstalledFound loc)
   return (mkHomeModule home_unit (gwib_mod mod_name))
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
 
 findHomeModule :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
-findHomeModule fc fopts  home_unit mod_name = do
+findHomeModule fc fopts home_unit = findHomeModuleWithIsBoot fc fopts home_unit . notBoot
+
+findHomeModuleWithIsBoot :: FinderCache -> FinderOpts -> HomeUnit -> ModuleNameWithIsBoot -> IO FindResult
+findHomeModuleWithIsBoot fc fopts home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -381,12 +389,12 @@ mkHomeHidden uid =
            , fr_unusables = []
            , fr_suggestions = []}
 
-findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO FindResult
+findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO FindResult
 findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -414,9 +422,9 @@ findHomePackageModule fc fopts  home_unit mod_name = do
 --
 --  4. Some special-case code in GHCi (ToDo: Figure out why that needs to
 --  call this.)
-findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO InstalledFindResult
-findInstalledHomeModule fc fopts home_unit mod_name = do
-  homeSearchCache fc home_unit mod_name $
+findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult
+findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name } = do
+  homeSearchCache fc home_unit gwib $
    let
      maybe_working_dir = finder_workingDirectory fopts
      home_path = case maybe_working_dir of
@@ -432,16 +440,13 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
      mod = mkModule home_unit mod_name
 
      source_exts =
-      [ (os "hs",    mkHomeModLocationSearched fopts mod_name $ os "hs")
-      , (os "lhs",   mkHomeModLocationSearched fopts mod_name $ os "lhs")
-      , (os "hsig",  mkHomeModLocationSearched fopts mod_name $ os "hsig")
-      , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig")
-      ]
+      [ (ext, mkHomeModLocationSearched fopts (notBoot mod_name) ext)
+      | ext <- map os ["hs", "lhs", "hsig", "lhsig"]]
 
      -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that
      -- when hiDir field is set in dflags, we know to look there (see #16500)
-     hi_exts = [ (hisuf,                mkHomeModHiOnlyLocation fopts mod_name)
-               , (addBootSuffix hisuf,  mkHomeModHiOnlyLocation fopts mod_name)
+     hi_exts = [ (hisuf,                mkHomeModHiOnlyLocation fopts (GWIB mod_name NotBoot))
+               , (addBootSuffix hisuf,  mkHomeModHiOnlyLocation fopts (GWIB mod_name NotBoot))
                ]
 
         -- In compilation manager modes, we look for source files in the home
@@ -456,7 +461,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -467,9 +472,9 @@ augmentImports work_dir (fp:fps)
   | otherwise            = (work_dir  fp) : augmentImports work_dir fps
 
 -- | Search for a module in external packages only.
-findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult
+findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModuleWithIsBoot -> IO InstalledFindResult
 findPackageModule fc unit_state fopts mod = do
-  let pkg_id = moduleUnit mod
+  let pkg_id = moduleUnit (gwib_mod mod)
   case lookupUnitId unit_state pkg_id of
      Nothing -> return (InstalledNoPackage pkg_id)
      Just u  -> findPackageModule_ fc fopts mod u
@@ -481,15 +486,15 @@ findPackageModule fc unit_state fopts mod = do
 -- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
 -- The redundancy is to avoid an extra lookup in the package state
 -- for the appropriate config.
-findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ fc fopts mod pkg_conf = do
+findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModuleWithIsBoot -> UnitInfo -> IO InstalledFindResult
+findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc gwib $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +518,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,10 +552,10 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
-mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt
+mkHomeModLocationSearched :: FinderOpts -> ModuleNameWithIsBoot -> FileExt
                           -> OsPath -> BaseName -> ModLocation
 mkHomeModLocationSearched fopts mod suff path basename =
   mkHomeModLocation2 fopts mod (path  basename) suff
@@ -589,34 +594,35 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
+mkHomeModLocation :: FinderOpts -> ModuleNameWithIsBoot -> OsPath -> ModLocation
 mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
+   let (basename, extension) = OsPath.splitExtension src_filename
    in mkHomeModLocation2 dflags mod basename extension
 
 mkHomeModLocation2 :: FinderOpts
-                   -> ModuleName
+                   -> ModuleNameWithIsBoot
                    -> OsPath  -- Of source module, without suffix
                    -> FileExt    -- Suffix
                    -> ModLocation
-mkHomeModLocation2 fopts mod src_basename ext =
+mkHomeModLocation2 fopts (GWIB mod is_boot) src_basename ext =
    let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod
-
-       obj_fn = mkObjPath  fopts src_basename mod_basename
-       dyn_obj_fn = mkDynObjPath  fopts src_basename mod_basename
-       hi_fn  = mkHiPath   fopts src_basename mod_basename
-       dyn_hi_fn  = mkDynHiPath   fopts src_basename mod_basename
-       hie_fn = mkHiePath  fopts src_basename mod_basename
-
-   in (OsPathModLocation{ ml_hs_file_ospath   = Just (src_basename <.> ext),
-                          ml_hi_file_ospath   = hi_fn,
-                          ml_dyn_hi_file_ospath = dyn_hi_fn,
-                          ml_obj_file_ospath  = obj_fn,
+       bootify = if is_boot == IsBoot then addBootSuffix else id
+
+       obj_fn     = bootify $ mkObjPath    fopts src_basename mod_basename
+       dyn_obj_fn = bootify $ mkDynObjPath fopts src_basename mod_basename
+       hi_fn      = bootify $ mkHiPath     fopts src_basename mod_basename
+       dyn_hi_fn  = bootify $ mkDynHiPath  fopts src_basename mod_basename
+       hie_fn     = bootify $ mkHiePath    fopts src_basename mod_basename
+
+   in (OsPathModLocation{ ml_hs_file_ospath      = Just (src_basename <.> ext),
+                          ml_hi_file_ospath      = hi_fn,
+                          ml_dyn_hi_file_ospath  = dyn_hi_fn,
+                          ml_obj_file_ospath     = obj_fn,
                           ml_dyn_obj_file_ospath = dyn_obj_fn,
-                          ml_hie_file_ospath  = hie_fn })
+                          ml_hie_file_ospath     = hie_fn })
 
 mkHomeModHiOnlyLocation :: FinderOpts
-                        -> ModuleName
+                        -> ModuleNameWithIsBoot
                         -> OsPath
                         -> BaseName
                         -> ModLocation


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,10 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
-   , addBootSuffixLocn
-   , addBootSuffixLocnOut
    , removeBootSuffix
    , mkFileSrcSpan
    )
@@ -99,38 +95,6 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
--- | Add the @-boot@ suffix to all file paths associated with the module
-addBootSuffixLocn :: ModLocation -> ModLocation
-addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
-
--- | Add the @-boot@ suffix to all output file paths associated with the
--- module, not including the input file itself
-addBootSuffixLocnOut :: ModLocation -> ModLocation
-addBootSuffixLocnOut locn
-  = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn)
-         }
-
 -- | Compute a 'SrcSpan' from a 'ModLocation'.
 mkFileSrcSpan :: ModLocation -> SrcSpan
 mkFileSrcSpan mod_loc



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/49532ac118cdd11f078d2de1054ac59237cead77

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 14:00:49 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 10 Oct 2024 10:00:49 -0400
Subject: [Git][ghc/ghc][wip/fix-boot-orientation] compiler: Fix orientation of
 GHC.Hs.Doc boot file
Message-ID: <6707de11b1e7f_3884925e914689f0@gitlab.mail>



Matthew Pickering pushed to branch wip/fix-boot-orientation at Glasgow Haskell Compiler / GHC


Commits:
76117740 by Matthew Pickering at 2024-10-10T15:00:30+01:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -


4 changed files:

- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- − compiler/Language/Haskell/Syntax/ImpExp.hs-boot


Changes:

=====================================
compiler/GHC/Hs/Doc.hs-boot
=====================================
@@ -0,0 +1,19 @@
+{-# LANGUAGE RoleAnnotations #-}
+module GHC.Hs.Doc where
+
+-- See #21592 for progress on removing this boot file.
+
+import GHC.Types.SrcLoc
+import GHC.Hs.DocString
+import Data.Kind
+
+type role WithHsDocIdentifiers representational nominal
+type WithHsDocIdentifiers :: Type -> Type -> Type
+data WithHsDocIdentifiers a pass
+
+type HsDoc :: Type -> Type
+type HsDoc = WithHsDocIdentifiers HsDocString
+
+type LHsDoc :: Type -> Type
+type LHsDoc pass = Located (HsDoc pass)
+


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -110,7 +110,7 @@ import qualified Data.ByteString as BS
 import qualified Data.ByteString.Char8 as BS.Char8
 
 import Language.Haskell.Syntax.Module.Name
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
+import Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
 
 ---------------------------------------------------------------------
 -- MODULES


=====================================
compiler/Language/Haskell/Syntax/ImpExp.hs
=====================================
@@ -16,7 +16,7 @@ import Data.Int (Int)
 
 import Control.DeepSeq
 
-import GHC.Hs.Doc -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
+import {-# SOURCE #-} GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
 
 {-
 ************************************************************************


=====================================
compiler/Language/Haskell/Syntax/ImpExp.hs-boot deleted
=====================================
@@ -1,16 +0,0 @@
-module Language.Haskell.Syntax.ImpExp where
-
-import Data.Eq
-import Data.Ord
-import Text.Show
-import Data.Data
-
--- This boot file should be short lived: As soon as the dependency on
--- `GHC.Hs.Doc` is gone we'll no longer have cycles and can get rid this file.
-
-data IsBootInterface = NotBoot | IsBoot
-
-instance Eq IsBootInterface
-instance Ord IsBootInterface
-instance Show IsBootInterface
-instance Data IsBootInterface



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/761177407aa18ef096f3432107c54151129f52fb

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 17:12:13 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Thu, 10 Oct 2024 13:12:13 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] Only stores BOoleanFormula
 source-locations in leaves
Message-ID: <67080aede7302_3d0a1bbc64c206e4@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
2aa11fce by Hassan Al-Awwadi at 2024-10-10T19:10:54+02:00
Only stores BOoleanFormula source-locations in leaves

- - - - -


13 changed files:

- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Types/Basic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/BooleanFormula.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


Changes:

=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -50,9 +50,9 @@ bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
 bfMap f = go
   where
     go (Var    a  ) = Var     $ f a
-    go (And    bfs) = And     $ map (fmap go) bfs
-    go (Or     bfs) = Or      $ map (fmap go) bfs
-    go (Parens bf ) = Parens  $ fmap go bf
+    go (And    bfs) = And     $ map go bfs
+    go (Or     bfs) = Or      $ map go bfs
+    go (Parens bf ) = Parens  $     go bf
 
 bfTraverse  :: Applicative f
             => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
@@ -61,9 +61,9 @@ bfTraverse  :: Applicative f
 bfTraverse f = go
   where
     go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
-    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
-    go (Parens bf ) = Parens <$> traverse go bf
+    go (And    bfs) = And    <$> traverse @[] go bfs
+    go (Or     bfs) = Or     <$> traverse @[] go bfs
+    go (Parens bf ) = Parens <$>              go bf
 
 
 
@@ -114,10 +114,10 @@ isTrue (And []) = True
 isTrue _ = False
 
 eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
-eval f (Var x)  = f x
-eval f (And xs) = all (eval f . unLoc) xs
-eval f (Or xs)  = any (eval f . unLoc) xs
-eval f (Parens x) = eval f (unLoc x)
+eval f (Var x)    = f x
+eval f (And xs)   = all (eval f) xs
+eval f (Or xs)    = any (eval f) xs
+eval f (Parens x) = eval f x
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
@@ -128,9 +128,9 @@ simplify :: forall p. Eq (LIdP (GhcPass p))
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
-simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
-simplify f (Parens x) = simplify f (unLoc x)
+simplify f (And xs)   = mkAnd (map (simplify f) xs)
+simplify f (Or xs)    = mkOr  (map (simplify f) xs)
+simplify f (Parens x) = simplify f x
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
@@ -152,11 +152,11 @@ isUnsatisfied f bf
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
 impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
-Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
-And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
-           -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
-Parens x `impliesAtom` y = unLoc x `impliesAtom` y
+Var x  `impliesAtom` y = unLoc x == unLoc y
+And xs `impliesAtom` y = any (`impliesAtom` y) xs
+-- we have all of xs, so one of them implying y is enough
+Or  xs `impliesAtom` y = all (`impliesAtom` y) xs
+Parens x `impliesAtom` y =  x `impliesAtom` y
 
 implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
@@ -166,16 +166,16 @@ implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
         case hyp of
             Var x | memberClauseAtoms (unLoc x) r -> True
                   | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
-            Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
-            And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
-            Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
+            Parens hyp' -> go l { clauseExprs = hyp':hyps }     r
+            And hyps'  -> go l { clauseExprs =  hyps' ++ hyps } r
+            Or hyps'   -> all (\hyp' -> go l { clauseExprs = hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
             Var x | memberClauseAtoms (unLoc x) l -> True
                   | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
-            Parens con' -> go l r { clauseExprs = unLoc con':cons }
-            And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
-            Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
+            Parens con' -> go l r { clauseExprs = con':cons }
+            And cons'   -> all (\con' -> go l r { clauseExprs = con':cons }) cons'
+            Or cons'    -> go l r { clauseExprs = cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
@@ -203,10 +203,10 @@ pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
   go p (And []) = cparen (p > 0) empty
-  go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
+  go p (And xs) = pprAnd p (map (go 3) xs)
   go _ (Or  []) = keyword $ text "FALSE"
-  go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
-  go p (Parens x) = go p (unLoc x)
+  go p (Or  xs) = pprOr p (map (go 2) xs)
+  go p (Parens x) = go p x
 
 -- Pretty print in source syntax, "a | b | c,d,e"
 pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
@@ -234,7 +234,7 @@ pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> S
 pprBooleanFormulaNormal = go
   where
     go (Var x)    = pprPrefixOcc (unLoc x)
-    go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
+    go (And xs)   = fsep $ punctuate comma (map go xs)
     go (Or [])    = keyword $ text "FALSE"
-    go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)
-    go (Parens x) = parens (go $ unLoc x)
+    go (Or xs)    = fsep $ intersperse vbar (map go xs)
+    go (Parens x) = parens (go x)


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,7 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
-import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
+import GHC.Data.BooleanFormula ( BooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -934,8 +934,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
-pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
+pprMinimalSig :: OutputableBndrId p  => BooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig = pprBooleanFormulaNormal
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -342,13 +342,14 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
 
-toIfaceBooleanFormula ::  NamedThing (IdP (GhcPass p)) => BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
+toIfaceBooleanFormula ::  NamedThing (IdP (GhcPass p))
+                      => BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
 toIfaceBooleanFormula = go
   where
     go (Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $ nm
-    go (And bfs  ) = IfAnd    $ map (go . unLoc) bfs
-    go (Or bfs   ) = IfOr     $ map (go . unLoc) bfs
-    go (Parens bf) = IfParens $ go . unLoc $ bf
+    go (And bfs  ) = IfAnd    $ map go bfs
+    go (Or bfs   ) = IfOr     $ map go bfs
+    go (Parens bf) = IfParens $     go bf
 
 traverseIfaceBooleanFormula :: Applicative f
                             => (IfLclName -> f (LIdP (GhcPass p)))
@@ -357,6 +358,6 @@ traverseIfaceBooleanFormula :: Applicative f
 traverseIfaceBooleanFormula f = go
   where
     go (IfVar nm    ) = Var     <$> f nm
-    go (IfAnd ibfs  ) = And     <$> traverse (fmap noLocA . go) ibfs
-    go (IfOr ibfs   ) = Or      <$> traverse (fmap noLocA . go) ibfs
-    go (IfParens ibf) = Parens  <$> (fmap noLocA . go) ibf
\ No newline at end of file
+    go (IfAnd ibfs  ) = And     <$> traverse go ibfs
+    go (IfOr ibfs   ) = Or      <$> traverse go ibfs
+    go (IfParens ibf) = Parens  <$> go ibf
\ No newline at end of file


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2045,7 +2045,10 @@ instance ToHie PendingTcSplice where
 
 instance (HiePass p, Data (IdGhcP p))
   => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
-    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
+    toHie (L span form) =  concatM [makeNode form (locA span), toHie form]
+instance (HiePass p, Data (IdGhcP p))
+  => ToHie (BooleanFormula (GhcPass p)) where
+    toHie formula =  concatM $ case formula of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3700,30 +3700,26 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula GhcPs }
+name_boolformula_opt :: { BooleanFormula GhcPs }
         : name_boolformula          { $1 }
-        | {- empty -}               { noLocA mkTrue }
+        | {- empty -}               { mkTrue }
 
-name_boolformula :: { LBooleanFormula GhcPs }
-        : name_boolformula_and                      { $1 }
+name_boolformula :: { BooleanFormula GhcPs }
+        : name_boolformula_and       { $1 }
         | name_boolformula_and '|' name_boolformula
-                           {% do { h <- addTrailingVbarL $1 (gl $2)
-                                 ; return (sLLa $1 $> (Or [h,$3])) } }
+                           { (Or [$1, $3]) }
 
-name_boolformula_and :: { LBooleanFormula GhcPs }
-        : name_boolformula_and_list
-                  { sLLa (head $1) (last $1) (And ($1)) }
+name_boolformula_and :: { BooleanFormula GhcPs }
+        : name_boolformula_and_list { (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
-        : name_boolformula_atom                               { [$1] }
+name_boolformula_and_list :: { [BooleanFormula GhcPs] }
+        : name_boolformula_atom  { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
-            {% do { h <- addTrailingCommaL $1 (gl $2)
-                  ; return (h : $3) } }
+                                 {  ($1 : $3) }
 
-name_boolformula_atom :: { LBooleanFormula GhcPs }
-        : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
-                                      (AnnList Nothing (Just (mop $1)) (Just (mcp $3)) [] []) }
-        | name_var                  { sL1a $1 (Var $1) }
+name_boolformula_atom :: { BooleanFormula GhcPs }
+        : '(' name_boolformula ')'  {  (Parens $2) }
+        | name_var                  {  (Var $1) }
 
 namelist :: { Located [LocatedN RdrName] }
 namelist : name_var              { sL1 $1 [$1] }


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -1137,9 +1137,9 @@ renameSig ctxt (FixSig _ fsig)
   = do  { new_fsig <- rnSrcFixityDecl ctxt fsig
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
-renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
+renameSig ctxt sig@(MinimalSig (_, s) bf)
   = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
-       return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
+       return (MinimalSig (noAnn, s) new_bf, emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)
   = do  { new_vs <- mapM (lookupSigOccRnN ctxt sig) vs


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
+    defMindef = mkAnd [ mkVar (noLocA name)
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,7 +402,7 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef (L _ (MinimalSig _ bf)) = Just bf
     toMinimalDef _                             = Nothing
 
 {-


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -127,6 +127,19 @@ import GHC.Prelude
 import GHC.ForeignSrcLang
 import GHC.Data.FastString
 import GHC.Utils.Outputable
+    ( SDoc,
+      Outputable(..),
+      IsLine((<+>), sep, ftext, fsep, char, text, (<>)),
+      IsOutput(empty),
+      JoinPointHood(..),
+      parens,
+      vbar,
+      brackets,
+      ifPprDebug,
+      doubleQuotes,
+      int,
+      isJoinPoint,
+      OutputableP(..) )
 import GHC.Utils.Panic
 import GHC.Utils.Binary
 import GHC.Types.SourceText


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -28,7 +28,7 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   , GRHSs )
 import {-# SOURCE #-} Language.Haskell.Syntax.Pat
   ( LPat )
-import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
 
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
@@ -465,7 +465,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
+  | MinimalSig (XMinimalSig pass) (BooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -9,16 +9,16 @@ module Language.Haskell.Syntax.BooleanFormula(
 
 import Prelude hiding ( init, last )
 import Data.List ( nub )
-import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+import Language.Haskell.Syntax.Extension (XRec, LIdP)
 
 
 -- types
 type LBooleanFormula p = XRec p (BooleanFormula p)
-data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
-                      | Parens (LBooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [BooleanFormula p] | Or [BooleanFormula p]
+                      | Parens (BooleanFormula p)
 
 -- instances
-deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+deriving instance Eq (LIdP p) => Eq (BooleanFormula p)
 
 -- smart constructors
 -- see note [Simplification of BooleanFormulas]
@@ -35,28 +35,28 @@ mkBool False = mkFalse
 mkBool True  = mkTrue
 
 -- Make a conjunction, and try to simplify
-mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
 mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
   where
   -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
-  fromAnd bf = case unXRec @p bf of
+  fromAnd :: BooleanFormula p -> Maybe [BooleanFormula p]
+  fromAnd bf = case bf of
     (And xs) -> Just xs
      -- assume that xs are already simplified
      -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
     (Or [])  -> Nothing
      -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
     _        -> Just [bf]
-  mkAnd' [x] = unXRec @p x
+  mkAnd' [x] = x
   mkAnd' xs = And xs
 
-mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
 mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
   where
   -- See Note [Simplification of BooleanFormulas]
-  fromOr bf = case unXRec @p bf of
+  fromOr bf = case  bf of
     (Or xs)  -> Just xs
     (And []) -> Nothing
     _        -> Just [bf]
-  mkOr' [x] = unXRec @p x
-  mkOr' xs = Or xs
+  mkOr' [x] = x
+  mkOr' xs  = Or xs


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
=====================================
@@ -990,10 +990,10 @@ ppClassDecl
           ]
 
       -- Minimal complete definition
-      minimalBit = case [s | MinimalSig _ (L _ s) <- sigs] of
+      minimalBit = case [s | MinimalSig _ s <- sigs] of
         -- Miminal complete definition = every shown method
         And xs : _
-          | sort [getName n | L _ (Var (L _ n)) <- xs]
+          | sort [getName n | (Var (L _ n)) <- xs]
               == sort [getName n | ClassOpSig _ _ ns _ <- sigs, L _ n <- ns] ->
               noHtml
         -- Minimal complete definition = the only shown method
@@ -1007,11 +1007,11 @@ ppClassDecl
         _ -> noHtml
 
       ppMinimal _ (Var (L _ n)) = ppDocName qual Prefix True n
-      ppMinimal _ (And fs) = foldr1 (\a b -> a +++ ", " +++ b) $ map (ppMinimal True . unLoc) fs
-      ppMinimal p (Or fs) = wrap $ foldr1 (\a b -> a +++ " | " +++ b) $ map (ppMinimal False . unLoc) fs
+      ppMinimal _ (And fs) = foldr1 (\a b -> a +++ ", " +++ b) $ map (ppMinimal True) fs
+      ppMinimal p (Or fs) = wrap $ foldr1 (\a b -> a +++ " | " +++ b) $ map (ppMinimal False ) fs
         where
           wrap | p = parens | otherwise = id
-      ppMinimal p (Parens x) = ppMinimal p (unLoc x)
+      ppMinimal p (Parens x) = ppMinimal p x
 
       -- Instances
       instancesBit =


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -177,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -772,22 +772,22 @@ renameSig sig = case sig of
   FixSig _ (FixitySig _ lnames fixity) -> do
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
-  MinimalSig _ (L l s) -> do
+  MinimalSig _ s -> do
     s' <- bfTraverse (traverse lookupRn) s
-    return $ MinimalSig noExtField (L l s')
+    return $ MinimalSig noExtField s'
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
 bfTraverse  :: Applicative f
             => (LIdP (GhcPass p) -> f (LIdP DocNameI))
             -> BooleanFormula (GhcPass p)
-            -> f (BooleanFormula (DocNameI))
-bfTraverse f = go
-  where
+            -> f (BooleanFormula DocNameI)
+bfTraverse f = go 
+  where 
     go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
-    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
-    go (Parens bf ) = Parens <$> traverse go bf
+    go (And    bfs) = And    <$> traverse @[] go bfs
+    go (Or     bfs) = Or     <$> traverse @[] go bfs
+    go (Parens bf ) = Parens <$>              go bf
 
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2aa11fcefe1d067ae6c22afde92006133bf4ba1f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 17:35:30 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 13:35:30 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 2 commits: linker: Avoid linear
 search when looking up Haskell symbols via dlsym
Message-ID: <67081061efbbe_3d0a1b24b74c2494f@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
ef4903f2 by Alexis King at 2024-10-10T13:35:13-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
0e14a98d by Ben Gamari at 2024-10-10T13:35:13-04:00
hadrian: Update bootstrap plans

- - - - -


14 changed files:

- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- hadrian/bootstrap/generate_bootstrap_plans
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- rts/Linker.c
- rts/RtsSymbols.c
- rts/include/rts/Linker.h
- testsuite/tests/rts/linker/T2615.hs


Changes:

=====================================
compiler/GHC/ByteCode/Linker.hs
=====================================
@@ -25,6 +25,7 @@ import GHCi.ResolvedBCO
 import GHCi.BreakArray
 
 import GHC.Builtin.PrimOps
+import GHC.Builtin.PrimOps.Ids
 import GHC.Builtin.Names
 
 import GHC.Unit.Types
@@ -40,6 +41,8 @@ import GHC.Utils.Outputable
 
 import GHC.Types.Name
 import GHC.Types.Name.Env
+import qualified GHC.Types.Id as Id
+import GHC.Types.Unique.DFM
 
 import Language.Haskell.Syntax.Module.Name
 
@@ -54,32 +57,33 @@ import GHC.Exts
 
 linkBCO
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> UnlinkedBCO
   -> IO ResolvedBCO
-linkBCO interp le bco_ix breakarray
+linkBCO interp pkgs_loaded le bco_ix breakarray
            (UnlinkedBCO _ arity insns bitmap lits0 ptrs0) = do
   -- fromIntegral Word -> Word64 should be a no op if Word is Word64
   -- otherwise it will result in a cast to longlong on 32bit systems.
-  lits <- mapM (fmap fromIntegral . lookupLiteral interp le) (ssElts lits0)
-  ptrs <- mapM (resolvePtr interp le bco_ix breakarray) (ssElts ptrs0)
+  lits <- mapM (fmap fromIntegral . lookupLiteral interp pkgs_loaded le) (ssElts lits0)
+  ptrs <- mapM (resolvePtr interp pkgs_loaded le bco_ix breakarray) (ssElts ptrs0)
   return (ResolvedBCO isLittleEndian arity insns bitmap
               (listArray (0, fromIntegral (sizeSS lits0)-1) lits)
               (addListToSS emptySS ptrs))
 
-lookupLiteral :: Interp -> LinkerEnv -> BCONPtr -> IO Word
-lookupLiteral interp le ptr = case ptr of
+lookupLiteral :: Interp -> PkgsLoaded -> LinkerEnv -> BCONPtr -> IO Word
+lookupLiteral interp pkgs_loaded le ptr = case ptr of
   BCONPtrWord lit -> return lit
   BCONPtrLbl  sym -> do
     Ptr a# <- lookupStaticPtr interp sym
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrItbl nm -> do
-    Ptr a# <- lookupIE interp (itbl_env le) nm
+    Ptr a# <- lookupIE interp pkgs_loaded (itbl_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrAddr nm -> do
-    Ptr a# <- lookupAddr interp (addr_env le) nm
+    Ptr a# <- lookupAddr interp pkgs_loaded (addr_env le) nm
     return (W# (int2Word# (addr2Int# a#)))
   BCONPtrStr _ ->
     -- should be eliminated during assembleBCOs
@@ -93,19 +97,19 @@ lookupStaticPtr interp addr_of_label_string = do
     Nothing  -> linkFail "GHC.ByteCode.Linker: can't find label"
                   (unpackFS addr_of_label_string)
 
-lookupIE :: Interp -> ItblEnv -> Name -> IO (Ptr ())
-lookupIE interp ie con_nm =
+lookupIE :: Interp -> PkgsLoaded -> ItblEnv -> Name -> IO (Ptr ())
+lookupIE interp pkgs_loaded ie con_nm =
   case lookupNameEnv ie con_nm of
     Just (_, ItblPtr a) -> return (fromRemotePtr (castRemotePtr a))
     Nothing -> do -- try looking up in the object files.
        let sym_to_find1 = nameToCLabel con_nm "con_info"
-       m <- lookupSymbol interp sym_to_find1
+       m <- lookupHsSymbol interp pkgs_loaded con_nm "con_info"
        case m of
           Just addr -> return addr
           Nothing
              -> do -- perhaps a nullary constructor?
                    let sym_to_find2 = nameToCLabel con_nm "static_info"
-                   n <- lookupSymbol interp sym_to_find2
+                   n <- lookupHsSymbol interp pkgs_loaded con_nm "static_info"
                    case n of
                       Just addr -> return addr
                       Nothing   -> linkFail "GHC.ByteCode.Linker.lookupIE"
@@ -113,35 +117,36 @@ lookupIE interp ie con_nm =
                                        unpackFS sym_to_find2)
 
 -- see Note [Generating code for top-level string literal bindings] in GHC.StgToByteCode
-lookupAddr :: Interp -> AddrEnv -> Name -> IO (Ptr ())
-lookupAddr interp ae addr_nm = do
+lookupAddr :: Interp -> PkgsLoaded -> AddrEnv -> Name -> IO (Ptr ())
+lookupAddr interp pkgs_loaded ae addr_nm = do
   case lookupNameEnv ae addr_nm of
     Just (_, AddrPtr ptr) -> return (fromRemotePtr ptr)
     Nothing -> do -- try looking up in the object files.
       let sym_to_find = nameToCLabel addr_nm "bytes"
                           -- see Note [Bytes label] in GHC.Cmm.CLabel
-      m <- lookupSymbol interp sym_to_find
+      m <- lookupHsSymbol interp pkgs_loaded addr_nm "bytes"
       case m of
         Just ptr -> return ptr
         Nothing -> linkFail "GHC.ByteCode.Linker.lookupAddr"
                      (unpackFS sym_to_find)
 
-lookupPrimOp :: Interp -> PrimOp -> IO (RemotePtr ())
-lookupPrimOp interp primop = do
+lookupPrimOp :: Interp -> PkgsLoaded -> PrimOp -> IO (RemotePtr ())
+lookupPrimOp interp pkgs_loaded primop = do
   let sym_to_find = primopToCLabel primop "closure"
-  m <- lookupSymbol interp (mkFastString sym_to_find)
+  m <- lookupHsSymbol interp pkgs_loaded (Id.idName $ primOpId primop) "closure"
   case m of
     Just p -> return (toRemotePtr p)
     Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE(primop)" sym_to_find
 
 resolvePtr
   :: Interp
+  -> PkgsLoaded
   -> LinkerEnv
   -> NameEnv Int
   -> RemoteRef BreakArray
   -> BCOPtr
   -> IO ResolvedBCOPtr
-resolvePtr interp le bco_ix breakarray ptr = case ptr of
+resolvePtr interp pkgs_loaded le bco_ix breakarray ptr = case ptr of
   BCOPtrName nm
     | Just ix <- lookupNameEnv bco_ix nm
     -> return (ResolvedBCORef ix) -- ref to another BCO in this group
@@ -153,20 +158,42 @@ resolvePtr interp le bco_ix breakarray ptr = case ptr of
     -> assertPpr (isExternalName nm) (ppr nm) $
        do
           let sym_to_find = nameToCLabel nm "closure"
-          m <- lookupSymbol interp sym_to_find
+          m <- lookupHsSymbol interp pkgs_loaded nm "closure"
           case m of
             Just p -> return (ResolvedBCOStaticPtr (toRemotePtr p))
             Nothing -> linkFail "GHC.ByteCode.Linker.lookupCE" (unpackFS sym_to_find)
 
   BCOPtrPrimOp op
-    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp op
+    -> ResolvedBCOStaticPtr <$> lookupPrimOp interp pkgs_loaded op
 
   BCOPtrBCO bco
-    -> ResolvedBCOPtrBCO <$> linkBCO interp le bco_ix breakarray bco
+    -> ResolvedBCOPtrBCO <$> linkBCO interp pkgs_loaded le bco_ix breakarray bco
 
   BCOPtrBreakArray
     -> return (ResolvedBCOPtrBreakArray breakarray)
 
+-- | Look up the address of a Haskell symbol in the currently
+-- loaded units.
+--
+-- See Note [Looking up symbols in the relevant objects].
+lookupHsSymbol :: Interp -> PkgsLoaded -> Name -> String -> IO (Maybe (Ptr ()))
+lookupHsSymbol interp pkgs_loaded nm sym_suffix = do
+  massertPpr (isExternalName nm) (ppr nm)
+  let sym_to_find = nameToCLabel nm sym_suffix
+      pkg_id = moduleUnitId $ nameModule nm
+      loaded_dlls = maybe [] loaded_pkg_hs_dlls $ lookupUDFM pkgs_loaded pkg_id
+
+      go (dll:dlls) = do
+        mb_ptr <- lookupSymbolInDLL interp dll sym_to_find
+        case mb_ptr of
+          Just ptr -> pure (Just ptr)
+          Nothing -> go dlls
+      go [] =
+        -- See Note [Symbols may not be found in pkgs_loaded] in GHC.Linker.Types
+        lookupSymbol interp sym_to_find
+
+  go loaded_dlls
+
 linkFail :: String -> String -> IO a
 linkFail who what
    = throwGhcExceptionIO (ProgramError $


=====================================
compiler/GHC/Driver/Plugins.hs
=====================================
@@ -405,12 +405,12 @@ loadExternalPluginLib :: FilePath -> IO ()
 loadExternalPluginLib path = do
   -- load library
   loadDLL path >>= \case
-    Just errmsg -> pprPanic "loadExternalPluginLib"
-                    (vcat [ text "Can't load plugin library"
-                          , text "  Library path: " <> text path
-                          , text "  Error       : " <> text errmsg
-                          ])
-    Nothing -> do
+    Left errmsg -> pprPanic "loadExternalPluginLib"
+                     (vcat [ text "Can't load plugin library"
+                           , text "  Library path: " <> text path
+                           , text "  Error       : " <> text errmsg
+                           ])
+    Right _ -> do
       -- resolve objects
       resolveObjs >>= \case
         True -> return ()


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -56,6 +56,7 @@ import GHC.Tc.Utils.Monad
 import GHC.Runtime.Interpreter
 import GHCi.RemoteTypes
 import GHC.Iface.Load
+import GHCi.Message (LoadedDLL)
 
 import GHC.ByteCode.Linker
 import GHC.ByteCode.Asm
@@ -145,7 +146,7 @@ emptyLoaderState = LoaderState
   --
   -- The linker's symbol table is populated with RTS symbols using an
   -- explicit list.  See rts/Linker.c for details.
-  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] emptyUniqDSet)
+  where init_pkgs = unitUDFM rtsUnitId (LoadedPkgInfo rtsUnitId [] [] [] emptyUniqDSet)
 
 extendLoadedEnv :: Interp -> [(Name,ForeignHValue)] -> IO ()
 extendLoadedEnv interp new_bindings =
@@ -194,8 +195,8 @@ loadDependencies
   -> SrcSpan
   -> [Module]
   -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) -- ^ returns the set of linkables required
+-- When called, the loader state must have been initialized (see `initLoaderState`)
 loadDependencies interp hsc_env pls span needed_mods = do
---   initLoaderState (hsc_dflags hsc_env) dl
    let opts = initLinkDepsOpts hsc_env
 
    -- Find what packages and linkables are required
@@ -485,25 +486,25 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
     DLL dll_unadorned -> do
       maybe_errstr <- loadDLL interp (platformSOName platform dll_unadorned)
       case maybe_errstr of
-         Nothing -> maybePutStrLn logger "done"
-         Just mm | platformOS platform /= OSDarwin ->
+         Right _ -> maybePutStrLn logger "done"
+         Left mm | platformOS platform /= OSDarwin ->
            preloadFailed mm lib_paths lib_spec
-         Just mm | otherwise -> do
+         Left mm | otherwise -> do
            -- As a backup, on Darwin, try to also load a .so file
            -- since (apparently) some things install that way - see
            -- ticket #8770.
            let libfile = ("lib" ++ dll_unadorned) <.> "so"
            err2 <- loadDLL interp libfile
            case err2 of
-             Nothing -> maybePutStrLn logger "done"
-             Just _  -> preloadFailed mm lib_paths lib_spec
+             Right _ -> maybePutStrLn logger "done"
+             Left _  -> preloadFailed mm lib_paths lib_spec
       return pls
 
     DLLPath dll_path -> do
       do maybe_errstr <- loadDLL interp dll_path
          case maybe_errstr of
-            Nothing -> maybePutStrLn logger "done"
-            Just mm -> preloadFailed mm lib_paths lib_spec
+            Right _ -> maybePutStrLn logger "done"
+            Left mm -> preloadFailed mm lib_paths lib_spec
          return pls
 
     Framework framework ->
@@ -588,7 +589,7 @@ loadExpr interp hsc_env span root_ul_bco = do
         let le = linker_env pls
             nobreakarray = error "no break array"
             bco_ix = mkNameEnv [(unlinkedBCOName root_ul_bco, 0)]
-        resolved <- linkBCO interp le bco_ix nobreakarray root_ul_bco
+        resolved <- linkBCO interp (pkgs_loaded pls) le bco_ix nobreakarray root_ul_bco
         [root_hvref] <- createBCOs interp [resolved]
         fhv <- mkFinalizedHValue interp root_hvref
         return (pls, fhv)
@@ -651,7 +652,7 @@ loadDecls interp hsc_env span cbc at CompiledByteCode{..} = do
                        , addr_env = plusNameEnv (addr_env le) bc_strs }
 
           -- Link the necessary packages and linkables
-          new_bindings <- linkSomeBCOs interp le2 [cbc]
+          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 [cbc]
           nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
           let ce2  = extendClosureEnv (closure_env le2) nms_fhvs
               !pls2 = pls { linker_env = le2 { closure_env = ce2 } }
@@ -832,8 +833,8 @@ dynLoadObjs interp hsc_env pls at LoaderState{..} objs = do
     changeTempFilesLifetime tmpfs TFL_GhcSession [soFile]
     m <- loadDLL interp soFile
     case m of
-        Nothing -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
-        Just err -> linkFail msg err
+      Right _ -> return $! pls { temp_sos = (libPath, libName) : temp_sos }
+      Left err -> linkFail msg err
   where
     msg = "GHC.Linker.Loader.dynLoadObjs: Loading temp shared object failed"
 
@@ -873,7 +874,7 @@ dynLinkBCOs interp pls bcos = do
             ae2 = foldr plusNameEnv (addr_env le1) (map bc_strs cbcs)
             le2 = le1 { itbl_env = ie2, addr_env = ae2 }
 
-        names_and_refs <- linkSomeBCOs interp le2 cbcs
+        names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
 
         -- We only want to add the external ones to the ClosureEnv
         let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
@@ -888,6 +889,7 @@ dynLinkBCOs interp pls bcos = do
 
 -- Link a bunch of BCOs and return references to their values
 linkSomeBCOs :: Interp
+             -> PkgsLoaded
              -> LinkerEnv
              -> [CompiledByteCode]
              -> IO [(Name,HValueRef)]
@@ -895,7 +897,7 @@ linkSomeBCOs :: Interp
                         -- the incoming unlinked BCOs.  Each gives the
                         -- value of the corresponding unlinked BCO
 
-linkSomeBCOs interp le mods = foldr fun do_link mods []
+linkSomeBCOs interp pkgs_loaded le mods = foldr fun do_link mods []
  where
   fun CompiledByteCode{..} inner accum =
     case bc_breaks of
@@ -908,7 +910,7 @@ linkSomeBCOs interp le mods = foldr fun do_link mods []
     let flat = [ (breakarray, bco) | (breakarray, bcos) <- mods, bco <- bcos ]
         names = map (unlinkedBCOName . snd) flat
         bco_ix = mkNameEnv (zip names [0..])
-    resolved <- sequence [ linkBCO interp le bco_ix breakarray bco
+    resolved <- sequence [ linkBCO interp pkgs_loaded le bco_ix breakarray bco
                          | (breakarray, bco) <- flat ]
     hvrefs <- createBCOs interp resolved
     return (zip names hvrefs)
@@ -1071,18 +1073,18 @@ loadPackages' interp hsc_env new_pks pls = do
                -- Link dependents first
              ; pkgs' <- link pkgs deps
                 -- Now link the package itself
-             ; (hs_cls, extra_cls) <- loadPackage interp hsc_env pkg_cfg
+             ; (hs_cls, extra_cls, loaded_dlls) <- loadPackage interp hsc_env pkg_cfg
              ; let trans_deps = unionManyUniqDSets [ addOneToUniqDSet (loaded_pkg_trans_deps loaded_pkg_info) dep_pkg
                                                    | dep_pkg <- deps
                                                    , Just loaded_pkg_info <- pure (lookupUDFM pkgs' dep_pkg)
                                                    ]
-             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls trans_deps)) }
+             ; return (addToUDFM pkgs' new_pkg (LoadedPkgInfo new_pkg hs_cls extra_cls loaded_dlls trans_deps)) }
 
         | otherwise
         = throwGhcExceptionIO (CmdLineError ("unknown package: " ++ unpackFS (unitIdFS new_pkg)))
 
 
-loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec])
+loadPackage :: Interp -> HscEnv -> UnitInfo -> IO ([LibrarySpec], [LibrarySpec], [RemotePtr LoadedDLL])
 loadPackage interp hsc_env pkg
    = do
         let dflags    = hsc_dflags hsc_env
@@ -1124,7 +1126,9 @@ loadPackage interp hsc_env pkg
         let classifieds = hs_classifieds ++ extra_classifieds
 
         -- Complication: all the .so's must be loaded before any of the .o's.
-        let known_dlls = [ dll  | DLLPath dll    <- classifieds ]
+        let known_hs_dlls    = [ dll | DLLPath dll <- hs_classifieds ]
+            known_extra_dlls = [ dll | DLLPath dll <- extra_classifieds ]
+            known_dlls       = known_hs_dlls ++ known_extra_dlls
 #if defined(CAN_LOAD_DLL)
             dlls       = [ dll  | DLL dll        <- classifieds ]
 #endif
@@ -1145,10 +1149,13 @@ loadPackage interp hsc_env pkg
         loadFrameworks interp platform pkg
         -- See Note [Crash early load_dyn and locateLib]
         -- Crash early if can't load any of `known_dlls`
-        mapM_ (load_dyn interp hsc_env True) known_dlls
+        mapM_ (load_dyn interp hsc_env True) known_extra_dlls
+        loaded_dlls <- mapMaybeM (load_dyn interp hsc_env True) known_hs_dlls
         -- For remaining `dlls` crash early only when there is surely
         -- no package's DLL around ... (not is_dyn)
         mapM_ (load_dyn interp hsc_env (not is_dyn) . platformSOName platform) dlls
+#else
+        let loaded_dlls = []
 #endif
         -- After loading all the DLLs, we can load the static objects.
         -- Ordering isn't important here, because we do one final link
@@ -1168,7 +1175,7 @@ loadPackage interp hsc_env pkg
         if succeeded ok
            then do
              maybePutStrLn logger "done."
-             return (hs_classifieds, extra_classifieds)
+             return (hs_classifieds, extra_classifieds, loaded_dlls)
            else let errmsg = text "unable to load unit `"
                              <> pprUnitInfoForUser pkg <> text "'"
                  in throwGhcExceptionIO (InstallationError (showSDoc dflags errmsg))
@@ -1221,19 +1228,20 @@ restriction very easily.
 -- can be passed directly to loadDLL.  They are either fully-qualified
 -- ("/usr/lib/libfoo.so"), or unqualified ("libfoo.so").  In the latter case,
 -- loadDLL is going to search the system paths to find the library.
-load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO ()
+load_dyn :: Interp -> HscEnv -> Bool -> FilePath -> IO (Maybe (RemotePtr LoadedDLL))
 load_dyn interp hsc_env crash_early dll = do
   r <- loadDLL interp dll
   case r of
-    Nothing  -> return ()
-    Just err ->
+    Right loaded_dll -> pure (Just loaded_dll)
+    Left err ->
       if crash_early
         then cmdLineErrorIO err
-        else
+        else do
           when (diag_wopt Opt_WarnMissedExtraSharedLib diag_opts)
             $ logMsg logger
                 (mkMCDiagnostic diag_opts (WarningWithFlag Opt_WarnMissedExtraSharedLib) Nothing)
                   noSrcSpan $ withPprStyle defaultUserStyle (note err)
+          pure Nothing
   where
     diag_opts = initDiagOpts (hsc_dflags hsc_env)
     logger = hsc_logger hsc_env


=====================================
compiler/GHC/Linker/MacOS.hs
=====================================
@@ -172,6 +172,6 @@ loadFramework interp extraPaths rootname
      findLoadDLL (p:ps) errs =
        do { dll <- loadDLL interp (p  fwk_file)
           ; case dll of
-              Nothing  -> return Nothing
-              Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
+              Right _  -> return Nothing
+              Left err -> findLoadDLL ps ((p ++ ": " ++ err):errs)
           }


=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -40,7 +40,8 @@ import GHC.Prelude
 import GHC.Unit                ( UnitId, Module )
 import GHC.ByteCode.Types      ( ItblEnv, AddrEnv, CompiledByteCode )
 import GHC.Fingerprint.Type    ( Fingerprint )
-import GHCi.RemoteTypes        ( ForeignHValue )
+import GHCi.RemoteTypes        ( ForeignHValue, RemotePtr )
+import GHCi.Message            ( LoadedDLL )
 
 import GHC.Types.Var           ( Id )
 import GHC.Types.Name.Env      ( NameEnv, emptyNameEnv, extendNameEnvList, filterNameEnv )
@@ -75,6 +76,53 @@ initialised.
 
 The LinkerEnv maps Names to actual closures (for interpreted code only), for
 use during linking.
+
+Note [Looking up symbols in the relevant objects]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In #23415, we determined that a lot of time (>10s, or even up to >35s!) was
+being spent on dynamically loading symbols before actually interpreting code
+when `:main` was run in GHCi. The root cause was that for each symbol we wanted
+to lookup, we would traverse the list of loaded objects and try find the symbol
+in each of them with dlsym (i.e. looking up a symbol was, worst case, linear in
+the amount of loaded objects).
+
+To drastically improve load time (from +-38 seconds down to +-2s), we now:
+
+1. For every of the native objects loaded for a given unit, store the handles returned by `dlopen`.
+  - In `pkgs_loaded` of the `LoaderState`, which maps `UnitId`s to
+    `LoadedPkgInfo`s, where the handles live in its field `loaded_pkg_hs_dlls`.
+
+2. When looking up a Name (e.g. `lookupHsSymbol`), find that name's `UnitId` in
+    the `pkgs_loaded` mapping,
+
+3. And only look for the symbol (with `dlsym`) on the /handles relevant to that
+    unit/, rather than in every loaded object.
+
+Note [Symbols may not be found in pkgs_loaded]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Currently the `pkgs_loaded` mapping only contains the dynamic objects
+associated with loaded units. Symbols defined in a static object (e.g. from a
+statically-linked Haskell library) are found via the generic `lookupSymbol`
+function call by `lookupHsSymbol` when the symbol is not found in any of the
+dynamic objects of `pkgs_loaded`.
+
+The rationale here is two-fold:
+
+ * we have only observed major link-time issues in dynamic linking; lookups in
+ the RTS linker's static symbol table seem to be fast enough
+
+ * allowing symbol lookups restricted to a single ObjectCode would require the
+ maintenance of a symbol table per `ObjectCode`, which would introduce time and
+ space overhead
+
+This fallback is further needed because we don't look in the haskell objects
+loaded for the home units (see the call to `loadModuleLinkables` in
+`loadDependencies`, as opposed to the call to `loadPackages'` in the same
+function which updates `pkgs_loaded`). We should ultimately keep track of the
+objects loaded (probably in `objs_loaded`, for which `LinkableSet` is a bit
+unsatisfactory, see a suggestion in 51c5c4eb1f2a33e4dc88e6a37b7b7c135234ce9b)
+and be able to lookup symbols specifically in them too (similarly to
+`lookupSymbolInDLL`).
 -}
 
 newtype Loader = Loader { loader_state :: MVar (Maybe LoaderState) }
@@ -146,11 +194,13 @@ data LoadedPkgInfo
   { loaded_pkg_uid         :: !UnitId
   , loaded_pkg_hs_objs     :: ![LibrarySpec]
   , loaded_pkg_non_hs_objs :: ![LibrarySpec]
+  , loaded_pkg_hs_dlls     :: ![RemotePtr LoadedDLL]
+    -- ^ See Note [Looking up symbols in the relevant objects]
   , loaded_pkg_trans_deps  :: UniqDSet UnitId
   }
 
 instance Outputable LoadedPkgInfo where
-  ppr (LoadedPkgInfo uid hs_objs non_hs_objs trans_deps) =
+  ppr (LoadedPkgInfo uid hs_objs non_hs_objs _ trans_deps) =
     vcat [ppr uid
          , ppr hs_objs
          , ppr non_hs_objs
@@ -159,10 +209,10 @@ instance Outputable LoadedPkgInfo where
 
 -- | Information we can use to dynamically link modules into the compiler
 data Linkable = LM {
-  linkableTime     :: !UTCTime,          -- ^ Time at which this linkable was built
+  linkableTime     :: !UTCTime,         -- ^ Time at which this linkable was built
                                         -- (i.e. when the bytecodes were produced,
                                         --       or the mod date on the files)
-  linkableModule   :: !Module,           -- ^ The linkable module itself
+  linkableModule   :: !Module,          -- ^ The linkable module itself
   linkableUnlinked :: [Unlinked]
     -- ^ Those files and chunks of code we have yet to link.
     --


=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -37,6 +37,7 @@ module GHC.Runtime.Interpreter
   -- * The object-code linker
   , initObjLinker
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , loadDLL
   , loadArchive
@@ -478,6 +479,13 @@ lookupSymbol interp str = case interpInstance interp of
 
     ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str)
 
+lookupSymbolInDLL :: Interp -> RemotePtr LoadedDLL -> FastString -> IO (Maybe (Ptr ()))
+lookupSymbolInDLL interp _dll _str = case interpInstance interp of
+#if defined(HAVE_INTERNAL_INTERPRETER)
+  InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL _dll (unpackFS _str))
+#endif
+  ExternalInterp _ -> panic "lookupSymbolInDLL: not implemented for external interpreter" -- FIXME
+
 lookupClosure :: Interp -> String -> IO (Maybe HValueRef)
 lookupClosure interp str =
   interpCmd interp (LookupClosure str)
@@ -496,12 +504,7 @@ purgeLookupSymbolCache interp = case interpInstance interp of
 -- an absolute pathname to the file, or a relative filename
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
---
--- Returns:
---
--- Nothing      => success
--- Just err_msg => failure
-loadDLL :: Interp -> String -> IO (Maybe String)
+loadDLL :: Interp -> String -> IO (Either String (RemotePtr LoadedDLL))
 loadDLL interp str = interpCmd interp (LoadDLL str)
 
 loadArchive :: Interp -> String -> IO ()


=====================================
hadrian/bootstrap/generate_bootstrap_plans
=====================================
@@ -23,6 +23,11 @@ run_all() {
     run "9_4_4"
     run "9_6_1"
     run "9_6_2"
+    run "9_6_3"
+    run "9_6_4"
+    run "9_6_5"
+    run "9_8_1"
+    run "9_8_2"
 }
 
 if (( $# == 0 )); then


=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -21,6 +21,7 @@ module GHCi.Message
   , QState(..)
   , getMessage, putMessage, getTHMessage, putTHMessage
   , Pipe(..), remoteCall, remoteTHCall, readPipe, writePipe
+  , LoadedDLL
   ) where
 
 import Prelude -- See note [Why do we import Prelude here?]
@@ -69,8 +70,9 @@ data Message a where
   -- These all invoke the corresponding functions in the RTS Linker API.
   InitLinker :: Message ()
   LookupSymbol :: String -> Message (Maybe (RemotePtr ()))
+  LookupSymbolInDLL :: RemotePtr LoadedDLL -> String -> Message (Maybe (RemotePtr ()))
   LookupClosure :: String -> Message (Maybe HValueRef)
-  LoadDLL :: String -> Message (Maybe String)
+  LoadDLL :: String -> Message (Either String (RemotePtr LoadedDLL))
   LoadArchive :: String -> Message () -- error?
   LoadObj :: String -> Message () -- error?
   UnloadObj :: String -> Message () -- error?
@@ -394,6 +396,9 @@ data EvalResult a
 
 instance Binary a => Binary (EvalResult a)
 
+-- | A dummy type that tags pointers returned by 'LoadDLL'.
+data LoadedDLL
+
 -- SomeException can't be serialized because it contains dynamic
 -- types.  However, we do very limited things with the exceptions that
 -- are thrown by interpreted computations:
@@ -521,6 +526,7 @@ getMessage = do
       36 -> Msg <$> (Seq <$> get)
       37 -> Msg <$> return RtsRevertCAFs
       38 -> Msg <$> (ResumeSeq <$> get)
+      40 -> Msg <$> (LookupSymbolInDLL <$> get <*> get)
       _  -> error $ "Unknown Message code " ++ (show b)
 
 putMessage :: Message a -> Put
@@ -564,6 +570,7 @@ putMessage m = case m of
   Seq a                       -> putWord8 36 >> put a
   RtsRevertCAFs               -> putWord8 37
   ResumeSeq a                 -> putWord8 38 >> put a
+  LookupSymbolInDLL dll str   -> putWord8 40 >> put dll >> put str
 
 -- -----------------------------------------------------------------------------
 -- Reading/writing messages


=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -18,6 +18,7 @@ module GHCi.ObjLink
   , unloadObj
   , purgeObj
   , lookupSymbol
+  , lookupSymbolInDLL
   , lookupClosure
   , resolveObjs
   , addLibrarySearchPath
@@ -27,18 +28,17 @@ module GHCi.ObjLink
 
 import Prelude -- See note [Why do we import Prelude here?]
 import GHCi.RemoteTypes
+import GHCi.Message (LoadedDLL)
 import Control.Exception (throwIO, ErrorCall(..))
 import Control.Monad    ( when )
 import Foreign.C
-import Foreign.Marshal.Alloc ( free )
-import Foreign          ( nullPtr )
+import Foreign.Marshal.Alloc ( alloca, free )
+import Foreign          ( nullPtr, peek )
 import GHC.Exts
 import System.Posix.Internals ( CFilePath, withFilePath, peekFilePath )
 import System.FilePath  ( dropExtension, normalise )
 
 
-
-
 -- ---------------------------------------------------------------------------
 -- RTS Linker Interface
 -- ---------------------------------------------------------------------------
@@ -70,6 +70,15 @@ lookupSymbol str_in = do
         then return Nothing
         else return (Just addr)
 
+lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
+lookupSymbolInDLL dll str_in = do
+   let str = prefixUnderscore str_in
+   withCAString str $ \c_str -> do
+     addr <- c_lookupSymbolInDLL dll c_str
+     if addr == nullPtr
+       then return Nothing
+       else return (Just addr)
+
 lookupClosure :: String -> IO (Maybe HValueRef)
 lookupClosure str = do
   m <- lookupSymbol str
@@ -89,7 +98,7 @@ prefixUnderscore
 -- (e.g. "libfoo.so" or "foo.dll").  In the latter case, loadDLL
 -- searches the standard locations for the appropriate library.
 --
-loadDLL :: String -> IO (Maybe String)
+loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
 -- Nothing      => success
 -- Just err_msg => failure
 loadDLL str0 = do
@@ -101,12 +110,16 @@ loadDLL str0 = do
      str | isWindowsHost = dropExtension str0
          | otherwise     = str0
   --
-  maybe_errmsg <- withFilePath (normalise str) $ \dll -> c_addDLL dll
-  if maybe_errmsg == nullPtr
-        then return Nothing
-        else do str <- peekCString maybe_errmsg
-                free maybe_errmsg
-                return (Just str)
+  (maybe_handle, maybe_errmsg) <- withFilePath (normalise str) $ \dll ->
+    alloca $ \errmsg_ptr -> (,)
+      <$> c_addDLL dll errmsg_ptr
+      <*> peek errmsg_ptr
+
+  if maybe_handle == nullPtr
+    then do str <- peekCString maybe_errmsg
+            free maybe_errmsg
+            return (Left str)
+    else return (Right maybe_handle)
 
 loadArchive :: String -> IO ()
 loadArchive str = do
@@ -163,7 +176,8 @@ resolveObjs = do
 -- Foreign declarations to RTS entry points which does the real work;
 -- ---------------------------------------------------------------------------
 
-foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> IO CString
+foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL)
+foreign import ccall unsafe "lookupSymbolInDLL"       c_lookupSymbolInDLL       :: Ptr LoadedDLL -> CString -> IO (Ptr a)
 foreign import ccall unsafe "initLinker_"             c_initLinker_             :: CInt -> IO ()
 foreign import ccall unsafe "lookupSymbol"            c_lookupSymbol            :: CString -> IO (Ptr a)
 foreign import ccall unsafe "loadArchive"             c_loadArchive             :: CFilePath -> IO Int


=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -68,7 +68,7 @@ run m = case m of
   LookupClosure str           -> lookupJSClosure str
 #else
   InitLinker -> initObjLinker RetainCAFs
-  LoadDLL str -> loadDLL str
+  LoadDLL str -> fmap toRemotePtr <$> loadDLL str
   LoadArchive str -> loadArchive str
   LoadObj str -> loadObj str
   UnloadObj str -> unloadObj str
@@ -83,6 +83,8 @@ run m = case m of
 #endif
   RtsRevertCAFs -> rts_revertCAFs
   LookupSymbol str -> fmap toRemotePtr <$> lookupSymbol str
+  LookupSymbolInDLL dll str ->
+    fmap toRemotePtr <$> lookupSymbolInDLL (fromRemotePtr dll) str
   FreeHValueRefs rs -> mapM_ freeRemoteRef rs
   AddSptEntry fpr r -> localRef r >>= sptAddEntry fpr
   EvalStmt opts r -> evalStmt opts r


=====================================
rts/Linker.c
=====================================
@@ -578,13 +578,11 @@ typedef
 /* A list thereof. */
 static OpenedSO* openedSOs = NULL;
 
-static const char *
-internal_dlopen(const char *dll_name)
+static void *
+internal_dlopen(const char *dll_name, const char **errmsg_ptr)
 {
    OpenedSO* o_so;
    void *hdl;
-   const char *errmsg;
-   char *errmsg_copy;
 
    // omitted: RTLD_NOW
    // see http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html
@@ -619,14 +617,13 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&ccs_mutex);
 #endif
 
-   errmsg = NULL;
    if (hdl == NULL) {
       /* dlopen failed; return a ptr to the error msg. */
-      errmsg = dlerror();
+      char *errmsg = dlerror();
       if (errmsg == NULL) errmsg = "addDLL: unknown error";
-      errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
+      char *errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
       strcpy(errmsg_copy, errmsg);
-      errmsg = errmsg_copy;
+      *errmsg_ptr = errmsg_copy;
    } else {
       o_so = stgMallocBytes(sizeof(OpenedSO), "addDLL");
       o_so->handle = hdl;
@@ -637,7 +634,7 @@ internal_dlopen(const char *dll_name)
    RELEASE_LOCK(&dl_mutex);
    //--------------- End critical section -------------------
 
-   return errmsg;
+   return hdl;
 }
 
 /*
@@ -725,16 +722,29 @@ internal_dlsym(const char *symbol) {
     // we failed to find the symbol
     return NULL;
 }
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name)
+{
+#if defined(OBJFORMAT_MACHO)
+    CHECK(symbol_name[0] == '_');
+    symbol_name = symbol_name+1;
+#endif
+
+    ACQUIRE_LOCK(&dl_mutex); // dlsym alters dlerror
+    void *result = dlsym(handle, symbol_name);
+    RELEASE_LOCK(&dl_mutex);
+    return result;
+}
 #  endif
 
-const char *
-addDLL( pathchar *dll_name )
+void *addDLL(pathchar* dll_name, const char **errmsg_ptr)
 {
 #  if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
    /* ------------------- ELF DLL loader ------------------- */
 
 #define NMATCH 5
    regmatch_t match[NMATCH];
+   void *handle;
    const char *errmsg;
    FILE* fp;
    size_t match_length;
@@ -743,10 +753,10 @@ addDLL( pathchar *dll_name )
    int result;
 
    IF_DEBUG(linker, debugBelch("addDLL: dll_name = '%s'\n", dll_name));
-   errmsg = internal_dlopen(dll_name);
+   handle = internal_dlopen(dll_name, &errmsg);
 
-   if (errmsg == NULL) {
-      return NULL;
+   if (handle != NULL) {
+      return handle;
    }
 
    // GHC #2615
@@ -775,7 +785,8 @@ addDLL( pathchar *dll_name )
       line[match_length] = '\0'; // make sure string is null-terminated
       IF_DEBUG(linker, debugBelch("file name = '%s'\n", line));
       if ((fp = __rts_fopen(line, "r")) == NULL) {
-         return errmsg; // return original error if open fails
+         *errmsg_ptr = errmsg; // return original error if open fails
+         return NULL;
       }
       // try to find a GROUP or INPUT ( ... ) command
       while (fgets(line, MAXLINE, fp) != NULL) {
@@ -785,7 +796,7 @@ addDLL( pathchar *dll_name )
             IF_DEBUG(linker, debugBelch("match%s\n",""));
             line[match[2].rm_eo] = '\0';
             stgFree((void*)errmsg); // Free old message before creating new one
-            errmsg = internal_dlopen(line+match[2].rm_so);
+            handle = internal_dlopen(line+match[2].rm_so, errmsg_ptr);
             break;
          }
          // if control reaches here, no GROUP or INPUT ( ... ) directive
@@ -794,9 +805,10 @@ addDLL( pathchar *dll_name )
       }
       fclose(fp);
    }
-   return errmsg;
+   return handle;
 
 #  elif defined(OBJFORMAT_PEi386)
+   // FIXME
    return addDLL_PEi386(dll_name, NULL);
 
 #  else


=====================================
rts/RtsSymbols.c
=====================================
@@ -618,6 +618,7 @@ extern char **environ;
       SymI_HasProto(purgeObj)                                           \
       SymI_HasProto(insertSymbol)                                       \
       SymI_HasProto(lookupSymbol)                                       \
+      SymI_HasProto(lookupSymbolInDLL)                                  \
       SymI_HasDataProto(stg_makeStablePtrzh)                                \
       SymI_HasDataProto(stg_mkApUpd0zh)                                     \
       SymI_HasDataProto(stg_labelThreadzh)                                  \


=====================================
rts/include/rts/Linker.h
=====================================
@@ -91,7 +91,9 @@ void *loadNativeObj( pathchar *path, char **errmsg );
 HsInt unloadNativeObj( void *handle );
 
 /* load a dynamic library */
-const char *addDLL( pathchar* dll_name );
+void *addDLL(pathchar* dll_name, const char **errmsg);
+
+void *lookupSymbolInDLL(void *handle, const char *symbol_name);
 
 /* add a path to the library search path */
 HsPtr addLibrarySearchPath(pathchar* dll_path);


=====================================
testsuite/tests/rts/linker/T2615.hs
=====================================
@@ -6,5 +6,5 @@ main = do
   initObjLinker RetainCAFs
   result <- loadDLL library_name
   case result of
-    Nothing -> putStrLn (library_name ++ " loaded successfully")
-    Just x  -> putStrLn ("error: " ++ x)
+    Right _ -> putStrLn (library_name ++ " loaded successfully")
+    Left x  -> putStrLn ("error: " ++ x)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8362bd5cb0bf523312df3d6eefb223232a34d6bd...0e14a98d47808b845890966349cc50d8b92a1a5e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8362bd5cb0bf523312df3d6eefb223232a34d6bd...0e14a98d47808b845890966349cc50d8b92a1a5e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 17:43:13 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Thu, 10 Oct 2024 13:43:13 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] removed unused import
Message-ID: <670812318cfe8_3d0a1b24bcec294ba@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
65e5ca6b by Hassan Al-Awwadi at 2024-10-10T19:41:15+02:00
removed unused import

- - - - -


1 changed file:

- compiler/GHC/Iface/Decl.hs


Changes:

=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -45,8 +45,6 @@ import GHC.Types.Basic
 import GHC.Types.TyThing
 import GHC.Types.SrcLoc
 
-import GHC.Parser.Annotation (noLocA)
-
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/65e5ca6bf5d349ecb4ba1a0df4700c573f5252c8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 18:14:24 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 14:14:24 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 11 commits: Bump directory to
 1.3.8.5
Message-ID: <67081980ed981_3d0a1b551d4c38995@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
c0669a69 by Ben Gamari at 2024-10-10T14:14:11-04:00
Bump directory to 1.3.8.5

Bumps directory submodule.

- - - - -
c5531f83 by Matthew Pickering at 2024-10-10T14:14:17-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* An incorrect version guard on the stack decoding logic in ghc-heap
* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24077

(cherry picked from commit ef3d20f83499cf129b1cacac07906b8d6188fc17)

- - - - -
6e2d2e8a by Andreas Klebinger at 2024-10-10T14:14:17-04:00
NCG: Fix a bug in jump shortcutting.

When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.

We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.

Fixes #24507

(cherry picked from commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66)

- - - - -
5dc9aadc by Ben Gamari at 2024-10-10T14:14:17-04:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

(cherry picked from commit d04f384f35b76a6865dfb3b17098ef69563b3779)

- - - - -
aca115c2 by Matthew Pickering at 2024-10-10T14:14:17-04:00
configure: Correctly set --target flag for linker opts

Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4
arguments, when it only takes 3 arguments. Instead we need to use the
`FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags.

Actually fixes #24414

(cherry picked from commit ab9281a28f260b8f015fe43984ea6690a0669294)

- - - - -
72e3371f by Matthew Pickering at 2024-10-10T14:14:17-04:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

(cherry picked from commit 23f2a478b7dc6b61cab86cf7d0db7fec8a6d9a1f)

- - - - -
864b4721 by Rodrigo Mesquita at 2024-10-10T14:14:17-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

(cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f)

- - - - -
44947481 by Cheng Shao at 2024-10-10T14:14:17-04:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
75890c9f by Ben Gamari at 2024-10-10T14:14:17-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
328503ee by Alexis King at 2024-10-10T14:14:17-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
51b83c51 by Ben Gamari at 2024-10-10T14:14:17-04:00
hadrian: Update bootstrap plans

- - - - -


30 changed files:

- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- distrib/configure.ac.in
- hadrian/README.md
- hadrian/bindist/Makefile
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/src/CommandLine.hs
- hadrian/src/Settings/Builders/Haddock.hs
- hadrian/src/Settings/Packages.hs
- libraries/directory
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- linters/lint-whitespace/lint-whitespace.cabal
- linters/linters-common/linters-common.cabal
- rts/CheckUnload.c


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e14a98d47808b845890966349cc50d8b92a1a5e...51b83c516aac4fad199518305fedda79b74d02e5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e14a98d47808b845890966349cc50d8b92a1a5e...51b83c516aac4fad199518305fedda79b74d02e5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 18:50:59 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 10 Oct 2024 14:50:59 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Put RdrName
 in the foExt field of FieldOcc
Message-ID: <670822137a474_3d0a1b831a3043047@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
bba6167b by Hassan Al-Awwadi at 2024-10-10T12:55:57+02:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
98afbd2e by Cheng Shao at 2024-10-10T14:50:34-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
827d189c by Cristiano Moraes at 2024-10-10T14:50:39-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
6ab213d3 by sheaf at 2024-10-10T14:50:48-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
e815c861 by sheaf at 2024-10-10T14:50:48-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
9ff46f09 by Cheng Shao at 2024-10-10T14:50:48-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
4c02d862 by Ben Gamari at 2024-10-10T14:50:49-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
12c38a48 by Matthew Pickering at 2024-10-10T14:50:50-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ffdcebecb1fdd6431071fb7cae4ce0500164f62c...12c38a48549f24fc666eaadb4e023b279b7e25f8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ffdcebecb1fdd6431071fb7cae4ce0500164f62c...12c38a48549f24fc666eaadb4e023b279b7e25f8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 20:13:09 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 16:13:09 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 12 commits: Bump Cabal to 3.10.3.0
Message-ID: <670835551c5ae_2383171bc0d8943db@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
c4412f8d by Ben Gamari at 2024-10-10T16:11:51-04:00
Bump Cabal to 3.10.3.0

Bumps Cabal submodule.

- - - - -
f52257b8 by Ben Gamari at 2024-10-10T16:11:55-04:00
Bump directory to 1.3.8.5

Bumps directory submodule.

- - - - -
26f300dc by Matthew Pickering at 2024-10-10T16:11:55-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* An incorrect version guard on the stack decoding logic in ghc-heap
* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24077

(cherry picked from commit ef3d20f83499cf129b1cacac07906b8d6188fc17)

- - - - -
44e119c9 by Andreas Klebinger at 2024-10-10T16:11:55-04:00
NCG: Fix a bug in jump shortcutting.

When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.

We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.

Fixes #24507

(cherry picked from commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66)

- - - - -
f97d7fdf by Ben Gamari at 2024-10-10T16:11:55-04:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

(cherry picked from commit d04f384f35b76a6865dfb3b17098ef69563b3779)

- - - - -
96450f76 by Matthew Pickering at 2024-10-10T16:11:55-04:00
configure: Correctly set --target flag for linker opts

Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4
arguments, when it only takes 3 arguments. Instead we need to use the
`FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags.

Actually fixes #24414

(cherry picked from commit ab9281a28f260b8f015fe43984ea6690a0669294)

- - - - -
6e44c088 by Matthew Pickering at 2024-10-10T16:11:56-04:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

(cherry picked from commit 23f2a478b7dc6b61cab86cf7d0db7fec8a6d9a1f)

- - - - -
cb0af2c9 by Rodrigo Mesquita at 2024-10-10T16:11:56-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

(cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f)

- - - - -
26f0b035 by Cheng Shao at 2024-10-10T16:11:56-04:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
03e83bb8 by Ben Gamari at 2024-10-10T16:11:56-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
a1130d49 by Alexis King at 2024-10-10T16:11:56-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
bf04db2e by Ben Gamari at 2024-10-10T16:11:56-04:00
hadrian: Update bootstrap plans

- - - - -


30 changed files:

- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- distrib/configure.ac.in
- hadrian/README.md
- hadrian/bindist/Makefile
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/src/CommandLine.hs
- hadrian/src/Settings/Builders/Haddock.hs
- hadrian/src/Settings/Packages.hs
- libraries/Cabal
- libraries/directory
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- linters/lint-whitespace/lint-whitespace.cabal
- linters/linters-common/linters-common.cabal


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51b83c516aac4fad199518305fedda79b74d02e5...bf04db2eac47fc3eee229ee5822f290de332907c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51b83c516aac4fad199518305fedda79b74d02e5...bf04db2eac47fc3eee229ee5822f290de332907c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 20:34:01 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 16:34:01 -0400
Subject: [Git][ghc/ghc][wip/CLC208] 30 commits: base: Add `HasCallStack`
 constraint to `ioError`
Message-ID: <67083a3961e2f_23831740414c1025a9@gitlab.mail>



Ben Gamari pushed to branch wip/CLC208 at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
1eccd320 by Ben Gamari at 2024-10-10T16:33:53-04:00
ghc-internal: Drop GHC.Internal.Data.Enum

This module consists only of reexports and consequently there is no
reason for it to exist.

- - - - -
65fa0361 by Ben Gamari at 2024-10-10T16:33:53-04:00
base: Introduce Data.Bounded

As proposed in [CLC#208] but unfortunately `Data.Enum` was already
incorrectly introduced in the `ghc-internal` refactor.

[CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208

- - - - -
7735ce15 by Ben Gamari at 2024-10-10T16:33:53-04:00
base: Deprecate export of Bounded from Data.Enum

This begins the process of bringing us into compliance with
[CLC#208].

[CLC#208]: https://github.com/haskell/core-libraries-committee/issues/208

- - - - -
c198bdcf by Ben Gamari at 2024-10-10T16:33:53-04:00
base: Mention incorrect Data.Enum addition in changelog

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4312b0cd44ea988978c8b56169e727fdc7edf191...c198bdcfee3eec3341821108eccf44d001e7a33f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4312b0cd44ea988978c8b56169e727fdc7edf191...c198bdcfee3eec3341821108eccf44d001e7a33f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 20:51:23 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 16:51:23 -0400
Subject: [Git][ghc/ghc][wip/T25066] 30 commits: base: Add `HasCallStack`
 constraint to `ioError`
Message-ID: <67083e4be68b7_2383174041381072c1@gitlab.mail>



Ben Gamari pushed to branch wip/T25066 at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
cc992034 by Ben Gamari at 2024-10-09T16:48:13-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
281becac by Ben Gamari at 2024-10-09T16:48:13-04:00
base: Add test for #25066

- - - - -
7265e2d8 by Ben Gamari at 2024-10-10T16:51:05-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
64ac0a05 by Ben Gamari at 2024-10-10T16:51:05-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/StgToJS/Object.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c7e4fd200bb56f3c8074591cb7adeba04924fff...64ac0a0563ab743006e077f2d74f1410573b8f25

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c7e4fd200bb56f3c8074591cb7adeba04924fff...64ac0a0563ab743006e077f2d74f1410573b8f25
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 21:11:26 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 17:11:26 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] rts: Make addDLL a wrapper around
 loadNativeObj
Message-ID: <670842fec072b_19ff34bedc0470d7@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
34601024 by Rodrigo Mesquita at 2024-10-10T17:09:48-04:00
rts: Make addDLL a wrapper around loadNativeObj

Rewrite the implementation of `addDLL` as a wrapper around the more
principled `loadNativeObj` rts linker function. The latter should be
preferred while the former is preserved for backwards compatibility.

`loadNativeObj` was previously only available on ELF platforms, so this
commit further refactors the rts linker to transform loadNativeObj_ELF
into loadNativeObj_POSIX, which is available in ELF and MachO platforms.

The refactor made it possible to remove the `dl_mutex` mutex in favour
of always using `linker_mutex` (rather than a combination of both).

Lastly, we implement `loadNativeObj` for Windows too.

(cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb)

- - - - -


13 changed files:

- libraries/ghci/GHCi/ObjLink.hs
- rts/Linker.c
- rts/LinkerInternals.h
- rts/RtsSymbols.c
- rts/include/rts/Linker.h
- rts/linker/Elf.c
- rts/linker/Elf.h
- + rts/linker/LoadNativeObjPosix.c
- + rts/linker/LoadNativeObjPosix.h
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- rts/rts.cabal.in
- testsuite/tests/ghci/linking/dyn/T3372.hs


Changes:

=====================================
libraries/ghci/GHCi/ObjLink.hs
=====================================
@@ -74,7 +74,7 @@ lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a))
 lookupSymbolInDLL dll str_in = do
    let str = prefixUnderscore str_in
    withCAString str $ \c_str -> do
-     addr <- c_lookupSymbolInDLL dll c_str
+     addr <- c_lookupSymbolInNativeObj dll c_str
      if addr == nullPtr
        then return Nothing
        else return (Just addr)
@@ -99,8 +99,6 @@ prefixUnderscore
 -- searches the standard locations for the appropriate library.
 --
 loadDLL :: String -> IO (Either String (Ptr LoadedDLL))
--- Nothing      => success
--- Just err_msg => failure
 loadDLL str0 = do
   let
      -- On Windows, addDLL takes a filename without an extension, because
@@ -112,7 +110,7 @@ loadDLL str0 = do
   --
   (maybe_handle, maybe_errmsg) <- withFilePath (normalise str) $ \dll ->
     alloca $ \errmsg_ptr -> (,)
-      <$> c_addDLL dll errmsg_ptr
+      <$> c_loadNativeObj dll errmsg_ptr
       <*> peek errmsg_ptr
 
   if maybe_handle == nullPtr
@@ -176,8 +174,8 @@ resolveObjs = do
 -- Foreign declarations to RTS entry points which does the real work;
 -- ---------------------------------------------------------------------------
 
-foreign import ccall unsafe "addDLL"                  c_addDLL                  :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL)
-foreign import ccall unsafe "lookupSymbolInDLL"       c_lookupSymbolInDLL       :: Ptr LoadedDLL -> CString -> IO (Ptr a)
+foreign import ccall unsafe "loadNativeObj"           c_loadNativeObj           :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL)
+foreign import ccall unsafe "lookupSymbolInNativeObj" c_lookupSymbolInNativeObj :: Ptr LoadedDLL -> CString -> IO (Ptr a)
 foreign import ccall unsafe "initLinker_"             c_initLinker_             :: CInt -> IO ()
 foreign import ccall unsafe "lookupSymbol"            c_lookupSymbol            :: CString -> IO (Ptr a)
 foreign import ccall unsafe "loadArchive"             c_loadArchive             :: CFilePath -> IO Int


=====================================
rts/Linker.c
=====================================
@@ -77,10 +77,16 @@
 #  include 
 #endif
 
+#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
+#  include "linker/LoadNativeObjPosix.h"
+#endif
+
 #if defined(dragonfly_HOST_OS)
 #include 
 #endif
 
+#define UNUSED(x) (void)(x)
+
 /*
  * Note [iconv and FreeBSD]
  * ~~~~~~~~~~~~~~~~~~~~~~~~
@@ -130,7 +136,7 @@ extern void iconv();
    - Indexing (e.g. ocVerifyImage and ocGetNames)
    - Initialization (e.g. ocResolve)
    - RunInit (e.g. ocRunInit)
-   - Lookup (e.g. lookupSymbol)
+   - Lookup (e.g. lookupSymbol/lookupSymbolInNativeObj)
 
    This is to enable lazy loading of symbols. Eager loading is problematic
    as it means that all symbols must be available, even those which we will
@@ -417,11 +423,8 @@ static int linker_init_done = 0 ;
 
 #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
 static void *dl_prog_handle;
-static regex_t re_invalid;
-static regex_t re_realso;
-#if defined(THREADED_RTS)
-Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section
-#endif
+regex_t re_invalid;
+regex_t re_realso;
 #endif
 
 void initLinker (void)
@@ -455,9 +458,6 @@ initLinker_ (int retain_cafs)
 
 #if defined(THREADED_RTS)
     initMutex(&linker_mutex);
-#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
-    initMutex(&dl_mutex);
-#endif
 #endif
 
     symhash = allocStrHashTable();
@@ -520,9 +520,6 @@ exitLinker( void ) {
    if (linker_init_done == 1) {
       regfree(&re_invalid);
       regfree(&re_realso);
-#if defined(THREADED_RTS)
-      closeMutex(&dl_mutex);
-#endif
    }
 #endif
    if (linker_init_done == 1) {
@@ -556,87 +553,6 @@ exitLinker( void ) {
 
 #  if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
 
-/* Suppose in ghci we load a temporary SO for a module containing
-       f = 1
-   and then modify the module, recompile, and load another temporary
-   SO with
-       f = 2
-   Then as we don't unload the first SO, dlsym will find the
-       f = 1
-   symbol whereas we want the
-       f = 2
-   symbol. We therefore need to keep our own SO handle list, and
-   try SOs in the right order. */
-
-typedef
-   struct _OpenedSO {
-      struct _OpenedSO* next;
-      void *handle;
-   }
-   OpenedSO;
-
-/* A list thereof. */
-static OpenedSO* openedSOs = NULL;
-
-static void *
-internal_dlopen(const char *dll_name, const char **errmsg_ptr)
-{
-   OpenedSO* o_so;
-   void *hdl;
-
-   // omitted: RTLD_NOW
-   // see http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html
-   IF_DEBUG(linker,
-      debugBelch("internal_dlopen: dll_name = '%s'\n", dll_name));
-
-   //-------------- Begin critical section ------------------
-   // This critical section is necessary because dlerror() is not
-   // required to be reentrant (see POSIX -- IEEE Std 1003.1-2008)
-   // Also, the error message returned must be copied to preserve it
-   // (see POSIX also)
-
-   ACQUIRE_LOCK(&dl_mutex);
-
-   // When dlopen() loads a profiled dynamic library, it calls the
-   // ctors which will call registerCcsList() to append the defined
-   // CostCentreStacks to CCS_LIST. This execution path starting from
-   // addDLL() was only protected by dl_mutex previously. However,
-   // another thread may be doing other things with the RTS linker
-   // that transitively calls refreshProfilingCCSs() which also
-   // accesses CCS_LIST, and those execution paths are protected by
-   // linker_mutex. So there's a risk of data race that may lead to
-   // segfaults (#24423), and we need to ensure the ctors are also
-   // protected by ccs_mutex.
-#if defined(PROFILING)
-   ACQUIRE_LOCK(&ccs_mutex);
-#endif
-
-   hdl = dlopen(dll_name, RTLD_LAZY|RTLD_LOCAL); /* see Note [RTLD_LOCAL] */
-
-#if defined(PROFILING)
-   RELEASE_LOCK(&ccs_mutex);
-#endif
-
-   if (hdl == NULL) {
-      /* dlopen failed; return a ptr to the error msg. */
-      char *errmsg = dlerror();
-      if (errmsg == NULL) errmsg = "addDLL: unknown error";
-      char *errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL");
-      strcpy(errmsg_copy, errmsg);
-      *errmsg_ptr = errmsg_copy;
-   } else {
-      o_so = stgMallocBytes(sizeof(OpenedSO), "addDLL");
-      o_so->handle = hdl;
-      o_so->next   = openedSOs;
-      openedSOs    = o_so;
-   }
-
-   RELEASE_LOCK(&dl_mutex);
-   //--------------- End critical section -------------------
-
-   return hdl;
-}
-
 /*
   Note [RTLD_LOCAL]
   ~~~~~~~~~~~~~~~~~
@@ -657,11 +573,10 @@ internal_dlopen(const char *dll_name, const char **errmsg_ptr)
 
 static void *
 internal_dlsym(const char *symbol) {
-    OpenedSO* o_so;
     void *v;
 
-    // We acquire dl_mutex as concurrent dl* calls may alter dlerror
-    ACQUIRE_LOCK(&dl_mutex);
+    // concurrent dl* calls may alter dlerror
+    ASSERT_LOCK_HELD(&linker_mutex);
 
     // clears dlerror
     dlerror();
@@ -669,20 +584,19 @@ internal_dlsym(const char *symbol) {
     // look in program first
     v = dlsym(dl_prog_handle, symbol);
     if (dlerror() == NULL) {
-        RELEASE_LOCK(&dl_mutex);
         IF_DEBUG(linker, debugBelch("internal_dlsym: found symbol '%s' in program\n", symbol));
         return v;
     }
 
-    for (o_so = openedSOs; o_so != NULL; o_so = o_so->next) {
-        v = dlsym(o_so->handle, symbol);
-        if (dlerror() == NULL) {
+    for (ObjectCode *nc = loaded_objects; nc; nc = nc->next_loaded_object) {
+        if (nc->type == DYNAMIC_OBJECT) {
+          v = dlsym(nc->dlopen_handle, symbol);
+          if (dlerror() == NULL) {
             IF_DEBUG(linker, debugBelch("internal_dlsym: found symbol '%s' in shared object\n", symbol));
-            RELEASE_LOCK(&dl_mutex);
             return v;
+          }
         }
     }
-    RELEASE_LOCK(&dl_mutex);
 
     IF_DEBUG(linker, debugBelch("internal_dlsym: looking for symbol '%s' in special cases\n", symbol));
 #   define SPECIAL_SYMBOL(sym) \
@@ -722,98 +636,42 @@ internal_dlsym(const char *symbol) {
     // we failed to find the symbol
     return NULL;
 }
+#  endif
 
-void *lookupSymbolInDLL(void *handle, const char *symbol_name)
+void *lookupSymbolInNativeObj(void *handle, const char *symbol_name)
 {
+    ACQUIRE_LOCK(&linker_mutex);
+
 #if defined(OBJFORMAT_MACHO)
+    // The Mach-O standard says ccall symbols representing a function are prefixed with _
+    // https://math-atlas.sourceforge.net/devel/assembly/MachORuntime.pdf
     CHECK(symbol_name[0] == '_');
     symbol_name = symbol_name+1;
 #endif
-
-    ACQUIRE_LOCK(&dl_mutex); // dlsym alters dlerror
+#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
     void *result = dlsym(handle, symbol_name);
-    RELEASE_LOCK(&dl_mutex);
+#elif defined(OBJFORMAT_PEi386)
+    void *result = lookupSymbolInDLL_PEi386(symbol_name, handle, NULL, NULL);
+#else
+    void* result;
+    UNUSED(handle);
+    UNUSED(symbol_name);
+    barf("lookupSymbolInNativeObj: Unsupported platform");
+#endif
+
+    RELEASE_LOCK(&linker_mutex);
     return result;
 }
-#  endif
 
-void *addDLL(pathchar* dll_name, const char **errmsg_ptr)
+const char *addDLL(pathchar* dll_name)
 {
-#  if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
-   /* ------------------- ELF DLL loader ------------------- */
-
-#define NMATCH 5
-   regmatch_t match[NMATCH];
-   void *handle;
-   const char *errmsg;
-   FILE* fp;
-   size_t match_length;
-#define MAXLINE 1000
-   char line[MAXLINE];
-   int result;
-
-   IF_DEBUG(linker, debugBelch("addDLL: dll_name = '%s'\n", dll_name));
-   handle = internal_dlopen(dll_name, &errmsg);
-
-   if (handle != NULL) {
-      return handle;
-   }
-
-   // GHC #2615
-   // On some systems (e.g., Gentoo Linux) dynamic files (e.g. libc.so)
-   // contain linker scripts rather than ELF-format object code. This
-   // code handles the situation by recognizing the real object code
-   // file name given in the linker script.
-   //
-   // If an "invalid ELF header" error occurs, it is assumed that the
-   // .so file contains a linker script instead of ELF object code.
-   // In this case, the code looks for the GROUP ( ... ) linker
-   // directive. If one is found, the first file name inside the
-   // parentheses is treated as the name of a dynamic library and the
-   // code attempts to dlopen that file. If this is also unsuccessful,
-   // an error message is returned.
-
-   // see if the error message is due to an invalid ELF header
-   IF_DEBUG(linker, debugBelch("errmsg = '%s'\n", errmsg));
-   result = regexec(&re_invalid, errmsg, (size_t) NMATCH, match, 0);
-   IF_DEBUG(linker, debugBelch("result = %i\n", result));
-   if (result == 0) {
-      // success -- try to read the named file as a linker script
-      match_length = (size_t) stg_min((match[1].rm_eo - match[1].rm_so),
-                                 MAXLINE-1);
-      strncpy(line, (errmsg+(match[1].rm_so)),match_length);
-      line[match_length] = '\0'; // make sure string is null-terminated
-      IF_DEBUG(linker, debugBelch("file name = '%s'\n", line));
-      if ((fp = __rts_fopen(line, "r")) == NULL) {
-         *errmsg_ptr = errmsg; // return original error if open fails
-         return NULL;
-      }
-      // try to find a GROUP or INPUT ( ... ) command
-      while (fgets(line, MAXLINE, fp) != NULL) {
-         IF_DEBUG(linker, debugBelch("input line = %s", line));
-         if (regexec(&re_realso, line, (size_t) NMATCH, match, 0) == 0) {
-            // success -- try to dlopen the first named file
-            IF_DEBUG(linker, debugBelch("match%s\n",""));
-            line[match[2].rm_eo] = '\0';
-            stgFree((void*)errmsg); // Free old message before creating new one
-            handle = internal_dlopen(line+match[2].rm_so, errmsg_ptr);
-            break;
-         }
-         // if control reaches here, no GROUP or INPUT ( ... ) directive
-         // was found and the original error message is returned to the
-         // caller
-      }
-      fclose(fp);
+   char *errmsg;
+   if (loadNativeObj(dll_name, &errmsg)) {
+     return NULL;
+   } else {
+     ASSERT(errmsg != NULL);
+     return errmsg;
    }
-   return handle;
-
-#  elif defined(OBJFORMAT_PEi386)
-   // FIXME
-   return addDLL_PEi386(dll_name, NULL);
-
-#  else
-   barf("addDLL: not implemented on this platform");
-#  endif
 }
 
 /* -----------------------------------------------------------------------------
@@ -1246,10 +1104,10 @@ void freeObjectCode (ObjectCode *oc)
     }
 
     if (oc->type == DYNAMIC_OBJECT) {
-#if defined(OBJFORMAT_ELF)
-        ACQUIRE_LOCK(&dl_mutex);
-        freeNativeCode_ELF(oc);
-        RELEASE_LOCK(&dl_mutex);
+#if defined(OBJFORMAT_ELF) || defined(darwin_HOST_OS)
+        ACQUIRE_LOCK(&linker_mutex);
+        freeNativeCode_POSIX(oc);
+        RELEASE_LOCK(&linker_mutex);
 #else
         barf("freeObjectCode: This shouldn't happen");
 #endif
@@ -1913,12 +1771,20 @@ HsInt purgeObj (pathchar *path)
     return r;
 }
 
+ObjectCode *lookupObjectByPath(pathchar *path) {
+  for (ObjectCode *o = objects; o; o = o->next) {
+     if (0 == pathcmp(o->fileName, path)) {
+         return o;
+     }
+  }
+  return NULL;
+}
+
 OStatus getObjectLoadStatus_ (pathchar *path)
 {
-    for (ObjectCode *o = objects; o; o = o->next) {
-       if (0 == pathcmp(o->fileName, path)) {
-           return o->status;
-       }
+    ObjectCode *oc = lookupObjectByPath(path);
+    if (oc) {
+      return oc->status;
     }
     return OBJECT_NOT_LOADED;
 }
@@ -2003,27 +1869,35 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc,
                        size, kind ));
 }
 
-#define UNUSED(x) (void)(x)
-
-#if defined(OBJFORMAT_ELF)
 void * loadNativeObj (pathchar *path, char **errmsg)
 {
+   IF_DEBUG(linker, debugBelch("loadNativeObj: path = '%" PATH_FMT "'\n", path));
    ACQUIRE_LOCK(&linker_mutex);
-   void *r = loadNativeObj_ELF(path, errmsg);
-   RELEASE_LOCK(&linker_mutex);
-   return r;
-}
+
+#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
+   void *r = loadNativeObj_POSIX(path, errmsg);
+#elif defined(OBJFORMAT_PEi386)
+   void *r = NULL;
+   *errmsg = (char*)addDLL_PEi386(path, (HINSTANCE*)&r);
 #else
-void * STG_NORETURN
-loadNativeObj (pathchar *path, char **errmsg)
-{
-   UNUSED(path);
+   void *r;
    UNUSED(errmsg);
    barf("loadNativeObj: not implemented on this platform");
-}
 #endif
 
-HsInt unloadNativeObj (void *handle)
+#if defined(OBJFORMAT_ELF)
+   if (!r) {
+       // Check if native object may be a linker script and try loading a native
+       // object from it
+       r = loadNativeObjFromLinkerScript_ELF(errmsg);
+   }
+#endif
+
+   RELEASE_LOCK(&linker_mutex);
+   return r;
+}
+
+static HsInt unloadNativeObj_(void *handle)
 {
     bool unloadedAnyObj = false;
 
@@ -2056,11 +1930,18 @@ HsInt unloadNativeObj (void *handle)
     if (unloadedAnyObj) {
         return 1;
     } else {
-        errorBelch("unloadObjNativeObj_ELF: can't find `%p' to unload", handle);
+        errorBelch("unloadObjNativeObj_: can't find `%p' to unload", handle);
         return 0;
     }
 }
 
+HsInt unloadNativeObj(void *handle) {
+  ACQUIRE_LOCK(&linker_mutex);
+  HsInt r = unloadNativeObj_(handle);
+  RELEASE_LOCK(&linker_mutex);
+  return r;
+}
+
 /* -----------------------------------------------------------------------------
  * Segment management
  */


=====================================
rts/LinkerInternals.h
=====================================
@@ -412,10 +412,6 @@ extern Elf_Word shndx_table_uninit_label;
 
 #if defined(THREADED_RTS)
 extern Mutex linker_mutex;
-
-#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
-extern Mutex dl_mutex;
-#endif
 #endif /* THREADED_RTS */
 
 /* Type of an initializer */
@@ -515,9 +511,9 @@ HsInt loadArchive_ (pathchar *path);
 #define USE_CONTIGUOUS_MMAP 0
 #endif
 
-
 HsInt isAlreadyLoaded( pathchar *path );
 OStatus getObjectLoadStatus_ (pathchar *path);
+ObjectCode *lookupObjectByPath(pathchar *path);
 HsInt loadOc( ObjectCode* oc );
 ObjectCode* mkOc( ObjectType type, pathchar *path, char *image, int imageSize,
                   bool mapped, pathchar *archiveMemberName,


=====================================
rts/RtsSymbols.c
=====================================
@@ -508,6 +508,7 @@ extern char **environ;
       SymI_HasDataProto(stg_block_putmvar)                                  \
       MAIN_CAP_SYM                                                      \
       SymI_HasProto(addDLL)                                             \
+      SymI_HasProto(loadNativeObj)                                      \
       SymI_HasProto(addLibrarySearchPath)                               \
       SymI_HasProto(removeLibrarySearchPath)                            \
       SymI_HasProto(findSystemLibrary)                                  \
@@ -618,7 +619,7 @@ extern char **environ;
       SymI_HasProto(purgeObj)                                           \
       SymI_HasProto(insertSymbol)                                       \
       SymI_HasProto(lookupSymbol)                                       \
-      SymI_HasProto(lookupSymbolInDLL)                                  \
+      SymI_HasProto(lookupSymbolInNativeObj)                            \
       SymI_HasDataProto(stg_makeStablePtrzh)                                \
       SymI_HasDataProto(stg_mkApUpd0zh)                                     \
       SymI_HasDataProto(stg_labelThreadzh)                                  \


=====================================
rts/include/rts/Linker.h
=====================================
@@ -90,10 +90,10 @@ void *loadNativeObj( pathchar *path, char **errmsg );
    Takes the handle returned from loadNativeObj() as an argument. */
 HsInt unloadNativeObj( void *handle );
 
-/* load a dynamic library */
-void *addDLL(pathchar* dll_name, const char **errmsg);
+void *lookupSymbolInNativeObj(void *handle, const char *symbol_name);
 
-void *lookupSymbolInDLL(void *handle, const char *symbol_name);
+/* load a dynamic library */
+const char *addDLL(pathchar* dll_name);
 
 /* add a path to the library search path */
 HsPtr addLibrarySearchPath(pathchar* dll_path);


=====================================
rts/linker/Elf.c
=====================================
@@ -27,11 +27,15 @@
 #include "sm/OSMem.h"
 #include "linker/util.h"
 #include "linker/elf_util.h"
+#include "linker/LoadNativeObjPosix.h"
 
+#include 
 #include 
 #include 
 #include 
 #include 
+#include     // regex is already used by dlopen() so this is OK
+                      // to use here without requiring an additional lib
 #if defined(HAVE_DLFCN_H)
 #include 
 #endif
@@ -2071,159 +2075,6 @@ int ocRunFini_ELF( ObjectCode *oc )
     return true;
 }
 
-/*
- * Shared object loading
- */
-
-#if defined(HAVE_DLINFO)
-struct piterate_cb_info {
-  ObjectCode *nc;
-  void *l_addr;   /* base virtual address of the loaded code */
-};
-
-static int loadNativeObjCb_(struct dl_phdr_info *info,
-    size_t _size STG_UNUSED, void *data) {
-  struct piterate_cb_info *s = (struct piterate_cb_info *) data;
-
-  // This logic mimicks _dl_addr_inside_object from glibc
-  // For reference:
-  // int
-  // internal_function
-  // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr)
-  // {
-  //   int n = l->l_phnum;
-  //   const ElfW(Addr) reladdr = addr - l->l_addr;
-  //
-  //   while (--n >= 0)
-  //     if (l->l_phdr[n].p_type == PT_LOAD
-  //         && reladdr - l->l_phdr[n].p_vaddr >= 0
-  //         && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz)
-  //       return 1;
-  //   return 0;
-  // }
-
-  if ((void*) info->dlpi_addr == s->l_addr) {
-    int n = info->dlpi_phnum;
-    while (--n >= 0) {
-      if (info->dlpi_phdr[n].p_type == PT_LOAD) {
-        NativeCodeRange* ncr =
-          stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_");
-        ncr->start = (void*) ((char*) s->l_addr + info->dlpi_phdr[n].p_vaddr);
-        ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz);
-
-        ncr->next = s->nc->nc_ranges;
-        s->nc->nc_ranges = ncr;
-      }
-    }
-  }
-  return 0;
-}
-#endif /* defined(HAVE_DLINFO) */
-
-static void copyErrmsg(char** errmsg_dest, char* errmsg) {
-  if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error";
-  *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF");
-  strcpy(*errmsg_dest, errmsg);
-}
-
-// need dl_mutex
-void freeNativeCode_ELF (ObjectCode *nc) {
-  dlclose(nc->dlopen_handle);
-
-  NativeCodeRange *ncr = nc->nc_ranges;
-  while (ncr) {
-    NativeCodeRange* last_ncr = ncr;
-    ncr = ncr->next;
-    stgFree(last_ncr);
-  }
-}
-
-void * loadNativeObj_ELF (pathchar *path, char **errmsg)
-{
-   ObjectCode* nc;
-   void *hdl, *retval;
-
-   IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path));
-
-   retval = NULL;
-   ACQUIRE_LOCK(&dl_mutex);
-
-   /* Loading the same object multiple times will lead to chaos
-    * as we will have two ObjectCodes but one underlying dlopen
-    * handle. Fail if this happens.
-    */
-   if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) {
-     copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded");
-     goto dlopen_fail;
-   }
-
-   nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0);
-
-   foreignExportsLoadingObject(nc);
-   hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL);
-   nc->dlopen_handle = hdl;
-   foreignExportsFinishedLoadingObject();
-   if (hdl == NULL) {
-     /* dlopen failed; save the message in errmsg */
-     copyErrmsg(errmsg, dlerror());
-     goto dlopen_fail;
-   }
-
-#if defined(HAVE_DLINFO)
-   struct link_map *map;
-   if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) {
-     /* dlinfo failed; save the message in errmsg */
-     copyErrmsg(errmsg, dlerror());
-     goto dlinfo_fail;
-   }
-
-   hdl = NULL; // pass handle ownership to nc
-
-   struct piterate_cb_info piterate_info = {
-     .nc = nc,
-     .l_addr = (void *) map->l_addr
-   };
-   dl_iterate_phdr(loadNativeObjCb_, &piterate_info);
-   if (!nc->nc_ranges) {
-     copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj");
-     goto dl_iterate_phdr_fail;
-   }
-   nc->unloadable = true;
-#else
-   nc->nc_ranges = NULL;
-   nc->unloadable = false;
-#endif /* defined (HAVE_DLINFO) */
-
-   insertOCSectionIndices(nc);
-
-   nc->next_loaded_object = loaded_objects;
-   loaded_objects = nc;
-
-   retval = nc->dlopen_handle;
-
-#if defined(PROFILING)
-  // collect any new cost centres that were defined in the loaded object.
-  refreshProfilingCCSs();
-#endif
-
-   goto success;
-
-dl_iterate_phdr_fail:
-   // already have dl_mutex
-   freeNativeCode_ELF(nc);
-dlinfo_fail:
-   if (hdl) dlclose(hdl);
-dlopen_fail:
-success:
-
-   RELEASE_LOCK(&dl_mutex);
-
-   IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval));
-
-   return retval;
-}
-
-
 /*
  * PowerPC & X86_64 ELF specifics
  */
@@ -2273,4 +2124,80 @@ int ocAllocateExtras_ELF( ObjectCode *oc )
 
 #endif /* NEED_SYMBOL_EXTRAS */
 
+extern regex_t re_invalid;
+extern regex_t re_realso;
+
+// Try interpreting an object which couldn't be loaded as a linker script and
+// load the first object in the linker GROUP ( ... ) directive (see comment below).
+//
+// Receives the non-NULL error message outputted from an attempt to load an
+// object (eg `loadNativeObj_POSIX` ).
+//
+// Returns the handle to the loaded object first mentioned in the linker script.
+// If this process fails at any point, the function returns NULL and outputs a
+// new error message.
+void * loadNativeObjFromLinkerScript_ELF(char **errmsg)
+{
+   // GHC #2615
+   // On some systems (e.g., Gentoo Linux) dynamic files (e.g. libc.so)
+   // contain linker scripts rather than ELF-format object code. This
+   // code handles the situation by recognizing the real object code
+   // file name given in the linker script.
+   //
+   // If an "invalid ELF header" error occurs, it is assumed that the
+   // .so file contains a linker script instead of ELF object code.
+   // In this case, the code looks for the GROUP ( ... ) linker
+   // directive. If one is found, the first file name inside the
+   // parentheses is treated as the name of a dynamic library and the
+   // code attempts to dlopen that file. If this is also unsuccessful,
+   // an error message is returned.
+
+#define NMATCH 5
+   regmatch_t match[NMATCH];
+   FILE* fp;
+   size_t match_length;
+#define MAXLINE 1000
+   char line[MAXLINE];
+   int result;
+   void* r = NULL;
+
+   ASSERT_LOCK_HELD(&linker_mutex);
+
+   // see if the error message is due to an invalid ELF header
+   IF_DEBUG(linker, debugBelch("errmsg = '%s'\n", *errmsg));
+   result = regexec(&re_invalid, *errmsg, (size_t) NMATCH, match, 0);
+   IF_DEBUG(linker, debugBelch("result = %i\n", result));
+   if (result == 0) {
+      // success -- try to read the named file as a linker script
+      match_length = (size_t) stg_min((match[1].rm_eo - match[1].rm_so),
+                                 MAXLINE-1);
+      strncpy(line, (*errmsg+(match[1].rm_so)),match_length);
+      line[match_length] = '\0'; // make sure string is null-terminated
+      IF_DEBUG(linker, debugBelch("file name = '%s'\n", line));
+      if ((fp = __rts_fopen(line, "r")) == NULL) {
+         // return original error if open fails
+         return NULL;
+      }
+      // try to find a GROUP or INPUT ( ... ) command
+      while (fgets(line, MAXLINE, fp) != NULL) {
+         IF_DEBUG(linker, debugBelch("input line = %s", line));
+         if (regexec(&re_realso, line, (size_t) NMATCH, match, 0) == 0) {
+            // success -- try to dlopen the first named file
+            IF_DEBUG(linker, debugBelch("match%s\n",""));
+            line[match[2].rm_eo] = '\0';
+            stgFree((void*)*errmsg); // Free old message before creating new one
+            r = loadNativeObj_POSIX(line+match[2].rm_so, errmsg);
+            break;
+         }
+         // if control reaches here, no GROUP or INPUT ( ... ) directive
+         // was found and the original error message is returned to the
+         // caller
+      }
+      fclose(fp);
+   }
+
+   return r;
+}
+
+
 #endif /* elf */


=====================================
rts/linker/Elf.h
=====================================
@@ -14,7 +14,6 @@ int ocResolve_ELF        ( ObjectCode* oc );
 int ocRunInit_ELF        ( ObjectCode* oc );
 int ocRunFini_ELF        ( ObjectCode* oc );
 int ocAllocateExtras_ELF ( ObjectCode *oc );
-void freeNativeCode_ELF  ( ObjectCode *nc );
-void *loadNativeObj_ELF  ( pathchar *path, char **errmsg );
+void *loadNativeObjFromLinkerScript_ELF( char **errmsg );
 
 #include "EndPrivate.h"


=====================================
rts/linker/LoadNativeObjPosix.c
=====================================
@@ -0,0 +1,214 @@
+#include "LinkerInternals.h"
+#include "Rts.h"
+
+#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO)
+
+#include "CheckUnload.h"
+#include "ForeignExports.h"
+#include "RtsUtils.h"
+#include "Profiling.h"
+
+#include "linker/LoadNativeObjPosix.h"
+
+#if defined(HAVE_DLFCN_H)
+#include 
+#endif
+
+#if defined(HAVE_DLINFO)
+#include 
+#endif
+
+#include 
+
+/*
+ * Shared object loading
+ */
+
+#if defined(HAVE_DLINFO)
+struct piterate_cb_info {
+  ObjectCode *nc;
+  void *l_addr;   /* base virtual address of the loaded code */
+};
+
+static int loadNativeObjCb_(struct dl_phdr_info *info,
+    size_t _size STG_UNUSED, void *data) {
+  struct piterate_cb_info *s = (struct piterate_cb_info *) data;
+
+  // This logic mimicks _dl_addr_inside_object from glibc
+  // For reference:
+  // int
+  // internal_function
+  // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr)
+  // {
+  //   int n = l->l_phnum;
+  //   const ElfW(Addr) reladdr = addr - l->l_addr;
+  //
+  //   while (--n >= 0)
+  //     if (l->l_phdr[n].p_type == PT_LOAD
+  //         && reladdr - l->l_phdr[n].p_vaddr >= 0
+  //         && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz)
+  //       return 1;
+  //   return 0;
+  // }
+
+  if ((void*) info->dlpi_addr == s->l_addr) {
+    int n = info->dlpi_phnum;
+    while (--n >= 0) {
+      if (info->dlpi_phdr[n].p_type == PT_LOAD) {
+        NativeCodeRange* ncr =
+          stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_");
+        ncr->start = (void*) ((char*) s->l_addr + info->dlpi_phdr[n].p_vaddr);
+        ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz);
+
+        ncr->next = s->nc->nc_ranges;
+        s->nc->nc_ranges = ncr;
+      }
+    }
+  }
+  return 0;
+}
+#endif /* defined(HAVE_DLINFO) */
+
+static void copyErrmsg(char** errmsg_dest, char* errmsg) {
+  if (errmsg == NULL) errmsg = "loadNativeObj_POSIX: unknown error";
+  *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_POSIX");
+  strcpy(*errmsg_dest, errmsg);
+}
+
+void freeNativeCode_POSIX (ObjectCode *nc) {
+  ASSERT_LOCK_HELD(&linker_mutex);
+
+  dlclose(nc->dlopen_handle);
+
+  NativeCodeRange *ncr = nc->nc_ranges;
+  while (ncr) {
+    NativeCodeRange* last_ncr = ncr;
+    ncr = ncr->next;
+    stgFree(last_ncr);
+  }
+}
+
+void * loadNativeObj_POSIX (pathchar *path, char **errmsg)
+{
+   ObjectCode* nc;
+   void *hdl, *retval;
+
+   ASSERT_LOCK_HELD(&linker_mutex);
+
+   IF_DEBUG(linker, debugBelch("loadNativeObj_POSIX %" PATH_FMT "\n", path));
+
+   retval = NULL;
+
+
+   /* If we load the same object multiple times, just return the
+    * already-loaded handle. Note that this is broken if unloadNativeObj
+    * is used, as we don’t do any reference counting; see #24345.
+    */
+   ObjectCode *existing_oc = lookupObjectByPath(path);
+   if (existing_oc && existing_oc->status != OBJECT_UNLOADED) {
+     if (existing_oc->type == DYNAMIC_OBJECT) {
+       retval = existing_oc->dlopen_handle;
+       goto success;
+     }
+     copyErrmsg(errmsg, "loadNativeObj_POSIX: already loaded as non-dynamic object");
+     goto dlopen_fail;
+   }
+
+   nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0);
+
+   foreignExportsLoadingObject(nc);
+
+   // When dlopen() loads a profiled dynamic library, it calls the ctors which
+   // will call registerCcsList() to append the defined CostCentreStacks to
+   // CCS_LIST. However, another thread may be doing other things with the RTS
+   // linker that transitively calls refreshProfilingCCSs() which also accesses
+   // CCS_LIST. So there's a risk of data race that may lead to segfaults
+   // (#24423), and we need to ensure the ctors are also protected by
+   // ccs_mutex.
+#if defined(PROFILING)
+   ACQUIRE_LOCK(&ccs_mutex);
+#endif
+
+   // If we HAVE_DLINFO, we use RTLD_NOW rather than RTLD_LAZY because we want
+   // to learn eagerly about all external functions. Otherwise, there is no
+   // additional advantage to being eager, so it is better to be lazy and only bind
+   // functions when needed for better performance.
+   int dlopen_mode;
+#if defined(HAVE_DLINFO)
+   dlopen_mode = RTLD_NOW;
+#else
+   dlopen_mode = RTLD_LAZY;
+#endif
+
+   hdl = dlopen(path, dlopen_mode|RTLD_LOCAL); /* see Note [RTLD_LOCAL] */
+   nc->dlopen_handle = hdl;
+   nc->status = OBJECT_READY;
+
+#if defined(PROFILING)
+   RELEASE_LOCK(&ccs_mutex);
+#endif
+
+   foreignExportsFinishedLoadingObject();
+
+   if (hdl == NULL) {
+     /* dlopen failed; save the message in errmsg */
+     copyErrmsg(errmsg, dlerror());
+     goto dlopen_fail;
+   }
+
+#if defined(HAVE_DLINFO)
+   struct link_map *map;
+   if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) {
+     /* dlinfo failed; save the message in errmsg */
+     copyErrmsg(errmsg, dlerror());
+     goto dlinfo_fail;
+   }
+
+   hdl = NULL; // pass handle ownership to nc
+
+   struct piterate_cb_info piterate_info = {
+     .nc = nc,
+     .l_addr = (void *) map->l_addr
+   };
+   dl_iterate_phdr(loadNativeObjCb_, &piterate_info);
+   if (!nc->nc_ranges) {
+     copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj");
+     goto dl_iterate_phdr_fail;
+   }
+   nc->unloadable = true;
+#else
+   nc->nc_ranges = NULL;
+   nc->unloadable = false;
+#endif /* defined (HAVE_DLINFO) */
+
+   insertOCSectionIndices(nc);
+
+   nc->next_loaded_object = loaded_objects;
+   loaded_objects = nc;
+
+   retval = nc->dlopen_handle;
+
+#if defined(PROFILING)
+  // collect any new cost centres that were defined in the loaded object.
+  refreshProfilingCCSs();
+#endif
+
+   goto success;
+
+#if defined(HAVE_DLINFO)
+dl_iterate_phdr_fail:
+#endif
+   freeNativeCode_POSIX(nc);
+#if defined(HAVE_DLINFO)
+dlinfo_fail:
+#endif
+   if (hdl) dlclose(hdl);
+dlopen_fail:
+success:
+
+   IF_DEBUG(linker, debugBelch("loadNativeObj_POSIX result=%p\n", retval));
+
+   return retval;
+}
+
+#endif /* elf + macho */


=====================================
rts/linker/LoadNativeObjPosix.h
=====================================
@@ -0,0 +1,11 @@
+#pragma once
+
+#include "Rts.h"
+#include "LinkerInternals.h"
+
+#include "BeginPrivate.h"
+
+void freeNativeCode_POSIX  ( ObjectCode *nc );
+void *loadNativeObj_POSIX  ( pathchar *path, char **errmsg );
+
+#include "EndPrivate.h"


=====================================
rts/linker/PEi386.c
=====================================
@@ -867,6 +867,7 @@ error:
     stgFree(buf);
 
     char* errormsg = stgMallocBytes(sizeof(char) * 80, "addDLL_PEi386");
+    if (loaded) *loaded = NULL;
     snprintf(errormsg, 80, "addDLL: %" PATH_FMT " or dependencies not loaded. (Win32 error %lu)", dll_name, GetLastError());
     /* LoadLibrary failed; return a ptr to the error msg. */
     return errormsg;
@@ -1014,7 +1015,10 @@ bool checkAndLoadImportLibrary( pathchar* arch_name, char* member_name, FILE* f
     stgFree(dllName);
 
     IF_DEBUG(linker, debugBelch("loadArchive: read symbol %s from lib `%" PATH_FMT "'\n", symbol, dll));
-    const char* result = addDLL(dll);
+    // We must call `addDLL_PEi386` directly rather than `addDLL` because `addDLL`
+    // is now a wrapper around `loadNativeObj` which acquires a lock which we
+    // already have here.
+    const char* result = addDLL_PEi386(dll, NULL);
 
     stgFree(image);
 
@@ -1138,47 +1142,57 @@ SymbolAddr*
 lookupSymbolInDLLs ( const SymbolName* lbl, ObjectCode *dependent )
 {
     OpenedDLL* o_dll;
-    SymbolAddr* sym;
+    SymbolAddr* res;
 
-    for (o_dll = opened_dlls; o_dll != NULL; o_dll = o_dll->next) {
-        /* debugBelch("look in %ls for %s\n", o_dll->name, lbl); */
+    for (o_dll = opened_dlls; o_dll != NULL; o_dll = o_dll->next)
+        if ((res = lookupSymbolInDLL_PEi386(lbl, o_dll->instance, o_dll->name, dependent)))
+            return res;
+    return NULL;
+}
 
-        sym = GetProcAddress(o_dll->instance, lbl+STRIP_LEADING_UNDERSCORE);
-        if (sym != NULL) {
-            /*debugBelch("found %s in %s\n", lbl+1,o_dll->name);*/
-            return sym;
-        }
+SymbolAddr*
+lookupSymbolInDLL_PEi386 ( const SymbolName* lbl, HINSTANCE instance, pathchar* dll_name STG_UNUSED, ObjectCode *dependent)
+{
+    SymbolAddr* sym;
 
-        // TODO: Drop this
-        /* Ticket #2283.
-           Long description: http://support.microsoft.com/kb/132044
-           tl;dr:
-             If C/C++ compiler sees __declspec(dllimport) ... foo ...
-             it generates call *__imp_foo, and __imp_foo here has exactly
-             the same semantics as in __imp_foo = GetProcAddress(..., "foo")
-         */
-        if (sym == NULL && strncmp (lbl, "__imp_", 6) == 0) {
-            sym = GetProcAddress(o_dll->instance,
-                                 lbl + 6 + STRIP_LEADING_UNDERSCORE);
-            if (sym != NULL) {
-                SymbolAddr** indirect = m32_alloc(dependent->rw_m32, sizeof(SymbolAddr*), 8);
-                if (indirect == NULL) {
-                    barf("lookupSymbolInDLLs: Failed to allocation indirection");
-                }
-                *indirect = sym;
-                IF_DEBUG(linker,
-                  debugBelch("warning: %s from %S is linked instead of %s\n",
-                             lbl+6+STRIP_LEADING_UNDERSCORE, o_dll->name, lbl));
-                return (void*) indirect;
-               }
-        }
+    /* debugBelch("look in %ls for %s\n", dll_name, lbl); */
 
-        sym = GetProcAddress(o_dll->instance, lbl);
+    sym = GetProcAddress(instance, lbl+STRIP_LEADING_UNDERSCORE);
+    if (sym != NULL) {
+        /*debugBelch("found %s in %ls\n", lbl+STRIP_LEADING_UNDERSCORE,dll_name);*/
+        return sym;
+    }
+
+    // TODO: Drop this
+    /* Ticket #2283.
+       Long description: http://support.microsoft.com/kb/132044
+       tl;dr:
+         If C/C++ compiler sees __declspec(dllimport) ... foo ...
+         it generates call *__imp_foo, and __imp_foo here has exactly
+         the same semantics as in __imp_foo = GetProcAddress(..., "foo")
+     */
+    if (sym == NULL && strncmp (lbl, "__imp_", 6) == 0) {
+        sym = GetProcAddress(instance,
+                             lbl + 6 + STRIP_LEADING_UNDERSCORE);
         if (sym != NULL) {
-            /*debugBelch("found %s in %s\n", lbl,o_dll->name);*/
-            return sym;
+            SymbolAddr** indirect = m32_alloc(dependent->rw_m32, sizeof(SymbolAddr*), 8);
+            if (indirect == NULL) {
+                barf("lookupSymbolInDLLs: Failed to allocation indirection");
+            }
+            *indirect = sym;
+            IF_DEBUG(linker,
+              debugBelch("warning: %s from %S is linked instead of %s\n",
+                         lbl+6+STRIP_LEADING_UNDERSCORE, dll_name, lbl));
+            return (void*) indirect;
            }
     }
+
+    sym = GetProcAddress(instance, lbl);
+    if (sym != NULL) {
+        /*debugBelch("found %s in %s\n", lbl,dll_name);*/
+        return sym;
+       }
+
     return NULL;
 }
 


=====================================
rts/linker/PEi386.h
=====================================
@@ -60,6 +60,7 @@ bool ocRunFini_PEi386     ( ObjectCode *oc );
 bool ocGetNames_PEi386    ( ObjectCode* oc );
 bool ocVerifyImage_PEi386 ( ObjectCode* oc );
 SymbolAddr *lookupSymbol_PEi386(SymbolName *lbl, ObjectCode *dependent, SymType *type);
+SymbolAddr *lookupSymbolInDLL_PEi386 (const SymbolName* lbl, HINSTANCE instance, pathchar* dll_name, ObjectCode *dependent);
 
 /* See Note [mingw-w64 name decoration scheme] */
 /* We use myindex to calculate array addresses, rather than


=====================================
rts/rts.cabal.in
=====================================
@@ -624,6 +624,7 @@ library
                  linker/Elf.c
                  linker/InitFini.c
                  linker/LoadArchive.c
+                 linker/LoadNativeObjPosix.c
                  linker/M32Alloc.c
                  linker/MMap.c
                  linker/MachO.c


=====================================
testsuite/tests/ghci/linking/dyn/T3372.hs
=====================================
@@ -1,3 +1,6 @@
+-- Note: This test exercises running concurrent GHCi sessions, but
+-- although this test is expected to pass, running concurrent GHCi
+-- sessions is currently broken in other ways; see #24345.
 {-# LANGUAGE MagicHash #-}
 
 module Main where



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34601024f6164efbf7dfd8ede7e5d820e55007fa

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 21:25:00 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 17:25:00 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25365
Message-ID: <6708462c2d10d_19ff3433237c478dd@gitlab.mail>



Ben Gamari pushed new branch wip/T25365 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25365
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 21:33:30 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 17:33:30 -0400
Subject: [Git][ghc/ghc][wip/T25365] 2 commits: base: Capture backtrace from
 throwSTM
Message-ID: <6708482a426a0_19ff343316e848059@gitlab.mail>



Ben Gamari pushed to branch wip/T25365 at Glasgow Haskell Compiler / GHC


Commits:
743b1d3d by Ben Gamari at 2024-10-10T17:32:33-04:00
base: Capture backtrace from throwSTM

Fixes #25365.

- - - - -
e3818c71 by Ben Gamari at 2024-10-10T17:33:09-04:00
base: Annotate rethrown exceptions in catcHSTM with WhileHandling

- - - - -


2 changed files:

- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -4,6 +4,8 @@
   * Restrict `Data.List.NonEmpty.unzip` to `NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)`. ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
   * Modify the implementation of `Control.Exception.throw` to avoid call-sites being inferred as diverging via precise exception.
     ([GHC #25066](https://gitlab.haskell.org/ghc/ghc/-/issues/25066), [CLC proposal #290](https://github.com/haskell/core-libraries-committee/issues/290))
+  * `GHC.Conc.throwSTM` and `GHC.Conc.Sync.throwSTM` now attach a `Backtrace` annotation to the thrown exception. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365))
+  * `GHC.Conc.catchSTM` and `GHC.Conc.Sync.catchSTM` now attach `WhileHandling` annotation to exceptions thrown from the handler. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365))
 
 ## 4.21.0.0 *TBA*
   * `GHC.Desugar` has been deprecated and should be removed in GHC 9.14. ([CLC proposal #216](https://github.com/haskell/core-libraries-committee/issues/216))


=====================================
libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
=====================================
@@ -117,11 +117,14 @@ import GHC.Internal.Int
 import GHC.Internal.IO
 import GHC.Internal.IO.Exception
 import GHC.Internal.Exception
+import GHC.Internal.Exception.Context ( ExceptionAnnotation )
+import GHC.Internal.Exception.Type ( WhileHandling(..) )
 import GHC.Internal.IORef
 import GHC.Internal.MVar
 import GHC.Internal.Ptr
 import GHC.Internal.Real         ( fromIntegral )
 import GHC.Internal.Show         ( Show(..), showParen, showString )
+import GHC.Internal.Stack ( HasCallStack )
 import GHC.Internal.Weak
 import GHC.Internal.Word
 
@@ -821,8 +824,13 @@ orElse (STM m) e = STM $ \s -> catchRetry# m (unSTM e) s
 -- raise an exception within the 'STM' monad because it guarantees
 -- ordering with respect to other 'STM' operations, whereas 'throw'
 -- does not.
-throwSTM :: Exception e => e -> STM a
-throwSTM e = STM $ raiseIO# (toException e)
+throwSTM :: HasCallStack => Exception e => e -> STM a
+throwSTM e = do
+    -- N.B. Typically use of unsafeIOToSTM is very much frowned upon as this
+    -- is an easy way to end up with nested transactions. However, we can be
+    -- certain that toExceptionWithBacktrace will not initiate a transaction.
+    se <- unsafeIOToSTM (toExceptionWithBacktrace e)
+    STM $ raiseIO# se
 
 -- | Exception handling within STM actions.
 --
@@ -834,9 +842,16 @@ catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
 catchSTM (STM m) handler = STM $ catchSTM# m handler'
     where
       handler' e = case fromException e of
-                     Just e' -> unSTM (handler e')
+                     Just e' -> unSTM (annotateSTM (WhileHandling e) (handler e'))
                      Nothing -> raiseIO# e
 
+-- | Execute an 'STM' action, adding the given 'ExceptionContext'
+-- to any thrown synchronous exceptions.
+annotateSTM :: forall e a. ExceptionAnnotation e => e -> STM a -> STM a
+annotateSTM ann (STM io) = STM (catch# io handler)
+  where
+    handler se = raiseIO# (addExceptionContext ann se)
+
 -- |Shared memory locations that support atomic memory transactions.
 data TVar a = TVar (TVar# RealWorld a)
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa61b3a25a8ae49e5f64500da3de5f555a85030e...e3818c7189531f4d398a35fe370f971a85207c40

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa61b3a25a8ae49e5f64500da3de5f555a85030e...e3818c7189531f4d398a35fe370f971a85207c40
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 21:50:37 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 17:50:37 -0400
Subject: [Git][ghc/ghc][wip/bump-process] Bump process submodule to v1.6.25.0
Message-ID: <67084c2d72c5_19ff342f74fc55495@gitlab.mail>



Ben Gamari pushed to branch wip/bump-process at Glasgow Haskell Compiler / GHC


Commits:
5e3ed7d2 by Ben Gamari at 2024-10-10T17:50:28-04:00
Bump process submodule to v1.6.25.0

- - - - -


5 changed files:

- libraries/process
- testsuite/tests/process/process004.hs
- testsuite/tests/process/process004.stdout
- testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
- testsuite/tests/process/process004.stdout-mingw32


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b
+Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e


=====================================
testsuite/tests/process/process004.hs
=====================================
@@ -4,8 +4,13 @@ import System.IO.Error
 import System.Process
 
 main :: IO ()
-main = do test1 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
-          test2 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
+main = do
+  -- N.B. Only show the error type since the exact error text
+  -- may depend upon precise system call which @process@ decided
+  -- to use.
+  let printError e = putStrLn ("Exc: " ++ show (ioeGetErrorType e))
+  test1 `catchIOError` printError
+  test2 `catchIOError` printError
 
 test1 :: IO ()
 test1 = do


=====================================
testsuite/tests/process/process004.stdout
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: chdir: invalid argument (Bad file descriptor)
-Exc: true: runProcess: chdir: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: does not exist (No such file or directory)
-Exc: true: runProcess: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-mingw32
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: invalid argument (Invalid argument)
-Exc: true: runProcess: invalid argument (Invalid argument)
+Exc: invalid argument
+Exc: invalid argument



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e3ed7d2f19998b74cc54abd191eeb173039ff20

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 22:06:30 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 18:06:30 -0400
Subject: [Git][ghc/ghc][wip/doc-unpack] users-guide: Document field coalescence
Message-ID: <67084fe6a218c_19ff34672438607dc@gitlab.mail>



Ben Gamari pushed to branch wip/doc-unpack at Glasgow Haskell Compiler / GHC


Commits:
8f94fd6f by Ben Gamari at 2024-10-10T18:06:24-04:00
users-guide: Document field coalescence

- - - - -


1 changed file:

- docs/users_guide/exts/pragmas.rst


Changes:

=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -959,6 +959,35 @@ effect of adding ``{-# UNPACK #-}`` to every strict constructor field which is
 of a single-constructor data type. Sum types won't be unpacked automatically
 by this though, only with the explicit pragma.
 
+Also note that GHC will coalesce adjacent sub-word size fields into
+words. For instance, consider (on a 64-bit platform) ::
+
+    data T = T {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
+
+As ``Word32`` is represented by the unlifted 32-bit ``Word32#`` type, the ``T``
+constructor will be represent its two ``Word32`` fields using only a single
+64-bit word.
+
+Note that during coalescence padding will be inserted to ensure that each field
+remains naturally aligned. For instance, on a 64-bit platform ::
+
+    data T = T {-# UNPACK #-} !Word32
+               {-# UNPACK #-} !Word8
+               {-# UNPACK #-} !Word32
+
+will require two 64-bit words since padding is necessary after the ``Word8`` to
+ensure that the subsequent ``Word64`` is naturally aligned:
+
+.. code-block:: none
+
+     ┌───────────────────────────────────┐
+     │ Header                            │
+     ├─────────────────┬────────┬────────┤
+     │ Word32          │ Word8  │ padding│
+     ├─────────────────┼────────┴────────┤
+     │ Word32          │ padding         │
+     └─────────────────┴─────────────────┘
+
 .. [1]
    In fact, :pragma:`UNPACK` has no effect without :ghc-flag:`-O`, for technical
    reasons (see :ghc-ticket:`5252`).



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8f94fd6f3f5103b9729f4a7b265d8fedae0b0554

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 22:07:57 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 10 Oct 2024 18:07:57 -0400
Subject: [Git][ghc/ghc][wip/doc-unpack] users-guide: Document field coalescence
Message-ID: <6708503d7e3ae_19ff346723d462936@gitlab.mail>



Ben Gamari pushed to branch wip/doc-unpack at Glasgow Haskell Compiler / GHC


Commits:
157f21bc by Ben Gamari at 2024-10-10T18:07:50-04:00
users-guide: Document field coalescence

- - - - -


1 changed file:

- docs/users_guide/exts/pragmas.rst


Changes:

=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -959,6 +959,35 @@ effect of adding ``{-# UNPACK #-}`` to every strict constructor field which is
 of a single-constructor data type. Sum types won't be unpacked automatically
 by this though, only with the explicit pragma.
 
+Also note that GHC will coalesce adjacent sub-word size fields into
+words. For instance, consider (on a 64-bit platform) ::
+
+    data T = T {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
+
+As ``Word32`` is represented by the unlifted 32-bit ``Word32#`` type, the ``T``
+constructor will be represent its two ``Word32`` fields using only a single
+64-bit word.
+
+Note that during coalescence padding will be inserted to ensure that each field
+remains naturally aligned. For instance, on a 64-bit platform ::
+
+    data T = T {-# UNPACK #-} !Word32
+               {-# UNPACK #-} !Word8
+               {-# UNPACK #-} !Word32
+
+the fields of ``T`` require two 64-bit words since padding is necessary after
+the ``Word8`` to ensure that the subsequent ``Word64`` is naturally aligned:
+
+.. code-block:: none
+
+     ┌───────────────────────────────────┐
+     │ Header                            │
+     ├─────────────────┬────────┬────────┤
+     │ Word32          │ Word8  │ padding│
+     ├─────────────────┼────────┴────────┤
+     │ Word32          │ padding         │
+     └─────────────────┴─────────────────┘
+
 .. [1]
    In fact, :pragma:`UNPACK` has no effect without :ghc-flag:`-O`, for technical
    reasons (see :ghc-ticket:`5252`).



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/157f21bc1c23955e9ea0d1b2c57e7ae8135e970c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 23:06:36 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 10 Oct 2024 19:06:36 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] Don't use a user SrcSpan on a
 Stmt expansoin
Message-ID: <67085dfc8bba4_223712ccf045884d@gitlab.mail>



Simon Peyton Jones pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
b30ee4cc by Simon Peyton Jones at 2024-10-11T00:05:37+01:00
Don't use a user SrcSpan on a Stmt expansoin

- - - - -


3 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Tc/Gen/Do.hs
- testsuite/tests/typecheck/should_fail/tcfail128.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -519,14 +519,6 @@ data XXExprGhcRn
                                                    -- in `GHC.Tc.Gen.Do`
 
 
--- | Wrap a located expression with a `PopErrCtxt`
-mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn
-mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
-
--- | Wrap a located expression with a PopSrcExpr with an appropriate location
-mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
-mkPopErrCtxtExprAt loc a = L loc $ mkPopErrCtxtExpr a
-
 -- | Build an expression using the extension constructor `XExpr`,
 --   and the two components of the expansion: original expression and
 --   expanded expressions.
@@ -556,22 +548,6 @@ mkExpandedPatRn
 mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav
                                                          , xrn_expanded = eExpr })
 
--- | Build an expression using the extension constructor `XExpr`,
---   and the two components of the expansion: original do stmt and
---   expanded expression and associate it with a provided location
-mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
-  -> HsDoFlavour          -- ^ the flavour of the statement
-  -> HsExpr GhcRn         -- ^ expanded expression
-  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
-  = L loc $ mkExpandedStmt oStmt flav eExpr
-
 data XXExprGhcTc
   = WrapExpr        -- Type and evidence application and abstractions
       {-# UNPACK #-} !(HsWrap HsExpr)


=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -563,3 +563,29 @@ It stores the original statement (with location) and the expanded expression
   We hence use a tag `GenReason` in `Ghc.Tc.Origin`. When typechecking a `HsLam` in `Tc.Gen.Expr.tcExpr`
   the `match_ctxt` is set to a `StmtCtxt` if `GenOrigin` is a `DoExpansionOrigin`.
 -}
+
+
+-- | Wrap a located expression with a `PopErrCtxt`
+mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn
+mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
+
+-- | Wrap a located expression with a PopSrcExpr with an appropriate location
+mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
+mkPopErrCtxtExprAt _loc a = wrapGenSpan $ mkPopErrCtxtExpr a
+
+-- | Build an expression using the extension constructor `XExpr`,
+--   and the two components of the expansion: original do stmt and
+--   expanded expression and associate it with a provided location
+mkExpandedStmtAt
+  :: Bool                 -- ^ Wrap this expansion with a pop?
+  -> SrcSpanAnnA          -- ^ Location for the expansion expression
+  -> ExprLStmt GhcRn      -- ^ source statement
+  -> HsDoFlavour          -- ^ the flavour of the statement
+  -> HsExpr GhcRn         -- ^ expanded expression
+  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
+mkExpandedStmtAt addPop _loc oStmt flav eExpr
+  | addPop
+  = mkPopErrCtxtExprAt _loc (wrapGenSpan $ mkExpandedStmt oStmt flav eExpr)
+  | otherwise
+  = wrapGenSpan $ mkExpandedStmt oStmt flav eExpr
+


=====================================
testsuite/tests/typecheck/should_fail/tcfail128.hs
=====================================
@@ -11,10 +11,13 @@ import Data.Array.IArray as IA (Array,listArray)
 main :: IO ()
 main = do let sL = [1,4,6,3,2,5]
               dim = length sL
-              help :: [FlatVector]
+
+          let help :: [FlatVector]
               help = [listFlatVector (1,s) [0|i<-[1..s]]|s<-sL]
-              tmp :: Vector FlatVector
+
+          let tmp :: Vector FlatVector
               tmp = listVector (1,dim) help
+
           v <- thaw tmp
           return ()
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 10 23:07:15 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 10 Oct 2024 19:07:15 -0400
Subject: [Git][ghc/ghc][wip/T25266] 14 commits: ci: RISCV64 cross-compile
 testing
Message-ID: <67085e2366281_223712c0808591f3@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
73565a71 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
6f8ca7c1 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Work in progress on #25266

- - - - -
d7308086 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Better generalisation

- - - - -
5544800d by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Wibbles to short cuts

- - - - -
757a41b8 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Iterating in decideAndPromote

- - - - -
88b93f2a by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Wibble

- - - - -
a3cd2d19 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Wibble Solver

- - - - -
dd8ba563 by Simon Peyton Jones at 2024-10-10T23:32:47+01:00
Wibble

- - - - -
11e78c22 by Simon Peyton Jones at 2024-10-11T00:03:38+01:00
Keep variables in correct order

- - - - -
e905dd14 by Simon Peyton Jones at 2024-10-11T00:06:51+01:00
Wibble solver

- - - - -


25 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2921f22bb1d031969a7013ec9c30f12cee5f6688...e905dd142c9d4ecd375e09864d4909100ab1a904

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2921f22bb1d031969a7013ec9c30f12cee5f6688...e905dd142c9d4ecd375e09864d4909100ab1a904
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 02:42:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 10 Oct 2024 22:42:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: Handle
 exceptions from IO manager backend
Message-ID: <6708907a8da14_1154f15c3e03589@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
11f43b6e by Hassan Al-Awwadi at 2024-10-10T22:41:32-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
25b11923 by Cheng Shao at 2024-10-10T22:41:33-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
f9b400ba by Cristiano Moraes at 2024-10-10T22:41:38-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
47428444 by Simon Peyton Jones at 2024-10-10T22:41:38-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
d31399df by Simon Peyton Jones at 2024-10-10T22:41:38-04:00
Wibbles

- - - - -
9aa8d82d by Simon Peyton Jones at 2024-10-10T22:41:38-04:00
Spelling errors

- - - - -
7b49ddb9 by sheaf at 2024-10-10T22:41:43-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
fa0add2d by sheaf at 2024-10-10T22:41:43-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
06150763 by Cheng Shao at 2024-10-10T22:41:43-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
2cd5e06b by Ben Gamari at 2024-10-10T22:41:44-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
43ca92d9 by Matthew Pickering at 2024-10-10T22:41:45-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12c38a48549f24fc666eaadb4e023b279b7e25f8...43ca92d919405ab413ba0df63a456abb15169b9d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12c38a48549f24fc666eaadb4e023b279b7e25f8...43ca92d919405ab413ba0df63a456abb15169b9d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:52:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:52:25 -0400
Subject: [Git][ghc/ghc][master] Handle exceptions from IO manager backend
Message-ID: <6708d9399ad6b_9cace1e59b022883@gitlab.mail>



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


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -


8 changed files:

- libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Internal/Types.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Manager.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs
- + testsuite/tests/concurrent/should_run/T21969.hs
- + testsuite/tests/concurrent/should_run/T21969.stdout
- testsuite/tests/concurrent/should_run/all.T


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Conc/IO.hs
=====================================
@@ -176,14 +176,22 @@ threadWaitWriteSTM fd
       let killAction = Sync.killThread t
       return (waitAction, killAction)
 
--- | Close a file descriptor in a concurrency-safe way (GHC only).  If
--- you are using 'threadWaitRead' or 'threadWaitWrite' to perform
--- blocking I\/O, you /must/ use this function to close file
--- descriptors, or blocked threads may not be woken.
+-- | Close a file descriptor in a concurrency-safe way as far as the runtime
+-- system is concerned (GHC only).  If you are using 'threadWaitRead' or
+-- 'threadWaitWrite' to perform blocking I\/O, you /must/ use this function
+-- to close file descriptors, or blocked threads may not be woken.
 --
 -- Any threads that are blocked on the file descriptor via
 -- 'threadWaitRead' or 'threadWaitWrite' will be unblocked by having
 -- IO exceptions thrown.
+--
+-- Note that on systems that reuse file descriptors (such as Linux),
+-- using this function on a file descriptor while other threads can still
+-- potentially use it is always prone to race conditions without further
+-- synchronization.
+--
+-- It is recommended to only call @'closeFdWith'@ once no other threads can
+-- use the given file descriptor anymore.
 closeFdWith :: (Fd -> IO ()) -- ^ Low-level action that performs the real close.
             -> Fd            -- ^ File descriptor to close.
             -> IO ()


=====================================
libraries/ghc-internal/src/GHC/Internal/Event/Internal.hs
=====================================
@@ -41,6 +41,14 @@ data Backend = forall a. Backend {
 
     -- | Register, modify, or unregister interest in the given events
     -- on the given file descriptor.
+    --
+    -- Returns 'True' if the modification succeeded.
+    -- Returns 'False' if this backend does not support
+    -- event notifications on this type of file.
+    --
+    -- If this function throws, the IO manager assumes that the registration
+    -- of the file descriptor failed, so the backend must not throw if the
+    -- registration was successful.
     , _beModifyFd :: a
                   -> Fd       -- file descriptor
                   -> Event    -- old events to watch for ('mempty' for new)
@@ -49,6 +57,14 @@ data Backend = forall a. Backend {
 
     -- | Register interest in new events on a given file descriptor, set
     -- to be deactivated after the first event.
+    --
+    -- Returns 'True' if the modification succeeded.
+    -- Returns 'False' if this backend does not support
+    -- event notifications on this type of file.
+    --
+    -- If this function throws, the IO manager assumes that the registration
+    -- of the file descriptor failed, so the backend must not throw if the
+    -- registration was successful.
     , _beModifyFdOnce :: a
                          -> Fd    -- file descriptor
                          -> Event -- new events to watch


=====================================
libraries/ghc-internal/src/GHC/Internal/Event/Internal/Types.hs
=====================================
@@ -61,6 +61,11 @@ evtWrite = Event 2
 {-# INLINE evtWrite #-}
 
 -- | Another thread closed the file descriptor.
+--
+-- This event is only meant to be used by @'closeFdWith'@ to signal other
+-- threads currently waiting on the same file descriptor that it was closed.
+-- It is not meant to be waited on directly and intentionally not exposed
+-- in the external interface (only @'evtRead'@ and @'evtWrite'@ are).
 evtClose :: Event
 evtClose = Event 4
 {-# INLINE evtClose #-}


=====================================
libraries/ghc-internal/src/GHC/Internal/Event/Manager.hs
=====================================
@@ -312,6 +312,11 @@ step mgr at EventManager{..} = do
 -- platform's @select@ or @epoll@ system call, which tend to vary in
 -- what sort of fds are permitted. For instance, waiting on regular files
 -- is not allowed on many platforms.
+--
+-- This function rethrows exceptions originating from the underlying backend,
+-- for instance due to concurrently closing a file descriptor while it is
+-- just being registered. In that case, it assumes that the registration was
+-- not successful. See #21969.
 registerFd_ :: EventManager -> IOCallback -> Fd -> Event -> Lifetime
             -> IO (FdKey, Bool)
 registerFd_ mgr@(EventManager{..}) cb fd evs lt = do
@@ -327,13 +332,20 @@ registerFd_ mgr@(EventManager{..}) cb fd evs lt = do
 
         el' :: EventLifetime
         el' = prevEvs `mappend` el
+
+        -- Used for restoring the old state if registering the FD
+        -- in the backend failed, due to either
+        -- 1. that file type not being supported, or
+        -- 2. the backend throwing an exception
+        undoRegistration = IT.reset fd' oldFdd tbl
     case I.elLifetime el' of
       -- All registrations want one-shot semantics and this is supported
       OneShot | haveOneShot -> do
         ok <- I.modifyFdOnce emBackend fd (I.elEvent el')
+          `onException` undoRegistration
         if ok
           then return (False, True)
-          else IT.reset fd' oldFdd tbl >> return (False, False)
+          else undoRegistration >> return (False, False)
 
       -- We don't want or don't support one-shot semantics
       _ -> do
@@ -342,10 +354,11 @@ registerFd_ mgr@(EventManager{..}) cb fd evs lt = do
               then let newEvs = I.elEvent el'
                        oldEvs = I.elEvent prevEvs
                    in I.modifyFd emBackend fd oldEvs newEvs
+                        `onException` undoRegistration
               else return True
         if ok
           then return (modify, True)
-          else IT.reset fd' oldFdd tbl >> return (False, False)
+          else undoRegistration >> return (False, False)
   -- this simulates behavior of old IO manager:
   -- i.e. just call the callback if the registration fails.
   when (not ok) (cb reg evs)


=====================================
libraries/ghc-internal/src/GHC/Internal/Event/Thread.hs
=====================================
@@ -112,6 +112,13 @@ threadWaitWrite = threadWait evtWrite
 -- Any threads that are blocked on the file descriptor via
 -- 'threadWaitRead' or 'threadWaitWrite' will be unblocked by having
 -- IO exceptions thrown.
+--
+-- Closing file descriptors on one thread while they are still being
+-- used by other threads is always prone to race conditions (since e.g.
+-- on Linux file descriptors can be immediately reused after closing).
+--
+-- It is recommended to only call @'closeFdWith'@ when the file descriptor
+-- can no longer be used by other threads.
 closeFdWith :: (Fd -> IO ())        -- ^ Action that performs the close.
             -> Fd                   -- ^ File descriptor to close.
             -> IO ()
@@ -154,6 +161,10 @@ closeFdWith close fd = close_loop
             close fd `finally` sequence_ (zipWith3 finish mgrs tables cbApps)
             pure (pure ())
 
+-- | Wait for an event on a file descriptor.
+--
+-- The given @'Event'@ may only be (a combination of) @'evtRead'@ or
+-- @'evtWrite'@, but not @'evtClose'@. See @'evtClose'@ for more details.
 threadWait :: Event -> Fd -> IO ()
 threadWait evt fd = mask_ $ do
   m <- newEmptyMVar


=====================================
testsuite/tests/concurrent/should_run/T21969.hs
=====================================
@@ -0,0 +1,100 @@
+{-# LANGUAGE NumericUnderscores  #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module Main where
+
+import           Control.Concurrent      (ThreadId, forkIO, killThread,
+                                          threadDelay)
+import           Control.Concurrent.MVar (newEmptyMVar, putMVar, takeMVar)
+import           Control.Exception       (Exception (..), SomeAsyncException,
+                                          SomeException, bracket, catch, handle,
+                                          throwIO)
+import           Control.Monad           (forM_, unless)
+import           GHC.Conc.IO             (threadWaitRead, threadWaitWrite)
+
+import qualified Data.ByteString         as BS
+import           GHC.IO.FD               (FD (..))
+import           GHC.IO.Handle.FD        (handleToFd)
+import           System.Environment      (getArgs)
+import           System.IO               (BufferMode (NoBuffering), Handle,
+                                          hClose, hSetBuffering)
+import           System.IO.Error         (isResourceVanishedError)
+import           System.Posix            (Fd (..))
+import           System.Posix.IO         (createPipe, fdToHandle)
+
+main :: IO ()
+main = do
+  [iterations] <- getArgs
+  -- Usually 1000-2000 tries are enough to lock up, do even more just in case
+  forM_ [1 :: Int .. read iterations] $ \_ -> do
+    bracket setupPipes closePipes $ \(readH, writeH) -> do
+      let
+        handler e
+          | Just as <- fromException e = throwIO (as :: SomeAsyncException)
+          | otherwise = pure ()
+
+      withThread (writer writeH) $ \_ ->
+        reader readH `catch` handler
+
+
+-- | Return a @(read, write)@ handle pair for an anonymous pipe.
+setupPipes :: IO (Handle, Handle)
+setupPipes = do
+  (readFd, writeFd) <- createPipe
+  (,)
+    <$> fdToHandle readFd -- fdToHandle' readFd Nothing True ("read fd " <> show readFd) ReadMode True
+    <*> fdToHandle writeFd -- fdToHandle' writeFd Nothing True ("write fd " <> show writeFd) WriteMode True
+
+-- | Close the handles returned by 'setupPipes'.
+closePipes :: (Handle, Handle) -> IO ()
+closePipes (readH, writeH) = do
+  dropResourceVanishedError $ hClose readH
+  dropResourceVanishedError $ hClose writeH
+
+reader :: Handle -> IO ()
+reader readHandle = do
+  let
+    drain = do
+      fd <- handleToFd readHandle
+      threadWaitRead (Fd (fdFD fd))
+      msg <- BS.hGetSome readHandle 1024
+      unless (BS.null msg) drain
+
+  -- The MVar ensures we more or less simultaneously start reading and closing, increasing the
+  -- chance of hitting the race condition
+  readingBarrier <- newEmptyMVar
+  _ <- forkIO $ do
+    takeMVar readingBarrier
+    hClose readHandle `catch` \(_ :: SomeException) -> pure ()
+
+  putMVar readingBarrier ()
+  drain
+
+withThread :: IO () -> (ThreadId -> IO r) -> IO r
+withThread bgAction mainAction = do
+  bracket
+    (forkIO bgAction)
+    killThread
+    mainAction
+
+-- | Something to keep the reader busy reading.
+writer :: Handle -> IO ()
+writer writeHandle = do
+  hSetBuffering writeHandle NoBuffering
+  let
+    loop = do
+      fd <- handleToFd writeHandle
+      threadWaitWrite (Fd (fdFD fd))
+      BS.hPut writeHandle $ BS.replicate 1024 65
+      -- We need a short delay so that the reader actually needs to wait for data to be present.
+      -- Only then can we trigger the epoll registration race condition.
+      threadDelay 10_000
+      loop
+
+  dropResourceVanishedError loop
+
+-- | Ignore broken pipe errors
+dropResourceVanishedError :: IO () -> IO ()
+dropResourceVanishedError = handle $ \err ->
+  if isResourceVanishedError err
+  then pure ()
+  else throwIO err


=====================================
testsuite/tests/concurrent/should_run/T21969.stdout
=====================================


=====================================
testsuite/tests/concurrent/should_run/all.T
=====================================
@@ -265,6 +265,16 @@ test('T21651',
      ],
      compile_and_run, [''])
 
+test('T21969',
+     [ only_ways(['threaded1','threaded2', 'nonmoving_thr', 'profthreaded']),
+       when(opsys('mingw32'),skip), # uses POSIX pipes
+       extra_run_opts('50000'),
+       run_timeout_multiplier(0.3), # default timeout seems to be 300, but lockups happen quickly
+       req_target_smp,
+       req_ghc_smp
+     ],
+     compile_and_run, [''])
+
 test('hs_try_putmvar001',
      [
      when(opsys('mingw32'),skip), # uses pthread APIs in the C code



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69960230cc2c04a8b554ae8b7ebb85626749bf45

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:52:59 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:52:59 -0400
Subject: [Git][ghc/ghc][master] Put RdrName in the foExt field of FieldOcc
Message-ID: <6708d95b5d7d5_9cace1aea5026594@gitlab.mail>



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


Commits:
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1587cccfe7c3c1db3ccc48437b47ccb6ae215701

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:53:40 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:53:40 -0400
Subject: [Git][ghc/ghc][master] driver: bail out when -fllvm is passed to GHC
 not configured with LLVM
Message-ID: <6708d98478c34_9cace1e5974314a2@gitlab.mail>



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


Commits:
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -


5 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Types/Error/Codes.hs
- testsuite/tests/diagnostic-codes/codes.stdout


Changes:

=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -35,6 +35,7 @@ import GHC.HsToCore.Errors.Types (DsMessage)
 import GHC.Iface.Errors.Types
 import GHC.Tc.Errors.Ppr () -- instance Diagnostic TcRnMessage
 import GHC.Iface.Errors.Ppr () -- instance Diagnostic IfaceMessage
+import GHC.CmmToLlvm.Version (llvmVersionStr, supportedLlvmVersionLowerBound, supportedLlvmVersionUpperBound)
 
 --
 -- Suggestions
@@ -268,6 +269,14 @@ instance Diagnostic DriverMessage where
       mkSimpleDecorated $
         vcat [ text "Unexpected backpack instantiation in dependency graph while constructing Makefile:"
              , nest 2 $ ppr node ]
+    DriverNoConfiguredLLVMToolchain ->
+      mkSimpleDecorated $
+        text "GHC was not configured with a supported LLVM toolchain" $$
+          text ("Make sure you have installed LLVM between ["
+            ++ llvmVersionStr supportedLlvmVersionLowerBound
+            ++ " and "
+            ++ llvmVersionStr supportedLlvmVersionUpperBound
+            ++ ") and reinstall GHC to make -fllvm work")
 
   diagnosticReason = \case
     DriverUnknownMessage m
@@ -337,6 +346,8 @@ instance Diagnostic DriverMessage where
       -> ErrorWithoutFlag
     DriverInstantiationNodeInDependencyGeneration {}
       -> ErrorWithoutFlag
+    DriverNoConfiguredLLVMToolchain
+      -> ErrorWithoutFlag
 
   diagnosticHints = \case
     DriverUnknownMessage m
@@ -408,5 +419,7 @@ instance Diagnostic DriverMessage where
       -> noHints
     DriverInstantiationNodeInDependencyGeneration {}
       -> noHints
+    DriverNoConfiguredLLVMToolchain
+      -> noHints
 
   diagnosticCode = constructorCode


=====================================
compiler/GHC/Driver/Errors/Types.hs
=====================================
@@ -402,6 +402,14 @@ data DriverMessage where
        Backpack 'InstantiationNode's. -}
   DriverInstantiationNodeInDependencyGeneration :: InstantiatedUnit -> DriverMessage
 
+  {-| DriverNoConfiguredLLVMToolchain is an error that occurs if there is no
+     LLVM toolchain configured but -fllvm is passed as an option to the compiler.
+
+    Test cases: None.
+
+  -}
+  DriverNoConfiguredLLVMToolchain :: DriverMessage
+
 deriving instance Generic DriverMessage
 
 data DriverMessageOpts =


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -19,7 +19,6 @@ import GHC.Settings
 import GHC.SysTools.Process
 
 import GHC.Driver.Session
-
 import GHC.Utils.Exception as Exception
 import GHC.Utils.Error
 import GHC.Utils.Outputable
@@ -28,10 +27,16 @@ import GHC.Utils.Logger
 import GHC.Utils.TmpFs
 import GHC.Utils.Panic
 
+import Control.Monad
 import Data.List (tails, isPrefixOf)
 import Data.Maybe (fromMaybe)
 import System.IO
 import System.Process
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Errors
+import GHC.Driver.Errors.Types (GhcMessage(..), DriverMessage (DriverNoConfiguredLLVMToolchain))
+import GHC.Driver.CmdLine (warnsToMessages)
+import GHC.Types.SrcLoc (noLoc)
 
 {-
 ************************************************************************
@@ -277,12 +282,26 @@ runEmscripten logger dflags args = traceSystoolCommand logger "emcc" $ do
 figureLlvmVersion :: Logger -> DynFlags -> IO (Maybe LlvmVersion)
 figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do
   let (pgm,opts) = pgm_lc dflags
+      diag_opts = initDiagOpts dflags
       args = filter notNull (map showOpt opts)
       -- we grab the args even though they should be useless just in
       -- case the user is using a customised 'llc' that requires some
       -- of the options they've specified. llc doesn't care what other
       -- options are specified when '-version' is used.
       args' = args ++ ["-version"]
+  -- Since !12001, when GHC is not configured with llc/opt with
+  -- supported version range, configure script will leave llc/opt
+  -- commands as blank in settings. In this case, we should bail out
+  -- with a proper error, see #25011.
+  --
+  -- Note that this does not make the -Wunsupported-llvm-version
+  -- warning logic redundant! Power users might want to use
+  -- -pgmlc/-pgmlo to override llc/opt locations to test LLVM outside
+  -- officially supported version range, and the driver will produce
+  -- the warning and carry on code generation.
+  when (null pgm) $
+    printOrThrowDiagnostics logger (initPrintConfig dflags) diag_opts
+      (GhcDriverMessage <$> warnsToMessages diag_opts [noLoc DriverNoConfiguredLLVMToolchain])
   catchIO (do
               (pin, pout, perr, p) <- runInteractiveProcess pgm args'
                                               Nothing Nothing
@@ -360,4 +379,3 @@ runWindres logger dflags args = traceSystoolCommand logger "windres" $ do
       opts = map Option (getOpts dflags opt_windres)
   mb_env <- getGccEnv cc_args
   runSomethingFiltered logger id "Windres" windres (opts ++ args) Nothing mb_env
-


=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -323,6 +323,7 @@ type family GhcDiagnosticCode c = n | n -> c where
   GhcDiagnosticCode "DriverDeprecatedFlag"                          = 53692
   GhcDiagnosticCode "DriverModuleGraphCycle"                        = 92213
   GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284
+  GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain"               = 66599
 
   -- Constraint solver diagnostic codes
   GhcDiagnosticCode "BadTelescope"                                  = 97739


=====================================
testsuite/tests/diagnostic-codes/codes.stdout
=====================================
@@ -42,6 +42,7 @@
 [GHC-37141] is untested (constructor = DriverCannotLoadInterfaceFile)
 [GHC-29747] is untested (constructor = DriverMissingSafeHaskellMode)
 [GHC-74284] is untested (constructor = DriverInstantiationNodeInDependencyGeneration)
+[GHC-66599] is untested (constructor = DriverNoConfiguredLLVMToolchain)
 [GHC-06200] is untested (constructor = BlockedEquality)
 [GHC-81325] is untested (constructor = ExpectingMoreArguments)
 [GHC-78125] is untested (constructor = AmbiguityPreventsSolvingCt)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2338a971ce45ce7bc6ba2711e40966ec5ff12359

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:54:19 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:54:19 -0400
Subject: [Git][ghc/ghc][master] configure: Find C++ probing when GCC version
 is the latest but G++ is old #23118
Message-ID: <6708d9ab4e635_9cace70c9ac3528b@gitlab.mail>



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


Commits:
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -


1 changed file:

- m4/fp_find_cxx_std_lib.m4


Changes:

=====================================
m4/fp_find_cxx_std_lib.m4
=====================================
@@ -61,10 +61,11 @@ EOF
         try_libs() {
             dnl Try to link a plain object with CC manually
             AC_MSG_CHECKING([for linkage against '${3}'])
-            if "$CC" -o actest actest.o ${1} 2>/dev/null; then
+            dnl Ensures that CC uses same library path of CXX.
+            p="`"$CXX" --print-file-name ${2}`"
+            d="`dirname "$p"`"
+            if "$CC" -o actest actest.o ${1} -L"$d" 2>/dev/null; then
                 CXX_STD_LIB_LIBS="${3}"
-                p="`"$CXX" --print-file-name ${2}`"
-                d="`dirname "$p"`"
                 dnl On some platforms (e.g. Windows) the C++ standard library
                 dnl can be found in the system search path. In this case $CXX
                 dnl --print-file-name will simply print the filename without a



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78ad81ecef846f73fee0f6c1a86cd6f19aa29b21

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:55:03 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:55:03 -0400
Subject: [Git][ghc/ghc][master] 3 commits: Consider Wanteds with rewriters as
 insoluble
Message-ID: <6708d9d71117c_9cace883218402d7@gitlab.mail>



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


Commits:
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -


6 changed files:

- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Types/Constraint.hs
- testsuite/tests/polykinds/T14172.stderr
- + testsuite/tests/typecheck/should_fail/T25325.hs
- + testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -470,6 +470,8 @@ mkErrorItem ct
              flav = ctFlavour ct
 
        ; (suppress, m_evdest) <- case ctEvidence ct of
+         -- For this `suppress` stuff
+         -- see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
            CtGiven {} -> return (False, Nothing)
            CtWanted { ctev_rewriters = rewriters, ctev_dest = dest }
              -> do { rewriters' <- zonkRewriterSet rewriters


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -76,7 +76,7 @@ module GHC.Tc.Types.Constraint (
         ctEvPred, ctEvLoc, ctEvOrigin, ctEvEqRel,
         ctEvExpr, ctEvTerm, ctEvCoercion, ctEvEvId,
         ctEvRewriters, ctEvUnique, tcEvDestUnique,
-        ctEvRewriteRole, ctEvRewriteEqRel, setCtEvPredType, setCtEvLoc, arisesFromGivens,
+        ctEvRewriteRole, ctEvRewriteEqRel, setCtEvPredType, setCtEvLoc,
         tyCoVarsOfCtEvList, tyCoVarsOfCtEv, tyCoVarsOfCtEvsList,
 
         -- RewriterSet
@@ -1331,10 +1331,10 @@ nonDefaultableTyVarsOfWC (WC { wc_simple = simples, wc_impl = implics, wc_errors
 insolubleWC :: WantedConstraints -> Bool
 insolubleWC (WC { wc_impl = implics, wc_simple = simples, wc_errors = errors })
   =  anyBag insolubleWantedCt simples
+       -- insolubleWantedCt: wanteds only: see Note [Given insolubles]
   || anyBag insolubleImplic implics
   || anyBag is_insoluble errors
-
-    where
+  where
       is_insoluble (DE_Hole hole) = isOutOfScopeHole hole -- See Note [Insoluble holes]
       is_insoluble (DE_NotConcrete {}) = True
       is_insoluble (DE_Multiplicity {}) = False
@@ -1342,15 +1342,41 @@ insolubleWC (WC { wc_impl = implics, wc_simple = simples, wc_errors = errors })
 insolubleWantedCt :: Ct -> Bool
 -- Definitely insoluble, in particular /excluding/ type-hole constraints
 -- Namely:
---   a) an insoluble constraint as per 'insolubleCt', i.e. either
+--   a) an insoluble constraint as per 'insolubleIrredCt', i.e. either
 --        - an insoluble equality constraint (e.g. Int ~ Bool), or
 --        - a custom type error constraint, TypeError msg :: Constraint
 --   b) that does not arise from a Given or a Wanted/Wanted fundep interaction
+-- See Note [Insoluble Wanteds]
+insolubleWantedCt ct
+  | CIrredCan ir_ct <- ct
+      -- CIrredCan: see (IW1) in Note [Insoluble Wanteds]
+  , IrredCt { ir_ev = ev } <- ir_ct
+  , CtWanted { ctev_loc = loc, ctev_rewriters = rewriters }  <- ev
+      -- It's a Wanted
+  , insolubleIrredCt ir_ct
+      -- It's insoluble
+  , isEmptyRewriterSet rewriters
+      -- It has no rewriters; see (IW2) in Note [Insoluble Wanteds]
+  , not (isGivenLoc loc)
+      -- isGivenLoc: see (IW3) in Note [Insoluble Wanteds]
+  , not (isWantedWantedFunDepOrigin (ctLocOrigin loc))
+      -- origin check: see (IW4) in Note [Insoluble Wanteds]
+  = True
+
+  | otherwise
+  = False
+
+-- | Returns True of constraints that are definitely insoluble,
+--   as well as TypeError constraints.
+-- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
 --
--- See Note [Given insolubles].
-insolubleWantedCt ct = insolubleCt ct &&
-                       not (arisesFromGivens ct) &&
-                       not (isWantedWantedFunDepOrigin (ctOrigin ct))
+-- The function is tuned for application /after/ constraint solving
+--       i.e. assuming canonicalisation has been done
+-- That's why it looks only for IrredCt; all insoluble constraints
+-- are put into CIrredCan
+insolubleCt :: Ct -> Bool
+insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
+insolubleCt _                 = False
 
 insolubleIrredCt :: IrredCt -> Bool
 -- Returns True of Irred constraints that are /definitely/ insoluble
@@ -1380,18 +1406,6 @@ insolubleIrredCt (IrredCt { ir_ev = ev, ir_reason = reason })
   -- >   Assert 'True  _errMsg = ()
   -- >   Assert _check errMsg  = errMsg
 
--- | Returns True of constraints that are definitely insoluble,
---   as well as TypeError constraints.
--- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
---
--- The function is tuned for application /after/ constraint solving
---       i.e. assuming canonicalisation has been done
--- That's why it looks only for IrredCt; all insoluble constraints
--- are put into CIrredCan
-insolubleCt :: Ct -> Bool
-insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
-insolubleCt _                 = False
-
 -- | Does this hole represent an "out of scope" error?
 -- See Note [Insoluble holes]
 isOutOfScopeHole :: Hole -> Bool
@@ -1435,6 +1449,31 @@ in GHC.Tc.Errors), so we may fail to report anything at all!  Yikes.
 Bottom line: insolubleWC (called in GHC.Tc.Solver.setImplicationStatus)
              should ignore givens even if they are insoluble.
 
+Note [Insoluble Wanteds]
+~~~~~~~~~~~~~~~~~~~~~~~~
+insolubleWantedCt returns True of a Wanted constraint that definitely
+can't be solved.  But not quite all such constraints; see wrinkles.
+
+(IW1) insolubleWantedCt is tuned for application /after/ constraint
+   solving i.e. assuming canonicalisation has been done.  That's why
+   it looks only for IrredCt; all insoluble constraints are put into
+   CIrredCan
+
+(IW2) We only treat it as insoluble if it has an empty rewriter set.  (See Note
+   [Wanteds rewrite Wanteds].)  Otherwise #25325 happens: a Wanted constraint A
+   that is /not/ insoluble rewrites some other Wanted constraint B, so B has A
+   in its rewriter set.  Now B looks insoluble.  The danger is that we'll
+   suppress reporting B because of its empty rewriter set; and suppress
+   reporting A because there is an insoluble B lying around.  (This suppression
+   happens in GHC.Tc.Errors.mkErrorItem.)  Solution: don't treat B as insoluble.
+
+(IW3) If the Wanted arises from a Given (how can that happen?), don't
+   treat it as a Wanted insoluble (obviously).
+
+(IW4) If the Wanted came from a  Wanted/Wanted fundep interaction, don't
+   treat the constraint as insoluble. See Note [Suppressing confusing errors]
+   in GHC.Tc.Errors
+
 Note [Insoluble holes]
 ~~~~~~~~~~~~~~~~~~~~~~
 Hole constraints that ARE NOT treated as truly insoluble:
@@ -2095,9 +2134,6 @@ tcEvDestUnique (HoleDest co_hole) = varUnique (coHoleCoVar co_hole)
 setCtEvLoc :: CtEvidence -> CtLoc -> CtEvidence
 setCtEvLoc ctev loc = ctev { ctev_loc = loc }
 
-arisesFromGivens :: Ct -> Bool
-arisesFromGivens ct = isGivenCt ct || isGivenLoc (ctLoc ct)
-
 -- | Set the type of CtEvidence.
 --
 -- This function ensures that the invariants on 'CtEvidence' hold, by updating


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,10 +1,7 @@
-
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'’
-      Where: ‘a'’ is a rigid type variable bound by
-               the inferred type of
-                 traverseCompose :: (a -> f b) -> g a -> f (h a')
-               at T14172.hs:8:1-46
+    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
+      Where: ‘k0’ is an ambiguous type variable
+             ‘a'1’ is an ambiguous type variable
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -13,17 +10,19 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
-        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
-                -> Compose f'0 g'1 a'0 -> f (h a')
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
+        Actual: (Unwrapped (Compose f'0 g'1 a'0)
+                 -> f (Unwrapped (h a'1)))
+                -> Compose f'0 g'1 a'0 -> f (h a'1)
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a')
+          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a')
+        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
           (bound at T14172.hs:8:1)
+


=====================================
testsuite/tests/typecheck/should_fail/T25325.hs
=====================================
@@ -0,0 +1,14 @@
+module T25325 where
+
+import Control.Monad.State
+
+data (f :+: g) a = Inl (f a) | Inr (g a)
+
+newtype Buggy f m = Buggy { thing :: m Int }
+
+class GhcBug f where
+  demo :: MonadState (Buggy f m) m => f (m Int) -> m Int
+
+instance (GhcBug f, GhcBug g) => GhcBug (f :+: g) where
+    demo (Inl l) = demo l
+    demo (Inr r) = demo r


=====================================
testsuite/tests/typecheck/should_fail/T25325.stderr
=====================================
@@ -0,0 +1,15 @@
+T25325.hs:14:20: error: [GHC-39999]
+    • Could not deduce ‘MonadState (Buggy g m) m’
+        arising from a use of ‘demo’
+      from the context: (GhcBug f, GhcBug g)
+        bound by the instance declaration at T25325.hs:12:10-49
+      or from: MonadState (Buggy (f :+: g) m) m
+        bound by the type signature for:
+                   demo :: forall (m :: * -> *).
+                           MonadState (Buggy (f :+: g) m) m =>
+                           (:+:) f g (m Int) -> m Int
+        at T25325.hs:13:5-8
+    • In the expression: demo r
+      In an equation for ‘demo’: demo (Inr r) = demo r
+      In the instance declaration for ‘GhcBug (f :+: g)’
+


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -730,3 +730,4 @@ test('T23739b', normal, compile_fail, [''])
 test('T23739c', normal, compile_fail, [''])
 test('T24868', normal, compile_fail, [''])
 test('T24938', normal, compile_fail, [''])
+test('T25325', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78ad81ecef846f73fee0f6c1a86cd6f19aa29b21...09d24d828e48c2588a317e6dad711f8673983703

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78ad81ecef846f73fee0f6c1a86cd6f19aa29b21...09d24d828e48c2588a317e6dad711f8673983703
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:56:23 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:56:23 -0400
Subject: [Git][ghc/ghc][master] 2 commits: LLVM: use sse4.2 instead of sse42
Message-ID: <6708da27adbf4_9cace1feb90504ea@gitlab.mail>



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


Commits:
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -


5 changed files:

- compiler/GHC/Driver/Pipeline/Execute.hs
- + testsuite/tests/llvm/should_compile/T25019.hs
- + testsuite/tests/llvm/should_compile/T25353.asm
- + testsuite/tests/llvm/should_compile/T25353.hs
- testsuite/tests/llvm/should_compile/all.T


Changes:

=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -987,7 +987,11 @@ llvmOptions llvm_config dflags =
 
         attrs :: String
         attrs = intercalate "," $ mattr
-              ++ ["+sse42"   | isSse4_2Enabled dflags   ]
+              ++ ["+sse4.2"  | isSse4_2Enabled dflags   ]
+              ++ ["+popcnt"  | isSse4_2Enabled dflags   ]
+                   -- LLVM gates POPCNT instructions behind the popcnt flag,
+                   -- while the GHC NCG (as well as GCC, Clang) gates it
+                   -- behind SSE4.2 instead.
               ++ ["+sse2"    | isSse2Enabled platform   ]
               ++ ["+sse"     | isSseEnabled platform    ]
               ++ ["+avx512f" | isAvx512fEnabled dflags  ]


=====================================
testsuite/tests/llvm/should_compile/T25019.hs
=====================================
@@ -0,0 +1 @@
+module T25019 where


=====================================
testsuite/tests/llvm/should_compile/T25353.asm
=====================================
@@ -0,0 +1 @@
+popcnt 
\ No newline at end of file


=====================================
testsuite/tests/llvm/should_compile/T25353.hs
=====================================
@@ -0,0 +1,10 @@
+module Main where
+
+import Data.Bits
+
+{-# NOINLINE foo #-}
+foo :: Int -> Int
+foo x = 1 + popCount x
+
+main :: IO ()
+main = print (foo 42)


=====================================
testsuite/tests/llvm/should_compile/all.T
=====================================
@@ -20,3 +20,5 @@ test('T7575', unless(wordsize(32), skip), compile, [''])
 test('T8131b', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile, [''])
 test('T11649', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile, [''])
 test('T17920fail', cmm_src, compile_fail, ['-no-hs-main'])
+test('T25019', unless((arch('x86_64') or arch('i386')) and have_cpu_feature('sse4_2'),skip), compile, ['-msse4.2'])
+test('T25353', unless((arch('x86_64') or arch('i386')) and have_cpu_feature('sse4_2'),skip), compile_grep_asm, ['hs', True, '-msse4.2'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/09d24d828e48c2588a317e6dad711f8673983703...06ae85071b95376bd1eb354f7cc7901aed45b625

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/09d24d828e48c2588a317e6dad711f8673983703...06ae85071b95376bd1eb354f7cc7901aed45b625
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:57:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:57:02 -0400
Subject: [Git][ghc/ghc][master] Drop obsolete libffi Makefile
Message-ID: <6708da4eb00d4_9cacee30af853344@gitlab.mail>



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


Commits:
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -


2 changed files:

- − libffi/Makefile
- − libffi/ln


Changes:

=====================================
libffi/Makefile deleted
=====================================
@@ -1,15 +0,0 @@
-# -----------------------------------------------------------------------------
-#
-# (c) 2009 The University of Glasgow
-#
-# This file is part of the GHC build system.
-#
-# To understand how the build system works and how to modify it, see
-#      https://gitlab.haskell.org/ghc/ghc/wikis/building/architecture
-#      https://gitlab.haskell.org/ghc/ghc/wikis/building/modifying
-#
-# -----------------------------------------------------------------------------
-
-dir = libffi
-TOP = ..
-include $(TOP)/mk/sub-makefile.mk


=====================================
libffi/ln deleted
=====================================
@@ -1,3 +0,0 @@
-#!/bin/sh
-exit 1
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fe843c730a2d882af98dac53958731624dfe0a3

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:57:47 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:57:47 -0400
Subject: [Git][ghc/ghc][master] ghc-internal: Fix incomplete matches on IOError
Message-ID: <6708da7b9d7c9_9cace70c9ac563d9@gitlab.mail>



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


Commits:
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
=====================================
@@ -77,7 +77,7 @@ import GHC.Internal.IO.Windows.Encoding (withGhcInternalToUTF16, withUTF16ToGhcI
 import GHC.Internal.IO.Windows.Paths (getDevicePath)
 import GHC.Internal.IO.Handle.Internals (debugIO)
 import GHC.Internal.IORef
-import GHC.Internal.Event.Windows (LPOVERLAPPED, withOverlappedEx, IOResult(..))
+import GHC.Internal.Event.Windows (LPOVERLAPPED, withOverlappedEx)
 import GHC.Internal.Foreign.Ptr
 import GHC.Internal.Foreign.C.Types
 import GHC.Internal.Foreign.C.Error
@@ -465,10 +465,10 @@ hwndReadNonBlocking :: Io NativeHandle -> Ptr Word8 -> Word64 -> Int
                     -> IO (Maybe Int)
 hwndReadNonBlocking hwnd ptr offset bytes
   = do mngr <- Mgr.getSystemManager
-       val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
+       Mgr.withException "hwndReadNonBlocking" $
+              withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
                                (isAsynchronous hwnd) offset (startCB ptr)
                                completionCB
-       return $ ioValue val
   where
     startCB inputBuf lpOverlapped = do
       debugIO ":: hwndReadNonBlocking"
@@ -511,10 +511,11 @@ hwndWrite hwnd ptr offset bytes
 hwndWriteNonBlocking :: Io NativeHandle -> Ptr Word8 -> Word64 -> Int -> IO Int
 hwndWriteNonBlocking hwnd ptr offset bytes
   = do mngr <- Mgr.getSystemManager
-       val <- withOverlappedEx mngr "hwndReadNonBlocking" (toHANDLE hwnd)
-                               (isAsynchronous hwnd) offset (startCB ptr)
-                               completionCB
-       return $ fromIntegral $ ioValue val
+       fmap fromIntegral $
+           Mgr.withException "hwndWriteNonBlocking" $
+           withOverlappedEx mngr "hwndWriteNonBlocking" (toHANDLE hwnd)
+                            (isAsynchronous hwnd) offset (startCB ptr)
+                            completionCB
   where
     startCB :: Ptr a -> LPOVERLAPPED -> IO (Mgr.CbResult a1)
     startCB outBuf lpOverlapped = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:58:14 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 03:58:14 -0400
Subject: [Git][ghc/ghc][master] compiler: Fix orientation of GHC.Hs.Doc boot
 file
Message-ID: <6708da96cf941_9cace8706f4579c9@gitlab.mail>



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


Commits:
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -


4 changed files:

- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- − compiler/Language/Haskell/Syntax/ImpExp.hs-boot


Changes:

=====================================
compiler/GHC/Hs/Doc.hs-boot
=====================================
@@ -0,0 +1,19 @@
+{-# LANGUAGE RoleAnnotations #-}
+module GHC.Hs.Doc where
+
+-- See #21592 for progress on removing this boot file.
+
+import GHC.Types.SrcLoc
+import GHC.Hs.DocString
+import Data.Kind
+
+type role WithHsDocIdentifiers representational nominal
+type WithHsDocIdentifiers :: Type -> Type -> Type
+data WithHsDocIdentifiers a pass
+
+type HsDoc :: Type -> Type
+type HsDoc = WithHsDocIdentifiers HsDocString
+
+type LHsDoc :: Type -> Type
+type LHsDoc pass = Located (HsDoc pass)
+


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -110,7 +110,7 @@ import qualified Data.ByteString as BS
 import qualified Data.ByteString.Char8 as BS.Char8
 
 import Language.Haskell.Syntax.Module.Name
-import {-# SOURCE #-} Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
+import Language.Haskell.Syntax.ImpExp (IsBootInterface(..))
 
 ---------------------------------------------------------------------
 -- MODULES


=====================================
compiler/Language/Haskell/Syntax/ImpExp.hs
=====================================
@@ -16,7 +16,7 @@ import Data.Int (Int)
 
 import Control.DeepSeq
 
-import GHC.Hs.Doc -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
+import {-# SOURCE #-} GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST
 
 {-
 ************************************************************************


=====================================
compiler/Language/Haskell/Syntax/ImpExp.hs-boot deleted
=====================================
@@ -1,16 +0,0 @@
-module Language.Haskell.Syntax.ImpExp where
-
-import Data.Eq
-import Data.Ord
-import Text.Show
-import Data.Data
-
--- This boot file should be short lived: As soon as the dependency on
--- `GHC.Hs.Doc` is gone we'll no longer have cycles and can get rid this file.
-
-data IsBootInterface = NotBoot | IsBoot
-
-instance Eq IsBootInterface
-instance Ord IsBootInterface
-instance Show IsBootInterface
-instance Data IsBootInterface



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8584504b68418eaa12f1332a22ccb7d354aacc00

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 07:59:00 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Fri, 11 Oct 2024 03:59:00 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 15 commits: Handle exceptions from IO
 manager backend
Message-ID: <6708dac440772_9cace1e599c581f5@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
465cb564 by Zubin Duggal at 2024-10-11T07:58:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
05bcb67c by Zubin Duggal at 2024-10-11T07:58:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
e127d3da by Zubin Duggal at 2024-10-11T07:58:57+00:00
Bump Cabal submodule to 3.14

Metric Increase:
    haddock.Cabal

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50ec8c4ab9db8d0bec202b44a5075790bb45e9eb...e127d3da421e3bab0907db350c23ce1103c78320

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50ec8c4ab9db8d0bec202b44a5075790bb45e9eb...e127d3da421e3bab0907db350c23ce1103c78320
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 08:28:08 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Fri, 11 Oct 2024 04:28:08 -0400
Subject: [Git][ghc/ghc] Pushed new branch
 wip/supersven/superfluous_register_constants
Message-ID: <6708e19872e7d_9cace164522058756@gitlab.mail>



Sven Tennie pushed new branch wip/supersven/superfluous_register_constants at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/superfluous_register_constants
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 08:31:55 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Fri, 11 Oct 2024 04:31:55 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 19 commits: Fix typo in the
 @since annotation of annotateIO
Message-ID: <6708e27bc578a_1a1d20bc3f4686da@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
6fdc60c5 by Hassan Al-Awwadi at 2024-10-11T10:25:17+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, and we parameterized it over the ghcPass instead
of over some arbitrary type.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -
a43e0018 by Hassan Al-Awwadi at 2024-10-11T10:25:17+02:00
review changes for BooleanFormula

* Removed bfExprMap, instead bfMap is fully defined inside Ghc.Data.BooleanFormula
* Cleaned up some classes for BooleanFormula
* Simplified toIfaceBooleanFormula to no longer be a higher order function
* And removed fromIfaceBooleanFormula completely

- - - - -
f782fe43 by Hassan Al-Awwadi at 2024-10-11T10:25:17+02:00
removed unused import

- - - - -
44f510b5 by Hassan Al-Awwadi at 2024-10-11T10:25:17+02:00
Only stores BOoleanFormula source-locations in leaves

- - - - -
274d57d1 by Hassan Al-Awwadi at 2024-10-11T10:25:17+02:00
removed unused import

- - - - -


30 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65e5ca6bf5d349ecb4ba1a0df4700c573f5252c8...274d57d1f658940baf5d95f1bb9b666ab7ca2f8d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65e5ca6bf5d349ecb4ba1a0df4700c573f5252c8...274d57d1f658940baf5d95f1bb9b666ab7ca2f8d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 08:31:57 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Fri, 11 Oct 2024 04:31:57 -0400
Subject: [Git][ghc/ghc][wip/supersven/superfluous_register_constants] 17
 commits: ci: RISCV64 cross-compile testing
Message-ID: <6708e27daf314_1a1d20bc520688ac@gitlab.mail>



Sven Tennie pushed to branch wip/supersven/superfluous_register_constants at Glasgow Haskell Compiler / GHC


Commits:
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
2c25f315 by Sven Tennie at 2024-10-11T08:30:16+00:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c407a293688d8edd60f7a51a304994da3d83f35...2c25f315488db52ff0d20ca172e075cf60a0280e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c407a293688d8edd60f7a51a304994da3d83f35...2c25f315488db52ff0d20ca172e075cf60a0280e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 08:37:03 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Fri, 11 Oct 2024 04:37:03 -0400
Subject: [Git][ghc/ghc][wip/ttg/lits] 13 commits: Handle exceptions from IO
 manager backend
Message-ID: <6708e3af62891_1a1d20bc3f472692@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/lits at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
198661eb by Hassan Al-Awwadi at 2024-10-11T10:31:20+02:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf1a60fd9c9308cc4a97f4de273f1570170a50b9...198661ebad49f117cd3e4742cdd7bec4b2a4daa3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf1a60fd9c9308cc4a97f4de273f1570170a50b9...198661ebad49f117cd3e4742cdd7bec4b2a4daa3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 09:19:30 2024
From: gitlab at gitlab.haskell.org (Jade (@Jade))
Date: Fri, 11 Oct 2024 05:19:30 -0400
Subject: [Git][ghc/ghc][wip/structured-ghci-errors] 100 commits: ci: Run
 abi-test on test-abi label
Message-ID: <6708eda2d31ff_1a1d205834dc79620@gitlab.mail>



Jade pushed to branch wip/structured-ghci-errors at Glasgow Haskell Compiler / GHC


Commits:
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
0f3eb951 by sheaf at 2024-10-11T09:21:48+02:00
Generalise GHC diagnostic code infrastructure

This commit generalises the infrastructure used for diagnostic codes,
allowing it to be used for other namespaces than the GHC namespace.
In particular, this enables GHCi to re-use the same infrastructure to
emit error messages.

- - - - -
4f677e84 by Jade at 2024-10-11T11:11:08+02:00
Add structured errors to GHCi (#23338)

This patch creates the 'GhciCommandErrorMessage' data type which
implents the 'Diagnostic' class and also provides error code for these
error conditions.

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be47d68a3c0b0a81da08b57541a34256b2056857...4f677e846558ae7f3a2300e07f955fb659fb1f1c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be47d68a3c0b0a81da08b57541a34256b2056857...4f677e846558ae7f3a2300e07f955fb659fb1f1c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 10:18:25 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Fri, 11 Oct 2024 06:18:25 -0400
Subject: [Git][ghc/ghc][wip/only_job] 28 commits: javascript: Read fields of
 ObjectBlock lazily
Message-ID: <6708fb71540e3_1a1d208e422091069@gitlab.mail>



Matthew Pickering pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
cca59600 by Matthew Pickering at 2024-10-11T11:17:27+01:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


29 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/653f25bd90528f614e115a1d9de830afaa52d8bb...cca59600f31f2b3e59bd5f8eeca99901a879d007

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/653f25bd90528f614e115a1d9de830afaa52d8bb...cca59600f31f2b3e59bd5f8eeca99901a879d007
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 11:02:43 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 11 Oct 2024 07:02:43 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibbles related to the MR
Message-ID: <670905d3160b4_3646cedd9a01069b8@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
46564aa6 by Simon Peyton Jones at 2024-10-11T12:02:20+01:00
Wibbles related to the MR

- - - - -


1 changed file:

- compiler/GHC/Tc/Solver.hs


Changes:

=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -61,6 +61,7 @@ import GHC.Types.Error
 import GHC.Driver.DynFlags( DynFlags, xopt )
 import GHC.Utils.Panic
 import GHC.Utils.Outputable
+import GHC.Utils.Misc( filterOut )
 
 import GHC.Data.Bag
 
@@ -1469,19 +1470,17 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- mono_tvs0 are all the type variables we can't quantify over
              mono_tvs0
                | isTopTcLevel tc_lvl
-                 -- At top level: we want to promote tyvars that are
+                 -- At top level: we want to promote only tyvars that are
                  --  (a) free in envt (already promoted)
                  --  (b) will be defaulted
                  --  (c) determined by (a) or (b)
                  -- mono_tvs0 deals with (a) or (b); closeWrtFunDeps deals with (c)
                = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
-                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
 
                | otherwise
                = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
                      -- outerLevelTyVars are free in the envt, so can't quantify them
                  `unionVarSet` tyCoVarsOfTypes no_quant
-                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
                  `unionVarSet` co_var_tvs
                      -- If we don't quantify over a constraint in no_quant, we
                      -- can either not-quantify its free vars (hoping that call
@@ -1500,9 +1499,9 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- We need to know not to quantify over beta or gamma, because they
              -- are in the equality constraint with alpha. Actual test case:
              -- typecheck/should_compile/tc213
-             -- See Note [growThetaTyVars vs closeWrtFunDeps]
+             -- see Note [growThetaTyVars vs closeWrtFunDeps]
              mono_tvs1 = closeWrtFunDeps post_mr_quant $
-                         mono_tvs0 `unionVarSet` tyCoVarsOfTypes mr_no_quant
+                         (mono_tvs0 `unionVarSet` tyCoVarsOfTypes mr_no_quant)
 
              -- Finally, delete psig_qtvs
              -- If the user has explicitly asked for quantification, then that
@@ -1513,6 +1512,14 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- in Step 2 of Note [Deciding quantification].
              mono_tvs = mono_tvs1 `delVarSetList` psig_qtvs
 
+             -- Do not quantify over any constraint mentioning a "newly-mono" tyvar
+             -- The "newly-mono" tyvars are the ones not free in the envt
+             -- nor forced to be promoted by the MR; but are deternmined by them
+             newly_mono = mono_tvs `minusVarSet` mono_tvs0
+             final_quant
+               | isTopTcLevel tc_lvl = filterOut (predMentions newly_mono) post_mr_quant
+               | otherwise           = post_mr_quant
+
        -- Check if the Monomorphism Restriction has bitten
        ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $
          do { let mono_tvs_wo_mr = closeWrtFunDeps post_mr_quant mono_tvs0
@@ -1537,10 +1544,11 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
            , text "post_mr_quant =" <+> ppr post_mr_quant
            , text "no_quant =" <+> ppr no_quant
            , text "mr_no_quant =" <+> ppr mr_no_quant
+           , text "final_quant =" <+> ppr final_quant
            , text "mono_tvs =" <+> ppr mono_tvs
            , text "co_vars =" <+> ppr co_vars ]
 
-       ; return (post_mr_quant, co_vars) }
+       ; return (final_quant, co_vars) }
 
 -------------------
 applyMR :: DynFlags -> InferMode -> [PredType]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46564aa68229130568ef932b0e140187de436191

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 11:27:13 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 11 Oct 2024 07:27:13 -0400
Subject: [Git][ghc/ghc][wip/T25266] Respond to rae review
Message-ID: <67090b91c44f2_3646ce2d48e4109535@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
5cce9971 by Simon Peyton Jones at 2024-10-11T12:26:52+01:00
Respond to rae review

- - - - -


4 changed files:

- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -763,10 +763,10 @@ simplifyDeriv (DS { ds_loc = loc, ds_tvs = tvs
        -- See [STEP DAC HOIST]
        -- From the simplified constraints extract a subset 'good' that will
        -- become the context 'min_theta' for the derived instance.
-       ; let (simple1, simple2) = approximateWC solved_wanteds
-             residual_simple    = simple1 `unionBags` simple2
-             head_size          = pSizeClassPred clas inst_tys
-             good = mapMaybeBag get_good residual_simple
+       ; let (residual_simple, _) = approximateWC solved_wanteds
+                -- Ignore any equalities hidden under Given equalities
+             head_size = pSizeClassPred clas inst_tys
+             good      = mapMaybeBag get_good residual_simple
 
              -- Returns @Just p@ (where @p@ is the type of the Ct) if a Ct is
              -- suitable to be inferred in the context of a derived instance.


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -59,6 +59,7 @@ import GHC.Types.Basic
 import GHC.Types.Error
 
 import GHC.Driver.DynFlags( DynFlags, xopt )
+import GHC.Driver.Flags( WarningFlag(..) )
 import GHC.Utils.Panic
 import GHC.Utils.Outputable
 import GHC.Utils.Misc( filterOut )
@@ -1408,7 +1409,7 @@ When generalising `f`, closeWrtFunDeps will promote beta[1] to beta[0].
 But we do NOT want to make a top level type
   f :: C Int beta[0] => blah
 The danger is that beta[0] is defaulted to Any, and that then appears
-in a user error message.  Even the type `blah` mentions beta[0], /and/
+in a user error message.  Even if the type `blah` mentions beta[0], /and/
 there is a call that fixes beta[0] to (say) Bool, we'll end up with
 [W] C Int Bool, which is insoluble.  Why insoluble? If there was an
    instance C Int Bool
@@ -1417,9 +1418,9 @@ then fundeps would have fixed beta:=Bool in the first place.
 If the binding of `f` is nested, things are different: we can
 definitely see all the calls.
 
-TODO: this reasoning is incomplete.  Shouldn't it apply to nested
-bindings too, when this promotion happens so it's not because
-beta is already free in the envt???
+For nested bindings, I think it just doesn't matter. No one cares what this
+variable ends up being; it seems silly to halt compilation around it. (Like in
+the length [] case.)
 -}
 
 decideAndPromoteTyVars :: InferMode
@@ -1521,7 +1522,8 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
                | otherwise           = post_mr_quant
 
        -- Check if the Monomorphism Restriction has bitten
-       ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $
+       ; warn_mr <- woptM Opt_WarnMonomorphism
+       ; when (warn_mr && case infer_mode of { ApplyMR -> True; _ -> False}) $
          do { let mono_tvs_wo_mr = closeWrtFunDeps post_mr_quant mono_tvs0
                                    `delVarSetList` psig_qtvs
 
@@ -1662,7 +1664,8 @@ decideQuantifiedTyVars skol_info name_taus psigs candidates
        ; quantifyTyVars skol_info DefaultNonStandardTyVars dvs_plus }
 
 ------------------
-getSeedTys :: [(Name,TcType)] -> [TcIdSigInst]
+getSeedTys :: [(Name,TcType)]    -- The type of each RHS in the group
+           -> [TcIdSigInst]      -- Any partial type signatures
            -> TcM ( [TcTyVar]    -- Zonked partial-sig quantified tyvars
                   , ThetaType    -- Zonked partial signature thetas
                   , [TcType] )   -- Zonked tau-tys from the bindings


=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -822,6 +822,8 @@ findDefaultableGroups (default_tys, extended_defaults) wanteds
     simples                = simples1 `unionBags` simples2
       -- simples: for the purpose of defaulting we don't care
       --          about shape or enclosing equalities
+      -- See (W3) in Note [ApproximateWC] in GHC.Tc.Types.Constraint
+
     (unaries, non_unaries) = partitionWith find_unary (bagToList simples)
     unary_groups           = equivClasses cmp_tv unaries
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1776,9 +1776,10 @@ At the end, we will hopefully have substituted uf1 := F alpha, and we
 will be able to report a more informative error:
     'Can't construct the infinite type beta ~ F alpha beta'
 
+
 ************************************************************************
 *                                                                      *
-            Invariant checking (debug only)
+                     approximateWC
 *                                                                      *
 ************************************************************************
 -}
@@ -1813,8 +1814,8 @@ approximateWC wc
     float_ct :: Bool -> TcTyCoVarSet -> Ct
              -> ApproxWC -> ApproxWC
     float_ct encl_eqs skol_tvs ct acc@(quant, no_quant)
-       | isGivenCt ct                                = acc
-       | insolubleCt ct                              = acc
+       | assertPpr (isWantedCt ct) (ppr ct) $  -- Only Wanteds expected here
+         insolubleCt ct                              = acc
        | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
        | otherwise
        = case classifyPredType (ctPred ct) of
@@ -1894,9 +1895,9 @@ Wrinkle (W2)
   abstracting over more constraints does no harm.
 
 Wrinkle (W3)
-  In findDefaultableGroups we are not worried about the
-  most-general type; and we /do/ want to float out of equalities
-  (#12797).  Hence the boolean flag to approximateWC.
+  In findDefaultableGroups we are not worried about the most-general type; and
+  we /do/ want to float out of equalities (#12797).  Hence we just union the two
+  returned lists.
 
 ------ Historical note -----------
 There used to be a second caveat, driven by #8155



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5cce9971b5b86d21e619ae4d5a0dacf7c4f769b8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 11:41:31 2024
From: gitlab at gitlab.haskell.org (=?UTF-8?B?QmVyayDDlnprw7x0w7xrIChAb3prdXR1ayk=?=)
Date: Fri, 11 Oct 2024 07:41:31 -0400
Subject: [Git][ghc/ghc][wip/ozkutuk/sprint-fun] 434 commits: Replace
 '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw
Message-ID: <67090eeba21d6_3646ce3f26401182d3@gitlab.mail>



Berk Özkütük pushed to branch wip/ozkutuk/sprint-fun at Glasgow Haskell Compiler / GHC


Commits:
edfe6140 by qqwy at 2024-06-08T11:23:54-04:00
Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw

- - - - -
35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00
rts: cleanup inlining logic

This patch removes pre-C11 legacy code paths related to
INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE
is treated as static inline in most cases (fixes #24945), and also
corrects the comments accordingly.

- - - - -
9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00
CODEOWNERS: add @core-libraries to track base interface changes

A low-tech tactical solution for #24919

- - - - -
580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update CHANGELOG to reflect current version

- - - - -
391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update prologue.txt to reflect package description

- - - - -
3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00
compiler: Clarify comment regarding need for MOVABS

The comment wasn't clear in stating that it was only applicable to
immediate source and memory target operands.

- - - - -
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
2f550bc9 by Berk Özkütük at 2024-10-11T13:38:21+02:00
Disambiguate closures' printing from thunks (#23507)

- - - - -
fcb6bfac by Berk Özkütük at 2024-10-11T13:38:37+02:00
Only print function closures

- - - - -


18 changed files:

- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4404090cae7ca440eaa81809b492c282b233cffe...fcb6bfac962ac843ef528fcf27f8ef194cfa2c88

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4404090cae7ca440eaa81809b492c282b233cffe...fcb6bfac962ac843ef528fcf27f8ef194cfa2c88
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 11:52:05 2024
From: gitlab at gitlab.haskell.org (jeffrey young (@doyougnu))
Date: Fri, 11 Oct 2024 07:52:05 -0400
Subject: [Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef]
 ghc-internal: hide linkerOptimistic in MiscFlags
Message-ID: <670911651e955_3646ce6a32e0122344@gitlab.mail>



jeffrey young pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
979407b1 by doyougnu at 2024-10-11T07:51:41-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -


5 changed files:

- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,7 +162,8 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
-    , linkerOptimistic      :: Bool
+    -- TODO: #25354 uncomment to expose this flag to base.
+    -- , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag
@@ -537,8 +538,9 @@ getMiscFlags = do
                   (#{peek MISC_FLAGS, internalCounters} ptr :: IO CBool))
             <*> (toBool <$>
                   (#{peek MISC_FLAGS, linkerAlwaysPic} ptr :: IO CBool))
-            <*> (toBool <$>
-                  (#{peek MISC_FLAGS, linkerOptimistic} ptr :: IO CBool))
+            -- TODO: #25354 uncomment to expose this flag to base.
+            -- <*> (toBool <$>
+            --       (#{peek MISC_FLAGS, linkerOptimistic} ptr :: IO CBool))
             <*> #{peek MISC_FLAGS, linkerMemBase} ptr
             <*> (toEnum . fromIntegral
                  <$> (#{peek MISC_FLAGS, ioManager} ptr :: IO Word32))


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9106,7 +9106,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -12148,7 +12148,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -9330,7 +9330,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -9106,7 +9106,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/979407b14e93aa903606d22fc9cd1cddf443bc60

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 14:01:52 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 10:01:52 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: Put RdrName
 in the foExt field of FieldOcc
Message-ID: <67092fd0a51fb_3646ceda85e01433eb@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
198661eb by Hassan Al-Awwadi at 2024-10-11T10:31:20+02:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
d148f6e0 by Artem Pelenitsyn at 2024-10-11T10:01:46-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43ca92d919405ab413ba0df63a456abb15169b9d...d148f6e01938a9d243f9dbb6bae6a3951077a348

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43ca92d919405ab413ba0df63a456abb15169b9d...d148f6e01938a9d243f9dbb6bae6a3951077a348
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 14:21:50 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Fri, 11 Oct 2024 10:21:50 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 3 commits: hadrian: Handle broken
 symlinks properly when creating source dist directories
Message-ID: <6709347e3e896_1f869ebcac0558fc@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
88f7e72b by Zubin Duggal at 2024-10-11T19:05:51+05:30
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
8e421252 by Zubin Duggal at 2024-10-11T19:05:51+05:30
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
14d492a2 by Zubin Duggal at 2024-10-11T19:51:09+05:30
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -


4 changed files:

- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -55,8 +55,9 @@ archiveSourceTree prepare fname = do
   runBuilderWithCmdOptions
       [Cwd $ sourceDistRoot -/- dirName]
       (Tar Create)
-      ["chJf", ".." -/- tarName,  baseName]
-      ["chJf", ".." -/- tarName] [baseName]
+      -- See https://github.com/haskell/cabal/issues/10442 for why we exclude this file.
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName,  baseName]
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName] [baseName]
 
 
 -- | This creates a symlink to the 'source' at 'target'
@@ -74,7 +75,9 @@ copyFileSourceDist source target = do
       error ("source-dist: tried to create non-relative symlink in source dist: " ++ show link_target)
     putProgressInfo =<< renderAction ("Create symlink (" ++ link_target ++ ")") source target
     isDirectory <- liftIO $ IO.doesDirectoryExist source
-    when (not isDirectory) $
+    -- We don't want to call `need` on broken symlinks
+    linkTargetExists <- liftIO $ IO.doesPathExist link_target
+    when (not isDirectory && linkTargetExists) $
       need [source]
     let createLink src tgt
           | isDirectory = liftIO $ IO.createDirectoryLink src tgt


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e127d3da421e3bab0907db350c23ce1103c78320...14d492a264e43973970cf5c39989bf249b9f9509

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e127d3da421e3bab0907db350c23ce1103c78320...14d492a264e43973970cf5c39989bf249b9f9509
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 14:25:55 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Fri, 11 Oct 2024 10:25:55 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] booleanFormula p ->
 booleanFormula a
Message-ID: <67093573402d2_1f869ebdc045636@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
cf67d010 by Hassan Al-Awwadi at 2024-10-11T16:25:14+02:00
booleanFormula p -> booleanFormula a

its been quite the cycle, but this time its ok because we don't need to have a p to pop into XRec

- - - - -


17 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/BooleanFormula.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


Changes:

=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,7 +26,6 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
-import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -136,7 +135,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
+type ClassMinimalDef = BooleanFormula Name -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -43,6 +43,7 @@ module GHC.CoreToIface
     , toIfaceVar
       -- * Other stuff
     , toIfaceLFInfo
+    , toIfaceBooleanFormula
       -- * CgBreakInfo
     , dehydrateCgBreakInfo
     ) where
@@ -88,6 +89,7 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc
 
 import Data.Maybe ( isNothing, catMaybes )
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
 
 {- Note [Avoiding space leaks in toIface*]
    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -689,6 +691,10 @@ toIfaceLFInfo nm lfi = case lfi of
     LFLetNoEscape ->
       panic "toIfaceLFInfo: LFLetNoEscape"
 
+toIfaceBooleanFormula :: NamedThing a
+                      => BooleanFormula a -> IfaceBooleanFormula
+toIfaceBooleanFormula = fmap (mkIfLclName . getOccFS)
+
 -- Dehydrating CgBreakInfo
 
 dehydrateCgBreakInfo :: [TyVar] -> [Maybe (Id, Word)] -> Type -> CgBreakInfo


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -11,7 +11,6 @@
 module GHC.Data.BooleanFormula (
         module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
-        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
         pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
@@ -23,50 +22,10 @@ import Data.List.NonEmpty ( NonEmpty (..), init, last )
 import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
-import GHC.Types.SrcLoc (unLoc)
 import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( SrcSpanAnnL )
-import GHC.Hs.Extension (GhcPass (..), OutputableBndrId)
-import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
 import Language.Haskell.Syntax.BooleanFormula
 
 
-----------------------------------------------------------------------
--- Boolean formula type and smart constructors
-----------------------------------------------------------------------
-
-type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
-
--- if we had Functor/Traversable (LbooleanFormula p) we could use that
--- as a constraint and we wouldn't need to specialize to just GhcPass p,
--- but becuase LBooleanFormula is a type synonym such a constraint is
--- impossible.
-
--- BooleanFormula can't be an instance of functor because it can't lift
--- arbitrary functions `a -> b`, only functions of type `LIdP a -> LIdP b`
--- ditto for Traversable.
-bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
-      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
-bfMap f = go
-  where
-    go (Var    a  ) = Var     $ f a
-    go (And    bfs) = And     $ map go bfs
-    go (Or     bfs) = Or      $ map go bfs
-    go (Parens bf ) = Parens  $     go bf
-
-bfTraverse  :: Applicative f
-            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
-            -> BooleanFormula (GhcPass p)
-            -> f (BooleanFormula (GhcPass p'))
-bfTraverse f = go
-  where
-    go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] go bfs
-    go (Or     bfs) = Or     <$> traverse @[] go bfs
-    go (Parens bf ) = Parens <$>              go bf
-
-
-
 {-
 Note [Simplification of BooleanFormulas]
 ~~~~~~~~~~~~~~~~~~~~~~
@@ -105,15 +64,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula (GhcPass p) -> Bool
+isFalse :: BooleanFormula a -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula (GhcPass p) -> Bool
+isTrue :: BooleanFormula a -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
+eval :: (a -> Bool) -> BooleanFormula a -> Bool
 eval f (Var x)    = f x
 eval f (And xs)   = all (eval f) xs
 eval f (Or xs)    = any (eval f) xs
@@ -121,10 +80,10 @@ eval f (Parens x) = eval f x
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: forall p. Eq (LIdP (GhcPass p))
-          => (LIdP (GhcPass p) ->  Maybe Bool)
-          -> BooleanFormula (GhcPass p)
-          -> BooleanFormula (GhcPass p)
+simplify  :: Eq a
+          => (a ->  Maybe Bool)
+          -> BooleanFormula a
+          -> BooleanFormula a
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
@@ -135,10 +94,10 @@ simplify f (Parens x) = simplify f x
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq (LIdP (GhcPass p))
-              => (LIdP (GhcPass p) -> Bool)
-              -> BooleanFormula (GhcPass p)
-              -> Maybe (BooleanFormula (GhcPass p))
+isUnsatisfied :: Eq a
+              => (a -> Bool)
+              -> BooleanFormula a
+              -> Maybe (BooleanFormula a)
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -151,42 +110,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
-Var x  `impliesAtom` y = unLoc x == unLoc y
+impliesAtom :: Eq a => BooleanFormula a -> a-> Bool
+Var x  `impliesAtom` y = x == y
 And xs `impliesAtom` y = any (`impliesAtom` y) xs
 -- we have all of xs, so one of them implying y is enough
 Or  xs `impliesAtom` y = all (`impliesAtom` y) xs
 Parens x `impliesAtom` y =  x `impliesAtom` y
 
-implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
+implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
+    go :: Uniquable a => Clause a -> Clause a -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms (unLoc x) r -> True
-                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms x r -> True
+                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = hyp':hyps }     r
             And hyps'  -> go l { clauseExprs =  hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms (unLoc x) l -> True
-                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
+            Var x | memberClauseAtoms x l -> True
+                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause p = Clause {
-        clauseAtoms :: UniqSet (IdP p),
-        clauseExprs :: [BooleanFormula p]
+data Clause a = Clause {
+        clauseAtoms :: UniqSet a,
+        clauseExprs :: [BooleanFormula a]
     }
-extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
+extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
+memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -195,10 +154,10 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+pprBooleanFormula'  :: (Rational -> a -> SDoc)
                     -> (Rational -> [SDoc] -> SDoc)
                     -> (Rational -> [SDoc] -> SDoc)
-                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
+                    -> Rational -> BooleanFormula a -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
@@ -209,15 +168,15 @@ pprBooleanFormula' pprVar pprAnd pprOr = go
   go p (Parens x) = go p x
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
-                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
+pprBooleanFormula :: (Rational -> a -> SDoc)
+                  -> Rational -> BooleanFormula a -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
+pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -227,13 +186,13 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance OutputableBndrId p => Outputable (BooleanFormula (GhcPass p)) where
+instance OutputableBndr a => Outputable (BooleanFormula a) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
+pprBooleanFormulaNormal :: OutputableBndr a => BooleanFormula a -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc (unLoc x)
+    go (Var x)    = pprPrefixOcc x
     go (And xs)   = fsep $ punctuate comma (map go xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map go xs)


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -13,6 +13,8 @@
                                       -- in module Language.Haskell.Syntax.Extension
 
 {-# OPTIONS_GHC -Wno-orphans #-} -- Outputable
+{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
+{-# HLINT ignore "Use camelCase" #-}
 
 {-
 (c) The University of Glasgow 2006
@@ -933,8 +935,9 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: OutputableBndrId p  => BooleanFormula (GhcPass p) -> SDoc
-pprMinimalSig = pprBooleanFormulaNormal
+pprMinimalSig :: (OutputableBndr name)
+              => BooleanFormula (GenLocated l name) -> SDoc
+pprMinimalSig bf = ppr (fmap unLoc bf)
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -591,5 +591,5 @@ deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
 
-deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+deriving instance Data a => Data (BooleanFormula a)
 ---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -13,10 +13,6 @@
 module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
-   , toIfaceBooleanFormula
-
-   -- converting back
-   , traverseIfaceBooleanFormula
    )
 where
 
@@ -340,22 +336,4 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
 
-toIfaceBooleanFormula ::  NamedThing (IdP (GhcPass p))
-                      => BooleanFormula (GhcPass p)  -> IfaceBooleanFormula
-toIfaceBooleanFormula = go
-  where
-    go (Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $ nm
-    go (And bfs  ) = IfAnd    $ map go bfs
-    go (Or bfs   ) = IfOr     $ map go bfs
-    go (Parens bf) = IfParens $     go bf
-
-traverseIfaceBooleanFormula :: Applicative f
-                            => (IfLclName -> f (LIdP (GhcPass p)))
-                            -> IfaceBooleanFormula
-                            -> f (BooleanFormula (GhcPass p))
-traverseIfaceBooleanFormula f = go
-  where
-    go (IfVar nm    ) = Var     <$> f nm
-    go (IfAnd ibfs  ) = And     <$> traverse go ibfs
-    go (IfOr ibfs   ) = Or      <$> traverse go ibfs
-    go (IfParens ibf) = Parens  <$> go ibf
\ No newline at end of file
+


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2041,24 +2041,13 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance (HiePass p, Data (IdGhcP p))
-  => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
-    toHie (L span form) =  concatM [makeNode form (locA span), toHie form]
-instance (HiePass p, Data (IdGhcP p))
-  => ToHie (BooleanFormula (GhcPass p)) where
-    toHie formula =  concatM $ case formula of
-      Var a ->
-        [ toHie $ C Use a
-        ]
-      And forms ->
-        [ toHie forms
-        ]
-      Or forms ->
-        [ toHie forms
-        ]
-      Parens f ->
-        [ toHie f
-        ]
+instance ToHie (LocatedN (BooleanFormula (LocatedN Name))) where
+  toHie (L span form) =  concatM [makeNode form (locA span), toHie form]
+instance ToHie (BooleanFormula (LocatedN Name)) where
+  toHie (Var a)     = toHie $ C Use a
+  toHie (And forms) = toHie forms
+  toHie (Or forms ) = toHie forms
+  toHie (Parens f ) = toHie f
 
 instance ToHie (LocatedAn NoEpAnns HsIPName) where
   toHie (L span e) = makeNodeA e span


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -6,6 +6,7 @@
 
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE DeriveTraversable #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
 
 module GHC.Iface.Syntax (
         module GHC.Iface.Type,
@@ -92,6 +93,9 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
                        seqList, zipWithEqual )
 
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula(..))
+import GHC.Data.BooleanFormula (pprBooleanFormula, isTrue)
+
 import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
@@ -212,12 +216,7 @@ data IfaceClassBody
      ifMinDef    :: IfaceBooleanFormula       -- Minimal complete definition
     }
 
-data IfaceBooleanFormula
-  = IfVar IfLclName
-  | IfAnd [IfaceBooleanFormula]
-  | IfOr [IfaceBooleanFormula]
-  | IfParens IfaceBooleanFormula
-  deriving Eq
+type IfaceBooleanFormula = BooleanFormula IfLclName
 
 data IfaceTyConParent
   = IfNoParent
@@ -1033,29 +1032,12 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | otherwise     = Nothing
 
       pprMinDef :: IfaceBooleanFormula -> SDoc
-      pprMinDef minDef = ppUnless (ifLclIsTrue minDef) $ -- hide empty definitions
+      pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
-        pprifLclBooleanFormula
+        pprBooleanFormula
           (\_ def -> let fs = ifLclNameFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
-      ifLclIsTrue :: IfaceBooleanFormula -> Bool
-      ifLclIsTrue (IfAnd []) = True
-      ifLclIsTrue _          = False
-
-      pprifLclBooleanFormula  :: (Rational -> IfLclName -> SDoc)
-                              -> Rational -> IfaceBooleanFormula -> SDoc
-      pprifLclBooleanFormula pprVar = go
-        where
-        go p (IfVar x)  = pprVar p x
-        go p (IfAnd []) = cparen (p > 0) empty
-        go p (IfAnd xs) = pprAnd p (map (go 3) xs)
-        go _ (IfOr  []) = keyword $ text "FALSE"
-        go p (IfOr  xs) = pprOr p (map (go 2) xs)
-        go p (IfParens x) = go p x
-        pprAnd p = cparen (p > 3) . fsep . punctuate comma
-        pprOr  p = cparen (p > 2) . fsep . intersperse vbar
-
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 
@@ -2146,17 +2128,17 @@ instance Binary IfaceDecl where
 
 instance Binary IfaceBooleanFormula where
     put_ bh = \case
-        IfVar a1    -> putByte bh 0 >> put_ bh a1
-        IfAnd a1    -> putByte bh 1 >> put_ bh a1
-        IfOr a1     -> putByte bh 2 >> put_ bh a1
-        IfParens a1 -> putByte bh 3 >> put_ bh a1
+        Var a1    -> putByte bh 0 >> put_ bh a1
+        And a1    -> putByte bh 1 >> put_ bh a1
+        Or a1     -> putByte bh 2 >> put_ bh a1
+        Parens a1 -> putByte bh 3 >> put_ bh a1
 
     get bh = do
         getByte bh >>= \case
-            0 -> IfVar    <$> get bh
-            1 -> IfAnd    <$> get bh
-            2 -> IfOr     <$> get bh
-            _ -> IfParens <$> get bh
+            0 -> Var    <$> get bh
+            1 -> And    <$> get bh
+            2 -> Or     <$> get bh
+            _ -> Parens <$> get bh
 
 {- Note [Lazy deserialization of IfaceId]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -2813,10 +2795,10 @@ instance NFData IfaceClassBody where
 
 instance NFData IfaceBooleanFormula where
   rnf = \case
-      IfVar f1    -> rnf f1
-      IfAnd f1    -> rnf f1
-      IfOr f1     -> rnf f1
-      IfParens f1 -> rnf f1
+      Var f1    -> rnf f1
+      And f1    -> rnf f1
+      Or f1     -> rnf f1
+      Parens f1 -> rnf f1
 
 instance NFData IfaceAT where
   rnf (IfaceAT f1 f2) = rnf f1 `seq` rnf f2


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -44,7 +44,6 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (traverseIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -139,6 +138,7 @@ import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
+import Language.Haskell.Syntax.BooleanFormula (mkOr)
 
 {-
 This module takes
@@ -299,23 +299,9 @@ mergeIfaceDecl d1 d2
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
 
-          -- same as BooleanFormula's mkOr, but specialized to IfaceBooleanFormula,
-          -- which can be taught of as being (BooleanFormula IfacePass) morally.
-          -- In practice, however, its a seperate type so it needs its own function
-          -- It makes an Or and does some super basic simplification.
-          mkIfaceOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
-          mkIfaceOr = maybe (IfAnd []) (mkIfaceOr' . nub . concat) . mapM fromOr
-            where
-            fromOr bf = case bf of
-              (IfOr xs)  -> Just xs
-              (IfAnd []) -> Nothing
-              _        -> Just [bf]
-            mkIfaceOr' [x] = x
-            mkIfaceOr' xs = IfOr xs
-
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = mkIfaceOr [bf1, bf2]
+                ifMinDef = mkOr [bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -811,7 +797,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; mindef <- traverseIfaceBooleanFormula (fmap noLocA . lookupIfaceTop . mkVarOccFS . ifLclNameFS) if_mindef
+    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)


=====================================
compiler/GHC/Parser.y
=====================================
@@ -55,7 +55,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 
 import GHC.Data.OrdList
-import GHC.Data.BooleanFormula ( BooleanFormula(..), LBooleanFormula, mkTrue )
 import GHC.Data.FastString
 import GHC.Data.Maybe          ( orElse )
 
@@ -96,6 +95,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, sumTyCon,
                            unrestrictedFunTyCon )
 
 import Language.Haskell.Syntax.Basic (FieldLabelString(..))
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula(..), mkTrue )
 
 import qualified Data.Semigroup as Semi
 }
@@ -3701,26 +3701,24 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { BooleanFormula GhcPs }
+name_boolformula_opt :: { BooleanFormula (LocatedN RdrName) }
         : name_boolformula          { $1 }
         | {- empty -}               { mkTrue }
 
-name_boolformula :: { BooleanFormula GhcPs }
-        : name_boolformula_and       { $1 }
-        | name_boolformula_and '|' name_boolformula
-                           { (Or [$1, $3]) }
+name_boolformula :: { BooleanFormula (LocatedN RdrName) }
+        : name_boolformula_and                      { $1 }
+        | name_boolformula_and '|' name_boolformula { Or [ $1 , $3 ] }
 
-name_boolformula_and :: { BooleanFormula GhcPs }
+name_boolformula_and :: { BooleanFormula (LocatedN RdrName) }
         : name_boolformula_and_list { (And ($1)) }
 
-name_boolformula_and_list :: { [BooleanFormula GhcPs] }
-        : name_boolformula_atom  { [$1] }
-        | name_boolformula_atom ',' name_boolformula_and_list
-                                 {  ($1 : $3) }
+name_boolformula_and_list :: { [BooleanFormula (LocatedN RdrName)] }
+        : name_boolformula_atom                               {  [$1]      }
+        | name_boolformula_atom ',' name_boolformula_and_list {  ($1 : $3) }
 
-name_boolformula_atom :: { BooleanFormula GhcPs }
-        : '(' name_boolformula ')'  {  (Parens $2) }
-        | name_var                  {  (Var $1) }
+name_boolformula_atom :: { BooleanFormula (LocatedN RdrName) }
+        : '(' name_boolformula ')'  { (Parens $2) }
+        | name_var                  { (Var    $1) }
 
 namelist :: { Located [LocatedN RdrName] }
 namelist : name_var              { sL1 $1 [$1] }
@@ -4724,4 +4722,4 @@ combineHasLocs a b = combineSrcSpans (getHasLoc a) (getHasLoc b)
 fromTrailingN :: SrcSpanAnnN -> SrcSpanAnnA
 fromTrailingN (EpAnn anc ann cs)
     = EpAnn anc (AnnListItem (nann_trailing ann)) cs
-}
+}
\ No newline at end of file


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,7 +80,6 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
-import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1138,7 +1137,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) bf)
-  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) new_bf, emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ mkVar (noLocA name)
+    defMindef = mkAnd [ mkVar name
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ bf)) = Just bf
-    toMinimalDef _                             = Nothing
+    toMinimalDef (L _ (MinimalSig _ bf)) = Just $ fmap unLoc bf
+    toMinimalDef _                       = Nothing
 
 {-
 Note [Polymorphic methods]


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -465,7 +465,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (BooleanFormula pass)
+  | MinimalSig (XMinimalSig pass) (BooleanFormula (LIdP pass))
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -3,43 +3,38 @@
 {-# LANGUAGE QuantifiedConstraints #-}
 
 module Language.Haskell.Syntax.BooleanFormula(
-  BooleanFormula(..), LBooleanFormula,
+  BooleanFormula(..),
   mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr
   ) where
 
 import Prelude hiding ( init, last )
 import Data.List ( nub )
-import Language.Haskell.Syntax.Extension (XRec, LIdP)
-
 
 -- types
-type LBooleanFormula p = XRec p (BooleanFormula p)
-data BooleanFormula p = Var (LIdP p) | And [BooleanFormula p] | Or [BooleanFormula p]
-                      | Parens (BooleanFormula p)
-
--- instances
-deriving instance Eq (LIdP p) => Eq (BooleanFormula p)
+data BooleanFormula a = Var a | And [BooleanFormula a] | Or [BooleanFormula a]
+                      | Parens (BooleanFormula a)
 
+                      deriving (Eq, Functor, Foldable, Traversable)
 -- smart constructors
 -- see note [Simplification of BooleanFormulas]
-mkVar :: LIdP p -> BooleanFormula p
+mkVar :: a -> BooleanFormula a
 mkVar = Var
 
-mkFalse, mkTrue :: BooleanFormula p
+mkFalse, mkTrue :: BooleanFormula a
 mkFalse = Or []
 mkTrue = And []
 
 -- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula p
+mkBool :: Bool -> BooleanFormula a
 mkBool False = mkFalse
 mkBool True  = mkTrue
 
 -- Make a conjunction, and try to simplify
-mkAnd :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
+mkAnd :: Eq a => [BooleanFormula a] -> BooleanFormula a
 mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
   where
   -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: BooleanFormula p -> Maybe [BooleanFormula p]
+  fromAnd :: BooleanFormula a -> Maybe [BooleanFormula a]
   fromAnd bf = case bf of
     (And xs) -> Just xs
      -- assume that xs are already simplified
@@ -50,7 +45,7 @@ mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
   mkAnd' [x] = x
   mkAnd' xs = And xs
 
-mkOr :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
+mkOr :: Eq a => [BooleanFormula a] -> BooleanFormula a
 mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
   where
   -- See Note [Simplification of BooleanFormulas]


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -177,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . fmap noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -773,21 +773,12 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ s -> do
-    s' <- bfTraverse (traverse lookupRn) s
+    s' <- traverse (traverse lookupRn) s
     return $ MinimalSig noExtField s'
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
-bfTraverse  :: Applicative f
-            => (LIdP (GhcPass p) -> f (LIdP DocNameI))
-            -> BooleanFormula (GhcPass p)
-            -> f (BooleanFormula DocNameI)
-bfTraverse f = go 
-  where 
-    go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] go bfs
-    go (Or     bfs) = Or     <$> traverse @[] go bfs
-    go (Parens bf ) = Parens <$>              go bf
+
 
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 15:19:41 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 11 Oct 2024 11:19:41 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 7 commits: Fix haddock source
 links and hyperlinked source
Message-ID: <6709420d7107d_1f869e44a69c773ac@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
3dc62f2e by Matthew Pickering at 2024-10-11T11:16:35-04:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

(cherry picked from commit 23f2a478b7dc6b61cab86cf7d0db7fec8a6d9a1f)

- - - - -
3a033e29 by Rodrigo Mesquita at 2024-10-11T11:16:35-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

(cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f)

- - - - -
20f80b77 by Cheng Shao at 2024-10-11T11:16:35-04:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
2166d290 by Ben Gamari at 2024-10-11T11:16:35-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
fc1dcd02 by Alexis King at 2024-10-11T11:16:35-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
9d1ecdb9 by Ben Gamari at 2024-10-11T11:16:35-04:00
hadrian: Update bootstrap plans

- - - - -
1413e1dd by Rodrigo Mesquita at 2024-10-11T11:16:35-04:00
rts: Make addDLL a wrapper around loadNativeObj

Rewrite the implementation of `addDLL` as a wrapper around the more
principled `loadNativeObj` rts linker function. The latter should be
preferred while the former is preserved for backwards compatibility.

`loadNativeObj` was previously only available on ELF platforms, so this
commit further refactors the rts linker to transform loadNativeObj_ELF
into loadNativeObj_POSIX, which is available in ELF and MachO platforms.

The refactor made it possible to remove the `dl_mutex` mutex in favour
of always using `linker_mutex` (rather than a combination of both).

Lastly, we implement `loadNativeObj` for Windows too.

(cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb)

- - - - -


30 changed files:

- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- hadrian/README.md
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/src/CommandLine.hs
- hadrian/src/Settings/Builders/Haddock.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- rts/CheckUnload.c
- rts/Linker.c
- rts/LinkerInternals.h
- rts/Profiling.c
- rts/Profiling.h
- rts/RtsSymbols.c
- rts/include/rts/Linker.h
- rts/linker/Elf.c
- rts/linker/Elf.h
- + rts/linker/LoadNativeObjPosix.c
- + rts/linker/LoadNativeObjPosix.h
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- rts/rts.cabal.in
- testsuite/tests/ghci/linking/dyn/T3372.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34601024f6164efbf7dfd8ede7e5d820e55007fa...1413e1dd7a2d9161be986a66609b86e2de792b28

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34601024f6164efbf7dfd8ede7e5d820e55007fa...1413e1dd7a2d9161be986a66609b86e2de792b28
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 15:39:10 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 11 Oct 2024 11:39:10 -0400
Subject: [Git][ghc/ghc][wip/T25281] 14 commits: Handle exceptions from IO
 manager backend
Message-ID: <6709469ee97c5_1f869e8025009270@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d660dcb6 by Sebastian Graf at 2024-10-11T16:38:18+01:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
fe5d8e3c by Simon Peyton Jones at 2024-10-11T16:38:25+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de030c0b6096a2696f863d1b07151c607ee7a4e0...fe5d8e3cfe5d3399c2c12774f444a1c7b82a3b99

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de030c0b6096a2696f863d1b07151c607ee7a4e0...fe5d8e3cfe5d3399c2c12774f444a1c7b82a3b99
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 16:10:21 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Fri, 11 Oct 2024 12:10:21 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/splice-imports-2024
Message-ID: <67094ded4f2de_33ce3e1a5d883135d@gitlab.mail>



Matthew Pickering pushed new branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/splice-imports-2024
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 16:55:23 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 12:55:23 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 434 commits: JS:
 establish single source of truth for symbols
Message-ID: <6709587b52f6b_33ce3e4431445252a@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
dfca9db8 by Rodrigo Mesquita at 2024-10-11T16:48:29+01:00
ttg: Start using Text over FastString in the AST

Towards the goal of making the AST independent of GHC, this commit
starts the task of replacing usages of `FastString` with `Text` in the
AST (Language.Haskell.* modules).

Even though we /do/ want to use FastStrings -- critically in Names or Ids
-- there is no particular reason for the FastStrings that occur in the
AST proper to be FastStrings. Primarily, ...

Progress towards #21592

- - - - -
36251cd3 by Rodrigo Mesquita at 2024-10-11T16:49:59+01:00
A handful of progress

- - - - -
b4e16b58 by Rodrigo Mesquita at 2024-10-11T16:51:20+01:00
more

- - - - -
d7f9b42b by Rodrigo Mesquita at 2024-10-11T16:51:21+01:00
CType Text rather than FastString

Todo: maybe don't use decode/encode utf8 in binary instance?

- - - - -
46d06a05 by Rodrigo Mesquita at 2024-10-11T16:52:02+01:00
Parser getSTRING progress

- - - - -
772ff158 by Rodrigo Mesquita at 2024-10-11T16:52:51+01:00
HsLit Text-backed Strings

- - - - -
8c039d84 by Rodrigo Mesquita at 2024-10-11T16:55:25+01:00
the biggest boy

- - - - -
6263f9a6 by Rodrigo Mesquita at 2024-10-11T17:55:00+01:00
FIX

- - - - -


18 changed files:

- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9408cc56ae54d0bd86a27308fe97dbf635fe727...6263f9a6e0ff1ada977d71422a2e0a8aef1a46d4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9408cc56ae54d0bd86a27308fe97dbf635fe727...6263f9a6e0ff1ada977d71422a2e0a8aef1a46d4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 16:56:34 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 12:56:34 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] FIX
Message-ID: <670958c24d1b4_33ce3e43a58052762@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
295606ed by Rodrigo Mesquita at 2024-10-11T17:56:23+01:00
FIX

- - - - -


4 changed files:

- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/Language/Haskell/Syntax/Lit.hs
- utils/haddock/haddock-api/haddock-api.cabal


Changes:

=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -140,14 +140,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls
         -- explicit prelude imports
         && case ideclPkgQual decl of
             NoRawPkgQual -> True
-<<<<<<< HEAD
             RawPkgQual {} -> False
-||||||| parent of d9408cc56ae (the biggest boy)
-            RawPkgQual b -> sl_fs b == unitIdFS baseUnitId
-=======
-            RawPkgQual b -> sl_fs b == fastStringToText (unitIdFS baseUnitId)
->>>>>>> d9408cc56ae (the biggest boy)
-
 
       loc' = noAnnSrcSpan loc
       preludeImportDecl :: LImportDecl GhcPs


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -923,14 +923,8 @@ data Token
                                          -- Note [Literal source text] in "GHC.Types.SourceText"
 
   | ITchar     SourceText Char       -- Note [Literal source text] in "GHC.Types.SourceText"
-<<<<<<< HEAD
-  | ITstring   SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-  | ITstringMulti SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-||||||| parent of b7e90ce15e3 (more)
-  | ITstring   SourceText Text       -- Note [Literal source text] in "GHC.Types.SourceText"
-=======
-  | ITstring   SourceText String     -- Note [Literal source text] in "GHC.Types.SourceText"
->>>>>>> b7e90ce15e3 (more)
+  | ITstring   SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
+  | ITstringMulti SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITinteger  IntegralLit           -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITrational FractionalLit
 


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -52,7 +52,7 @@ data HsLit x
       -- ^ Unboxed character
   | HsString (XHsString x) {- SourceText -} Text
       -- ^ String
-  | HsMultilineString (XHsMultilineString x) {- SourceText -} FastString
+  | HsMultilineString (XHsMultilineString x) {- SourceText -} Text
       -- ^ String
   | HsStringPrim (XHsStringPrim x) {- SourceText -} !ByteString
       -- ^ Packed bytes


=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -83,6 +83,7 @@ library
                , haddock-library ^>= 1.11
                , xhtml           ^>= 3000.2.2
                , parsec          ^>= 3.1.13.0
+               , text             >= 2.0 && < 2.2
 
   -- Versions for the dependencies below are transitively pinned by
   -- the non-reinstallable `ghc` package and hence need no version



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/295606ed9d000133c3f1ba59096a562a2b71ba0b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:10:22 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Fri, 11 Oct 2024 13:10:22 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/mkTickUnsafeCoerce
Message-ID: <67095bfe2051b_33ce3e6f367858415@gitlab.mail>



Andreas Klebinger pushed new branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/mkTickUnsafeCoerce
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:12:11 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 13:12:11 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] FIX
Message-ID: <67095c6be5c4f_33ce3e6b8078586fb@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
003f611e by Rodrigo Mesquita at 2024-10-11T18:12:00+01:00
FIX

- - - - -


5 changed files:

- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/Language/Haskell/Syntax/Lit.hs
- utils/haddock/haddock-api/haddock-api.cabal


Changes:

=====================================
compiler/GHC/Builtin/Utils.hs
=====================================
@@ -82,6 +82,7 @@ import GHC.Hs.Doc
 import GHC.Unit.Module.ModIface (IfaceExport)
 import GHC.Unit.Module.Warnings
 
+import GHC.Data.FastString (fastStringToText)
 import GHC.Data.List.SetOps
 
 import Control.Applicative ((<|>))
@@ -271,7 +272,7 @@ ghcPrimWarns = WarnSome
   []
   where
     mk_txt msg =
-      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText msg Nothing) []]
+      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText (fastStringToText msg) Nothing) []]
     mk_decl_dep (occ, msg) = (occ, mk_txt msg)
 
 ghcPrimFixities :: [(OccName,Fixity)]


=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -140,14 +140,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls
         -- explicit prelude imports
         && case ideclPkgQual decl of
             NoRawPkgQual -> True
-<<<<<<< HEAD
             RawPkgQual {} -> False
-||||||| parent of d9408cc56ae (the biggest boy)
-            RawPkgQual b -> sl_fs b == unitIdFS baseUnitId
-=======
-            RawPkgQual b -> sl_fs b == fastStringToText (unitIdFS baseUnitId)
->>>>>>> d9408cc56ae (the biggest boy)
-
 
       loc' = noAnnSrcSpan loc
       preludeImportDecl :: LImportDecl GhcPs


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -923,14 +923,8 @@ data Token
                                          -- Note [Literal source text] in "GHC.Types.SourceText"
 
   | ITchar     SourceText Char       -- Note [Literal source text] in "GHC.Types.SourceText"
-<<<<<<< HEAD
-  | ITstring   SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-  | ITstringMulti SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-||||||| parent of b7e90ce15e3 (more)
-  | ITstring   SourceText Text       -- Note [Literal source text] in "GHC.Types.SourceText"
-=======
-  | ITstring   SourceText String     -- Note [Literal source text] in "GHC.Types.SourceText"
->>>>>>> b7e90ce15e3 (more)
+  | ITstring   SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
+  | ITstringMulti SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITinteger  IntegralLit           -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITrational FractionalLit
 


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -52,7 +52,7 @@ data HsLit x
       -- ^ Unboxed character
   | HsString (XHsString x) {- SourceText -} Text
       -- ^ String
-  | HsMultilineString (XHsMultilineString x) {- SourceText -} FastString
+  | HsMultilineString (XHsMultilineString x) {- SourceText -} Text
       -- ^ String
   | HsStringPrim (XHsStringPrim x) {- SourceText -} !ByteString
       -- ^ Packed bytes


=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -83,6 +83,7 @@ library
                , haddock-library ^>= 1.11
                , xhtml           ^>= 3000.2.2
                , parsec          ^>= 3.1.13.0
+               , text             >= 2.0 && < 2.2
 
   -- Versions for the dependencies below are transitively pinned by
   -- the non-reinstallable `ghc` package and hence need no version



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/003f611e3ae2eaba6588489172f1cd5a3eb5a092

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:13:42 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 13:13:42 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] FIX
Message-ID: <67095cc64343_33ce3e6b80786035@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
7cab27c8 by Rodrigo Mesquita at 2024-10-11T18:13:31+01:00
FIX

- - - - -


5 changed files:

- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/Language/Haskell/Syntax/Lit.hs
- utils/haddock/haddock-api/haddock-api.cabal


Changes:

=====================================
compiler/GHC/Builtin/Utils.hs
=====================================
@@ -82,6 +82,7 @@ import GHC.Hs.Doc
 import GHC.Unit.Module.ModIface (IfaceExport)
 import GHC.Unit.Module.Warnings
 
+import GHC.Data.FastString (fastStringToText)
 import GHC.Data.List.SetOps
 
 import Control.Applicative ((<|>))
@@ -271,7 +272,7 @@ ghcPrimWarns = WarnSome
   []
   where
     mk_txt msg =
-      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText msg Nothing) []]
+      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText (fastStringToText msg) Nothing) []]
     mk_decl_dep (occ, msg) = (occ, mk_txt msg)
 
 ghcPrimFixities :: [(OccName,Fixity)]


=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -140,14 +140,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls
         -- explicit prelude imports
         && case ideclPkgQual decl of
             NoRawPkgQual -> True
-<<<<<<< HEAD
             RawPkgQual {} -> False
-||||||| parent of d9408cc56ae (the biggest boy)
-            RawPkgQual b -> sl_fs b == unitIdFS baseUnitId
-=======
-            RawPkgQual b -> sl_fs b == fastStringToText (unitIdFS baseUnitId)
->>>>>>> d9408cc56ae (the biggest boy)
-
 
       loc' = noAnnSrcSpan loc
       preludeImportDecl :: LImportDecl GhcPs


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -923,14 +923,8 @@ data Token
                                          -- Note [Literal source text] in "GHC.Types.SourceText"
 
   | ITchar     SourceText Char       -- Note [Literal source text] in "GHC.Types.SourceText"
-<<<<<<< HEAD
-  | ITstring   SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-  | ITstringMulti SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-||||||| parent of b7e90ce15e3 (more)
-  | ITstring   SourceText Text       -- Note [Literal source text] in "GHC.Types.SourceText"
-=======
-  | ITstring   SourceText String     -- Note [Literal source text] in "GHC.Types.SourceText"
->>>>>>> b7e90ce15e3 (more)
+  | ITstring   SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
+  | ITstringMulti SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITinteger  IntegralLit           -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITrational FractionalLit
 
@@ -2183,7 +2177,7 @@ tok_string span buf len _buf2 = do
         addError err
       pure $ L span (ITprimstring src (unsafeMkByteString s))
     else
-      pure $ L span (ITstring src (T.pack s))
+      pure $ L span (ITstring src s)
   where
     src = SourceText $ lexemeToFastString buf len
     endsInHash = currentChar (offsetBytes (len - 1) buf) == '#'
@@ -2215,7 +2209,7 @@ tok_string_multi startSpan startBuf _len _buf2 = do
       lexMultilineString contentLen contentStartBuf
 
   setInput i'
-  pure $ L span $ ITstringMulti src (T.pack s)
+  pure $ L span $ ITstringMulti src s
   where
     goContent i0 =
       case alexScan i0 string_multi_content of


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -52,7 +52,7 @@ data HsLit x
       -- ^ Unboxed character
   | HsString (XHsString x) {- SourceText -} Text
       -- ^ String
-  | HsMultilineString (XHsMultilineString x) {- SourceText -} FastString
+  | HsMultilineString (XHsMultilineString x) {- SourceText -} Text
       -- ^ String
   | HsStringPrim (XHsStringPrim x) {- SourceText -} !ByteString
       -- ^ Packed bytes


=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -83,6 +83,7 @@ library
                , haddock-library ^>= 1.11
                , xhtml           ^>= 3000.2.2
                , parsec          ^>= 3.1.13.0
+               , text             >= 2.0 && < 2.2
 
   -- Versions for the dependencies below are transitively pinned by
   -- the non-reinstallable `ghc` package and hence need no version



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7cab27c82ab81971a2c8f60675313cce7f1ef4b9

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:18:36 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 13:18:36 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] FIX
Message-ID: <67095decba11b_33ce3e6d6ab46064e@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
a6038875 by Rodrigo Mesquita at 2024-10-11T18:14:11+01:00
FIX

- - - - -


6 changed files:

- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/Language/Haskell/Syntax/Lit.hs
- utils/haddock/haddock-api/haddock-api.cabal


Changes:

=====================================
compiler/GHC/Builtin/Utils.hs
=====================================
@@ -82,6 +82,7 @@ import GHC.Hs.Doc
 import GHC.Unit.Module.ModIface (IfaceExport)
 import GHC.Unit.Module.Warnings
 
+import GHC.Data.FastString (fastStringToText)
 import GHC.Data.List.SetOps
 
 import Control.Applicative ((<|>))
@@ -271,7 +272,7 @@ ghcPrimWarns = WarnSome
   []
   where
     mk_txt msg =
-      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText msg Nothing) []]
+      DeprecatedTxt NoSourceText [noLocA $ WithHsDocIdentifiers (StringLiteral NoSourceText (fastStringToText msg) Nothing) []]
     mk_decl_dep (occ, msg) = (occ, mk_txt msg)
 
 ghcPrimFixities :: [(OccName,Fixity)]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1168,7 +1168,7 @@ maybe_pkg :: { (Maybe EpaLocation, RawPkgQual) }
                         ; unless (looksLikePackageName pkgS) $
                              addError $ mkPlainErrorMsgEnvelope (getLoc $1) $
                                (PsErrInvalidPackageName pkgS)
-                        ; return (Just (glR $1), RawPkgQual (StringLiteral (getSTRINGs $1) (T.pack pkgF) Nothing)) } }
+                        ; return (Just (glR $1), RawPkgQual (StringLiteral (getSTRINGs $1) (T.pack pkgS) Nothing)) } }
         | {- empty -}                           { (Nothing,NoRawPkgQual) }
 
 optqualified :: { Located (Maybe EpaLocation) }


=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -140,14 +140,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls
         -- explicit prelude imports
         && case ideclPkgQual decl of
             NoRawPkgQual -> True
-<<<<<<< HEAD
             RawPkgQual {} -> False
-||||||| parent of d9408cc56ae (the biggest boy)
-            RawPkgQual b -> sl_fs b == unitIdFS baseUnitId
-=======
-            RawPkgQual b -> sl_fs b == fastStringToText (unitIdFS baseUnitId)
->>>>>>> d9408cc56ae (the biggest boy)
-
 
       loc' = noAnnSrcSpan loc
       preludeImportDecl :: LImportDecl GhcPs


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -923,14 +923,8 @@ data Token
                                          -- Note [Literal source text] in "GHC.Types.SourceText"
 
   | ITchar     SourceText Char       -- Note [Literal source text] in "GHC.Types.SourceText"
-<<<<<<< HEAD
-  | ITstring   SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-  | ITstringMulti SourceText Text -- Note [Literal source text] in "GHC.Types.SourceText"
-||||||| parent of b7e90ce15e3 (more)
-  | ITstring   SourceText Text       -- Note [Literal source text] in "GHC.Types.SourceText"
-=======
-  | ITstring   SourceText String     -- Note [Literal source text] in "GHC.Types.SourceText"
->>>>>>> b7e90ce15e3 (more)
+  | ITstring   SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
+  | ITstringMulti SourceText String -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITinteger  IntegralLit           -- Note [Literal source text] in "GHC.Types.SourceText"
   | ITrational FractionalLit
 
@@ -2183,7 +2177,7 @@ tok_string span buf len _buf2 = do
         addError err
       pure $ L span (ITprimstring src (unsafeMkByteString s))
     else
-      pure $ L span (ITstring src (T.pack s))
+      pure $ L span (ITstring src s)
   where
     src = SourceText $ lexemeToFastString buf len
     endsInHash = currentChar (offsetBytes (len - 1) buf) == '#'
@@ -2215,7 +2209,7 @@ tok_string_multi startSpan startBuf _len _buf2 = do
       lexMultilineString contentLen contentStartBuf
 
   setInput i'
-  pure $ L span $ ITstringMulti src (T.pack s)
+  pure $ L span $ ITstringMulti src s
   where
     goContent i0 =
       case alexScan i0 string_multi_content of


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -52,7 +52,7 @@ data HsLit x
       -- ^ Unboxed character
   | HsString (XHsString x) {- SourceText -} Text
       -- ^ String
-  | HsMultilineString (XHsMultilineString x) {- SourceText -} FastString
+  | HsMultilineString (XHsMultilineString x) {- SourceText -} Text
       -- ^ String
   | HsStringPrim (XHsStringPrim x) {- SourceText -} !ByteString
       -- ^ Packed bytes


=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -83,6 +83,7 @@ library
                , haddock-library ^>= 1.11
                , xhtml           ^>= 3000.2.2
                , parsec          ^>= 3.1.13.0
+               , text             >= 2.0 && < 2.2
 
   -- Versions for the dependencies below are transitively pinned by
   -- the non-reinstallable `ghc` package and hence need no version



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:20:58 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Fri, 11 Oct 2024 13:20:58 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] basics
Message-ID: <67095e7a2a28f_33ce3e6f34d46097e@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
9f6fc650 by Matthew Pickering at 2024-10-11T18:20:41+01:00
basics

- - - - -


17 changed files:

- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Utils/Monad.hs
- testsuite/tests/splice-imports/SI01.hs
- testsuite/tests/splice-imports/SI02.hs
- testsuite/tests/splice-imports/SI03.hs
- testsuite/tests/splice-imports/SI04.hs
- testsuite/tests/splice-imports/SI05.hs
- testsuite/tests/splice-imports/SI06.hs
- testsuite/tests/splice-imports/SI07.hs
- testsuite/tests/splice-imports/SI08.hs
- testsuite/tests/splice-imports/SI09.hs
- testsuite/tests/splice-imports/SI10.hs
- testsuite/tests/splice-imports/SI11.hs
- testsuite/tests/splice-imports/SI13.hs
- testsuite/tests/th/overloaded/TH_overloaded_csp.hs


Changes:

=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -311,8 +311,8 @@ finishHsVar :: LocatedA Name -> RnM (HsExpr GhcRn, FreeVars)
 -- when renaming infix expressions
 finishHsVar (L l name)
  = do { this_mod <- getModule
-      ; when (nameIsLocalOrFrom this_mod name) $
-        checkThLocalName name
+--      ; when (nameIsLocalOrFrom this_mod name) $
+      ; checkThLocalName name
       ; return (HsVar noExtField (L (l2l l) name), unitFV name) }
 
 rnUnboundVar :: RdrName -> RnM (HsExpr GhcRn, FreeVars)


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -970,6 +970,9 @@ checkThLocalName name
   | isUnboundName name   -- Do not report two errors for
   = return ()            --   $(not_in_scope args)
 
+  | isWiredInName name
+  = return ()
+
   | otherwise
   = do  { traceRn "checkThLocalName" (ppr name)
         ; mb_local_use <- getStageAndBindLevel name
@@ -981,10 +984,11 @@ checkThLocalName name
         ; traceRn "checkThLocalName" (ppr name <+> ppr bind_lvl
                                                <+> ppr use_stage
                                                <+> ppr use_lvl)
-        ; checkCrossStageLifting (StageCheckSplice name) top_lvl bind_lvl use_stage use_lvl name } } }
+        ; dflags <- getDynFlags
+        ; checkCrossStageLifting dflags (StageCheckSplice name) top_lvl bind_lvl use_stage use_lvl name } } }
 
 --------------------------------------
-checkCrossStageLifting :: StageCheckReason -> TopLevelFlag -> Set.Set ThLevel -> ThStage -> ThLevel
+checkCrossStageLifting :: DynFlags -> StageCheckReason -> TopLevelFlag -> Set.Set ThLevel -> ThStage -> ThLevel
                        -> Name -> TcM ()
 -- We are inside brackets, and (use_lvl > bind_lvl)
 -- Now we must check whether there's a cross-stage lift to do
@@ -994,13 +998,16 @@ checkCrossStageLifting :: StageCheckReason -> TopLevelFlag -> Set.Set ThLevel ->
 -- This code is similar to checkCrossStageLifting in GHC.Tc.Gen.Expr, but
 -- this is only run on *untyped* brackets.
 
-checkCrossStageLifting reason top_lvl bind_lvl use_stage use_lvl name
+checkCrossStageLifting dflags reason top_lvl bind_lvl use_stage use_lvl name
   | use_lvl `Set.member` bind_lvl = return ()
   | Brack _ (RnPendingUntyped ps_var) <- use_stage   -- Only for untyped brackets
   = do
       dflags <- getDynFlags
       let err = TcRnBadlyStaged reason bind_lvl use_lvl
       check_cross_stage_lifting err dflags top_lvl name ps_var
+  | Brack _ RnPendingTyped <- use_stage  -- Lift for typed brackets is inserted later.
+  , xopt LangExt.LiftCrossStagedPersistence dflags
+    = return ()
   | otherwise = addErrTc (TcRnBadlyStaged reason bind_lvl use_lvl)
 
 check_cross_stage_lifting :: TcRnMessage -> DynFlags -> TopLevelFlag -> Name -> TcRef [PendingRnSplice] -> TcM ()


=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -1060,6 +1060,7 @@ checkThLocalId :: Id -> TcM ()
 -- Here we just add constraints for cross-stage lifting
 checkThLocalId id
   = do  { mb_local_use <- getStageAndBindLevel (idName id)
+        ; pprTraceM "local" (ppr id $$ ppr mb_local_use)
         ; case mb_local_use of
              Just (top_lvl, bind_lvl, use_stage)
                 | thLevel use_stage `notElem` bind_lvl


=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -218,7 +218,7 @@ import GHC.Types.Name.Ppr
 import GHC.Types.Unique.FM ( emptyUFM )
 import GHC.Types.Unique.Supply
 import GHC.Types.Annotations
-import GHC.Types.Basic( TopLevelFlag, TypeOrKind(..) )
+import GHC.Types.Basic( TopLevelFlag(..), TypeOrKind(..) )
 import GHC.Types.CostCentre.State
 import GHC.Types.SourceFile
 
@@ -2079,7 +2079,10 @@ getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, Set.Set ThLevel, ThSt
 getStageAndBindLevel name
   = do { env <- getLclEnv;
        ; case lookupNameEnv (getLclEnvThBndrs env) name of
-           Nothing                  -> return Nothing
+           Nothing                  -> do
+              lvls <- getExternalBindLvl name
+              pprTraceM "lvls" (ppr name $$ ppr lvls $$ ppr (getLclEnvThStage env))
+              return (Just (TopLevel, lvls, getLclEnvThStage env))
            Just (top_lvl, bind_lvl) -> return (Just (top_lvl, Set.singleton bind_lvl, getLclEnvThStage env)) }
 
 getExternalBindLvl :: Name -> TcRn (Set.Set ThLevel)


=====================================
testsuite/tests/splice-imports/SI01.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI01 where
 


=====================================
testsuite/tests/splice-imports/SI02.hs
=====================================
@@ -1,5 +1,5 @@
 {-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI02 where
 


=====================================
testsuite/tests/splice-imports/SI03.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI03 where
 


=====================================
testsuite/tests/splice-imports/SI04.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI04 where
 


=====================================
testsuite/tests/splice-imports/SI05.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI04 where
 


=====================================
testsuite/tests/splice-imports/SI06.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 module SI06 where
 
 import splice SI01A


=====================================
testsuite/tests/splice-imports/SI07.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI07 where
 


=====================================
testsuite/tests/splice-imports/SI08.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI08 where
 


=====================================
testsuite/tests/splice-imports/SI09.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI09 where
 


=====================================
testsuite/tests/splice-imports/SI10.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE SpliceImports #-}
+{-# LANGUAGE ExplicitStageImports #-}
 {-# LANGUAGE TemplateHaskell #-}
 module SI09 where
 


=====================================
testsuite/tests/splice-imports/SI11.hs
=====================================
@@ -2,9 +2,12 @@
 {-# LANGUAGE TemplateHaskell #-}
 module SI11 where
 
+import Language.Haskell.TH
+
 -- Is path-based CSP banned?
 data X = X
 
+x :: X -> Q Exp
 x X = [| X |]
 
 


=====================================
testsuite/tests/splice-imports/SI13.hs
=====================================
@@ -2,8 +2,10 @@
 {-# LANGUAGE TemplateHaskell #-}
 module SI13 where
 
+import Language.Haskell.TH
 import quote Prelude
 
+x :: Q Exp
 x = [| id |]
 
 


=====================================
testsuite/tests/th/overloaded/TH_overloaded_csp.hs
=====================================
@@ -1,5 +1,6 @@
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 {-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE LiftCSP #-}
 module Main where
 -- A test to check that CSP works with overloaded quotes
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f6fc65014821360cceff29a387534367ad848a3

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:27:59 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 11 Oct 2024 13:27:59 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] ttg: Using Text over
 FastString in the AST
Message-ID: <6709601f5ad49_33ce3e8f15ec633c7@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
890dca4b by Rodrigo Mesquita at 2024-10-11T18:27:39+01:00
ttg: Using Text over FastString in the AST

Towards the goal of making the AST independent of GHC, this commit
starts the task of replacing usages of `FastString` with `Text` in the
AST (Language.Haskell.* modules).

Even though we /do/ want to use FastStrings -- critically in Names or Ids
-- there is no particular reason for the FastStrings that occur in the
AST proper to be FastStrings. Primarily, ...

Progress towards #21592

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/ThToHs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/890dca4b65d2f068695567ee48c922a88527dd4b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:31:37 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Fri, 11 Oct 2024 13:31:37 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] add another ad-hoc path
 persistence check
Message-ID: <670960f94f7ed_33ce3e6f36f0636bf@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
8e6c5f30 by Matthew Pickering at 2024-10-11T18:31:27+01:00
add another ad-hoc path persistence check

- - - - -


1 changed file:

- compiler/GHC/Rename/Splice.hs


Changes:

=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -1008,6 +1008,8 @@ checkCrossStageLifting dflags reason top_lvl bind_lvl use_stage use_lvl name
   | Brack _ RnPendingTyped <- use_stage  -- Lift for typed brackets is inserted later.
   , xopt LangExt.LiftCrossStagedPersistence dflags
     = return ()
+  | isTopLevel top_lvl
+  , xopt LangExt.PathCrossStagedPersistence dflags = return ()
   | otherwise = addErrTc (TcRnBadlyStaged reason bind_lvl use_lvl)
 
 check_cross_stage_lifting :: TcRnMessage -> DynFlags -> TopLevelFlag -> Name -> TcRef [PendingRnSplice] -> TcM ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8e6c5f30d27d4a8478b5b0ba1a7cf0d6959c1625

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:32:15 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Fri, 11 Oct 2024 13:32:15 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] remnant (BooleanFormula p)
Message-ID: <6709611f9df72_33ce3eb7a9a863813@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
fc204646 by Hassan Al-Awwadi at 2024-10-11T19:31:08+02:00
remnant (BooleanFormula p)

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3011,7 +3011,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula GhcPs) where
+instance ExactPrint (BF.BooleanFormula RdrName) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4697,7 +4697,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
+instance ExactPrint (LocatedL (BF.BooleanFormula RdrName)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 17:36:36 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Fri, 11 Oct 2024 13:36:36 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] actualy probably like this
Message-ID: <670962243a54e_33ce3ec9a36066598@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
e645bc16 by Hassan Al-Awwadi at 2024-10-11T19:36:14+02:00
actualy probably like this

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3011,7 +3011,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula RdrName) where
+instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4697,7 +4697,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula RdrName)) where
+instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 19:23:54 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Fri, 11 Oct 2024 15:23:54 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: aligned lits
Message-ID: <67097b4a74ee3_13583e2c9a34199a2@gitlab.mail>



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


Commits:
1d61ba90 by Serge S. Gulin at 2024-10-11T22:23:43+03:00
JS: aligned lits

- - - - -


2 changed files:

- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Types.hs


Changes:

=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d61ba90ab4f5a6725de185791ddb03e00d706dd

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 22:03:14 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 18:03:14 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: testsuite:
 Normalise trailing digits from hole fits output
Message-ID: <6709a0a2de7fa_1e3ffd5175c0108113@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d8546c7a by Ben Gamari at 2024-10-11T18:02:49-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
6c0152ec by Ben Gamari at 2024-10-11T18:02:49-04:00
base: Add test for #25066

- - - - -
6f1750ff by Ben Gamari at 2024-10-11T18:02:49-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
def9d16f by Ben Gamari at 2024-10-11T18:02:49-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
6b88bf39 by Ben Gamari at 2024-10-11T18:02:50-04:00
Bump process submodule to v1.6.25.0

- - - - -
d6f58db0 by Hassan Al-Awwadi at 2024-10-11T18:02:51-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
a150d4e0 by Artem Pelenitsyn at 2024-10-11T18:02:53-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
0914a12e by Ben Gamari at 2024-10-11T18:02:54-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
b8d2fb56 by Sylvain Henry at 2024-10-11T18:03:06-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
12c7d431 by Sven Tennie at 2024-10-11T18:03:07-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -


30 changed files:

- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/exts/linear_types.rst
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- + libraries/base/tests/T25066.hs
- + libraries/base/tests/T25066.stderr
- libraries/base/tests/all.T
- libraries/ghc-boot/GHC/Utils/Encoding.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/process
- rts/include/stg/MachRegs/loongarch64.h
- rts/include/stg/MachRegs/ppc.h
- rts/include/stg/MachRegs/riscv64.h
- + testsuite/tests/codeGen/should_run/T25364.hs
- + testsuite/tests/codeGen/should_run/T25364.stdout
- testsuite/tests/codeGen/should_run/all.T


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d148f6e01938a9d243f9dbb6bae6a3951077a348...12c7d4312ce3d8516b0e5b15e1bccf6be4d14207

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d148f6e01938a9d243f9dbb6bae6a3951077a348...12c7d4312ce3d8516b0e5b15e1bccf6be4d14207
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 22:33:12 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 11 Oct 2024 18:33:12 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] Use symbol cache in internal
 interpreter too
Message-ID: <6709a7a8deb82_3c928ebd0602787@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
54a48fa8 by Rodrigo Mesquita at 2024-10-11T18:33:02-04:00
Use symbol cache in internal interpreter too

This commit makes the symbol cache that was used by the external
interpreter available for the internal interpreter too.

This follows from the analysis in #23415 that suggests the internal
interpreter could benefit from this cache too, and that there is no good
reason not to have the cache for it too. It also makes it a bit more
uniform to have the symbol cache range over both the internal and
external interpreter.

This commit also refactors the cache into a function which is used by
both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the
caching logic to `lookupSymbolInDLL` too.

- - - - -


5 changed files:

- compiler/GHC.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Types.hs


Changes:

=====================================
compiler/GHC.hs
=====================================
@@ -397,6 +397,7 @@ import GHC.Types.Name.Ppr
 import GHC.Types.TypeEnv
 import GHC.Types.BreakInfo
 import GHC.Types.PkgQual
+import GHC.Types.Unique.FM
 
 import GHC.Unit
 import GHC.Unit.Env
@@ -676,6 +677,7 @@ setTopSessionDynFlags :: GhcMonad m => DynFlags -> m ()
 setTopSessionDynFlags dflags = do
   hsc_env <- getSession
   logger  <- getLogger
+  lookup_cache  <- liftIO $ newMVar emptyUFM
 
   -- Interpreter
   interp <- if
@@ -705,7 +707,7 @@ setTopSessionDynFlags dflags = do
             }
          s <- liftIO $ newMVar InterpPending
          loader <- liftIO Loader.uninitializedLoader
-         return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader))
+         return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader lookup_cache))
 
     -- JavaScript interpreter
     | ArchJavaScript <- platformArch (targetPlatform dflags)
@@ -723,7 +725,7 @@ setTopSessionDynFlags dflags = do
               , jsInterpFinderOpts  = initFinderOpts dflags
               , jsInterpFinderCache = hsc_FC hsc_env
               }
-         return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader))
+         return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader lookup_cache))
 
     -- Internal interpreter
     | otherwise
@@ -731,7 +733,7 @@ setTopSessionDynFlags dflags = do
 #if defined(HAVE_INTERNAL_INTERPRETER)
      do
       loader <- liftIO Loader.uninitializedLoader
-      return (Just (Interp InternalInterp loader))
+      return (Just (Interp InternalInterp loader lookup_cache))
 #else
       return Nothing
 #endif


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2647,7 +2647,7 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do
 
   case interp of
     -- always generate JS code for the JS interpreter (no bytecode!)
-    Interp (ExternalInterp (ExtJS i)) _ ->
+    Interp (ExternalInterp (ExtJS i)) _ _ ->
       jsCodeGen hsc_env srcspan i this_mod stg_binds_with_deps binding_id
 
     _ -> do


=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -159,22 +159,22 @@ The main pieces are:
   - implementation of Template Haskell (GHCi.TH)
   - a few other things needed to run interpreted code
 
-- top-level iserv directory, containing the codefor the external
-  server.  This is a fairly simple wrapper, most of the functionality
+- top-level iserv directory, containing the code for the external
+  server. This is a fairly simple wrapper, most of the functionality
   is provided by modules in libraries/ghci.
 
 - This module which provides the interface to the server used
   by the rest of GHC.
 
-GHC works with and without -fexternal-interpreter.  With the flag, all
-interpreted code is run by the iserv binary.  Without the flag,
+GHC works with and without -fexternal-interpreter. With the flag, all
+interpreted code is run by the iserv binary. Without the flag,
 interpreted code is run in the same process as GHC.
 
 Things that do not work with -fexternal-interpreter
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
 dynCompileExpr cannot work, because we have no way to run code of an
-unknown type in the remote process.  This API fails with an error
+unknown type in the remote process. This API fails with an error
 message if it is used with -fexternal-interpreter.
 
 Other Notes on Remote GHCi
@@ -463,7 +463,7 @@ lookupSymbol interp str = case interpInstance interp of
       -- making cross-process LookupSymbol calls, so I added a GHC-side
       -- cache which sped things up quite a lot.  We have to be careful
       -- to purge this cache when unloading code though.
-      cache <- readMVar (instLookupSymbolCache inst)
+      cache <- readMVar (interpLookupSymbolCache interp)
       case lookupUFM cache str of
         Just p -> return (Just p)
         Nothing -> do
@@ -474,30 +474,65 @@ lookupSymbol interp str = case interpInstance interp of
             Just r -> do
               let p        = fromRemotePtr r
                   cache'   = addToUFM cache str p
-              modifyMVar_ (instLookupSymbolCache inst) (const (pure cache'))
+              modifyMVar_ (interpLookupSymbolCache interp) (const (pure cache'))
               return (Just p)
 
     ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str)
 
 lookupSymbolInDLL :: Interp -> RemotePtr LoadedDLL -> FastString -> IO (Maybe (Ptr ()))
-lookupSymbolInDLL interp _dll _str = case interpInstance interp of
+lookupSymbolInDLL interp dll str = withSymbolCache interp str $
+  case interpInstance interp of
 #if defined(HAVE_INTERNAL_INTERPRETER)
-  InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL _dll (unpackFS _str))
+    InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL dll (unpackFS str))
 #endif
-  ExternalInterp _ -> panic "lookupSymbolInDLL: not implemented for external interpreter" -- FIXME
+    ExternalInterp ext -> case ext of
+      ExtIServ i -> withIServ i $ \inst -> fmap fromRemotePtr <$> do
+        uninterruptibleMask_ $
+          sendMessage inst (LookupSymbolInDLL dll (unpackFS str))
+      ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str)
 
 lookupClosure :: Interp -> String -> IO (Maybe HValueRef)
 lookupClosure interp str =
   interpCmd interp (LookupClosure str)
 
+-- | 'withSymbolCache' tries to find a symbol in the 'interpLookupSymbolCache'
+-- which maps symbols to the address where they are loaded.
+-- When there's a cache hit we simply return the cached address, when there is
+-- a miss we run the action which determines the symbol's address and populate
+-- the cache with the answer.
+withSymbolCache :: Interp
+                -> FastString
+                -- ^ The symbol we are looking up in the cache
+                -> IO (Maybe (Ptr ()))
+                -- ^ An action which determines the address of the symbol we
+                -- are looking up in the cache, which is run if there is a
+                -- cache miss. The result will be cached.
+                -> IO (Maybe (Ptr ()))
+withSymbolCache interp str determine_addr = do
+
+  -- Profiling of GHCi showed a lot of time and allocation spent
+  -- making cross-process LookupSymbol calls, so I added a GHC-side
+  -- cache which sped things up quite a lot. We have to be careful
+  -- to purge this cache when unloading code though.
+  --
+  -- The analysis in #23415 further showed this cache should also benefit the
+  -- internal interpreter's loading times, and needn't be used by the external
+  -- interpreter only.
+  cache <- readMVar (interpLookupSymbolCache interp)
+  case lookupUFM cache str of
+    Just p -> return (Just p)
+    Nothing -> do
+
+      maddr <- determine_addr
+      case maddr of
+        Nothing -> return Nothing
+        Just p -> do
+          let upd_cache cache' = addToUFM cache' str p
+          modifyMVar_ (interpLookupSymbolCache interp) (pure . upd_cache)
+          return (Just p)
+
 purgeLookupSymbolCache :: Interp -> IO ()
-purgeLookupSymbolCache interp = case interpInstance interp of
-#if defined(HAVE_INTERNAL_INTERPRETER)
-  InternalInterp -> pure ()
-#endif
-  ExternalInterp ext -> withExtInterpMaybe ext $ \case
-    Nothing   -> pure () -- interpreter stopped, nothing to do
-    Just inst -> modifyMVar_ (instLookupSymbolCache inst) (const (pure emptyUFM))
+purgeLookupSymbolCache interp = modifyMVar_ (interpLookupSymbolCache interp) (const (pure emptyUFM))
 
 -- | loadDLL loads a dynamic library using the OS's native linker
 -- (i.e. dlopen() on Unix, LoadLibrary() on Windows).  It takes either
@@ -563,11 +598,9 @@ spawnIServ conf = do
                   }
 
   pending_frees <- newMVar []
-  lookup_cache  <- newMVar emptyUFM
   let inst = ExtInterpInstance
         { instProcess           = process
         , instPendingFrees      = pending_frees
-        , instLookupSymbolCache = lookup_cache
         , instExtra             = ()
         }
   pure inst


=====================================
compiler/GHC/Runtime/Interpreter/JS.hs
=====================================
@@ -41,7 +41,6 @@ import GHC.Utils.Panic
 import GHC.Utils.Error (logInfo)
 import GHC.Utils.Outputable (text)
 import GHC.Data.FastString
-import GHC.Types.Unique.FM
 
 import Control.Concurrent
 import Control.Monad
@@ -178,11 +177,9 @@ spawnJSInterp cfg = do
         }
 
   pending_frees <- newMVar []
-  lookup_cache  <- newMVar emptyUFM
   let inst = ExtInterpInstance
         { instProcess           = proc
         , instPendingFrees      = pending_frees
-        , instLookupSymbolCache = lookup_cache
         , instExtra             = extra
         }
 


=====================================
compiler/GHC/Runtime/Interpreter/Types.hs
=====================================
@@ -51,6 +51,9 @@ data Interp = Interp
 
   , interpLoader   :: !Loader
       -- ^ Interpreter loader
+
+  , interpLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ())))
+      -- ^ LookupSymbol cache
   }
 
 data InterpInstance
@@ -108,9 +111,6 @@ data ExtInterpInstance c = ExtInterpInstance
       -- Finalizers for ForeignRefs can append values to this list
       -- asynchronously.
 
-  , instLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ())))
-      -- ^ LookupSymbol cache
-
   , instExtra             :: !c
       -- ^ Instance specific extra fields
   }



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54a48fa8e9a8a226cb7d2661758b27be6a74594f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 22:51:45 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 11 Oct 2024 18:51:45 -0400
Subject: [Git][ghc/ghc][wip/T25281] Elmininate incomplete record selectors
Message-ID: <6709ac01a8f29_3c928e2fa7b0457a@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
ee701461 by Simon Peyton Jones at 2024-10-11T23:51:24+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 23:07:34 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Fri, 11 Oct 2024 19:07:34 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] mkTick: Push ticks
 through unsafeCoerce#.
Message-ID: <6709afb662546_3c928e2f33985281@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
b394a664 by Andreas Klebinger at 2024-10-12T00:48:00+02:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -


2 changed files:

- compiler/GHC/Core/Utils.hs
- compiler/GHC/Types/Tickish.hs


Changes:

=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -318,6 +318,10 @@ mkTick t orig_expr = mkTick' id id orig_expr
           -> CoreExpr               -- current expression
           -> CoreExpr
   mkTick' top rest expr = case expr of
+    -- Float ticks into unsafe coerce.
+    Case scrut bndr ty alts@[Alt ac abs _rhs]
+      | Just rhs <- isUnsafeEqualityCase scrut bndr alts
+      -> mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
 
     -- Cost centre ticks should never be reordered relative to each
     -- other. Therefore we can stop whenever two collide.
@@ -1253,7 +1257,7 @@ Note [Tick trivial]
 Ticks are only trivial if they are pure annotations. If we treat
 "tick x" as trivial, it will be inlined inside lambdas and the
 entry count will be skewed, for example.  Furthermore "scc x" will
-turn into just "x" in mkTick.
+turn into just "x" in mkTick. At least if `x` is not a function.
 
 Note [Empty case is trivial]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/Types/Tickish.hs
=====================================
@@ -295,13 +295,15 @@ tickishCanSplit _  = False
 mkNoCount :: GenTickish pass -> GenTickish pass
 mkNoCount n | not (tickishCounts n)   = n
             | not (tickishCanSplit n) = panic "mkNoCount: Cannot split!"
-mkNoCount n at ProfNote{}                = n {profNoteCount = False}
+mkNoCount n at ProfNote{}                = let n' = n {profNoteCount = False}
+                                        in assert (profNoteCount n) n'
 mkNoCount _                           = panic "mkNoCount: Undefined split!"
 
 mkNoScope :: GenTickish pass -> GenTickish pass
 mkNoScope n | tickishScoped n == NoScope  = n
             | not (tickishCanSplit n)     = panic "mkNoScope: Cannot split!"
-mkNoScope n at ProfNote{}                    = n {profNoteScope = False}
+mkNoScope n at ProfNote{}                    = let n' = n {profNoteScope = False}
+                                            in assert (profNoteCount n) n'
 mkNoScope _                               = panic "mkNoScope: Undefined split!"
 
 -- | Return @True@ if this source annotation compiles to some backend



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 11 23:15:44 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 11 Oct 2024 19:15:44 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibbles
Message-ID: <6709b1a0a8e27_3c928e58627c702b@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
f9073e3d by Simon Peyton Jones at 2024-10-12T00:15:19+01:00
Wibbles

- - - - -


6 changed files:

- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Types/Constraint.hs
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/typecheck/should_fail/T18398.stderr


Changes:

=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -763,8 +763,9 @@ simplifyDeriv (DS { ds_loc = loc, ds_tvs = tvs
        -- See [STEP DAC HOIST]
        -- From the simplified constraints extract a subset 'good' that will
        -- become the context 'min_theta' for the derived instance.
-       ; let (residual_simple, _) = approximateWC solved_wanteds
-                -- Ignore any equalities hidden under Given equalities
+       ; let residual_simple = approximateWC False solved_wanteds
+                -- False: ignore any non-qauntifiable constraints,
+                --        including equalities hidden under Given equalities
              head_size = pSizeClassPred clas inst_tys
              good      = mapMaybeBag get_good residual_simple
 


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1453,7 +1453,7 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
        -- not mono. Need to zonk them because they are meta-tyvar TyVarTvs
        ; (psig_qtvs, psig_theta, tau_tys) <- getSeedTys name_taus psigs
 
-       ; let (can_quant_cts, no_quant_cts) = approximateWC wanted
+       ; let (can_quant_cts, no_quant_cts) = approximateWCX wanted
              can_quant = ctsPreds can_quant_cts
              no_quant  = ctsPreds no_quant_cts
              (post_mr_quant, mr_no_quant) = applyMR dflags infer_mode can_quant


=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -818,10 +818,9 @@ findDefaultableGroups (default_tys, extended_defaults) wanteds
     , defaultable_tyvar tv
     , defaultable_classes (map (classTyCon . sndOf3) group) ]
   where
-    (simples1,simples2)    = approximateWC wanteds
-    simples                = simples1 `unionBags` simples2
-      -- simples: for the purpose of defaulting we don't care
-      --          about shape or enclosing equalities
+    simples  = approximateWC True wanteds
+      -- True: for the purpose of defaulting we don't care
+      --       about shape or enclosing equalities
       -- See (W3) in Note [ApproximateWC] in GHC.Tc.Types.Constraint
 
     (unaries, non_unaries) = partitionWith find_unary (bagToList simples)


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -61,7 +61,7 @@ module GHC.Tc.Types.Constraint (
         tyCoVarsOfWC, tyCoVarsOfWCList,
         insolubleWantedCt, insolubleCt, insolubleIrredCt,
         insolubleImplic, nonDefaultableTyVarsOfWC,
-        approximateWC,
+        approximateWCX, approximateWC,
 
         Implication(..), implicationPrototype, checkTelescopeSkol,
         ImplicStatus(..), isInsolubleStatus, isSolvedStatus,
@@ -1788,10 +1788,18 @@ type ApproxWC = ( Bag Ct    -- Free quantifiable constraints
                 , Bag Ct )  -- Free non-quantifiable constraints
                             -- due to shape, or enclosing equality
 
-approximateWC :: WantedConstraints -> ApproxWC
+approximateWC include_non_quantifiable cts
+  | include_non_quantifiable = quant `unionBags` no_quant
+  | otherwise                = quant
+  where
+    (quant, no_quant) = approximateWCX cts
+
+approximateWCX :: WantedConstraints -> ApproxWC
+-- The "X" means "extended";
+--    we return both quantifiable and non-quantifiable constraints
 -- See Note [ApproximateWC]
 -- See Note [floatKindEqualities vs approximateWC]
-approximateWC wc
+approximateWCX wc
   = float_wc False emptyVarSet wc (emptyBag, emptyBag)
   where
     float_wc :: Bool           -- True <=> there are enclosing equalities


=====================================
testsuite/tests/partial-sigs/should_fail/T10615.stderr
=====================================
@@ -1,34 +1,39 @@
 
 T10615.hs:5:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w1’
-      Where: ‘w1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f1 :: w -> f
+               at T10615.hs:6:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f1 :: _ -> f
 
 T10615.hs:6:6: error: [GHC-25897]
-    • Couldn't match type ‘f’ with ‘b1 -> w1’
-      Expected: w1 -> f
-        Actual: w1 -> b1 -> w1
+    • Couldn't match type ‘f’ with ‘b1 -> w’
+      Expected: w -> f
+        Actual: w -> b1 -> w
       ‘f’ is a rigid type variable bound by
-        the inferred type of f1 :: w1 -> f
+        the inferred type of f1 :: w -> f
         at T10615.hs:5:1-12
     • In the expression: const
       In an equation for ‘f1’: f1 = const
-    • Relevant bindings include f1 :: w1 -> f (bound at T10615.hs:6:1)
+    • Relevant bindings include f1 :: w -> f (bound at T10615.hs:6:1)
 
 T10615.hs:8:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w0’
-      Where: ‘w0’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f2 :: w -> _f
+               at T10615.hs:9:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f2 :: _ -> _f
 
 T10615.hs:9:6: error: [GHC-25897]
-    • Couldn't match type ‘_f’ with ‘b0 -> w0’
-      Expected: w0 -> _f
-        Actual: w0 -> b0 -> w0
+    • Couldn't match type ‘_f’ with ‘b0 -> w’
+      Expected: w -> _f
+        Actual: w -> b0 -> w
       ‘_f’ is a rigid type variable bound by
-        the inferred type of f2 :: w0 -> _f
+        the inferred type of f2 :: w -> _f
         at T10615.hs:8:1-13
     • In the expression: const
       In an equation for ‘f2’: f2 = const
-    • Relevant bindings include f2 :: w0 -> _f (bound at T10615.hs:9:1)
+    • Relevant bindings include f2 :: w -> _f (bound at T10615.hs:9:1)
+


=====================================
testsuite/tests/typecheck/should_fail/T18398.stderr
=====================================
@@ -6,7 +6,7 @@ T18398.hs:13:34: error: [GHC-39999]
       In the expression: case x of MkEx _ -> meth x y
 
 T18398.hs:13:70: error: [GHC-39999]
-    • No instance for ‘C Ex t0’ arising from a use of ‘meth’
+    • No instance for ‘C Ex t1’ arising from a use of ‘meth’
     • In the expression: meth x z
       In a case alternative: MkEx _ -> meth x z
       In the expression: case x of MkEx _ -> meth x z



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:43:47 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:43:47 -0400
Subject: [Git][ghc/ghc][master] 4 commits: testsuite: Normalise trailing
 digits from hole fits output
Message-ID: <6709f07363895_2325073e09a41445d@gitlab.mail>



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


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -


8 changed files:

- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- + libraries/base/tests/T25066.hs
- + libraries/base/tests/T25066.stderr
- libraries/base/tests/all.T
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -2,6 +2,8 @@
 
 ## 4.22.0.0 *TBA*
   * Restrict `Data.List.NonEmpty.unzip` to `NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)`. ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+  * Modify the implementation of `Control.Exception.throw` to avoid call-sites being inferred as diverging via precise exception.
+    ([GHC #25066](https://gitlab.haskell.org/ghc/ghc/-/issues/25066), [CLC proposal #290](https://github.com/haskell/core-libraries-committee/issues/290))
 
 ## 4.21.0.0 *TBA*
   * `GHC.Desugar` has been deprecated and should be removed in GHC 9.14. ([CLC proposal #216](https://github.com/haskell/core-libraries-committee/issues/216))


=====================================
libraries/base/src/Control/Exception/Backtrace.hs
=====================================
@@ -7,8 +7,43 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- Mechanisms for collecting diagnostic backtraces and their representation.
+-- This module provides the 'Backtrace'\ s type, which provides a
+-- common representation for backtrace information which can be, e.g., attached
+-- to exceptions (via the 'Control.Exception.Context.ExceptionContext' facility).
+-- These backtraces preserve useful context about the execution state of the program
+-- using a variety of means; we call these means *backtrace mechanisms*.
 --
+-- We currently support four backtrace mechanisms:
+--
+--  - 'CostCentreBacktrace' captures the current cost-centre stack
+--    using 'GHC.Stack.CCS.getCurrentCCS'.
+--  - 'HasCallStackBacktrace' captures the 'HasCallStack' 'CallStack'.
+--  - 'ExecutionBacktrace' captures the execution stack, unwound and resolved
+--    to symbols via DWARF debug information.
+--  - 'IPEBacktrace' captures the execution stack, resolved to names via info-table
+--    provenance information.
+--
+-- Each of these are useful in different situations. While 'CostCentreBacktrace's are
+-- readily mapped back to the source program, they require that the program be instrumented
+-- with cost-centres, incurring runtime cost. Similarly, 'HasCallStackBacktrace's require that
+-- the program be manually annotated with 'HasCallStack' constraints.
+--
+-- By contrast, 'IPEBacktrace's incur no runtime instrumentation but require that (at least
+-- some subset of) the program be built with GHC\'s @-finfo-table-map@ flag. Moreover, because
+-- info-table provenance information is derived after optimisation, it may be harder to relate
+-- back to the structure of the source program.
+--
+-- 'ExecutionBacktrace's are similar to 'IPEBacktrace's but use DWARF stack unwinding
+-- and symbol resolution; this allows for useful backtraces even in the presence
+-- of foreign calls, both into and out of Haskell. However, for robust stack unwinding
+-- the entirety of the program (and its dependencies, both Haskell and native) must
+-- be compiled with debugging information (e.g. using GHC\'s @-g@ flag).
+
+
+-- Note [Backtrace mechanisms]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- See module docstring above.
+
 
 module Control.Exception.Backtrace
     ( -- * Backtrace mechanisms


=====================================
libraries/base/tests/T25066.hs
=====================================
@@ -0,0 +1,15 @@
+-- | Check that the demand signature of 'throw' doesn't suggest that it will
+-- throw a precise exception. Specifically, `g` should have a `b` divergence
+-- type in its demand signature.
+
+module T25066 (g) where
+
+import Control.Exception
+
+data MyException = MyException
+  deriving (Show)
+
+instance Exception MyException
+
+g :: a
+g = throw MyException


=====================================
libraries/base/tests/T25066.stderr
=====================================
@@ -0,0 +1,20 @@
+
+==================== Demand signatures ====================
+T25066.$fExceptionMyException:
+T25066.$fShowMyException:
+T25066.$tc'MyException:
+T25066.$tcMyException:
+T25066.$trModule:
+T25066.g: b
+
+
+
+==================== Demand signatures ====================
+T25066.$fExceptionMyException:
+T25066.$fShowMyException:
+T25066.$tc'MyException:
+T25066.$tcMyException:
+T25066.$trModule:
+T25066.g: b
+
+


=====================================
libraries/base/tests/all.T
=====================================
@@ -325,3 +325,4 @@ test('T23697',
   ], makefile_test, ['T23697'])
 test('stimesEndo', normal, compile_and_run, [''])
 test('T24807', exit_code(1), compile_and_run, [''])
+test('T25066', [only_ways(['optasm']), grep_errmsg('T25066.g')], compile, ['-ddump-dmd-signatures'])


=====================================
libraries/ghc-internal/src/GHC/Internal/Exception.hs
=====================================
@@ -81,9 +81,86 @@ import GHC.Internal.Exception.Type
 throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e.
          (HasCallStack, Exception e) => e -> a
 throw e =
-    let !se = unsafePerformIO (toExceptionWithBacktrace e)
+    -- Note the absolutely crucial bang "!" on this binding!
+    --   See Note [Capturing the backtrace in throw]
+    -- Note also the absolutely crucial `noinine` in the RHS!
+    --   See Note [Hiding precise exception signature in throw]
+    let se :: SomeException
+        !se = noinline (unsafePerformIO (toExceptionWithBacktrace e))
     in raise# se
 
+-- Note [Capturing the backtrace in throw]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- When `throw` captures a backtrace, it must be the backtrace *at the moment
+-- that `throw` is called*.   That is why the binding of `se` is marked strict,
+-- via the `!`:
+--
+--     !se = 
+--
+-- GHC can capture /four/ different sorts of backtraces (See Note [Backtrace
+-- mechanisms] in "Control.Exception.Backtrace" for details). One of them
+-- (`CallStack` constraints) does not need this strict-binding treatment,
+-- because the `CallStack` constraint is captured in the thunk. However, the
+-- other two (DWARF stack unwinding, and native Haskell stack unwinding) are
+-- much more fragile, and can only be captured right at the call of `throw`.
+--
+-- However, making `se` strict has downsides: see
+-- Note [Hiding precise exception signature in throw] below.
+--
+--
+-- Note [Hiding precise exception signature in throw]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- In 'throw' we use `unsafePerformIO . toExceptionWithBacktrace' to collect
+-- the backtraces which will be attached as the exception's 'ExceptionContext'.
+-- We must ensure that this is evaluated immediately in `throw` since
+-- `toExceptionWithBacktrace` must capture the execution state at the moment
+-- that the exception is thrown (see Note [Capturing the backtrace in throw]).
+-- Unfortunately, unless we take particular care this can lead to a
+-- catastrophic regression in 'throw's demand signature which will infect
+-- all callers (#25066)
+--
+-- Specifically, GHC's demand analysis has an approximate heuristic for tracking
+-- whether divergent functions diverge with precise or imprecise exceptions (namely
+-- the 'ExnOrDiv' and 'Diverges' constructors of 'GHC.Types.Demand.Divergence',
+-- respectively). This is because we can take considerably more liberties in
+-- optimising around functions which are known not to diverge via precise
+-- exception (see Note [Precise exceptions and strictness analysis]).
+-- For this reason, it is important that 'throw' have a 'Diverges' divergence
+-- type.
+--
+-- Unfortunately, this is broken if we allow `unsafePerformIO` to inline. Specifically,
+-- if we allow this inlining we will end up with Core of the form:
+--
+--   throw = \e ->
+--     case runRW# (\s -> ... toExceptionWithBacktrace e s ...) of
+--       se -> raise# se
+--
+-- so far this is fine; the demand analyzer's divergence heuristic
+-- will give 'throw' the expected 'Diverges' divergence.
+--
+-- However, the simplifier will subsequently notice that `raise#` can be fruitfully
+-- floated into the body of the `runRW#`:
+--
+--   throw = \e ->
+--     runRW# (\s -> case toExceptionWithBacktrace e s of
+--                     (# s', se #) -> raise# se)
+--
+-- This is problematic as one of the demand analyser's heuristics examines
+-- `case` scrutinees, looking for those that result in a `RealWorld#` token
+-- (see Note [Which scrutinees may throw precise exceptions], test (1)). The
+-- `case toExceptionWithBacktrace e of ...` here fails this check, causing the
+-- heuristic to conclude that `throw` may indeed diverge with a precise
+-- exception. This resulted in the significant performance regression noted in
+-- #25066.
+--
+-- To avoid this, we use `noinline` to ensure that `unsafePerformIO` does not unfold,
+-- meaning that the `raise#` cannot be floated under the `toExceptionWithBacktrace`
+-- case analysis.
+--
+-- Ultimately this is a bit of a horrible hack; the right solution would be to have
+-- primops which allow more precise guidance of the demand analyser's heuristic
+-- (e.g. #23847).
+
 -- | @since base-4.20.0.0
 toExceptionWithBacktrace :: (HasCallStack, Exception e)
                          => e -> IO SomeException


=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -33,7 +33,7 @@ data BacktraceMechanism
   = CostCentreBacktrace
   -- | collect 'HasCallStack' backtraces
   | HasCallStackBacktrace
-  -- | collect backtraces from native execution stack unwinding
+  -- | collect backtraces via native execution stack unwinding (e.g. using DWARF debug information)
   | ExecutionBacktrace
   -- | collect backtraces from Info Table Provenance Entries
   | IPEBacktrace


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -1,8 +1,17 @@
+import re
+
 # Args to vtc are: extra compile flags
 
 def f( name, opts ):
   opts.extra_hc_opts = '-fno-warn-incomplete-patterns'
 
+def normalise_type_vars(s):
+  """
+  Normalise away the trailing digits from type variable OccNames
+  in hole fits error messages as these tend to be non-deterministic.
+  """
+  return re.sub(r'([a-z])[0-9]+', r'\1', s)
+
 setTestOpts(f)
 
 test('tc001', normal, compile, [''])
@@ -392,7 +401,7 @@ test('local_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-ho
 test('subsumption_sort_hole_fits', normalise_version('ghc-internal', 'base'), compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fsort-by-subsumption-hole-fits'])
 test('valid_hole_fits_interactions', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits'])
 test('refinement_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2'])
-test('abstract_refinement_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -fabstract-refinement-hole-fits -funclutter-valid-hole-fits'])
+test('abstract_refinement_hole_fits', normalise_errmsg_fun(normalise_type_vars), compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -fabstract-refinement-hole-fits -funclutter-valid-hole-fits'])
 test('free_monad_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -funclutter-valid-hole-fits'])
 test('constraint_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -funclutter-valid-hole-fits'])
 test('type_in_type_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8584504b68418eaa12f1332a22ccb7d354aacc00...0060ece762d7a936daf28195676b6162c30dc845

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8584504b68418eaa12f1332a22ccb7d354aacc00...0060ece762d7a936daf28195676b6162c30dc845
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:44:17 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:44:17 -0400
Subject: [Git][ghc/ghc][master] Bump process submodule to v1.6.25.0
Message-ID: <6709f0914bcbf_2325073901c01777a@gitlab.mail>



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


Commits:
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -


5 changed files:

- libraries/process
- testsuite/tests/process/process004.hs
- testsuite/tests/process/process004.stdout
- testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
- testsuite/tests/process/process004.stdout-mingw32


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b
+Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e


=====================================
testsuite/tests/process/process004.hs
=====================================
@@ -4,8 +4,13 @@ import System.IO.Error
 import System.Process
 
 main :: IO ()
-main = do test1 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
-          test2 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
+main = do
+  -- N.B. Only show the error type since the exact error text
+  -- may depend upon precise system call which @process@ decided
+  -- to use.
+  let printError e = putStrLn ("Exc: " ++ show (ioeGetErrorType e))
+  test1 `catchIOError` printError
+  test2 `catchIOError` printError
 
 test1 :: IO ()
 test1 = do


=====================================
testsuite/tests/process/process004.stdout
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: chdir: invalid argument (Bad file descriptor)
-Exc: true: runProcess: chdir: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: does not exist (No such file or directory)
-Exc: true: runProcess: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-mingw32
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: invalid argument (Invalid argument)
-Exc: true: runProcess: invalid argument (Invalid argument)
+Exc: invalid argument
+Exc: invalid argument



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/18f532f3ed021fff9529f50da2006b8a8d8b1df7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:44:58 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:44:58 -0400
Subject: [Git][ghc/ghc][master] Move HsInteger and HsRat to an extension
 constructor
Message-ID: <6709f0ba35f08_2325076adfb02287c@gitlab.mail>



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


Commits:
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -


15 changed files:

- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -432,6 +432,8 @@ deriving instance Data XBindStmtTc
 -- deriving instance (DataId p) => Data (HsLit p)
 deriving instance Data (HsLit GhcPs)
 deriving instance Data (HsLit GhcRn)
+
+deriving instance Data HsLitTc
 deriving instance Data (HsLit GhcTc)
 
 -- deriving instance (DataIdLR p p) => Data (HsOverLit p)


=====================================
compiler/GHC/Hs/Lit.hs
=====================================
@@ -62,11 +62,26 @@ type instance XHsWord8Prim  (GhcPass _) = SourceText
 type instance XHsWord16Prim (GhcPass _) = SourceText
 type instance XHsWord32Prim (GhcPass _) = SourceText
 type instance XHsWord64Prim (GhcPass _) = SourceText
-type instance XHsInteger    (GhcPass _) = SourceText
-type instance XHsRat        (GhcPass _) = NoExtField
 type instance XHsFloatPrim  (GhcPass _) = NoExtField
 type instance XHsDoublePrim (GhcPass _) = NoExtField
-type instance XXLit         (GhcPass _) = DataConCantHappen
+
+type instance XXLit         GhcPs = DataConCantHappen
+type instance XXLit         GhcRn = DataConCantHappen
+type instance XXLit         GhcTc = HsLitTc
+
+data HsLitTc
+  = HsInteger SourceText Integer Type
+      -- ^ Genuinely an integer; arises only
+      -- from TRANSLATION (overloaded
+      -- literals are done with HsOverLit)
+  | HsRat FractionalLit Type
+      -- ^ Genuinely a rational; arises only from
+      -- TRANSLATION (overloaded literals are
+      -- done with HsOverLit)
+instance Eq HsLitTc where
+  (HsInteger _ x _) == (HsInteger _ y _) = x==y
+  (HsRat x _)       == (HsRat y _)       = x==y
+  _                 == _                 = False
 
 data OverLitRn
   = OverLitRn {
@@ -130,7 +145,7 @@ hsOverLitNeedsParens _ (XOverLit { }) = False
 --
 -- See Note [Printing of literals in Core] in GHC.Types.Literal
 -- for the reasoning.
-hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
+hsLitNeedsParens :: forall x. IsPass x => PprPrec -> HsLit (GhcPass x) -> Bool
 hsLitNeedsParens p = go
   where
     go (HsChar {})        = False
@@ -139,8 +154,6 @@ hsLitNeedsParens p = go
     go (HsMultilineString {}) = False
     go (HsStringPrim {})  = False
     go (HsInt _ x)        = p > topPrec && il_neg x
-    go (HsInteger _ x _)  = p > topPrec && x < 0
-    go (HsRat _ x _)      = p > topPrec && fl_neg x
     go (HsFloatPrim {})   = False
     go (HsDoublePrim {})  = False
     go (HsIntPrim {})     = False
@@ -153,10 +166,18 @@ hsLitNeedsParens p = go
     go (HsWord16Prim {})  = False
     go (HsWord64Prim {})  = False
     go (HsWord32Prim {})  = False
-    go (XLit _)           = False
-
--- | Convert a literal from one index type to another
-convertLit :: HsLit (GhcPass p1) -> HsLit (GhcPass p2)
+    go (XLit x)           = case ghcPass @x of
+      GhcTc -> case x of
+         (HsInteger _ x _) -> p > topPrec && x < 0
+         (HsRat  x _)      -> p > topPrec && fl_neg x
+
+
+-- | Convert a literal from one index type to another.
+-- The constraint XXLit (GhcPass p)~DataConCantHappen means that once the
+-- XLit constructor is inhabited, we can no longer go back to the case where
+-- its not. In practice it just means you can't just convertLit to go from
+-- (HsLit GhcTc) -> (HsLit GhcPs/GhcRn), while all other conversions are fine.
+convertLit :: XXLit (GhcPass p)~DataConCantHappen => HsLit (GhcPass p) -> HsLit (GhcPass p')
 convertLit (HsChar a x)       = HsChar a x
 convertLit (HsCharPrim a x)   = HsCharPrim a x
 convertLit (HsString a x)     = HsString a x
@@ -173,8 +194,6 @@ convertLit (HsWord8Prim a x)  = HsWord8Prim a x
 convertLit (HsWord16Prim a x) = HsWord16Prim a x
 convertLit (HsWord32Prim a x) = HsWord32Prim a x
 convertLit (HsWord64Prim a x) = HsWord64Prim a x
-convertLit (HsInteger a x b)  = HsInteger a x b
-convertLit (HsRat a x b)      = HsRat a x b
 convertLit (HsFloatPrim a x)  = HsFloatPrim a x
 convertLit (HsDoublePrim a x) = HsDoublePrim a x
 
@@ -194,7 +213,7 @@ Equivalently it's True if
 -}
 
 -- Instance specific to GhcPs, need the SourceText
-instance Outputable (HsLit (GhcPass p)) where
+instance IsPass p => Outputable (HsLit (GhcPass p)) where
     ppr (HsChar st c)       = pprWithSourceText st (pprHsChar c)
     ppr (HsCharPrim st c)   = pprWithSourceText st (pprPrimChar c)
     ppr (HsString st s)     = pprWithSourceText st (pprHsString s)
@@ -205,8 +224,6 @@ instance Outputable (HsLit (GhcPass p)) where
     ppr (HsStringPrim st s) = pprWithSourceText st (pprHsBytes s)
     ppr (HsInt _ i)
       = pprWithSourceText (il_text i) (integer (il_value i))
-    ppr (HsInteger st i _)  = pprWithSourceText st (integer i)
-    ppr (HsRat _ f _)       = ppr f
     ppr (HsFloatPrim _ f)   = ppr f <> primFloatSuffix
     ppr (HsDoublePrim _ d)  = ppr d <> primDoubleSuffix
     ppr (HsIntPrim st i)    = pprWithSourceText st (pprPrimInt i)
@@ -219,6 +236,10 @@ instance Outputable (HsLit (GhcPass p)) where
     ppr (HsWord16Prim st w) = pprWithSourceText st (pprPrimWord16 w)
     ppr (HsWord32Prim st w) = pprWithSourceText st (pprPrimWord32 w)
     ppr (HsWord64Prim st w) = pprWithSourceText st (pprPrimWord64 w)
+    ppr (XLit x)            = case ghcPass @p of
+      GhcTc -> case x of
+         (HsInteger st i _) -> pprWithSourceText st (integer i)
+         (HsRat  f _)       -> ppr f
 
 -- in debug mode, print the expression that it's resolved to, too
 instance OutputableBndrId p
@@ -237,7 +258,7 @@ instance Outputable OverLitVal where
 -- mainly for too reasons:
 --  * We do not want to expose their internal representation
 --  * The warnings become too messy
-pmPprHsLit :: HsLit (GhcPass x) -> SDoc
+pmPprHsLit :: forall p. IsPass p => HsLit (GhcPass p) -> SDoc
 pmPprHsLit (HsChar _ c)       = pprHsChar c
 pmPprHsLit (HsCharPrim _ c)   = pprHsChar c
 pmPprHsLit (HsString st s)    = pprWithSourceText st (pprHsString s)
@@ -254,10 +275,12 @@ pmPprHsLit (HsWord8Prim _ w)  = integer w
 pmPprHsLit (HsWord16Prim _ w) = integer w
 pmPprHsLit (HsWord32Prim _ w) = integer w
 pmPprHsLit (HsWord64Prim _ w) = integer w
-pmPprHsLit (HsInteger _ i _)  = integer i
-pmPprHsLit (HsRat _ f _)      = ppr f
 pmPprHsLit (HsFloatPrim _ f)  = ppr f
 pmPprHsLit (HsDoublePrim _ d) = ppr d
+pmPprHsLit (XLit x)           = case ghcPass @p of
+  GhcTc -> case x of
+   (HsInteger _ i _)  -> integer i
+   (HsRat f _)        -> ppr f
 
 negateOverLitVal :: OverLitVal -> OverLitVal
 negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i)


=====================================
compiler/GHC/Hs/Syn/Type.hs
=====================================
@@ -7,8 +7,7 @@ module GHC.Hs.Syn.Type (
     -- * Extracting types from HsExpr
     lhsExprType, hsExprType, hsWrapperType,
     -- * Extracting types from HsSyn
-    hsLitType, hsPatType, hsLPatType
-
+    hsLitType, hsPatType, hsLPatType,
   ) where
 
 import GHC.Prelude
@@ -72,7 +71,7 @@ hsPatType (XPat ext) =
     ExpansionPat _ pat -> hsPatType pat
 hsPatType (SplicePat v _)               = dataConCantHappen v
 
-hsLitType :: HsLit (GhcPass p) -> Type
+hsLitType :: forall p. IsPass p => HsLit (GhcPass p) -> Type
 hsLitType (HsChar _ _)       = charTy
 hsLitType (HsCharPrim _ _)   = charPrimTy
 hsLitType (HsString _ _)     = stringTy
@@ -89,10 +88,12 @@ hsLitType (HsWord8Prim _ _)  = word8PrimTy
 hsLitType (HsWord16Prim _ _) = word16PrimTy
 hsLitType (HsWord32Prim _ _) = word32PrimTy
 hsLitType (HsWord64Prim _ _) = word64PrimTy
-hsLitType (HsInteger _ _ ty) = ty
-hsLitType (HsRat _ _ ty)     = ty
 hsLitType (HsFloatPrim _ _)  = floatPrimTy
 hsLitType (HsDoublePrim _ _) = doublePrimTy
+hsLitType (XLit x)           = case ghcPass @p of
+      GhcTc -> case x of
+         (HsInteger _ _ ty) -> ty
+         (HsRat  _ ty)      -> ty
 
 
 -- | Compute the 'Type' of an @'LHsExpr' 'GhcTc'@ in a pure fashion.


=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -275,7 +275,7 @@ dsExpr (HsProjection x _)     = dataConCantHappen x
 
 dsExpr (HsLit _ lit)
   = do { warnAboutOverflowedLit lit
-       ; dsLit (convertLit lit) }
+       ; dsLit lit }
 
 dsExpr (HsOverLit _ lit)
   = do { warnAboutOverflowedOverLit lit


=====================================
compiler/GHC/HsToCore/Match/Literal.hs
=====================================
@@ -97,7 +97,7 @@ For numeric literals, we try to detect there use at a standard type
 See also below where we look for @DictApps@ for \tr{plusInt}, etc.
 -}
 
-dsLit :: HsLit GhcRn -> DsM CoreExpr
+dsLit :: forall p. IsPass p => HsLit (GhcPass p) -> DsM CoreExpr
 dsLit l = do
   dflags <- getDynFlags
   let platform = targetPlatform dflags
@@ -122,9 +122,11 @@ dsLit l = do
     HsChar _ c       -> return (mkCharExpr c)
     HsString _ str   -> mkStringExprFS str
     HsMultilineString _ str -> mkStringExprFS str
-    HsInteger _ i _  -> return (mkIntegerExpr platform i)
     HsInt _ i        -> return (mkIntExpr platform (il_value i))
-    HsRat _ fl ty    -> dsFractionalLitToRational fl ty
+    XLit x           -> case ghcPass @p of
+      GhcTc          -> case x of
+        HsInteger _ i _  -> return (mkIntegerExpr platform i)
+        HsRat fl ty      -> dsFractionalLitToRational fl ty
 
 {-
 Note [FractionalLit representation]
@@ -460,24 +462,24 @@ getIntegralLit _ = Nothing
 -- | If 'Integral', extract the value and type of the non-overloaded literal.
 getSimpleIntegralLit :: HsLit GhcTc -> Maybe (Integer, Type)
 getSimpleIntegralLit (HsInt _ IL{ il_value = i }) = Just (i, intTy)
-getSimpleIntegralLit (HsIntPrim _ i)    = Just (i, intPrimTy)
-getSimpleIntegralLit (HsWordPrim _ i)   = Just (i, wordPrimTy)
-getSimpleIntegralLit (HsInt8Prim _ i)   = Just (i, int8PrimTy)
-getSimpleIntegralLit (HsInt16Prim _ i)  = Just (i, int16PrimTy)
-getSimpleIntegralLit (HsInt32Prim _ i)  = Just (i, int32PrimTy)
-getSimpleIntegralLit (HsInt64Prim _ i)  = Just (i, int64PrimTy)
-getSimpleIntegralLit (HsWord8Prim _ i)  = Just (i, word8PrimTy)
-getSimpleIntegralLit (HsWord16Prim _ i) = Just (i, word16PrimTy)
-getSimpleIntegralLit (HsWord32Prim _ i) = Just (i, word32PrimTy)
-getSimpleIntegralLit (HsWord64Prim _ i) = Just (i, word64PrimTy)
-getSimpleIntegralLit (HsInteger _ i ty) = Just (i, ty)
+getSimpleIntegralLit (HsIntPrim _ i)            = Just (i, intPrimTy)
+getSimpleIntegralLit (HsWordPrim _ i)           = Just (i, wordPrimTy)
+getSimpleIntegralLit (HsInt8Prim _ i)           = Just (i, int8PrimTy)
+getSimpleIntegralLit (HsInt16Prim _ i)          = Just (i, int16PrimTy)
+getSimpleIntegralLit (HsInt32Prim _ i)          = Just (i, int32PrimTy)
+getSimpleIntegralLit (HsInt64Prim _ i)          = Just (i, int64PrimTy)
+getSimpleIntegralLit (HsWord8Prim _ i)          = Just (i, word8PrimTy)
+getSimpleIntegralLit (HsWord16Prim _ i)         = Just (i, word16PrimTy)
+getSimpleIntegralLit (HsWord32Prim _ i)         = Just (i, word32PrimTy)
+getSimpleIntegralLit (HsWord64Prim _ i)         = Just (i, word64PrimTy)
+getSimpleIntegralLit (XLit (HsInteger _ i ty))  = Just (i, ty)
 
 getSimpleIntegralLit HsChar{}           = Nothing
 getSimpleIntegralLit HsCharPrim{}       = Nothing
 getSimpleIntegralLit HsString{}         = Nothing
 getSimpleIntegralLit HsMultilineString{} = Nothing
 getSimpleIntegralLit HsStringPrim{}     = Nothing
-getSimpleIntegralLit HsRat{}            = Nothing
+getSimpleIntegralLit (XLit (HsRat{}))   = Nothing
 getSimpleIntegralLit HsFloatPrim{}      = Nothing
 getSimpleIntegralLit HsDoublePrim{}     = Nothing
 


=====================================
compiler/GHC/HsToCore/Pmc/Desugar.hs
=====================================
@@ -225,7 +225,7 @@ desugarPat x pat = case pat of
     mkPmLitGrds x lit'
 
   LitPat _ lit -> do
-    core_expr <- dsLit (convertLit lit)
+    core_expr <- dsLit lit
     let lit = expectJust "failed to detect Lit" (coreExprAsPmLit core_expr)
     mkPmLitGrds x lit
 


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -3010,7 +3010,7 @@ repTyVarSig (MkC bndr) = rep2 tyVarSigName [bndr]
 ----------------------------------------------------------
 --              Literals
 
-repLiteral :: HsLit GhcRn -> MetaM (Core TH.Lit)
+repLiteral ::  HsLit GhcRn -> MetaM (Core TH.Lit)
 repLiteral (HsStringPrim _ bs)
   = do word8_ty <- lookupType word8TyConName
        let w8s = unpack bs
@@ -3019,20 +3019,19 @@ repLiteral (HsStringPrim _ bs)
        rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr]
 repLiteral lit
   = do lit' <- case lit of
-                   HsIntPrim _ i    -> mk_integer i
-                   HsWordPrim _ w   -> mk_integer w
-                   HsInt _ i        -> mk_integer (il_value i)
-                   HsFloatPrim _ r  -> mk_rational r
-                   HsDoublePrim _ r -> mk_rational r
-                   HsCharPrim _ c   -> mk_char c
-                   _ -> return lit
-       lit_expr <- lift $ dsLit lit'
+                   HsIntPrim _ i    -> lift . dsLit <$> mk_integer i
+                   HsWordPrim _ w   -> lift . dsLit <$> mk_integer w
+                   HsInt _ i        -> lift . dsLit <$> mk_integer (il_value i)
+                   HsFloatPrim _ r  -> lift . dsLit <$> mk_rational r
+                   HsDoublePrim _ r -> lift . dsLit <$> mk_rational r
+                   HsCharPrim _ c   -> lift . dsLit <$> mk_char c
+                   _                -> return . lift . dsLit $ lit
+       lit_expr <- lit'
        case mb_lit_name of
           Just lit_name -> rep2_nw lit_name [lit_expr]
           Nothing -> notHandled (ThExoticLiteral lit)
   where
     mb_lit_name = case lit of
-                 HsInteger _ _ _  -> Just integerLName
                  HsInt _ _        -> Just integerLName
                  HsIntPrim _ _    -> Just intPrimLName
                  HsWordPrim _ _   -> Just wordPrimLName
@@ -3042,15 +3041,15 @@ repLiteral lit
                  HsCharPrim _ _   -> Just charPrimLName
                  HsString _ _     -> Just stringLName
                  HsMultilineString _ _ -> Just stringLName
-                 HsRat _ _ _      -> Just rationalLName
                  _                -> Nothing
 
-mk_integer :: Integer -> MetaM (HsLit GhcRn)
-mk_integer  i = return $ HsInteger NoSourceText i integerTy
+mk_integer :: Integer -> MetaM (HsLit GhcTc)
+mk_integer  i = return $ XLit $ HsInteger NoSourceText i integerTy
 
-mk_rational :: FractionalLit -> MetaM (HsLit GhcRn)
+mk_rational :: FractionalLit -> MetaM (HsLit GhcTc)
 mk_rational r = do rat_ty <- lookupType rationalTyConName
-                   return $ HsRat noExtField r rat_ty
+                   return $ XLit $ HsRat r rat_ty
+
 mk_string :: FastString -> MetaM (HsLit GhcRn)
 mk_string s = return $ HsString NoSourceText s
 
@@ -3059,15 +3058,25 @@ mk_char c = return $ HsChar NoSourceText c
 
 repOverloadedLiteral :: HsOverLit GhcRn -> MetaM (Core TH.Lit)
 repOverloadedLiteral (OverLit { ol_val = val})
-  = do { lit <- mk_lit val; repLiteral lit }
-        -- The type Rational will be in the environment, because
-        -- the smart constructor 'TH.Syntax.rationalL' uses it in its type,
-        -- and rationalL is sucked in when any TH stuff is used
-
-mk_lit :: OverLitVal -> MetaM (HsLit GhcRn)
-mk_lit (HsIntegral i)     = mk_integer  (il_value i)
-mk_lit (HsFractional f)   = mk_rational f
-mk_lit (HsIsString _ s)   = mk_string   s
+  = repOverLiteralVal val
+    -- The type Rational will be in the environment, because
+    -- the smart constructor 'TH.Syntax.rationalL' uses it in its type,
+    -- and rationalL is sucked in when any TH stuff is used
+
+repOverLiteralVal ::  OverLitVal -> MetaM (Core TH.Lit)
+repOverLiteralVal lit = do
+  lit' <- case lit of
+        (HsIntegral i)   -> lift . dsLit <$> mk_integer  (il_value i)
+        (HsFractional f) -> lift . dsLit <$> mk_rational f
+        (HsIsString _ s) -> lift . dsLit <$> mk_string   s
+  lit_expr <- lit'
+
+  let lit_name = case lit of
+        (HsIntegral _  ) -> integerLName
+        (HsFractional _) -> rationalLName
+        (HsIsString _ _) -> stringLName
+
+  rep2_nw lit_name [lit_expr]
 
 repRdrName :: RdrName -> MetaM (Core TH.Name)
 repRdrName rdr_name = do


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -383,7 +383,7 @@ rnExpr (HsLit x lit) | Just (src, s) <- stringLike lit
 
 rnExpr (HsLit x lit)
   = do { rnLit lit
-       ; return (HsLit x(convertLit lit), emptyFVs) }
+       ; return (HsLit x (convertLit lit), emptyFVs) }
 
 rnExpr (HsOverLit x lit)
   = do { ((lit', mb_neg), fvs) <- rnOverLit lit -- See Note [Negative zero]


=====================================
compiler/GHC/Tc/Utils/Instantiate.hs
=====================================
@@ -807,15 +807,14 @@ newNonTrivialOverloadedLit
     orig = LiteralOrigin lit
 
 ------------
-mkOverLit :: OverLitVal -> TcM (HsLit (GhcPass p))
+mkOverLit :: OverLitVal -> TcM (HsLit GhcTc)
 mkOverLit (HsIntegral i)
   = do  { integer_ty <- tcMetaTy integerTyConName
-        ; return (HsInteger (il_text i)
-                            (il_value i) integer_ty) }
+        ; return (XLit $ HsInteger  (il_text i) (il_value i) integer_ty) }
 
 mkOverLit (HsFractional r)
   = do  { rat_ty <- tcMetaTy rationalTyConName
-        ; return (HsRat noExtField r rat_ty) }
+        ; return (XLit $ HsRat r rat_ty) }
 
 mkOverLit (HsIsString src s) = return (HsString src s)
 


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -2368,7 +2368,7 @@ shortCutLit platform val res_ty
       | isWordTy res_ty && platformInWordRange platform i
       = Just (mkLit wordDataCon (HsWordPrim src i))
       | isIntegerTy res_ty
-      = Just (HsLit noExtField (HsInteger src i res_ty))
+      = Just (HsLit noExtField (XLit $ HsInteger src i res_ty))
       | otherwise
       = go_fractional (integralFractionalLit neg i)
         -- The 'otherwise' case is important


=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -940,9 +940,9 @@ zonkExpr (HsIPVar x _) = dataConCantHappen x
 
 zonkExpr (HsOverLabel x _) = dataConCantHappen x
 
-zonkExpr (HsLit x (HsRat e f ty))
+zonkExpr (HsLit x (XLit (HsRat f ty)))
   = do new_ty <- zonkTcTypeToTypeX ty
-       return (HsLit x (HsRat e f new_ty))
+       return (HsLit x (XLit $ HsRat f new_ty))
 
 zonkExpr (HsLit x lit)
   = return (HsLit x lit)


=====================================
compiler/Language/Haskell/Syntax/Extension.hs
=====================================
@@ -566,8 +566,6 @@ type family XHsWord8Prim x
 type family XHsWord16Prim x
 type family XHsWord32Prim x
 type family XHsWord64Prim x
-type family XHsInteger x
-type family XHsRat x
 type family XHsFloatPrim x
 type family XHsDoublePrim x
 type family XXLit x


=====================================
compiler/Language/Haskell/Syntax/Lit.hs
=====================================
@@ -21,7 +21,6 @@ module Language.Haskell.Syntax.Lit where
 import Language.Haskell.Syntax.Extension
 
 import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText)
-import GHC.Core.Type (Type)
 
 import GHC.Data.FastString (FastString, lexicalCompareFS)
 
@@ -80,22 +79,13 @@ data HsLit x
       -- ^ literal @Word32#@
   | HsWord64Prim (XHsWord64Prim x) {- SourceText -} Integer
       -- ^ literal @Word64#@
-  | HsInteger (XHsInteger x) {- SourceText -} Integer Type
-      -- ^ Genuinely an integer; arises only
-      -- from TRANSLATION (overloaded
-      -- literals are done with HsOverLit)
-  | HsRat (XHsRat x)  FractionalLit Type
-      -- ^ Genuinely a rational; arises only from
-      -- TRANSLATION (overloaded literals are
-      -- done with HsOverLit)
   | HsFloatPrim (XHsFloatPrim x)   FractionalLit
       -- ^ Unboxed Float
   | HsDoublePrim (XHsDoublePrim x) FractionalLit
       -- ^ Unboxed Double
-
   | XLit !(XXLit x)
 
-instance Eq (HsLit x) where
+instance (Eq (XXLit x)) => Eq (HsLit x) where
   (HsChar _ x1)       == (HsChar _ x2)       = x1==x2
   (HsCharPrim _ x1)   == (HsCharPrim _ x2)   = x1==x2
   (HsString _ x1)     == (HsString _ x2)     = x1==x2
@@ -105,10 +95,9 @@ instance Eq (HsLit x) where
   (HsWordPrim _ x1)   == (HsWordPrim _ x2)   = x1==x2
   (HsInt64Prim _ x1)  == (HsInt64Prim _ x2)  = x1==x2
   (HsWord64Prim _ x1) == (HsWord64Prim _ x2) = x1==x2
-  (HsInteger _ x1 _)  == (HsInteger _ x2 _)  = x1==x2
-  (HsRat _ x1 _)      == (HsRat _ x2 _)      = x1==x2
   (HsFloatPrim _ x1)  == (HsFloatPrim _ x2)  = x1==x2
   (HsDoublePrim _ x1) == (HsDoublePrim _ x2) = x1==x2
+  (XLit x1)           == (XLit x2)           = x1==x2
   _                   == _                   = False
 
 -- | Haskell Overloaded Literal


=====================================
testsuite/tests/ghc-api/annotations-literals/parsed.hs
=====================================
@@ -64,8 +64,6 @@ testOneFile libdir fileName = do
        = ["HsInt64Prim [" ++ unpackFS src ++ "] " ++ show c]
      doHsLit (HsWord64Prim (SourceText src) c)
        = ["HsWord64Prim [" ++ unpackFS src ++ "] " ++ show c]
-     doHsLit (HsInteger  (SourceText src) c _)
-       = ["HsInteger [" ++ unpackFS src ++ "] " ++ show c]
      doHsLit _ = []
 
      doOverLit :: OverLitVal -> [String]


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -4950,8 +4950,6 @@ hsLit2String lit =
     HsWord16Prim src v   -> toSourceTextWithSuffix src v ""
     HsWord32Prim src v   -> toSourceTextWithSuffix src v ""
     HsWord64Prim src v   -> toSourceTextWithSuffix src v ""
-    HsInteger    src v _ -> toSourceTextWithSuffix src v ""
-    HsRat        _ fl@(FL{fl_text = src }) _ -> toSourceTextWithSuffix src fl ""
     HsFloatPrim  _ fl@(FL{fl_text = src })   -> toSourceTextWithSuffix src fl "#"
     HsDoublePrim _ fl@(FL{fl_text = src })   -> toSourceTextWithSuffix src fl "##"
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:45:44 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:45:44 -0400
Subject: [Git][ghc/ghc][master] Docs: Linear types: link Strict Patterns
 subsection
Message-ID: <6709f0e8c56d0_23250788ac702626d@gitlab.mail>



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


Commits:
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -


1 changed file:

- docs/users_guide/exts/linear_types.rst


Changes:

=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -120,7 +120,7 @@ multiplicity if:
 - The binding is a pattern binding (including a simple variable)
   ``p=e`` (you can't write ``let %1 f x = u``, instead write ``let %1
   f = \x -> u``)
-- Either ``p`` is strict (see infra) or ``p`` is a variable. In
+- Either ``p`` is strict (see :ref:`strict-patterns-for-linear` below) or ``p`` is a variable. In
   particular neither ``x at y`` nor ``(x)`` are covered by “is a
   variable”
 
@@ -144,6 +144,8 @@ When ``-XMonoLocalBinds`` is off, the following also holds:
 - Non-variable pattern bindings which are inferred as polymorphic or
   qualified are inferred as having multiplicity ``Many``.
 
+.. _strict-patterns-for-linear:
+
 Strict patterns
 ~~~~~~~~~~~~~~~
 
@@ -189,6 +191,7 @@ Without ``-XStrict``::
    case u of ~(x, y) -> …
 
 With ``-XStrict``::
+
    -- good
    let %1 x = u in …
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4dd30cba51c7936dc53f0c1d331f88a590f93013

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:46:20 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:46:20 -0400
Subject: [Git][ghc/ghc][master] users guide: Address remaining TODOs in
 eventlog format docs
Message-ID: <6709f10c1e185_2325073e09a4306ec@gitlab.mail>



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


Commits:
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -


1 changed file:

- docs/users_guide/eventlog-formats.rst


Changes:

=====================================
docs/users_guide/eventlog-formats.rst
=====================================
@@ -79,14 +79,59 @@ There are two classes of event types:
 Runtime system diagnostics
 --------------------------
 
+The documentation below will refer to the following datatypes
+
  * ``ThreadId ~ Word32``
  * ``CapNo ~ Word16``
  * ``CapSetId ~ Word32``
 
+
 Capability sets
 ~~~~~~~~~~~~~~~
 
-TODO
+These events describe sets of capabilities which describe the
+structure of the program being run.
+
+Currently the following capability sets are defined:
+
+ * ``CAPSET_TYPE_CUSTOM == 1``: reserved for end-user applications
+ * ``CAPSET_TYPE_OSPROCESS == 2``: capabilities belonging to the same OS process
+ * ``CAPSET_TYPE_CLOCKDOMAIN == 3``: capabilities sharing a local clock
+
+.. event-type:: CAPSET_CREATE
+
+   :tag: 25
+   :length: fixed
+   :field CapSetId: Capability set
+   :field CapSetType: The type of the capability set
+
+   Create a capability set.
+
+.. event-type:: CAPSET_DELETE
+
+   :tag: 26
+   :length: fixed
+   :field CapSetId: Capability set
+
+   Delete a capability set.
+
+.. event-type:: CAPSET_ASSIGN_CAP
+
+   :tag: 27
+   :length: fixed
+   :field CapSetId: Capability set
+   :field CapNo: The Capability to be added.
+
+   Add a capability to a capability set.
+
+.. event-type:: CAPSET_REMOVE_CAP
+
+   :tag: 28
+   :length: fixed
+   :field CapSetId: Capability set
+   :field CapNo: The Capability to be added.
+
+   Remove a capability from a capability set.
 
 Environment information
 ~~~~~~~~~~~~~~~~~~~~~~~
@@ -118,7 +163,8 @@ environment which the program is being run in.
    :tag: 31
    :length: variable
    :field CapSetId: Capability set
-   :field [String]: The environment variable name/value pairs. (TODO: encoding?)
+   :field [String]: The environment variable name/value pairs.
+     This string is encoded using the platform's native string encoding.
 
    Describes the environment variables present in the program's environment.
 
@@ -359,7 +405,11 @@ in :ref:`nonmoving-gc-events`.
    :tag: 54
    :length: fixed
 
-   TODO
+   This event the moment in GC where all HECs are between
+   a stop-the-world GC and all other HECs should be between
+   their :event-type:`GC_START` and :event-type:`GC_END` events.
+   This allows one to match the GC pauses across HECs
+   to a particular global GC.
 
 .. event-type:: MEM_RETURN
 
@@ -458,14 +508,15 @@ Spark events
    :tag: 36
    :length: fixed
 
-   TODO
+   An attempt was made to spark a computation on a thunk that was already evaluated.
 
 .. event-type:: SPARK_OVERFLOW
 
    :tag: 37
    :length: fixed
 
-   TODO
+   An attempt was made to spark a computation while the spark pool
+   is at capacity.
 
 .. event-type:: SPARK_RUN
 
@@ -804,8 +855,12 @@ A variable-length packet encoding a profile sample.
 .. event-type:: BIO_PROF_SAMPLE_BEGIN
 
    :tag: 166
+   :length: fixed
+   :field Word64: sample era
+   :field Word64: time
+
+   Marks the beginning of a biographical profile sample.
 
-   TODO
 
 .. _nonmoving-gc-events:
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:46:51 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:46:51 -0400
Subject: [Git][ghc/ghc][master] Fix z-encoding of tuples (#25364)
Message-ID: <6709f12b8d8de_2325073901d4335ad@gitlab.mail>



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


Commits:
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -


4 changed files:

- libraries/ghc-boot/GHC/Utils/Encoding.hs
- + testsuite/tests/codeGen/should_run/T25364.hs
- + testsuite/tests/codeGen/should_run/T25364.stdout
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
libraries/ghc-boot/GHC/Utils/Encoding.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, MultiWayIf #-}
 {-# OPTIONS_GHC -O2 -fno-warn-name-shadowing #-}
 -- We always optimise this, otherwise performance of a non-optimised
@@ -88,14 +89,47 @@ type EncodedString = String     -- Encoded form
 
 
 zEncodeString :: UserString -> EncodedString
-zEncodeString cs = case maybe_tuple cs of
-                Just n  -> n            -- Tuples go to Z2T etc
-                Nothing -> go cs
-          where
-                go []     = []
-                go (c:cs) = encode_digit_ch c ++ go' cs
-                go' []     = []
-                go' (c:cs) = encode_ch c ++ go' cs
+zEncodeString = \case
+  []     -> []
+  (c:cs)
+    -- If a digit is at the start of a symbol then we need to encode it.
+    -- Otherwise package names like 9pH-0.1 give linker errors.
+    | c >= '0' && c <= '9' -> encode_as_unicode_char c ++ go cs
+    | otherwise            -> go (c:cs)
+  where
+    go = \case
+      [] -> []
+      -- encode boxed/unboxed tuples respectively as ZnT/ZnH (e.g. Z3T/Z3H for
+      -- 3-tuples). Note that the arity corresponds to the number of
+      -- commas+1. No comma means 0-arity, i.e. Z0T/Z0H.
+      --
+      -- The 1-arity unboxed tuple "(# #)" (notice the space between the '#'s)
+      -- isn't special-cased, i.e. it is encoded as "ZLzhz20UzhZR". There is no
+      -- 1-arity boxed tuple (we use Solo/MkSolo instead).
+      --
+      -- arity        boxed       z-name        unboxed       z-name
+      -- 0            ()          Z0T           (##)          Z0H
+      -- 1            N/A         N/A           (# #)         ZLzhz20UzhZR
+      -- 2            (,)         Z2T           (#,#)         Z2H
+      -- 3            (,,)        Z3T           (#,,#)        Z3H
+      -- ...
+      --
+      '(':'#':'#':')':cs -> "Z0H" ++ go cs
+      '(':')':cs         -> "Z0T" ++ go cs
+      '(':'#':cs
+        | (n, '#':')':cs') <- count_commas cs
+        -> 'Z' : shows (n+1) ('H': go cs')
+      '(':cs
+        | (n, ')':cs') <- count_commas cs
+        -> 'Z' : shows (n+1) ('T': go cs')
+      c:cs -> encode_ch c ++ go cs
+
+count_commas :: String -> (Int, String)
+count_commas = go 0
+  where
+    go !n = \case
+      ',':cs -> go (n+1) cs
+      cs     -> (n,cs)
 
 unencodedChar :: Char -> Bool   -- True for chars that don't need encoding
 unencodedChar 'Z' = False
@@ -104,12 +138,6 @@ unencodedChar c   =  c >= 'a' && c <= 'z'
                   || c >= 'A' && c <= 'Z'
                   || c >= '0' && c <= '9'
 
--- If a digit is at the start of a symbol then we need to encode it.
--- Otherwise package names like 9pH-0.1 give linker errors.
-encode_digit_ch :: Char -> EncodedString
-encode_digit_ch c | c >= '0' && c <= '9' = encode_as_unicode_char c
-encode_digit_ch c | otherwise            = encode_ch c
-
 encode_ch :: Char -> EncodedString
 encode_ch c | unencodedChar c = [c]     -- Common case first
 
@@ -215,34 +243,6 @@ decode_tuple d rest
     go n ('H':rest)     = '(' : '#' : replicate (n-1) ',' ++ "#)" ++ zDecodeString rest
     go n other = error ("decode_tuple: " ++ show n ++ ' ':other)
 
-{-
-Tuples are encoded as
-        Z3T or Z3H
-for 3-tuples or unboxed 3-tuples respectively.  No other encoding starts
-        Z
-
-* "(##)" is the tycon for an unboxed 0-tuple
-
-* "()" is the tycon for a boxed 0-tuple
--}
-
-maybe_tuple :: UserString -> Maybe EncodedString
-
-maybe_tuple "(##)" = Just("Z0H")
-maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
-                                 (n, '#' : ')' : _) -> Just ('Z' : shows (n+1) "H")
-                                 _                  -> Nothing
-maybe_tuple "()" = Just("Z0T")
-maybe_tuple ('(' : cs)       = case count_commas (0::Int) cs of
-                                 (n, ')' : _) -> Just ('Z' : shows (n+1) "T")
-                                 _            -> Nothing
-maybe_tuple _                = Nothing
-
-count_commas :: Int -> String -> (Int, String)
-count_commas n (',' : cs) = count_commas (n+1) cs
-count_commas n cs         = (n,cs)
-
-
 {-
 ************************************************************************
 *                                                                      *


=====================================
testsuite/tests/codeGen/should_run/T25364.hs
=====================================
@@ -0,0 +1,19 @@
+module Main where
+
+import GHC.Utils.Encoding (zEncodeString,zDecodeString)
+import Control.Monad
+
+main :: IO ()
+main = mapM_ test
+  [ "ghc-prim_GHC.Types_$tc'(#,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,#)_closure"
+  , "ghc-prim_GHC.Tuple_$tc'(,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,)2_closure"
+  , "ghc-prim_GHC.Tuple_(,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,)_info"
+  , "ghc-prim_GHC.Types_$tc'(# #)3_bytes"
+  ]
+
+test :: String -> IO ()
+test s = do
+  let e = zEncodeString s
+  putStrLn e
+  when (zDecodeString e /= s) $ do
+    error $ "Invalid z-encoding roundtrip for: " ++ s


=====================================
testsuite/tests/codeGen/should_run/T25364.stdout
=====================================
@@ -0,0 +1,4 @@
+ghczmprimzuGHCziTypeszuzdtczqZ32Hzuclosure
+ghczmprimzuGHCziTuplezuzdtczqZ35T2zuclosure
+ghczmprimzuGHCziTuplezuZ47Tzuinfo
+ghczmprimzuGHCziTypeszuzdtczqZLzhz20UzhZR3zubytes


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -252,3 +252,4 @@ test('T24700', normal, compile_and_run, ['-O'])
 test('T24893', normal, compile_and_run, ['-O'])
 
 test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
+test('T25364', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9291c125b6009f1531071d4591a9320f54c00b39

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 03:47:23 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 11 Oct 2024 23:47:23 -0400
Subject: [Git][ghc/ghc][master] Delete constants that can be deduced
Message-ID: <6709f14b984de_232507383b3c36423@gitlab.mail>



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


Commits:
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -


3 changed files:

- rts/include/stg/MachRegs/loongarch64.h
- rts/include/stg/MachRegs/ppc.h
- rts/include/stg/MachRegs/riscv64.h


Changes:

=====================================
rts/include/stg/MachRegs/loongarch64.h
=====================================
@@ -46,6 +46,3 @@
 #define REG_D2          fs5
 #define REG_D3          fs6
 #define REG_D4          fs7
-
-#define MAX_REAL_FLOAT_REG   4
-#define MAX_REAL_DOUBLE_REG  4


=====================================
rts/include/stg/MachRegs/ppc.h
=====================================
@@ -60,6 +60,3 @@
 #define REG_SpLim       r25
 #define REG_Hp          r26
 #define REG_Base        r27
-
-#define MAX_REAL_FLOAT_REG   6
-#define MAX_REAL_DOUBLE_REG  6
\ No newline at end of file


=====================================
rts/include/stg/MachRegs/riscv64.h
=====================================
@@ -56,6 +56,3 @@
 #define REG_D4          fs9
 #define REG_D5          fs10
 #define REG_D6          fs11
-
-#define MAX_REAL_FLOAT_REG   6
-#define MAX_REAL_DOUBLE_REG  6
\ No newline at end of file



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 04:57:56 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Sat, 12 Oct 2024 00:57:56 -0400
Subject: [Git][ghc/ghc][wip/T23479] 23 commits: Handle exceptions from IO
 manager backend
Message-ID: <670a01d44a905_23250713b9c0438355@gitlab.mail>



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


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8c212c95 by Serge S. Gulin at 2024-10-12T07:56:25+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


30 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d61ba90ab4f5a6725de185791ddb03e00d706dd...8c212c95b53b18d29bdfb574e1694150a544ae5f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d61ba90ab4f5a6725de185791ddb03e00d706dd...8c212c95b53b18d29bdfb574e1694150a544ae5f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 10:01:21 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 12 Oct 2024 06:01:21 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-pat] 23 commits: Handle
 exceptions from IO manager backend
Message-ID: <670a48f1448e2_1d1cd02b945490533@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-pat at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8a407894 by Alan Zimmerman at 2024-10-12T11:01:07+01:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/244b8c7c2d9acbd8a00e5d9d4d8f15b288f01568...8a4078948cd4702d6355a43224f345fb05a1ccbe

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/244b8c7c2d9acbd8a00e5d9d4d8f15b288f01568...8a4078948cd4702d6355a43224f345fb05a1ccbe
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 12:53:09 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 12 Oct 2024 08:53:09 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: testsuite:
 Normalise trailing digits from hole fits output
Message-ID: <670a71357ba55_108f04e738839ed@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
e3eec541 by Zubin Duggal at 2024-10-12T08:52:54-04:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
3e0a1bb3 by Zubin Duggal at 2024-10-12T08:52:54-04:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
11fa9aa9 by Zubin Duggal at 2024-10-12T08:52:54-04:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
8d658715 by Alan Zimmerman at 2024-10-12T08:52:55-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Extension.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12c7d4312ce3d8516b0e5b15e1bccf6be4d14207...8d65871587e59470a707246e8f6b9f76e797419f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12c7d4312ce3d8516b0e5b15e1bccf6be4d14207...8d65871587e59470a707246e8f6b9f76e797419f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 13:16:32 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 09:16:32 -0400
Subject: [Git][ghc/ghc][wip/T25266] Add type sig
Message-ID: <670a76b0e8f98_108f0433bf30677a@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
8ec42de6 by Simon Peyton Jones at 2024-10-12T14:16:05+01:00
Add type sig

Acked-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -


1 changed file:

- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1788,6 +1788,7 @@ type ApproxWC = ( Bag Ct    -- Free quantifiable constraints
                 , Bag Ct )  -- Free non-quantifiable constraints
                             -- due to shape, or enclosing equality
 
+approximateWC :: Bool -> WantedConstraints -> Bag Ct
 approximateWC include_non_quantifiable cts
   | include_non_quantifiable = quant `unionBags` no_quant
   | otherwise                = quant



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ec42de6d2eb057e34290a336d789812fcd82342

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 13:17:24 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 09:17:24 -0400
Subject: [Git][ghc/ghc][wip/T25281] Elmininate incomplete record selectors
Message-ID: <670a76e4e66c_108f043ba24071de@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
26f00641 by Simon Peyton Jones at 2024-10-12T14:12:28+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/26f00641517f246b31c08e1333b468f4ad993135

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 14:47:37 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Sat, 12 Oct 2024 10:47:37 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/riscv-vectors
Message-ID: <670a8c09c5bd3_20c77c31788864045@gitlab.mail>



Sven Tennie pushed new branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/riscv-vectors
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 15:55:40 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sat, 12 Oct 2024 11:55:40 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8-2] 2 commits: Bump process submodule
 to v1.6.25.0
Message-ID: <670a9bfc31f58_20c77c5a23a071226@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC


Commits:
2eb97a8c by Ben Gamari at 2024-10-12T11:39:11-04:00
Bump process submodule to v1.6.25.0

(cherry picked from commit 18f532f3ed021fff9529f50da2006b8a8d8b1df7)

- - - - -
20157588 by Ben Gamari at 2024-10-12T11:39:11-04:00
testsuite: Tests broken due to #22349 are fixed

- - - - -


6 changed files:

- libraries/process
- testsuite/tests/driver/T1372/all.T
- testsuite/tests/driver/recomp007/all.T
- testsuite/tests/patsyn/should_compile/T13350/all.T
- testsuite/tests/safeHaskell/check/pkg01/all.T
- testsuite/tests/typecheck/bug1465/all.T


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit 3466b14dacddc4628427c4d787482899dd0b17cd
+Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e


=====================================
testsuite/tests/driver/T1372/all.T
=====================================
@@ -1 +1 @@
-test('T1372', [extra_files(['p1/', 'p2/']), js_broken(22349)], makefile_test, ['T1372'])
+test('T1372', [extra_files(['p1/', 'p2/'])], makefile_test, ['T1372'])


=====================================
testsuite/tests/driver/recomp007/all.T
=====================================
@@ -5,5 +5,4 @@
 test('recomp007', [ extra_files(['Setup.hs', 'a1/', 'a2/', 'b/'])
                   , when(fast(), skip)
                   , normalise_slashes
-                  , js_broken(22349)
                   ], makefile_test, [])


=====================================
testsuite/tests/patsyn/should_compile/T13350/all.T
=====================================
@@ -1,6 +1,5 @@
 # Test that importing COMPLETE sets from external packages works
 
 test('T13350',
-     [extra_files(['T13350.hs', 'boolean']),
-     js_broken(22349)],
+     [extra_files(['T13350.hs', 'boolean'])],
      makefile_test, ['T13350'])


=====================================
testsuite/tests/safeHaskell/check/pkg01/all.T
=====================================
@@ -53,16 +53,14 @@ test('ImpSafe03',
 test('ImpSafe04', normalise_version('base'), compile_fail, ['-fpackage-trust -distrust base'])
 
 test('ImpSafeOnly01',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly01 ' + make_args)],
      compile,
      ['-fpackage-trust -package-db pdb.ImpSafeOnly01/local.db -trust base'])
 
 test('ImpSafeOnly02',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly02 ' + make_args)],
      compile,
@@ -70,8 +68,7 @@ test('ImpSafeOnly02',
 
 # Fail since we enable package trust (and still need safePkg01 trusted)
 test('ImpSafeOnly03',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly03 ' + make_args)],
      compile_fail,
@@ -79,23 +76,20 @@ test('ImpSafeOnly03',
 
 # Succeed since we don't enable package trust
 test('ImpSafeOnly04',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly04 ' + make_args)],
      compile, ['-package-db pdb.ImpSafeOnly04/local.db -trust base'])
 
 # fail due to missing trust of safePkg01, next test succeeds.
 test('ImpSafeOnly05',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly05 ' + make_args)],
      compile_fail,
      ['-fpackage-trust -package-db pdb.ImpSafeOnly05/local.db -trust base'])
 test('ImpSafeOnly06',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly06 ' + make_args)],
      compile,
@@ -103,24 +97,21 @@ test('ImpSafeOnly06',
 
 # fail due to missing trust
 test('ImpSafeOnly07',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly07 ' + make_args),
       normalise_version("bytestring", "base")],
      compile_fail,
      ['-fpackage-trust -package-db pdb.ImpSafeOnly07/local.db -trust safePkg01 -distrust bytestring'])
 test('ImpSafeOnly08',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly08 ' + make_args),
       normalise_version("bytestring", "base")],
      compile_fail,
      ['-fpackage-trust -package-db pdb.ImpSafeOnly08/local.db -trust safePkg01'])
 test('ImpSafeOnly09',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly09 ' + make_args),
       normalise_version("bytestring")],
@@ -129,8 +120,7 @@ test('ImpSafeOnly09',
 
 # finally succeed
 test('ImpSafeOnly10',
-     [js_broken(22349),
-      req_host_target_ghc,
+     [req_host_target_ghc,
       extra_files(['M_SafePkg.hs', 'M_SafePkg2.hs', 'M_SafePkg3.hs', 'M_SafePkg4.hs', 'M_SafePkg5.hs', 'M_SafePkg6.hs', 'M_SafePkg7.hs', 'M_SafePkg8.hs', 'Setup.hs', 'p.cabal']),
       pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly10 ' + make_args)],
      compile,


=====================================
testsuite/tests/typecheck/bug1465/all.T
=====================================
@@ -1 +1 @@
-test('bug1465', [extra_files(['B1.hs', 'B2.hs', 'C.hs', 'v1/', 'v2/']), js_broken(22349)], makefile_test, [])
+test('bug1465', [extra_files(['B1.hs', 'B2.hs', 'C.hs', 'v1/', 'v2/'])], makefile_test, [])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54a48fa8e9a8a226cb7d2661758b27be6a74594f...2015758896e9c163e6b6952142556dc1838c02ba

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54a48fa8e9a8a226cb7d2661758b27be6a74594f...2015758896e9c163e6b6952142556dc1838c02ba
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 16:55:42 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 12:55:42 -0400
Subject: [Git][ghc/ghc][wip/T25281] Elmininate incomplete record selectors
Message-ID: <670aaa0ea18be_2a5bb7270e2028fd@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
c35357a0 by Simon Peyton Jones at 2024-10-12T17:55:29+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 17:08:03 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 13:08:03 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibble assert in approximateWC
Message-ID: <670aacf3dc842_2a5bb7283a4837bc@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
e56d336e by Simon Peyton Jones at 2024-10-12T18:07:43+01:00
Wibble assert in approximateWC

- - - - -


1 changed file:

- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1823,8 +1823,11 @@ approximateWCX wc
     float_ct :: Bool -> TcTyCoVarSet -> Ct
              -> ApproxWC -> ApproxWC
     float_ct encl_eqs skol_tvs ct acc@(quant, no_quant)
-       | assertPpr (isWantedCt ct) (ppr ct) $  -- Only Wanteds expected here
-         insolubleCt ct                              = acc
+       | isGivenCt ct                                = acc
+           -- There can be (insoluble) Given constraints in wc_simple,
+           -- there so that we get error reports for unreachable code
+           -- See `given_insols` in GHC.Tc.Solver.Solve.solveImplication
+       | insolubleCt ct                              = acc
        | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
        | otherwise
        = case classifyPredType (ctPred ct) of



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 19:40:58 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 15:40:58 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibble assert in approximateWC
Message-ID: <670ad0cab18f6_2a5bb78b018c1024@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
72e4854d by Simon Peyton Jones at 2024-10-12T20:40:19+01:00
Wibble assert in approximateWC

- - - - -


2 changed files:

- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -14,6 +14,7 @@ module GHC.Tc.Solver(
        tcCheckGivens,
        tcCheckWanteds,
        tcNormalise,
+       approximateWC,    -- Exported for plugins to use
 
        captureTopConstraints,
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1823,8 +1823,11 @@ approximateWCX wc
     float_ct :: Bool -> TcTyCoVarSet -> Ct
              -> ApproxWC -> ApproxWC
     float_ct encl_eqs skol_tvs ct acc@(quant, no_quant)
-       | assertPpr (isWantedCt ct) (ppr ct) $  -- Only Wanteds expected here
-         insolubleCt ct                              = acc
+       | isGivenCt ct                                = acc
+           -- There can be (insoluble) Given constraints in wc_simple,
+           -- there so that we get error reports for unreachable code
+           -- See `given_insols` in GHC.Tc.Solver.Solve.solveImplication
+       | insolubleCt ct                              = acc
        | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
        | otherwise
        = case classifyPredType (ctPred ct) of



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/72e4854d10332e789ca13dbb0bbfee38ec705253

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 19:56:32 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sat, 12 Oct 2024 15:56:32 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 15 commits: Bump Cabal to 3.10.3.0
Message-ID: <670ad4702fab9_2a5bb7b3761c1332f@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
c4412f8d by Ben Gamari at 2024-10-10T16:11:51-04:00
Bump Cabal to 3.10.3.0

Bumps Cabal submodule.

- - - - -
f52257b8 by Ben Gamari at 2024-10-10T16:11:55-04:00
Bump directory to 1.3.8.5

Bumps directory submodule.

- - - - -
26f300dc by Matthew Pickering at 2024-10-10T16:11:55-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* An incorrect version guard on the stack decoding logic in ghc-heap
* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24077

(cherry picked from commit ef3d20f83499cf129b1cacac07906b8d6188fc17)

- - - - -
44e119c9 by Andreas Klebinger at 2024-10-10T16:11:55-04:00
NCG: Fix a bug in jump shortcutting.

When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.

We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.

Fixes #24507

(cherry picked from commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66)

- - - - -
f97d7fdf by Ben Gamari at 2024-10-10T16:11:55-04:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

(cherry picked from commit d04f384f35b76a6865dfb3b17098ef69563b3779)

- - - - -
3dc62f2e by Matthew Pickering at 2024-10-11T11:16:35-04:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

(cherry picked from commit 23f2a478b7dc6b61cab86cf7d0db7fec8a6d9a1f)

- - - - -
3a033e29 by Rodrigo Mesquita at 2024-10-11T11:16:35-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

(cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f)

- - - - -
20f80b77 by Cheng Shao at 2024-10-11T11:16:35-04:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
2166d290 by Ben Gamari at 2024-10-11T11:16:35-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
fc1dcd02 by Alexis King at 2024-10-11T11:16:35-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)
(cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad)

- - - - -
9d1ecdb9 by Ben Gamari at 2024-10-11T11:16:35-04:00
hadrian: Update bootstrap plans

- - - - -
1413e1dd by Rodrigo Mesquita at 2024-10-11T11:16:35-04:00
rts: Make addDLL a wrapper around loadNativeObj

Rewrite the implementation of `addDLL` as a wrapper around the more
principled `loadNativeObj` rts linker function. The latter should be
preferred while the former is preserved for backwards compatibility.

`loadNativeObj` was previously only available on ELF platforms, so this
commit further refactors the rts linker to transform loadNativeObj_ELF
into loadNativeObj_POSIX, which is available in ELF and MachO platforms.

The refactor made it possible to remove the `dl_mutex` mutex in favour
of always using `linker_mutex` (rather than a combination of both).

Lastly, we implement `loadNativeObj` for Windows too.

(cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb)

- - - - -
54a48fa8 by Rodrigo Mesquita at 2024-10-11T18:33:02-04:00
Use symbol cache in internal interpreter too

This commit makes the symbol cache that was used by the external
interpreter available for the internal interpreter too.

This follows from the analysis in #23415 that suggests the internal
interpreter could benefit from this cache too, and that there is no good
reason not to have the cache for it too. It also makes it a bit more
uniform to have the symbol cache range over both the internal and
external interpreter.

This commit also refactors the cache into a function which is used by
both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the
caching logic to `lookupSymbolInDLL` too.

- - - - -
2eb97a8c by Ben Gamari at 2024-10-12T11:39:11-04:00
Bump process submodule to v1.6.25.0

(cherry picked from commit 18f532f3ed021fff9529f50da2006b8a8d8b1df7)

- - - - -
20157588 by Ben Gamari at 2024-10-12T11:39:11-04:00
testsuite: Tests broken due to #22349 are fixed

- - - - -


30 changed files:

- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- hadrian/README.md
- hadrian/bindist/Makefile
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/src/CommandLine.hs
- hadrian/src/Settings/Builders/Haddock.hs
- hadrian/src/Settings/Packages.hs
- libraries/Cabal
- libraries/directory
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d90849d00871853c68dbb7b9b4e97349a999459...2015758896e9c163e6b6952142556dc1838c02ba

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d90849d00871853c68dbb7b9b4e97349a999459...2015758896e9c163e6b6952142556dc1838c02ba
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 19:56:47 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sat, 12 Oct 2024 15:56:47 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.8-2
Message-ID: <670ad47f5c2e1_2a5bb7a93634135d7@gitlab.mail>



Ben Gamari deleted branch wip/backports-9.8-2 at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 20:37:01 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sat, 12 Oct 2024 16:37:01 -0400
Subject: [Git][ghc/ghc][wip/cabal-3.14] 13 commits: testsuite: Normalise
 trailing digits from hole fits output
Message-ID: <670added282be_2a5bb7cd980820927@gitlab.mail>



Zubin pushed to branch wip/cabal-3.14 at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -


30 changed files:

- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Lit.hs
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/exts/linear_types.rst
- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- + libraries/base/tests/T25066.hs
- + libraries/base/tests/T25066.stderr
- libraries/base/tests/all.T
- libraries/ghc-boot/GHC/Utils/Encoding.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/process
- rts/include/stg/MachRegs/loongarch64.h
- rts/include/stg/MachRegs/ppc.h
- rts/include/stg/MachRegs/riscv64.h
- + testsuite/tests/codeGen/should_run/T25364.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14d492a264e43973970cf5c39989bf249b9f9509...f1a2c9fc140baa0aaeda00c02648aa75deb59723

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14d492a264e43973970cf5c39989bf249b9f9509...f1a2c9fc140baa0aaeda00c02648aa75deb59723
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 22:10:20 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sat, 12 Oct 2024 18:10:20 -0400
Subject: [Git][ghc/ghc][wip/T25281] Elmininate incomplete record selectors
Message-ID: <670af3cc9d8ee_2a5bb7115f00822778@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
00907f1c by Simon Peyton Jones at 2024-10-12T23:09:58+01:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/00907f1c00b1ffcc989aa98d752e26cdf6df4b93

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 12 22:11:21 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 12 Oct 2024 18:11:21 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-3
Message-ID: <670af409cd966_2a5bb7110d8e8234eb@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-3 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 01:05:43 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 12 Oct 2024 21:05:43 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Desugaring, 
 plus -Wincomplete-record-selectors
Message-ID: <670b1ce74dc82_3b677269e42066270@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
2c3eb7a3 by Sebastian Graf at 2024-10-12T21:05:34-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
73b3366b by Simon Peyton Jones at 2024-10-12T21:05:35-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
787491b7 by Alan Zimmerman at 2024-10-12T21:05:35-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d65871587e59470a707246e8f6b9f76e797419f...787491b7cbcee5f41972afeb5713cabf560b79f6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d65871587e59470a707246e8f6b9f76e797419f...787491b7cbcee5f41972afeb5713cabf560b79f6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 11:30:31 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 07:30:31 -0400
Subject: [Git][ghc/ghc][master] 3 commits: hadrian: Handle broken symlinks
 properly when creating source dist directories
Message-ID: <670baf57c85e1_2a10625328fc65b4@gitlab.mail>



Zubin pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -


4 changed files:

- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs


Changes:

=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -55,8 +55,9 @@ archiveSourceTree prepare fname = do
   runBuilderWithCmdOptions
       [Cwd $ sourceDistRoot -/- dirName]
       (Tar Create)
-      ["chJf", ".." -/- tarName,  baseName]
-      ["chJf", ".." -/- tarName] [baseName]
+      -- See https://github.com/haskell/cabal/issues/10442 for why we exclude this file.
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName,  baseName]
+      ["--exclude=cabal.project.symlink.broken","-chJf", ".." -/- tarName] [baseName]
 
 
 -- | This creates a symlink to the 'source' at 'target'
@@ -74,7 +75,9 @@ copyFileSourceDist source target = do
       error ("source-dist: tried to create non-relative symlink in source dist: " ++ show link_target)
     putProgressInfo =<< renderAction ("Create symlink (" ++ link_target ++ ")") source target
     isDirectory <- liftIO $ IO.doesDirectoryExist source
-    when (not isDirectory) $
+    -- We don't want to call `need` on broken symlinks
+    linkTargetExists <- liftIO $ IO.doesPathExist link_target
+    when (not isDirectory && linkTargetExists) $
       need [source]
     let createLink src tgt
           | isDirectory = liftIO $ IO.createDirectoryLink src tgt


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 56fb1dc9baa20b079eb0fa84ccafb284a6e91d41
+Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3


=====================================
testsuite/tests/driver/T4437.hs
=====================================
@@ -36,11 +36,7 @@ check title expected got
 
 -- See Note [Adding a language extension] in compiler/GHC/Driver/Session.hs.
 expectedGhcOnlyExtensions :: [String]
-expectedGhcOnlyExtensions =
-    [ "OrPatterns"
-    , "NamedDefaults"
-    , "MultilineStrings"
-    ]
+expectedGhcOnlyExtensions = [ ]
 
 expectedCabalOnlyExtensions :: [String]
 expectedCabalOnlyExtensions = ["Generics",


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -18,7 +18,7 @@ import Data.Maybe
 import Distribution.Text
 import Distribution.Types.PackageName
 import Distribution.InstalledPackageInfo
-import Distribution.Simple.Compiler (PackageDB(..))
+import Distribution.Simple.Compiler (PackageDB(..), PackageDBX( GlobalPackageDB ))
 import Distribution.Simple.GHC
 import Distribution.Simple.PackageIndex
 import Distribution.Simple.Program
@@ -257,7 +257,7 @@ baseDependencies ghcPath = do
 
     (comp, _, cfg) <- configure normal (Just ghcPath) Nothing
         defaultProgramDb
-    pkgIndex <- getInstalledPackages normal comp [GlobalPackageDB] cfg
+    pkgIndex <- getInstalledPackages normal comp Nothing [GlobalPackageDB] cfg
     let
       pkgs =
         [ "array"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c08b68bc7ab947843d20621eb483a0fc3c42703a...f1a2c9fc140baa0aaeda00c02648aa75deb59723

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c08b68bc7ab947843d20621eb483a0fc3c42703a...f1a2c9fc140baa0aaeda00c02648aa75deb59723
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 13:00:44 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Sun, 13 Oct 2024 09:00:44 -0400
Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: Trying to get
 simd000 test green
Message-ID: <670bc47c92208_2a10628fc96012356@gitlab.mail>



Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC


Commits:
a1398a7d by Sven Tennie at 2024-10-13T12:59:34+00:00
WIP: Trying to get simd000 test green

- - - - -


8 changed files:

- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
- compiler/GHC/StgToCmm/Prim.hs
- rts/CheckVectorSupport.c
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/simd/should_run/simd000.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -614,6 +614,21 @@ getRegister' config plat expr =
                 )
             )
         CmmFloat _f _w -> pprPanic "getRegister' (CmmLit:CmmFloat), unsupported float lit" (pdoc plat expr)
+
+        CmmVec lits |
+          VecFormat l sFmt <- cmmTypeFormat $ cmmLitType plat lit
+          , (f:fs) <- lits
+          , all (== f) fs ->  do
+              -- All vector elements are equal literals -> broadcast (splat)
+              let w = scalarWidth sFmt
+                  broadcast = if isFloatScalarFormat sFmt
+                              then MO_VF_Broadcast l w
+                              else MO_V_Broadcast l w
+                  fmt = cmmTypeFormat $ cmmLitType plat lit
+              (reg, format,code) <- getSomeReg $ CmmMachOp broadcast [CmmLit f]
+              return $ Any fmt (\dst -> code `snocOL` annExpr expr
+                                          (MOV (OpReg w dst) (OpReg (formatToWidth format) reg)))
+
         CmmVec _lits -> pprPanic "getRegister' (CmmLit:CmmVec): " (pdoc plat expr)
         CmmLabel lbl -> do
           let op = OpImm (ImmCLbl lbl)
@@ -795,6 +810,23 @@ getRegister' config plat expr =
         MO_AlignmentCheck align wordWidth -> do
           reg <- getRegister' config plat e
           addAlignmentCheck align wordWidth reg
+
+        --TODO: MO_V_Broadcast with immediate: If the right value is a literal,
+        -- it may use vmv.v.i (simpler)
+        MO_V_Broadcast _length w -> do
+          (reg_idx, format_idx, code_idx) <- getSomeReg e
+          let w_idx = formatToWidth format_idx
+          pure $ Any (intFormat w) $ \dst ->
+            code_idx `snocOL`
+            annExpr expr (VMV (OpReg w dst) (OpReg w_idx reg_idx))
+
+        MO_VF_Broadcast _length w -> do
+          (reg_idx, format_idx, code_idx) <- getSomeReg e
+          let w_idx = formatToWidth format_idx
+          pure $ Any (intFormat w) $ \dst ->
+            code_idx `snocOL`
+            annExpr expr (VMV (OpReg w dst) (OpReg w_idx reg_idx))
+
         x -> pprPanic ("getRegister' (monadic CmmMachOp): " ++ show x) (pdoc plat expr)
       where
         -- In the case of 16- or 8-bit values we need to sign-extend to 32-bits
@@ -1125,7 +1157,53 @@ getRegister' config plat expr =
         MO_Shl w -> intOp False w (\d x y -> unitOL $ annExpr expr (SLL d x y))
         MO_U_Shr w -> intOp False w (\d x y -> unitOL $ annExpr expr (SRL d x y))
         MO_S_Shr w -> intOp True w (\d x y -> unitOL $ annExpr expr (SRA d x y))
-        op -> pprPanic "getRegister' (unhandled dyadic CmmMachOp): " $ pprMachOp op <+> text "in" <+> pdoc plat expr
+
+        MO_VF_Extract length w -> do
+          (reg_v, format_v, code_v) <- getSomeReg x
+          (reg_idx, format_idx, code_idx) <- getSomeReg y
+          let tmpFormat = VecFormat length (floatScalarFormat w)
+              width_v = formatToWidth format_v
+          tmp <- getNewRegNat tmpFormat
+          pure $ Any (floatFormat w) $ \dst ->
+            code_v `appOL`
+            code_idx `snocOL`
+            -- Setup
+            -- vsetivli zero, 1, e32, m1, ta, ma
+            annExpr expr (VSETIVLI zeroReg 1 W32 M1 TA MA) `snocOL`
+            -- Move selected element to index 0
+            -- vslidedown.vi v8, v9, 2
+            VSLIDEDOWN (OpReg width_v tmp) (OpReg width_v reg_v) (OpReg (formatToWidth format_idx) reg_idx) `snocOL`
+            -- Move to float register
+            -- vmv.x.s a0, v8
+            VMV (OpReg w dst) (OpReg (formatToWidth tmpFormat) tmp)
+
+        _e -> panic $ "Missing operation " ++ show expr
+
+        -- Vectors
+
+        --TODO: MO_V_Broadcast with immediate: If the right value is a literal,
+        -- it may use vmv.v.i (simpler)
+--        MO_V_Broadcast _length w -> do
+--          (reg_v, format_v, code_v) <- getSomeReg x
+--          (reg_idx, format_idx, code_idx) <- getSomeReg y
+--          let w_v = formatToWidth format_v
+--              w_idx = formatToWidth format_idx
+--          pure $ Any (intFormat w) $ \dst ->
+--            code_v `appOL`
+--            code_idx `snocOL`
+--            annExpr expr (VMV (OpReg w_v reg_v) (OpReg w_idx reg_idx)) `snocOL`
+--            MOV (OpReg w dst) (OpReg w_v reg_v)
+--
+--        MO_VF_Broadcast _length w -> do
+--          (reg_v, format_v, code_v) <- getSomeReg x
+--          (reg_idx, format_idx, code_idx) <- getSomeReg y
+--          let w_v = formatToWidth format_v
+--              w_idx = formatToWidth format_idx
+--          pure $ Any (intFormat w) $ \dst ->
+--            code_v `appOL`
+--            code_idx `snocOL`
+--            annExpr expr (VMV (OpReg w_v reg_v) (OpReg w_idx reg_idx)) `snocOL`
+--            MOV (OpReg w dst) (OpReg w_v reg_v)
 
     -- Generic ternary case.
     CmmMachOp op [x, y, z] ->
@@ -1145,6 +1223,30 @@ getRegister' config plat expr =
                 FNMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMAdd d n m a)
           | otherwise
           -> sorry "The RISCV64 backend does not (yet) support vectors."
+        -- TODO: Implement length as immediate
+        MO_VF_Insert length w ->
+          do
+            (reg_v, format_v, code_v) <- getSomeReg x
+            (reg_f, format_f, code_f) <- getFloatReg y
+            (reg_idx, format_idx, code_idx) <- getSomeReg z
+            (reg_l, format_l, code_l) <- getSomeReg (CmmLit (CmmInt (toInteger length) W64))
+            tmp <- getNewRegNat (VecFormat length (floatScalarFormat w))
+            -- TODO: FmtInt8 should be FmtInt1 (which does not exist yet, so we're lying here)
+            reg_mask <- getNewRegNat (VecFormat length FmtInt8)
+            let targetFormat = VecFormat length (floatScalarFormat w)
+            pure $ Any targetFormat $ \dst ->
+              code_v `appOL`
+              code_f `appOL`
+              code_idx `appOL`
+              code_l `snocOL`
+              -- Build mask for index
+              -- 1. fill elements with index numbers
+              -- TODO: The Width is made up
+              annExpr expr (VID (OpReg W8 reg_mask) (OpReg (formatToWidth format_l) reg_l)) `snocOL`
+              -- Merge with mask -> set element at index
+              VMSEQ (OpReg W8 reg_mask) (OpReg W8 reg_mask) (OpReg (formatToWidth format_f) reg_f) `snocOL`
+              VMERGE (OpReg (formatToWidth format_v) dst) (OpReg (formatToWidth format_v) reg_v)  (OpReg (formatToWidth format_f) reg_f) (OpReg W8 reg_mask)
+
         _ ->
           pprPanic "getRegister' (unhandled ternary CmmMachOp): "
             $ pprMachOp op
@@ -2213,6 +2315,12 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks =
       FMIN {} -> 1
       FMAX {} -> 1
       FMA {} -> 1
+      VMV {} -> 1
+      VID {} -> 1
+      VMSEQ {} -> 1
+      VMERGE {} -> 1
+      VSLIDEDOWN {} -> 1
+      VSETIVLI {} -> 1
       -- estimate the subsituted size for jumps to lables
       -- jumps to registers have size 1
       BCOND {} -> long_bc_jump_size


=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -109,6 +109,12 @@ regUsageOfInstr platform instr = case instr of
   FABS dst src -> usage (regOp src, regOp dst)
   FMIN dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
   FMAX dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst)
+  VMV dst src1 -> usage (regOp src1, regOp dst)
+  VID dst src1 -> usage (regOp src1, regOp dst)
+  VMSEQ dst src op -> usage (regOp src ++ regOp op, regOp dst)
+  VMERGE dst op1 op2 opm -> usage (regOp op1 ++ regOp op2 ++ regOp opm, regOp dst)
+  VSLIDEDOWN dst op1 op2 -> usage (regOp op1 ++ regOp op2, regOp dst)
+  VSETIVLI dst _ _ _ _ _ -> usage ([], [dst])
   FMA _ dst src1 src2 src3 ->
     usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst)
   _ -> panic $ "regUsageOfInstr: " ++ instrCon instr
@@ -207,6 +213,12 @@ patchRegsOfInstr instr env = case instr of
   FABS o1 o2 -> FABS (patchOp o1) (patchOp o2)
   FMIN o1 o2 o3 -> FMIN (patchOp o1) (patchOp o2) (patchOp o3)
   FMAX o1 o2 o3 -> FMAX (patchOp o1) (patchOp o2) (patchOp o3)
+  VMV o1 o2 -> VMV (patchOp o1) (patchOp o2)
+  VID o1 o2 -> VID (patchOp o1) (patchOp o2)
+  VMSEQ o1 o2 o3 -> VMSEQ (patchOp o1) (patchOp o2) (patchOp o3)
+  VMERGE o1 o2 o3 o4 -> VMERGE (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4)
+  VSLIDEDOWN o1 o2 o3 -> VSLIDEDOWN (patchOp o1) (patchOp o2) (patchOp o3)
+  VSETIVLI o1 o2 o3 o4 o5 o6 -> VSETIVLI (env o1) o2 o3 o4 o5 o6
   FMA s o1 o2 o3 o4 ->
     FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4)
   _ -> panic $ "patchRegsOfInstr: " ++ instrCon instr
@@ -622,12 +634,34 @@ data Instr
     -- - fnmadd: d = - r1 * r2 - r3
     FMA FMASign Operand Operand Operand Operand
 
+  -- TODO: Care about the variants (.x.y) -> sum type
+  | VMV Operand Operand
+  | VID Operand Operand
+  | VMSEQ Operand Operand Operand
+  | VMERGE Operand Operand Operand Operand
+  | VSLIDEDOWN Operand Operand Operand
+  | VSETIVLI Reg Word Width VectorGrouping TailAgnosticFlag MaskAgnosticFlag
+
 -- | Operand of a FENCE instruction (@r@, @w@ or @rw@)
 data FenceType = FenceRead | FenceWrite | FenceReadWrite
 
 -- | Variant of a floating point conversion instruction
 data FcvtVariant = FloatToFloat | IntToFloat | FloatToInt
 
+data VectorGrouping = MF8 | MF4 | MF2 | M1 | M2 | M4 | M8
+
+data TailAgnosticFlag
+  = -- | Tail-agnostic
+    TA
+  | -- | Tail-undisturbed
+    TU
+
+data MaskAgnosticFlag
+  = -- | Mask-agnostic
+    MA
+  | -- | Mask-undisturbed
+    MU
+
 instrCon :: Instr -> String
 instrCon i =
   case i of
@@ -671,6 +705,12 @@ instrCon i =
     FABS {} -> "FABS"
     FMIN {} -> "FMIN"
     FMAX {} -> "FMAX"
+    VMV {} -> "VMV"
+    VID {} -> "VID"
+    VMSEQ {} -> "VMSEQ"
+    VMERGE {} -> "VMERGE"
+    VSLIDEDOWN {} -> "VSLIDEDOWN"
+    VSETIVLI {} -> "VSETIVLI"
     FMA variant _ _ _ _ ->
       case variant of
         FMAdd -> "FMADD"


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -677,6 +677,13 @@ pprInstr platform instr = case instr of
           FNMAdd -> text "\tfnmadd" <> dot <> floatPrecission d
           FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d
      in op4 fma d r1 r2 r3
+  VMV o1 o2 -> op2 (text "\tvmv.v.x") o1 o2
+  VID o1 o2 -> op2 (text "\tvid.v") o1 o2
+  VMSEQ o1 o2 o3 -> op3 (text "\tvmseq.v.x") o1 o2 o3
+  VMERGE o1 o2 o3 o4 -> op4 (text "\tvmerge.vxm") o1 o2 o3 o4
+  VSLIDEDOWN o1 o2 o3 -> op3 (text "\tvslidedown.vx") o1 o2 o3
+  VSETIVLI dst len width grouping ta ma -> line $
+    text "\tvsetivli" <+> pprReg W64 dst <> comma <+> (text.show) len <> comma <+> pprVWidth width <> comma <+> pprGrouping grouping <> comma <+> pprTA ta <> comma <+> pprMasking ma
   instr -> panic $ "RV64.pprInstr - Unknown instruction: " ++ instrCon instr
   where
     op2 op o1 o2 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2
@@ -690,6 +697,27 @@ pprInstr platform instr = case instr of
       | isDoubleOp o = text "d"
       | otherwise = pprPanic "Impossible floating point precission: " (pprOp platform o)
 
+    pprTA TA = text "ta"
+    pprTA TU = text "tu"
+
+    pprVWidth :: IsLine doc => Width -> doc
+    pprVWidth W8 = text "e8"
+    pprVWidth W16 = text "e16"
+    pprVWidth W32 = text "e32"
+    pprVWidth W64 = text "e64"
+    pprVWidth w = panic $ "Unsupported vector element size: " ++ show w
+
+    pprGrouping MF2 = text "mf2"
+    pprGrouping MF4 = text "mf4"
+    pprGrouping MF8 = text "mf8"
+    pprGrouping M1 = text "m1"
+    pprGrouping M2 = text "m2"
+    pprGrouping M4 = text "m4"
+    pprGrouping M8 = text "m8"
+
+    pprMasking MA = text "ma"
+    pprMasking MU = text "mu"
+
 floatOpPrecision :: Platform -> Operand -> Operand -> String
 floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isSingleOp l && isSingleOp r = "s" -- single precision
 floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isDoubleOp l && isDoubleOp r = "d" -- double precision


=====================================
compiler/GHC/CmmToAsm/RV64/Regs.hs
=====================================
@@ -72,6 +72,12 @@ fa7RegNo, d17RegNo :: RegNo
 d17RegNo = 49
 fa7RegNo = d17RegNo
 
+v0RegNo ::RegNo
+v0RegNo = 64
+
+v31RegNo :: RegNo
+v31RegNo = 95
+
 -- Note [The made-up RISCV64 TMP (IP) register]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 --
@@ -99,6 +105,9 @@ spMachReg = regSingle 2
 
 tmpReg = regSingle tmpRegNo
 
+v0Reg :: Reg
+v0Reg = regSingle v0RegNo
+
 -- | All machine register numbers.
 allMachRegNos :: [RegNo]
 allMachRegNos = intRegs ++ fpRegs


=====================================
compiler/GHC/StgToCmm/Prim.hs
=====================================
@@ -2570,6 +2570,7 @@ checkVecCompatibility cfg vcat l w =
   case stgToCmmVecInstrsErr cfg of
     Nothing | isX86 -> checkX86 vecWidth vcat l w
             | platformArch platform == ArchAArch64 -> checkAArch64 vecWidth
+            | platformArch platform == ArchRISCV64 -> checkRISCV64 vecWidth
             | otherwise -> sorry "SIMD vector instructions are not supported on this architecture."
     Just err -> sorry err  -- incompatible backend, do panic
   where
@@ -2603,6 +2604,10 @@ checkVecCompatibility cfg vcat l w =
     checkAArch64 W512 = sorry $ "512-bit wide SIMD vector instructions are not supported."
     checkAArch64 _ = return ()
 
+    -- TODO: This needs to be implemented according to VLEN
+    checkRISCV64 :: Width -> FCode ()
+    checkRISCV64 _ = return ()
+
     vecWidth = typeWidth (vecCmmType vcat l w)
 
 ------------------------------------------------------------------------------


=====================================
rts/CheckVectorSupport.c
=====================================
@@ -64,18 +64,20 @@ int checkVectorSupport(void) {
     supports_V32 = hwcap & PPC_FEATURE_HAS_VSX;
 */
 
-  #elif defined(__riscv)
-// csrr instruction nott allowed in user-mode qemu emulation of riscv
-// Backend doesn't yet support vector registers, so hard-coded to no vector support
-// for now.
-//
-//    unsigned long vlenb;
-//    asm volatile ("csrr %0, vlenb" : "=r" (vlenb));
-    // VLENB gives the length in bytes
-    supports_V16 = 0;
-    supports_V32 = 0;
-    supports_V64 = 0;
+  #elif defined(__riscv_v) && defined(__riscv_v_intrinsic)
+    // __riscv_v ensures we only get here when the compiler target (arch)
+    // supports vectors.
+
+    // TODO: Check the machine supports V extension 1.0. Or, implement the older
+    // comman versions.
+    #include 
 
+    unsigned vlenb = __riscv_vlenb();
+
+    // VLENB gives the length in bytes
+    supports_V16 = vlenb >= 16;
+    supports_V32 = vlenb >= 32;
+    supports_V64 = vlenb >= 64;
   #else
     // On other platforms, we conservatively return no vector support.
     supports_V16 = 0;


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -2,7 +2,7 @@ setTestOpts(
   # Currently, the only GHC backends to support SIMD are:
   #   - the X86 NCG
   #   - LLVM (any architecture)
-  [ unless(arch('x86_64'), only_ways(llvm_ways))
+  [ unless(arch('x86_64') or arch('riscv64'), only_ways(llvm_ways))
 
   # Architectures which support at least 128 bit wide SIMD vectors:
   #  - X86 with SSE4.1


=====================================
testsuite/tests/simd/should_run/simd000.hs
=====================================
@@ -9,11 +9,12 @@ main = do
     -- FloatX4#
     case unpackFloatX4# (broadcastFloatX4# 1.5#) of
         (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d)
-    case unpackFloatX4# (packFloatX4# (# 4.5#,7.8#, 2.3#, 6.5# #)) of
-        (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d)
-
-    -- DoubleX2#
-    case unpackDoubleX2# (broadcastDoubleX2# 6.5##) of
-        (# a, b #) -> print (D# a, D# b)
-    case unpackDoubleX2# (packDoubleX2# (# 8.9##,7.2## #)) of
-        (# a, b #) -> print (D# a, D# b)
+-- TODO: Uncomment again
+--    case unpackFloatX4# (packFloatX4# (# 4.5#,7.8#, 2.3#, 6.5# #)) of
+--        (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d)
+--
+--    -- DoubleX2#
+--    case unpackDoubleX2# (broadcastDoubleX2# 6.5##) of
+--        (# a, b #) -> print (D# a, D# b)
+--    case unpackDoubleX2# (packDoubleX2# (# 8.9##,7.2## #)) of
+--        (# a, b #) -> print (D# a, D# b)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 13:17:55 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 13 Oct 2024 09:17:55 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-3] Remove [AddEpAnn] from
 PatBuilderOpApp
Message-ID: <670bc883e8714_1b3b4bc45841949@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-3 at Glasgow Haskell Compiler / GHC


Commits:
b8244ff9 by Alan Zimmerman at 2024-10-13T11:22:29+01:00
Remove [AddEpAnn] from PatBuilderOpApp

- - - - -


3 changed files:

- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/Types.hs


Changes:

=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -72,6 +72,7 @@ module GHC.Parser.Lexer (
    disableHaddock,
    lexTokenStream,
    mkParensEpAnn,
+   mkParensEpToks,
    mkParensLocs,
    getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
    getEofPos,
@@ -3628,6 +3629,7 @@ warn_unknown_prag prags span buf len buf2 = do
 %************************************************************************
 -}
 
+-- TODO:AZ: we should have only mkParensEpToks. Delee mkParensEpAnn, mkParensLocs
 
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'AddEpAnn' values for the opening and closing bordering on the start
@@ -3644,6 +3646,22 @@ mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
     lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
     lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
 
+-- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
+-- 'AddEpAnn' values for the opening and closing bordering on the start
+-- and end of the span
+mkParensEpToks :: RealSrcSpan -> (EpToken "(", EpToken ")")
+mkParensEpToks ss = (EpTok (EpaSpan (RealSrcSpan lo Strict.Nothing)),
+                    EpTok (EpaSpan (RealSrcSpan lc Strict.Nothing)))
+  where
+    f = srcSpanFile ss
+    sl = srcSpanStartLine ss
+    sc = srcSpanStartCol ss
+    el = srcSpanEndLine ss
+    ec = srcSpanEndCol ss
+    lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
+    lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
+
+
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'EpaLocation' values for the opening and closing bordering on the start
 -- and end of the span


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -161,7 +161,7 @@ import GHC.Utils.Error
 import GHC.Utils.Misc
 import GHC.Utils.Monad (unlessM)
 import Data.Either
-import Data.List        ( findIndex, partition )
+import Data.List        ( findIndex )
 import Data.Foldable
 import qualified Data.Semigroup as Semi
 import GHC.Unit.Module.Warnings
@@ -738,8 +738,7 @@ mkPatSynMatchGroup (L loc patsyn_name) (L ld decls) =
         do { unless (name == patsyn_name) $
                wrongNameBindingErr (locA loc) decl
            -- conAnn should only be AnnOpenP, AnnCloseP, so the rest should be empty
-           ; let (ann_fun, rest) = mk_ann_funrhs []
-           ; unless (null rest) $ return $ panic "mkPatSynMatchGroup: unexpected anns"
+           ; let ann_fun = mk_ann_funrhs [] []
            ; match <- case details of
                PrefixCon _ pats -> return $ Match { m_ext = noExtField
                                                   , m_ctxt = ctxt, m_pats = L l pats
@@ -1332,12 +1331,12 @@ checkAPat loc e0 = do
      addError $ mkPlainErrorMsgEnvelope (getLocA op) PsErrAtInPatPos
      return (WildPat noExtField)
 
-   PatBuilderOpApp l (L cl c) r anns
+   PatBuilderOpApp l (L cl c) r (_os,_cs)
      | isRdrDataCon c || isRdrTc c -> do
          l <- checkLPat l
          r <- checkLPat r
          return $ ConPat
-           { pat_con_ext = mk_ann_conpat anns
+           { pat_con_ext = noAnn
            , pat_con = L cl c
            , pat_args = InfixCon l r
            }
@@ -1390,9 +1389,8 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
   = do  { mb_fun <- isFunLhs lhs
         ; case mb_fun of
-            Just (fun, is_infix, pats, ann) -> do
-              let (ann_fun, ann_rest) = mk_ann_funrhs ann
-              unless (null ann_rest) $ panic "checkValDef: unexpected anns"
+            Just (fun, is_infix, pats, ops, cps) -> do
+              let ann_fun = mk_ann_funrhs ops cps
               let l = listLocation pats
               checkFunBind loc ann_fun
                            fun is_infix (L l pats) grhss
@@ -1405,29 +1403,8 @@ checkValDef loc lhs (mult_ann, Nothing) ghrss
   = do lhs' <- checkPattern lhs
        checkPatBind loc lhs' ghrss mult_ann
 
-mk_ann_funrhs :: [AddEpAnn] -> (AnnFunRhs, [AddEpAnn])
-mk_ann_funrhs ann = (AnnFunRhs strict (map to_tok opens) (map to_tok closes), rest)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenP) ann
-    (closes, ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseP) ra0
-    (bangs, rest) = partition (\(AddEpAnn kw _) -> kw == AnnBang) ra1
-    strict = case bangs of
-               (AddEpAnn _ s:_) -> EpTok s
-               _ -> NoEpTok
-    to_tok (AddEpAnn _ s) = EpTok s
-
-mk_ann_conpat :: [AddEpAnn] -> (Maybe (EpToken "{"), Maybe (EpToken "}"))
-mk_ann_conpat ann = (open, close)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenC) ann
-    (closes, _ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseC) ra0
-    open = case opens of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    close = case closes of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    to_tok (AddEpAnn _ s) = EpTok s
+mk_ann_funrhs :: [EpToken "("] -> [EpToken ")"] -> AnnFunRhs
+mk_ann_funrhs ops cps = AnnFunRhs NoEpTok ops cps
 
 checkFunBind :: SrcSpan
              -> AnnFunRhs
@@ -1469,10 +1446,10 @@ checkPatBind :: SrcSpan
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat an (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m ans v)]))
+                [L (noAnnSrcSpan loc) (m an v)]))
   where
     m a v = Match { m_ext = noExtField
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1518,7 +1495,7 @@ checkDoAndIfThenElse err guardExpr semiThen thenExpr semiElse elseExpr
 
 isFunLhs :: LocatedA (PatBuilder GhcPs)
       -> P (Maybe (LocatedN RdrName, LexicalFixity,
-                   [LocatedA (ArgPatBuilder GhcPs)],[AddEpAnn]))
+                   [LocatedA (ArgPatBuilder GhcPs)],[EpToken "("],[EpToken ")"]))
 -- A variable binding is parsed as a FunBind.
 -- Just (fun, is_infix, arg_pats) if e is a function LHS
 isFunLhs e = go e [] [] []
@@ -1528,7 +1505,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderVar (L loc f))) es ops cps
        | not (isRdrDataCon f)        = do
            let (_l, loc') = transferCommentsOnlyA l loc
-           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+           return (Just (L loc' f, Prefix, es, (reverse ops), cps))
    go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
      let (_l, lf') = transferCommentsOnlyA l lf
      go (L lf' f) (mk e:es) ops cps
@@ -1538,21 +1515,21 @@ isFunLhs e = go e [] [] []
       -- of funlhs.
      where
        (_l, le') = transferCommentsOnlyA l le
-       (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
+       (o,c) = mkParensEpToks (realSrcSpan $ locA l)
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r (os,cs))) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
-           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (os ++ reverse ops), (cs ++ cps))) }
       | otherwise                     -- Infix data con; keep going
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
            ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
-          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
-            = Just (op', Infix, j : op_app : es', anns')
+          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', ops', cps')
+            = Just (op', Infix, j : op_app : es', ops', cps')
             where
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
-                                    (L loc' op) r (reverse ops ++ cps))
+                                    (L loc' op) r (reverse ops, cps))
           reassociate _other = Nothing
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
@@ -2052,7 +2029,7 @@ instance DisambECP (PatBuilder GhcPs) where
   superInfixOp m = m
   mkHsOpAppPV l p1 op p2 = do
     !cs <- getCommentsFor l
-    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 []
+    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 ([],[])
 
   mkHsLamPV l lam_variant _ _     = addFatalError $ mkPlainErrorMsgEnvelope l (PsErrLambdaInPat lam_variant)
 


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -57,7 +57,7 @@ data PatBuilder p
   | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p))
   | PatBuilderAppType (LocatedA (PatBuilder p)) (EpToken "@") (HsTyPat GhcPs)
   | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName)
-                    (LocatedA (PatBuilder p)) [AddEpAnn]
+                    (LocatedA (PatBuilder p)) ([EpToken "("], [EpToken ")"])
   | PatBuilderVar (LocatedN RdrName)
   | PatBuilderOverLit (HsOverLit GhcPs)
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 16:08:28 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Sun, 13 Oct 2024 12:08:28 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/layouter
Message-ID: <670bf07cdbd4_2d76cadc460865b9@gitlab.mail>



Sebastian Graf pushed new branch wip/layouter at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/layouter
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 18:42:48 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 14:42:48 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/9.12.1-alpha
Message-ID: <670c14a89d79d_25022d2f18e0475a9@gitlab.mail>



Zubin pushed new branch wip/9.12.1-alpha at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12.1-alpha
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 18:44:40 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 14:44:40 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha] Prepare 9.12.1 alpha
Message-ID: <670c151893472_25022d32cc7447786@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha at Glasgow Haskell Compiler / GHC


Commits:
c02441dd by Zubin Duggal at 2024-10-14T00:14:21+05:30
Prepare 9.12.1 alpha

- - - - -


7 changed files:

- configure.ac
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/T19847a.stderr
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -2,8 +2,8 @@
   [1 of 1] Compiling Int[sig]         ( p/Int.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
-    Instantiating p[Int=base-4.20.0.0:GHC.Exts]
-    [1 of 1] Including base-4.20.0.0
-    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+  [1 of 1] Including p[Int=base-4.21.0.0:GHC.Exts]
+    Instantiating p[Int=base-4.21.0.0:GHC.Exts]
+    [1 of 1] Including base-4.21.0.0
+    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-IGyTyFjGSwsAZUyiqkSOii/Int.o )
   [1 of 1] Instantiating p


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -2,9 +2,9 @@
   [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
-    Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.21.0.0:Prelude]
+    Instantiating p[ShouldFail=base-4.21.0.0:Prelude]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-6Y9KU411vP4Ie9fA4vOgAe/ShouldFail.o )
 : error: [GHC-15843]
     • Type constructor ‘Either’ has conflicting definitions in the module
       and its hsig file.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -2,9 +2,9 @@
   [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
-    Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.21.0.0:Data.STRef]
+    Instantiating p[ShouldFail=base-4.21.0.0:Data.STRef]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-BMUxBGoNweW7OjBbjZ6k3h/ShouldFail.o )
 : error: [GHC-12424]
     • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
       but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’


=====================================
testsuite/tests/gadt/T19847a.stderr
=====================================
@@ -9,4 +9,4 @@ DATA CONSTRUCTORS
          (x ~ y, c ~ [x], Ord x) =>
          x -> y -> T (x, y) b c
 Dependent modules: []
-Dependent packages: [base-4.20.0.0]
+Dependent packages: [base-4.21.0.0]


=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
 				  >D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.21.0.0-inplace" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.21.0.0-inplace" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.21.0.0-inplace" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.21.0.0-inplace" 'False) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.21.0.0-inplace" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.21.0.0-inplace" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.21.0.0-inplace" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.21.0.0-inplace" 'True) (C1

From gitlab at gitlab.haskell.org  Sun Oct 13 18:53:48 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 14:53:48 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/9.12.1-alpha1
Message-ID: <670c173cb0678_25022d32e51051199@gitlab.mail>



Zubin pushed new branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12.1-alpha1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 20:23:43 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 16:23:43 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] Prepare 9.12.1 alpha
Message-ID: <670c2c4fec0d3_2c8584ca6e8273e@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
0bfd5b70 by Zubin Duggal at 2024-10-14T01:53:31+05:30
Prepare 9.12.1 alpha

- - - - -


1 changed file:

- configure.ac


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bfd5b70ca0883115faa9bcd9a396e9436d2d88c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 21:09:38 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 13 Oct 2024 17:09:38 -0400
Subject: [Git][ghc/ghc][wip/T25281] Add
 -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi
Message-ID: <670c3712b9278_33041dbd3d086346@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
9acd713c by Simon Peyton Jones at 2024-10-13T22:09:02+01:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -


1 changed file:

- .gitlab-ci.yml


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -435,7 +435,12 @@ hadrian-multi:
     # workaround for docker permissions
     - sudo chown ghc:ghc -R .
   variables:
-    GHC_FLAGS: "-Werror -Wwarn=deprecations"
+    GHC_FLAGS: "-Werror=-Wno-error=incomplete-record-selectors -Wwarn=deprecations"
+       # -Wno-error=incomplete-record-selectors is present because -Wall now
+       # includes -Wincomplete-record-selectors, and hadrian-multi has many, many
+       # warnings about incomplete record selectors.  A better fix would be to
+       # remove the use of incomplete record selectors, since each of them represents
+       # a potential crash.
     CONFIGURE_ARGS: --enable-bootstrap-with-devel-snapshot
   tags:
     - x86_64-linux



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9acd713c8f452ac4196906db8edcc7452f71054e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 13 23:19:17 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Sun, 13 Oct 2024 19:19:17 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] Prepare 9.12.1 alpha
Message-ID: <670c5575dca5a_33041d5f7e18905c4@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
bcb1249a by Zubin Duggal at 2024-10-14T04:49:07+05:30
Prepare 9.12.1 alpha

- - - - -


12 changed files:

- configure.ac
- testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail2.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail7.stderr
- testsuite/tests/ghc-e/should_fail/T18441fail8.stderr
- testsuite/tests/ghc-e/should_fail/T23663.stderr
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
=====================================
@@ -1,5 +1,3 @@
-Preprocessing library 'impl' for bkpcabal08-0.1.0.0...
-Building library 'impl' for bkpcabal08-0.1.0.0...
 Preprocessing library 'p' for bkpcabal08-0.1.0.0...
 Building library 'p' instantiated with
   A = 
@@ -13,13 +11,15 @@ Building library 'q' instantiated with
 for bkpcabal08-0.1.0.0...
 [2 of 4] Compiling B[sig]           ( q/B.hsig, nothing )
 [3 of 4] Compiling M                ( q/M.hs, nothing ) [A changed]
-[4 of 4] Instantiating bkpcabal08-0.1.0.0-5O1mUtZZLBeDZEqqtwJcCj-p
+[4 of 4] Instantiating bkpcabal08-0.1.0.0-JFnXKb43Tjd5Ei9uYvX9E-p
+Preprocessing library 'impl' for bkpcabal08-0.1.0.0...
+Building library 'impl' for bkpcabal08-0.1.0.0...
 Preprocessing library 'q' for bkpcabal08-0.1.0.0...
 Building library 'q' instantiated with
-  A = bkpcabal08-0.1.0.0-DlVb5PcmUolGCHYbfTL7EP-impl:A
-  B = bkpcabal08-0.1.0.0-DlVb5PcmUolGCHYbfTL7EP-impl:B
+  A = bkpcabal08-0.1.0.0-6cBwUrCiUFQKCdAuMXtpGu-impl:A
+  B = bkpcabal08-0.1.0.0-6cBwUrCiUFQKCdAuMXtpGu-impl:B
 for bkpcabal08-0.1.0.0...
-[1 of 3] Compiling A[sig]           ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-LFiTKyjPqyn9yyuysCoVKg-q+5IA1jA4bEzCFcXtraqAC38/A.o ) [Prelude package changed]
-[2 of 3] Compiling B[sig]           ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-LFiTKyjPqyn9yyuysCoVKg-q+5IA1jA4bEzCFcXtraqAC38/B.o ) [Prelude package changed]
+[1 of 3] Compiling A[sig]           ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-LRjRtflqw8R2ohK3RZio0P-q+HNnLEPa1vvkBEsyN3mwRDH/A.o ) [Prelude package changed]
+[2 of 3] Compiling B[sig]           ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-LRjRtflqw8R2ohK3RZio0P-q+HNnLEPa1vvkBEsyN3mwRDH/B.o ) [Prelude package changed]
 Preprocessing library 'r' for bkpcabal08-0.1.0.0...
 Building library 'r' for bkpcabal08-0.1.0.0...


=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -5,5 +5,5 @@
   [1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
     Instantiating p[Int=base-4.20.0.0:GHC.Exts]
     [1 of 1] Including base-4.20.0.0
-    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-GnaxkVR4D4kD3V7gnFza02/Int.o )
   [1 of 1] Instantiating p


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -4,7 +4,7 @@
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
     Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-JNXn93fVwieGTH3NZgh1Ui/ShouldFail.o )
 : error: [GHC-15843]
     • Type constructor ‘Either’ has conflicting definitions in the module
       and its hsig file.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -4,7 +4,7 @@
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
     Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-6ZalQA0KzA80LTIgBZYTnY/ShouldFail.o )
 : error: [GHC-12424]
     • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
       but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’


=====================================
testsuite/tests/ghc-e/should_fail/T18441fail2.stderr
=====================================
@@ -3,36 +3,36 @@
 unrecognised flag: -Xabcde
 
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling unrecognised flag: -Xabcde
   |
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.11-inplace:GHC.Driver.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-inplace:System.Console.Haskeline.InputT
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.12-8fe2:GHC.Driver.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-0cb0:System.Console.Haskeline.InputT
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
 
 HasCallStack backtrace:
-  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.11-inplace:GHC.Utils.Error
+  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.12-8fe2:GHC.Utils.Error
 
 1


=====================================
testsuite/tests/ghc-e/should_fail/T18441fail7.stderr
=====================================
@@ -2,35 +2,35 @@
 
 IO error:  "Abcde" does not exist
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling IO error:  "Abcde" does not exist
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.11-inplace:GHC.Driver.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-inplace:System.Console.Haskeline.InputT
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.12-8fe2:GHC.Driver.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-0cb0:System.Console.Haskeline.InputT
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
 
 HasCallStack backtrace:
-  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.11-inplace:GHC.Utils.Error
+  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.12-8fe2:GHC.Utils.Error
 
 1


=====================================
testsuite/tests/ghc-e/should_fail/T18441fail8.stderr
=====================================
@@ -2,35 +2,35 @@
 
 syntax:  :script 
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling syntax:  :script 
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.11-inplace:GHC.Driver.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-inplace:System.Console.Haskeline.InputT
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.12-8fe2:GHC.Driver.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-0cb0:System.Console.Haskeline.InputT
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
 
 HasCallStack backtrace:
-  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.11-inplace:GHC.Utils.Error
+  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.12-8fe2:GHC.Utils.Error
 
 1


=====================================
testsuite/tests/ghc-e/should_fail/T23663.stderr
=====================================
@@ -5,7 +5,7 @@ did you mean one of:
   -XCUSKs
 
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
@@ -14,29 +14,29 @@ While handling unrecognised flag: -XCUSKS
   |   -XCUSKs
   |
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.11-inplace:GHC.Driver.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-inplace:System.Console.Haskeline.InputT
-  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.11.20240923-inplace:GHCi.UI.Monad
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.12-8fe2:GHC.Driver.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-0cb0:System.Console.Haskeline.InputT
+  |   throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.12.20241013-50da:GHCi.UI.Monad
 
 HasCallStack backtrace:
-  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.11-inplace:GHC.Utils.Error
+  throwIO, called at compiler/GHC/Utils/Error.hs:512:19 in ghc-9.12-8fe2:GHC.Utils.Error
 
 1


=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -3,46 +3,46 @@ ghc: Exception:
 default output name would overwrite the input file; must specify -o explicitly
 Usage: For basic information, try the `--help' option.
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling default output name would overwrite the input file; must specify -o explicitly
   | Usage: For basic information, try the `--help' option.
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   | Usage: For basic information, try the `--help' option.
   |   |
-  |   | Package: ghc-9.11-inplace
+  |   | Package: ghc-9.12-8fe2
   |   | Module: GHC.Utils.Panic
   |   | Type: GhcException
   |   |
   |   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   |   | Usage: For basic information, try the `--help' option.
   |   |   |
-  |   |   | Package: ghc-9.11-inplace
+  |   |   | Package: ghc-9.12-8fe2
   |   |   | Module: GHC.Utils.Panic
   |   |   | Type: GhcException
   |   |   |
   |   |   | HasCallStack backtrace:
-  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.11-inplace:GHC.Utils.Panic
+  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.12-8fe2:GHC.Utils.Panic
   |   |
   |   | HasCallStack backtrace:
-  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-inplace:System.Semaphore
+  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-c856:System.Semaphore
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   onException, called at compiler/GHC/Driver/Make.hs:2986:23 in ghc-9.11-inplace:GHC.Driver.Make
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   onException, called at compiler/GHC/Driver/Make.hs:2988:23 in ghc-9.12-8fe2:GHC.Driver.Make
 
 HasCallStack backtrace:
-  bracket, called at compiler/GHC/Driver/Make.hs:2953:3 in ghc-9.11-inplace:GHC.Driver.Make
+  bracket, called at compiler/GHC/Driver/Make.hs:2955:3 in ghc-9.12-8fe2:GHC.Driver.Make
 


=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
 				  >D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.20.0.0-a2e5" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.20.0.0-a2e5" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.20.0.0-a2e5" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base-4.20.0.0-a2e5" 'False) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.20.0.0-a2e5" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.20.0.0-a2e5" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.20.0.0-a2e5" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base-4.20.0.0-a2e5" 'True) (C1

From gitlab at gitlab.haskell.org  Mon Oct 14 00:34:02 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sun, 13 Oct 2024 20:34:02 -0400
Subject: [Git][ghc/ghc][wip/doc-unpack] users-guide: Document field coalescence
Message-ID: <670c66fae37_11009dca29c5526b@gitlab.mail>



Ben Gamari pushed to branch wip/doc-unpack at Glasgow Haskell Compiler / GHC


Commits:
3481b865 by Ben Gamari at 2024-10-13T20:33:55-04:00
users-guide: Document field coalescence

- - - - -


1 changed file:

- docs/users_guide/exts/pragmas.rst


Changes:

=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -959,6 +959,35 @@ effect of adding ``{-# UNPACK #-}`` to every strict constructor field which is
 of a single-constructor data type. Sum types won't be unpacked automatically
 by this though, only with the explicit pragma.
 
+Also note that GHC will coalesce adjacent sub-word size fields into
+words. For instance, consider (on a 64-bit platform) ::
+
+    data T = T {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
+
+As ``Word32`` is represented by the unlifted 32-bit ``Word32#`` type, the ``T``
+constructor will represent its two ``Word32`` fields using only a single
+64-bit word.
+
+Note that during coalescence padding will be inserted to ensure that each field
+remains naturally aligned. For instance, on a 64-bit platform ::
+
+    data T = T {-# UNPACK #-} !Word32
+               {-# UNPACK #-} !Word8
+               {-# UNPACK #-} !Word32
+
+the fields of ``T`` require two 64-bit words since padding is necessary after
+the ``Word8`` to ensure that the subsequent ``Word64`` is naturally aligned:
+
+.. code-block:: none
+
+     ┌───────────────────────────────────┐
+     │ Header                            │
+     ├─────────────────┬────────┬────────┤
+     │ Word32          │ Word8  │ padding│
+     ├─────────────────┼────────┴────────┤
+     │ Word32          │ padding         │
+     └─────────────────┴─────────────────┘
+
 .. [1]
    In fact, :pragma:`UNPACK` has no effect without :ghc-flag:`-O`, for technical
    reasons (see :ghc-ticket:`5252`).



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3481b86501026d1e5f88213675ff8e5d47ad4874

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 00:43:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 13 Oct 2024 20:43:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: hadrian:
 Handle broken symlinks properly when creating source dist directories
Message-ID: <670c6916d059d_11009d1d7acc60591@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
d2e25a43 by Ben Gamari at 2024-10-13T20:42:57-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
651cf587 by Alan Zimmerman at 2024-10-13T20:42:58-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/ThToHs.hs
- docs/users_guide/ghci.rst
- hadrian/src/Rules/SourceDist.hs
- libraries/Cabal
- testsuite/tests/driver/T4437.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/787491b7cbcee5f41972afeb5713cabf560b79f6...651cf5870662d98f1014d408ff4558ef5eec6408

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/787491b7cbcee5f41972afeb5713cabf560b79f6...651cf5870662d98f1014d408ff4558ef5eec6408
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 02:53:26 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sun, 13 Oct 2024 22:53:26 -0400
Subject: [Git][ghc/ghc][ghc-9.8] docs: Release notes for 9.8.3
Message-ID: <670c87a6667c7_16b9bb42f4781597@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
846acd22 by Ben Gamari at 2024-10-13T22:13:57-04:00
docs: Release notes for 9.8.3

- - - - -


1 changed file:

- docs/users_guide/9.8.3-notes.rst


Changes:

=====================================
docs/users_guide/9.8.3-notes.rst
=====================================
@@ -16,13 +16,98 @@ Compiler
 
 - Fixed a bug that caused GHC to panic when using the AArch64 ncg and :ghc-flag:`-fregs-graph`
   on certain programs (:ghc-ticket:`24941`).
+- Fix invalid optimisation of Cmm programs on 32-bit platforms when targetting 64-bit targets (:ghc-ticket:`24893` and :ghc-ticket:`24700`)
+- Improve float-out surrounding applications of ``runRW#`` (:ghc-ticket:`25055`)
+- Fix :ghc-flag:`-fregs-graph` crash when targetting AArch64 (:ghc-ticket:`24941`)
+- Fix native code generator miscompilation of signed sub-word arguments of FFI calls on x86 (:ghc-ticket:`25018`)
+- Fix code generation of foreign exports with more than 6 arguments when some are subword-width (:ghc-ticket:`24314`)
+- Fix recompilation avoidance behavior of :ghc-flag:`-fwrite-if-simplified-core` (:ghc-ticket:`24656`)
+- Fix linking error when :extension:`TypeData` and :extension:`StrictData` are in use (:ghc-ticket:`24620`)
+- Fix miscompilation by x86 native code generator due to shortcutting (:ghc-ticket:`24507`)
+- Fix uses of ``(~)`` and ``(@)`` being rejected in :extension:`TemplateHaskell` splices (:ghc-ticket:`23748`)
 
 Runtime system
 --------------
 
-- Internal fragmentation incurred by the non-moving GC's allocator has been reduced for small objects.
+- Significantly improve performance of code loading via dynamic linking (:ghc-ticket:`23415`)
+- Internal fragmentation incurred by the non-moving garbage collector's allocator has been reduced for small objects.
   In one real-world application, this has reduced resident set size by about 20% and modestly improved run-time.
   See :ghc-ticket:`23340`.
   :rts-flag:`--nonmoving-dense-allocator-count=⟨count⟩` has been added to fine-tune this behaviour.
+- Fix runtime crash of the :rts-flag:`nonmoving garbage collector <--nonmoving-gc>` due to weak pointers with static key (:ghc-ticket:`24492`)
+- Allow heap profiling when the :rts-flag:`--nonmoving-gc` is in use
 
+GHCi
+----
+
+- Fix a crash involving use of field selectors in GHCi (:ghc-ticket:`25109`)
+
+JavaScript backend
+------------------
+
+- Fix compiler crash involving rubbish literals (:ghc-ticket:`25177`, :ghc-ticket:`24664`)
+
+``base``
+--------
+
+- Fix spurious closing of file descriptors after ``fork`` on platforms using the KQueue event manager backend (:ghc-ticket:`24672`)
+
+Haddock
+-------
+- Fix source links to hyperlinked sources output (:ghc-ticket:`24086`)
+
+Other Core Libraries
+--------------------
+
+- Bump ``stm`` to 2.5.3.1
+- Bump ``deepseq`` to 1.5.1.0
+- Bump ``array`` to 0.5.8.0
+- Bump ``Cabal`` to 3.10.3.0
+- Bump ``directory`` to 1.3.8.5
+- Bump ``process`` to 1.6.25.0
+
+Included libraries
+------------------
+
+The package database provided with this distribution also contains a number of
+packages other than GHC itself. See the changelogs provided with these packages
+for further change information.
+
+.. ghc-package-list::
+
+    libraries/array/array.cabal:             Dependency of ``ghc`` library
+    libraries/base/base.cabal:               Core library
+    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
+    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
+    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
+    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
+    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
+    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
+    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
+    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
+    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
+    compiler/ghc.cabal:                      The compiler itself
+    libraries/ghci/ghci.cabal:               The REPL interface
+    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
+    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
+    libraries/ghc-compact/ghc-compact.cabal: Core library
+    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
+    libraries/ghc-prim/ghc-prim.cabal:       Core library
+    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
+    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
+    libraries/integer-gmp/integer-gmp.cabal: Core library
+    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
+    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
+    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
+    libraries/process/process.cabal:         Dependency of ``ghc`` library
+    libraries/semaphore-compat/semaphore-compat.cabal: Dependency of ``ghc`` library
+    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
+    libraries/template-haskell/template-haskell.cabal: Core library
+    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
+    libraries/text/text.cabal:               Dependency of ``Cabal`` library
+    libraries/time/time.cabal:               Dependency of ``ghc`` library
+    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
+    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
+    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
+    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/846acd2206c0eaa3056a0bee17a6951fc3033331

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 07:32:39 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 14 Oct 2024 03:32:39 -0400
Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 62 commits: base: Add
 `HasCallStack` constraint to `ioError`
Message-ID: <670cc91741122_16d768262eec5052c@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC


Commits:
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
d3df37d4 by Matthew Pickering at 2024-10-14T08:32:04+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
50a1a926 by Rodrigo Mesquita at 2024-10-14T08:32:07+01:00
Add test for #25300

- - - - -
5b762e2d by Rodrigo Mesquita at 2024-10-14T08:32:07+01:00
exceptions: Improve the message layout as per #285

This commit fixes the layout of the additional information included when
displaying an exception, namely the type of the exception.

It also fixes the default handler's heading message to work well
together with the improved display message of SomeException.

CLC proposal#285

- - - - -
cedb17b6 by Rodrigo Mesquita at 2024-10-14T08:32:07+01:00
Display type and callstack of exception on handler

This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.

At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.

However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).

This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.

The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.

Discussion of the ammendment is part of CLC#285.

- - - - -
7f882ddf by Rodrigo Mesquita at 2024-10-14T08:32:07+01:00
Remove redundant CallStack from exceptions

Before the exception backtraces proposal was implemented, ErrorCall
accumulated its own callstack via HasCallStack constraints, but
ExceptionContext is now accumulated automatically.

The original ErrorCall mechanism is now redundant and we get a duplicate
CallStack

Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall

CLC proposal#285

Fixes #25283

- - - - -
39d55509 by Rodrigo Mesquita at 2024-10-14T08:32:08+01:00
Freeze call stack in error throwing functions

CLC proposal#285

- - - - -
397d39df by Rodrigo Mesquita at 2024-10-14T08:32:08+01:00
De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too,
which was missing.

- - - - -
7dee9c02 by Rodrigo Mesquita at 2024-10-14T08:32:08+01:00
Re-export NoBacktrace from Control.Exception

This was originally proposed and accepted in section
    "2.7   Capturing Backtraces on Exceptions"
of the CLC proposal for exception backtraces.

However, the implementation missed this re-export, which this commit now
fixes.

- - - - -
b66cb06b by Rodrigo Mesquita at 2024-10-14T08:32:08+01:00
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8670c3f3772121d5c430184204d155f241c808a2...b66cb06bc842e45ba39183cd7bd34d2186b92dbe

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8670c3f3772121d5c430184204d155f241c808a2...b66cb06bc842e45ba39183cd7bd34d2186b92dbe
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 08:51:09 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 04:51:09 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 5 commits: haddock: oneshot tests
 can drop files if they share modtimes. Stop this by
Message-ID: <670cdb7d875a1_16d768574b8066147@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
e78c7ef9 by Zubin Duggal at 2024-10-14T14:20:59+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

- - - - -
4feb361f by Zubin Duggal at 2024-10-14T14:20:59+05:30
testsuite: normalise some versions in callstacks

- - - - -
b872c09a by Zubin Duggal at 2024-10-14T14:20:59+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
9e6fa9e0 by Zubin Duggal at 2024-10-14T14:20:59+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
380d89bb by Zubin Duggal at 2024-10-14T14:20:59+05:30
Prepare 9.12.1 alpha

- - - - -


13 changed files:

- configure.ac
- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/ghc-e/should_fail/all.T
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
- utils/haddock/html-test/Main.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
testsuite/tests/backpack/should_compile/all.T
=====================================
@@ -8,7 +8,7 @@ test('bkp11', normal, backpack_compile, [''])
 test('bkp12', normal, backpack_compile, [''])
 test('bkp14', normal, backpack_compile, [''])
 test('bkp15', normal, backpack_compile, [''])
-test('bkp16', normalise_version('base', 'ghc-internal'), backpack_compile, [''])
+test('bkp16', [normalise_version('base', 'ghc-internal')], backpack_compile, ['-fhide-source-paths'])
 test('bkp17', normal, backpack_compile, [''])
 test('bkp18', normal, backpack_compile, [''])
 test('bkp19', normal, backpack_compile, [''])
@@ -60,4 +60,4 @@ test('T13214', normal, backpack_compile, [''])
 test('T13250', normal, backpack_compile, [''])
 test('T13323', normal, backpack_compile, [''])
 test('T20396', normal, backpack_compile, [''])
-test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])
\ No newline at end of file
+test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])


=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -1,9 +1,9 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling Int[sig]         ( p/Int.hsig, nothing )
+  [1 of 1] Compiling Int[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
     Instantiating p[Int=base-4.20.0.0:GHC.Exts]
     [1 of 1] Including base-4.20.0.0
-    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+    [1 of 1] Compiling Int[sig]
   [1 of 1] Instantiating p


=====================================
testsuite/tests/backpack/should_fail/all.T
=====================================
@@ -12,9 +12,9 @@ test('bkpfail13', normal, backpack_compile_fail, [''])
 test('bkpfail14', normal, backpack_compile_fail, [''])
 test('bkpfail15', normal, backpack_compile_fail, [''])
 test('bkpfail16', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
-test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail18', normal, backpack_compile_fail, [''])
-test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail20', normal, backpack_compile_fail, [''])
 test('bkpfail21', normal, backpack_compile_fail, [''])
 test('bkpfail22', normal, backpack_compile_fail, [''])


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
     Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-15843]
     • Type constructor ‘Either’ has conflicting definitions in the module
       and its hsig file.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
     Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-12424]
     • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
       but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’


=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -3,46 +3,46 @@ ghc: Exception:
 default output name would overwrite the input file; must specify -o explicitly
 Usage: For basic information, try the `--help' option.
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling default output name would overwrite the input file; must specify -o explicitly
   | Usage: For basic information, try the `--help' option.
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   | Usage: For basic information, try the `--help' option.
   |   |
-  |   | Package: ghc-9.11-inplace
+  |   | Package: ghc-9.12-8fe2
   |   | Module: GHC.Utils.Panic
   |   | Type: GhcException
   |   |
   |   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   |   | Usage: For basic information, try the `--help' option.
   |   |   |
-  |   |   | Package: ghc-9.11-inplace
+  |   |   | Package: ghc-9.12-8fe2
   |   |   | Module: GHC.Utils.Panic
   |   |   | Type: GhcException
   |   |   |
   |   |   | HasCallStack backtrace:
-  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.11-inplace:GHC.Utils.Panic
+  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.12-8fe2:GHC.Utils.Panic
   |   |
   |   | HasCallStack backtrace:
-  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-inplace:System.Semaphore
+  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-c856:System.Semaphore
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   onException, called at compiler/GHC/Driver/Make.hs:2986:23 in ghc-9.11-inplace:GHC.Driver.Make
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   onException, called at compiler/GHC/Driver/Make.hs:2988:23 in ghc-9.12-8fe2:GHC.Driver.Make
 
 HasCallStack backtrace:
-  bracket, called at compiler/GHC/Driver/Make.hs:2953:3 in ghc-9.11-inplace:GHC.Driver.Make
+  bracket, called at compiler/GHC/Driver/Make.hs:2955:3 in ghc-9.12-8fe2:GHC.Driver.Make
 


=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -15,6 +15,7 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
 test('T9930fail',
      [extra_files(['T9930']),
       when(opsys('mingw32'), skip),
+      normalise_version('ghc'),
       # broken for JS until cross-compilers become stage2 compilers (#19174)
       # or until we bootstrap with a 9.10 compiler
       js_broken(19174)],
@@ -24,7 +25,7 @@ test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])
 
 test('T18441fail1', req_interp, makefile_test, ['T18441fail1'])
 
-test('T18441fail2', req_interp, makefile_test, ['T18441fail2'])
+test('T18441fail2', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail2'])
 
 test('T18441fail3', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":! abcde"'])
 
@@ -34,9 +35,9 @@ test('T18441fail5', req_interp, makefile_test, ['T18441fail5'])
 
 test('T18441fail6', req_interp, makefile_test, ['T18441fail6'])
 
-test('T18441fail7', req_interp, makefile_test, ['T18441fail7'])
+test('T18441fail7', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail7'])
 
-test('T18441fail8', req_interp, makefile_test, ['T18441fail8'])
+test('T18441fail8', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail8'])
 
 test('T18441fail9', req_interp, makefile_test, ['T18441fail9'])
 
@@ -60,6 +61,6 @@ test('T18441fail18', req_interp, makefile_test, ['T18441fail18'])
 
 test('T18441fail19', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":cd abcd"'])
 
-test('T23663', req_interp, makefile_test, ['T23663'])
+test('T23663', [req_interp, normalise_version('ghc')], makefile_test, ['T23663'])
 
 test('T24172', normal, compile_fail, ['-fdiagnostics-color=always'])


=====================================
utils/haddock/haddock-test/src/Test/Haddock.hs
=====================================
@@ -156,7 +156,7 @@ runHaddock cfg@(Config{..}) = do
 
       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
+      filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (\mt -> ((mt,file),file)) <$> getModificationTime (hiDir  file)) files
       let srcRef = if "--hyperlinked-source" `elem` cfgHaddockArgs then ",src,visible," else ""
           loop [] = pure True
           loop (file : files) = do


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
=====================================
@@ -8,6 +8,7 @@ module Test.Haddock.Xhtml
   , stripIdsWhen
   , stripFooter
   , fixAttrValueWhen
+  , stripVersions
   ) where
 
 {-
@@ -22,7 +23,7 @@ and since the `xhtml` library already handles the pretty-printing aspect,
 this would appear to be a reasonable compromise for now.
 -}
 
-import Data.Char (isSpace)
+import Data.Char (isSpace, isAlphaNum)
 import Data.List (isPrefixOf, stripPrefix)
 
 -- | Simple wrapper around the pretty-printed HTML source
@@ -142,3 +143,18 @@ stripFooter (Xml body) = Xml (findDiv body)
           Just valRest''
       | otherwise =
           dropToDiv cs
+
+-- | Strip strings of the form --
+-- to just 
+stripVersions :: [String] -> Xml -> Xml
+stripVersions xs (Xml body) = Xml $ foldr id body $ map go xs
+  where
+    go pkg "" = ""
+    go pkg body@(x:body') = case stripPrefix pkg body of
+      Just ('-':rest)
+        | (version,'-':rest') <- span (/= '-') rest
+        , all (`elem` ('.':['0'..'9'])) version
+        , let (hash, rest'') = span isAlphaNum rest'
+        -> pkg ++ go pkg rest''
+      _ -> x:go pkg body'
+


=====================================
utils/haddock/html-test/Main.hs
=====================================
@@ -42,7 +42,7 @@ main = do
 
 stripIfRequired :: String -> Xml -> Xml
 stripIfRequired mdl =
-    stripLinks' . stripFooter
+    stripLinks' . stripFooter . stripVersions ["base"]
   where
     stripLinks'
         | mdl `elem` preserveLinksModules = id


=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
 				  >D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1

From gitlab at gitlab.haskell.org  Mon Oct 14 08:54:21 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 04:54:21 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/9.12-testsuite-fixes
Message-ID: <670cdc3d1c4e2_2e9350bc55c95173@gitlab.mail>



Zubin pushed new branch wip/9.12-testsuite-fixes at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12-testsuite-fixes
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 09:00:10 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 05:00:10 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 2 commits: Bump base bound to 4.21
 for GHC 9.12
Message-ID: <670cdd9a39d1b_2e9350bc59810048d@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
8122cf39 by Zubin Duggal at 2024-10-14T14:29:06+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
49a1ce19 by Zubin Duggal at 2024-10-14T14:29:06+05:30
Prepare 9.12.1 alpha

- - - - -


29 changed files:

- compiler/ghc.cabal.in
- configure.ac
- libraries/Cabal
- libraries/array
- libraries/base/base.cabal.in
- libraries/deepseq
- libraries/directory
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/unix
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock.cabal
- utils/hsc2hs


Changes:

=====================================
compiler/ghc.cabal.in
=====================================
@@ -114,7 +114,7 @@ Library
         extra-libraries: zstd
       CPP-Options: -DHAVE_LIBZSTD
 
-    Build-Depends: base       >= 4.11 && < 4.21,
+    Build-Depends: base       >= 4.11 && < 4.22,
                    deepseq    >= 1.4 && < 1.6,
                    directory  >= 1   && < 1.4,
                    process    >= 1   && < 1.7,


=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 2a48e40fdf320caa4240ce8eb28841e31f4f3de3
+Subproject commit 6eb0369e3f736ef62192a5760a9fce3b1a989543


=====================================
libraries/array
=====================================
@@ -1 +1 @@
-Subproject commit c9cb2c1e8762aa83b6e77af82c87a55e03e990e4
+Subproject commit a8ec1173bce79b12ad5a7d2581b8a0862432f311


=====================================
libraries/base/base.cabal.in
=====================================
@@ -4,7 +4,7 @@ cabal-version:  3.0
 -- Make sure you are editing ghc-experimental.cabal.in, not ghc-experimental.cabal
 
 name:           base
-version:        4.20.0.0
+version:        4.21.0.0
 -- NOTE: Don't forget to update ./changelog.md
 
 license:        BSD-3-Clause


=====================================
libraries/deepseq
=====================================
@@ -1 +1 @@
-Subproject commit 7ce6e2d3760b23336fd5f9a36f50df6571606947
+Subproject commit af115cc226cc87fba89d0f6e2e9212e755c24983


=====================================
libraries/directory
=====================================
@@ -1 +1 @@
-Subproject commit 6045b93c4ef7a713c8f3d6837ca69f8e96b12bf1
+Subproject commit 0c88ffff883d33df96b50879d1983a67e9dfeb81


=====================================
libraries/filepath
=====================================
@@ -1 +1 @@
-Subproject commit 87a09e296ea6fc137a0b32edda1bd0f54332642e
+Subproject commit bf2374ddfd7b2e5ba4e69d5ffbf4ebf6286c9c22


=====================================
libraries/ghc-boot-th/ghc-boot-th.cabal.in
=====================================
@@ -49,7 +49,7 @@ Library
             GHC.Lexeme
 
     build-depends:
-        base       >= 4.7 && < 4.21,
+        base       >= 4.7 && < 4.22,
         ghc-prim,
         pretty      == 1.1.*
 


=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -75,7 +75,7 @@ Library
             GHC.Version
             GHC.Platform.Host
 
-    build-depends: base       >= 4.7 && < 4.21,
+    build-depends: base       >= 4.7 && < 4.22,
                    binary     == 0.8.*,
                    bytestring >= 0.10 && < 0.13,
                    containers >= 0.5 && < 0.8,


=====================================
libraries/ghc-compact/ghc-compact.cabal
=====================================
@@ -40,7 +40,7 @@ library
     CPP
 
   build-depends: ghc-prim   >= 0.5.3 && < 0.12,
-                 base       >= 4.9.0 && < 4.21,
+                 base       >= 4.9.0 && < 4.22,
                  bytestring >= 0.10.6.0 && <0.13
   ghc-options: -Wall
 


=====================================
libraries/ghc-experimental/ghc-experimental.cabal.in
=====================================
@@ -39,7 +39,7 @@ library
     if arch(wasm32)
         exposed-modules:  GHC.Wasm.Prim
     other-extensions:
-    build-depends:    base ^>=4.20,
+    build-depends:    base >=4.20 && < 4.22,
                       ghc-internal == @ProjectVersionForLib at .*,
                       ghc-prim >= 0.11 && < 0.12
     hs-source-dirs:   src


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -84,7 +84,7 @@ library
     Build-Depends:
         rts,
         array            == 0.5.*,
-        base             >= 4.8 && < 4.21,
+        base             >= 4.8 && < 4.22,
         -- ghc-internal     == @ProjectVersionForLib at .*
         -- TODO: Use GHC.Internal.Desugar and GHC.Internal.Base from
         -- ghc-internal instead of ignoring the deprecation warning in GHCi.TH


=====================================
libraries/haskeline
=====================================
@@ -1 +1 @@
-Subproject commit 76157646fb5836fc022e770f7db2156661e899c3
+Subproject commit 5f4bf62bf1f4846ad0b8d1fa9d45f902e3934511


=====================================
libraries/hpc
=====================================
@@ -1 +1 @@
-Subproject commit 4989c41b96c7c9ca09a6687da638ac28f3d3688b
+Subproject commit 9e29abb785ab4f82c37c7a4e73ec999083955b09


=====================================
libraries/os-string
=====================================
@@ -1 +1 @@
-Subproject commit 6d31aafde2f7b8c3050ffee7dd9f658225cfd1a4
+Subproject commit 1d0553e20499d4bbaefe30d0489a08bc3523d331


=====================================
libraries/parsec
=====================================
@@ -1 +1 @@
-Subproject commit 9c071b05fbb077afbaf0dd2dfdab21265859ae91
+Subproject commit 903f9d8561a23376d26a7b857aa9fa5b35531d6f


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b
+Subproject commit 8364eaa2c83f7918be41cf3bd520e4ede1b07c35


=====================================
libraries/semaphore-compat
=====================================
@@ -1 +1 @@
-Subproject commit e8719d3b8e7e069b8f9200004b3d8a77446c91d3
+Subproject commit 54882cd9a07322a4cf95d4fc0627107eaf1eb051


=====================================
libraries/stm
=====================================
@@ -1 +1 @@
-Subproject commit cb861ea10065f229bbc5b6a1e2b9bde998f18184
+Subproject commit 789f7b117c02aa380cb59186307dff913643b6d7


=====================================
libraries/template-haskell/template-haskell.cabal.in
=====================================
@@ -52,7 +52,7 @@ Library
         Language.Haskell.TH.CodeDo
 
     build-depends:
-        base        >= 4.11 && < 4.21,
+        base        >= 4.11 && < 4.22,
         ghc-boot-th == @ProjectVersionMunged@
 
     other-modules:


=====================================
libraries/terminfo
=====================================
@@ -1 +1 @@
-Subproject commit 5b43c14f6843973d8704fb60486e6c458fc0ac8c
+Subproject commit a76fac0c60cf6db7ed724d9b5c5067d77a23efc7


=====================================
libraries/unix
=====================================
@@ -1 +1 @@
-Subproject commit 69552a5267c7dc5c46a8bceec5ec4b40d26b9463
+Subproject commit ca5b0b64aa36348b42416e1f59f55992c3f3d177


=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -3,46 +3,46 @@ ghc: Exception:
 default output name would overwrite the input file; must specify -o explicitly
 Usage: For basic information, try the `--help' option.
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling default output name would overwrite the input file; must specify -o explicitly
   | Usage: For basic information, try the `--help' option.
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   | Usage: For basic information, try the `--help' option.
   |   |
-  |   | Package: ghc-9.11-inplace
+  |   | Package: ghc-9.12-8fe2
   |   | Module: GHC.Utils.Panic
   |   | Type: GhcException
   |   |
   |   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   |   | Usage: For basic information, try the `--help' option.
   |   |   |
-  |   |   | Package: ghc-9.11-inplace
+  |   |   | Package: ghc-9.12-8fe2
   |   |   | Module: GHC.Utils.Panic
   |   |   | Type: GhcException
   |   |   |
   |   |   | HasCallStack backtrace:
-  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.11-inplace:GHC.Utils.Panic
+  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.12-8fe2:GHC.Utils.Panic
   |   |
   |   | HasCallStack backtrace:
-  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-inplace:System.Semaphore
+  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-c856:System.Semaphore
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   onException, called at compiler/GHC/Driver/Make.hs:2986:23 in ghc-9.11-inplace:GHC.Driver.Make
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   onException, called at compiler/GHC/Driver/Make.hs:2988:23 in ghc-9.12-8fe2:GHC.Driver.Make
 
 HasCallStack backtrace:
-  bracket, called at compiler/GHC/Driver/Make.hs:2953:3 in ghc-9.11-inplace:GHC.Driver.Make
+  bracket, called at compiler/GHC/Driver/Make.hs:2955:3 in ghc-9.12-8fe2:GHC.Driver.Make
 


=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -78,7 +78,7 @@ library
     build-depends: ghc-paths       ^>= 0.1.0.12
 
   -- this package typically supports only single major versions
-  build-depends: base             >= 4.16 && < 4.21
+  build-depends: base             >= 4.16 && < 4.22
                , ghc             ^>= 9.12
                , haddock-library ^>= 1.11
                , xhtml           ^>= 3000.2.2


=====================================
utils/haddock/haddock-library/haddock-library.cabal
=====================================
@@ -46,7 +46,7 @@ common ghc-options
     -Wnoncanonical-monad-instances -Wmissing-home-modules
 
   build-depends:
-    , base         >= 4.10     && < 4.21
+    , base         >= 4.10     && < 4.22
     , containers   ^>= 0.4.2.1 || ^>= 0.5.0.0 || ^>= 0.6.0.1 || ^>= 0.7
     , text         ^>= 1.2.3.0 || ^>= 2.0 || ^>= 2.1
     , parsec       ^>= 3.1.13.0


=====================================
utils/haddock/haddock-test/haddock-test.cabal
=====================================
@@ -16,7 +16,7 @@ library
   default-language: Haskell2010
   ghc-options: -Wall
   hs-source-dirs:   src
-  build-depends:    base >= 4.3 && < 4.21, bytestring, directory, process, filepath, Cabal
+  build-depends:    base >= 4.3 && < 4.22, bytestring, directory, process, filepath, Cabal
 
   exposed-modules:
     Test.Haddock


=====================================
utils/haddock/haddock.cabal
=====================================
@@ -91,7 +91,7 @@ executable haddock
 
   -- haddock typically only supports a single GHC major version
   build-depends:
-    base >= 4.13.0.0 && <4.21,
+    base >= 4.13.0.0 && <4.22,
     -- in order for haddock's advertised version number to have proper meaning,
     -- we pin down to a single haddock-api version.
     haddock-api == 2.30.0


=====================================
utils/hsc2hs
=====================================
@@ -1 +1 @@
-Subproject commit b0b0cca3db42fc9bf8ebc7da8ddd6fa937c5aa25
+Subproject commit c3b21800a67366c9591dc85a471d1dfdb1efcf29



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/380d89bb917085ce4e8dadf441af5e583b488782...49a1ce190c071072cff68d9ad1f7d9bf02292696

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/380d89bb917085ce4e8dadf441af5e583b488782...49a1ce190c071072cff68d9ad1f7d9bf02292696
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 09:44:04 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 14 Oct 2024 05:44:04 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] ttg: Using Text over
 FastString in the AST
Message-ID: <670ce7e49f4a1_2e93506460e0122270@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
f547b958 by Rodrigo Mesquita at 2024-10-14T10:43:34+01:00
ttg: Using Text over FastString in the AST

Towards the goal of making the AST independent of GHC, this commit
starts the task of replacing usages of `FastString` with `Text` in the
AST (Language.Haskell.* modules).

Even though we /do/ want to use FastStrings -- critically in Names or Ids
-- there is no particular reason for the FastStrings that occur in the
AST proper to be FastStrings. Primarily, ...

Progress towards #21592

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/ThToHs.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 13:13:40 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 09:13:40 -0400
Subject: [Git][ghc/ghc][master] users-guide: Document GHCi :where command
Message-ID: <670d1904b0ac1_2e935010cb1a013987e@gitlab.mail>



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


Commits:
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -


1 changed file:

- docs/users_guide/ghci.rst


Changes:

=====================================
docs/users_guide/ghci.rst
=====================================
@@ -1601,6 +1601,10 @@ breakpoint on a let expression, but there will always be a breakpoint on
 its body, because we are usually interested in inspecting the values of
 the variables bound by the let.
 
+While stopped at a breakpoint one can show the current evaluation
+stack with the :ghci-cmd:`:where` command.
+
+
 Managing breakpoints
 ^^^^^^^^^^^^^^^^^^^^
 
@@ -3081,6 +3085,10 @@ commonly used commands.
 
     The :ghci-cmd:`:uses` command requires :ghci-cmd:`:set +c` to be set.
 
+.. ghci-cmd:: :where
+
+   Show the current evaluation stack while stopped at a breakpoint.
+
 .. ghci-cmd:: :: ⟨builtin-command⟩
 
     Executes the GHCi built-in command (e.g. ``::type 3``). That is,



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/745dd590eac8f29b547747f4a7554029aaf2c188

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 13:14:19 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 09:14:19 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove [AddEpAnn] from IE, Pat and some
 Tys
Message-ID: <670d192bacd5c_2e9350eeaa8414337f@gitlab.mail>



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


Commits:
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_compile/T20846.stderr


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 13:35:23 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 14 Oct 2024 09:35:23 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 14 commits: testsuite:
 Normalise trailing digits from hole fits output
Message-ID: <670d1e1bb155f_2e9350145783c1439e8@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
39c058b2 by Rodrigo Mesquita at 2024-10-14T14:34:28+01:00
ttg: Using Text over FastString in the AST

Towards the goal of making the AST independent of GHC, this commit
starts the task of replacing usages of `FastString` with `Text` in the
AST (Language.Haskell.* modules).

Even though we /do/ want to use FastStrings -- critically in Names or Ids
-- there is no particular reason for the FastStrings that occur in the
AST proper to be FastStrings. Primarily, ...

Progress towards #21592

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Bind.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f547b958c0b3f420bcdfd7e3520eb426c59a4ed0...39c058b2f94bf909167d1dd24a81305f49041fe1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f547b958c0b3f420bcdfd7e3520eb426c59a4ed0...39c058b2f94bf909167d1dd24a81305f49041fe1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 13:39:35 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 09:39:35 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 6 commits: testsuite: normalise
 some versions in callstacks
Message-ID: <670d1f17b2615_2e9350142dfb4144316@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
09aa9a37 by Zubin Duggal at 2024-10-14T19:09:17+05:30
testsuite: normalise some versions in callstacks

- - - - -
b62ef67f by Zubin Duggal at 2024-10-14T19:09:17+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
a07e9e8f by Zubin Duggal at 2024-10-14T19:09:17+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
cededff6 by Zubin Duggal at 2024-10-14T19:09:17+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
9a562799 by Zubin Duggal at 2024-10-14T19:09:28+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -
c14795ca by Zubin Duggal at 2024-10-14T19:09:28+05:30
Prepare 9.12.1 alpha

- - - - -


30 changed files:

- compiler/ghc.cabal.in
- configure.ac
- libraries/Cabal
- libraries/array
- libraries/base/base.cabal.in
- libraries/deepseq
- libraries/directory
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/unix
- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/49a1ce190c071072cff68d9ad1f7d9bf02292696...c14795caad9363cb42e53dbf73b25e796d0beec4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/49a1ce190c071072cff68d9ad1f7d9bf02292696...c14795caad9363cb42e53dbf73b25e796d0beec4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 13:41:12 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 09:41:12 -0400
Subject: [Git][ghc/ghc][wip/9.12-testsuite-fixes] 5 commits: testsuite:
 normalise some versions in callstacks
Message-ID: <670d1f7854a43_2e935013d398814466f@gitlab.mail>



Zubin pushed to branch wip/9.12-testsuite-fixes at Glasgow Haskell Compiler / GHC


Commits:
18a4f837 by Zubin Duggal at 2024-10-14T19:10:48+05:30
testsuite: normalise some versions in callstacks

- - - - -
a0c17d2f by Zubin Duggal at 2024-10-14T19:10:48+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
eb2ec6ff by Zubin Duggal at 2024-10-14T19:10:48+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
0d1f1677 by Zubin Duggal at 2024-10-14T19:10:48+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

- - - - -
da9e94d3 by Zubin Duggal at 2024-10-14T19:10:48+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -


12 changed files:

- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-e/should_fail/all.T
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
- utils/haddock/html-test/Main.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html


Changes:

=====================================
testsuite/tests/backpack/should_compile/all.T
=====================================
@@ -8,7 +8,7 @@ test('bkp11', normal, backpack_compile, [''])
 test('bkp12', normal, backpack_compile, [''])
 test('bkp14', normal, backpack_compile, [''])
 test('bkp15', normal, backpack_compile, [''])
-test('bkp16', normalise_version('base', 'ghc-internal'), backpack_compile, [''])
+test('bkp16', [normalise_version('base', 'ghc-internal')], backpack_compile, ['-fhide-source-paths'])
 test('bkp17', normal, backpack_compile, [''])
 test('bkp18', normal, backpack_compile, [''])
 test('bkp19', normal, backpack_compile, [''])
@@ -60,4 +60,4 @@ test('T13214', normal, backpack_compile, [''])
 test('T13250', normal, backpack_compile, [''])
 test('T13323', normal, backpack_compile, [''])
 test('T20396', normal, backpack_compile, [''])
-test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])
\ No newline at end of file
+test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])


=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -1,9 +1,9 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling Int[sig]         ( p/Int.hsig, nothing )
+  [1 of 1] Compiling Int[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
     Instantiating p[Int=base-4.20.0.0:GHC.Exts]
     [1 of 1] Including base-4.20.0.0
-    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+    [1 of 1] Compiling Int[sig]
   [1 of 1] Instantiating p


=====================================
testsuite/tests/backpack/should_fail/all.T
=====================================
@@ -12,9 +12,9 @@ test('bkpfail13', normal, backpack_compile_fail, [''])
 test('bkpfail14', normal, backpack_compile_fail, [''])
 test('bkpfail15', normal, backpack_compile_fail, [''])
 test('bkpfail16', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
-test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail18', normal, backpack_compile_fail, [''])
-test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail20', normal, backpack_compile_fail, [''])
 test('bkpfail21', normal, backpack_compile_fail, [''])
 test('bkpfail22', normal, backpack_compile_fail, [''])


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
     Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-15843]
     • Type constructor ‘Either’ has conflicting definitions in the module
       and its hsig file.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
     Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-12424]
     • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
       but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’


=====================================
testsuite/tests/gadt/all.T
=====================================
@@ -127,7 +127,7 @@ test('T20485', normal, compile, [''])
 test('T20485a', normal, compile, [''])
 test('T22235', normal, compile, [''])
 test('T19847', normal, compile, [''])
-test('T19847a', normal, compile, ['-ddump-types'])
+test('T19847a', normalise_version('base'), compile, ['-ddump-types'])
 test('T19847b', normal, compile, [''])
 test('T23022', normal, compile, ['-dcore-lint'])
 test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test?


=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -15,6 +15,7 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
 test('T9930fail',
      [extra_files(['T9930']),
       when(opsys('mingw32'), skip),
+      normalise_errmsg_fun(lambda s: normalise_version_("ghc")(s).replace('ghc--','ghc')),
       # broken for JS until cross-compilers become stage2 compilers (#19174)
       # or until we bootstrap with a 9.10 compiler
       js_broken(19174)],
@@ -24,7 +25,7 @@ test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])
 
 test('T18441fail1', req_interp, makefile_test, ['T18441fail1'])
 
-test('T18441fail2', req_interp, makefile_test, ['T18441fail2'])
+test('T18441fail2', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail2'])
 
 test('T18441fail3', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":! abcde"'])
 
@@ -34,9 +35,9 @@ test('T18441fail5', req_interp, makefile_test, ['T18441fail5'])
 
 test('T18441fail6', req_interp, makefile_test, ['T18441fail6'])
 
-test('T18441fail7', req_interp, makefile_test, ['T18441fail7'])
+test('T18441fail7', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail7'])
 
-test('T18441fail8', req_interp, makefile_test, ['T18441fail8'])
+test('T18441fail8', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail8'])
 
 test('T18441fail9', req_interp, makefile_test, ['T18441fail9'])
 
@@ -60,6 +61,6 @@ test('T18441fail18', req_interp, makefile_test, ['T18441fail18'])
 
 test('T18441fail19', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":cd abcd"'])
 
-test('T23663', req_interp, makefile_test, ['T23663'])
+test('T23663', [req_interp, normalise_version('ghc')], makefile_test, ['T23663'])
 
 test('T24172', normal, compile_fail, ['-fdiagnostics-color=always'])


=====================================
utils/haddock/haddock-test/src/Test/Haddock.hs
=====================================
@@ -156,7 +156,7 @@ runHaddock cfg@(Config{..}) = do
 
       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
+      filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (\mt -> ((mt,file),file)) <$> getModificationTime (hiDir  file)) files
       let srcRef = if "--hyperlinked-source" `elem` cfgHaddockArgs then ",src,visible," else ""
           loop [] = pure True
           loop (file : files) = do


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
=====================================
@@ -8,6 +8,7 @@ module Test.Haddock.Xhtml
   , stripIdsWhen
   , stripFooter
   , fixAttrValueWhen
+  , stripVersions
   ) where
 
 {-
@@ -22,7 +23,7 @@ and since the `xhtml` library already handles the pretty-printing aspect,
 this would appear to be a reasonable compromise for now.
 -}
 
-import Data.Char (isSpace)
+import Data.Char (isSpace, isAlphaNum)
 import Data.List (isPrefixOf, stripPrefix)
 
 -- | Simple wrapper around the pretty-printed HTML source
@@ -142,3 +143,18 @@ stripFooter (Xml body) = Xml (findDiv body)
           Just valRest''
       | otherwise =
           dropToDiv cs
+
+-- | Strip strings of the form --
+-- to just 
+stripVersions :: [String] -> Xml -> Xml
+stripVersions xs (Xml body) = Xml $ foldr id body $ map go xs
+  where
+    go pkg "" = ""
+    go pkg body@(x:body') = case stripPrefix pkg body of
+      Just ('-':rest)
+        | (version,'-':rest') <- span (/= '-') rest
+        , all (`elem` ('.':['0'..'9'])) version
+        , let (hash, rest'') = span isAlphaNum rest'
+        -> pkg ++ go pkg rest''
+      _ -> x:go pkg body'
+


=====================================
utils/haddock/html-test/Main.hs
=====================================
@@ -42,7 +42,7 @@ main = do
 
 stripIfRequired :: String -> Xml -> Xml
 stripIfRequired mdl =
-    stripLinks' . stripFooter
+    stripLinks' . stripFooter . stripVersions ["base"]
   where
     stripLinks'
         | mdl `elem` preserveLinksModules = id


=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
 				  >D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1

From gitlab at gitlab.haskell.org  Mon Oct 14 13:45:33 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 09:45:33 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: users-guide:
 Document GHCi :where command
Message-ID: <670d207da1e92_2e935018517f814713b@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
9905baf6 by Sebastian Graf at 2024-10-14T09:45:08-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
90dd8d41 by Simon Peyton Jones at 2024-10-14T09:45:08-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
19466bca by Simon Peyton Jones at 2024-10-14T09:45:08-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
b665a792 by Ben Gamari at 2024-10-14T09:45:08-04:00
users-guide: Document field coalescence

- - - - -
42ab1a17 by ARATA Mizuki at 2024-10-14T09:45:15-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/651cf5870662d98f1014d408ff4558ef5eec6408...42ab1a1709cdc78a4d64f4c1c3009f907df39487

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/651cf5870662d98f1014d408ff4558ef5eec6408...42ab1a1709cdc78a4d64f4c1c3009f907df39487
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 14:53:31 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 14 Oct 2024 10:53:31 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ttg/fixity-import
Message-ID: <670d306bd39a6_10e07335f28c7984@gitlab.mail>



Hassan Al-Awwadi pushed new branch wip/ttg/fixity-import at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ttg/fixity-import
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:04:56 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 11:04:56 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.8
Message-ID: <670d3318119d2_10e07332acbc905f2@gitlab.mail>



Ben Gamari pushed new branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:05:23 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 14 Oct 2024 11:05:23 -0400
Subject: [Git][ghc/ghc][wip/ttg/fixity-import] 28 commits: Handle exceptions
 from IO manager backend
Message-ID: <670d3333af5fe_10e0733fa0c09078f@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/fixity-import at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
c742cf88 by Hassan Al-Awwadi at 2024-10-14T17:04:54+02:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b441daccd5a6dd65bfcd8384f47205a135e5a9fc...c742cf889f980af8a21ff85eb7acb845dd83f36d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b441daccd5a6dd65bfcd8384f47205a135e5a9fc...c742cf889f980af8a21ff85eb7acb845dd83f36d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:36:34 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 14 Oct 2024 11:36:34 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibbles to solver and MR
Message-ID: <670d3a82cf5e7_1a729f2ea478499e8@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
423febc9 by Simon Peyton Jones at 2024-10-14T16:36:19+01:00
Wibbles to solver and MR

- - - - -


3 changed files:

- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Solver.hs
- testsuite/tests/typecheck/should_compile/T13785.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/Bind.hs
=====================================
@@ -773,6 +773,7 @@ checkMonomorphismRestriction :: [MonoBindInfo] -> [LHsBind GhcRn] -> TcM Bool
 checkMonomorphismRestriction mbis lbinds
   = do { mr_on <- xoptM LangExt.MonomorphismRestriction
        ; let mr_applies = mr_on && any (restricted . unLoc) lbinds
+       ; when mr_applies $ traceTc "cmr" (ppr lbinds $$ vcat (map (ppr . mbi_sig) mbis))
        ; when mr_applies $ mapM_ checkOverloadedSig mbis
        ; return mr_applies }
   where


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1469,19 +1469,35 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
                                          ++ tau_tys ++ post_mr_quant)
              co_var_tvs = closeOverKinds co_vars
 
+             -- outer_tvs are belong to some outer level,
+             -- so we definitely can't quantify over them
+             outer_tvs = outerLevelTyVars tc_lvl $
+                         tyCoVarsOfTypes can_quant `unionVarSet` tyCoVarsOfTypes no_quant
+
+             mono_tvs_ignoring_mr
+               | isTopTcLevel tc_lvl = outer_tvs
+               | otherwise           = outer_tvs
+                                       `unionVarSet` tyCoVarsOfTypes no_quant
+                                       `unionVarSet` co_var_tvs
+
+             mono_tvs_accounting_for_mr
+               = mono_tvs_ignoring_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
+
+{-
              -- mono_tvs0 are all the type variables we can't quantify over
              mono_tvs0
                | isTopTcLevel tc_lvl
                  -- At top level: we want to promote only tyvars that are
-                 --  (a) free in envt (already promoted)
-                 --  (b) will be defaulted
+                 --  (a) free in envt (outer_tvs)
+                 --  (b) will be defaulted (mr_no_quant)
                  --  (c) determined by (a) or (b)
                  -- mono_tvs0 deals with (a) or (b); closeWrtFunDeps deals with (c)
-               = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
+               = outer_tvs
+                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
 
                | otherwise
-               = outerLevelTyVars tc_lvl (tyCoVarsOfTypes post_mr_quant)
-                     -- outerLevelTyVars are free in the envt, so can't quantify them
+               = outer_tvs
+                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
                  `unionVarSet` tyCoVarsOfTypes no_quant
                  `unionVarSet` co_var_tvs
                      -- If we don't quantify over a constraint in no_quant, we
@@ -1489,9 +1505,22 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
                      -- sites will fix them) or just ignore it for the purposes
                      -- of mono_tvs0 (leaving behind a perhaps insoluble residual
                      -- constraint)
+-}
+
+             add_determined tvs = closeWrtFunDeps post_mr_quant tvs
+                                  `delVarSetList` psig_qtvs
+             -- Finally, delete psig_qtvs
+             -- If the user has explicitly asked for quantification, then that
+             -- request "wins" over the MR.
+             --
+             -- What if a psig variable is also free in the environment
+             -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
+             -- in Step 2 of Note [Deciding quantification].
+
+
 
-             -- Next, use closeWrtFunDeps to find any other variables that are determined
-             -- by mono_tvs0 + mr_no_quant, by functional dependencies or equalities.
+             -- Next, use closeWrtFunDeps to find any other variables that are
+             -- determined by mono_tvs0, by functional dependencies or equalities.
              -- Example
              --    f x y = ...
              --      where z = x 3
@@ -1502,21 +1531,18 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- are in the equality constraint with alpha. Actual test case:
              -- typecheck/should_compile/tc213
              -- see Note [growThetaTyVars vs closeWrtFunDeps]
-             mono_tvs1 = closeWrtFunDeps post_mr_quant $
-                         (mono_tvs0 `unionVarSet` tyCoVarsOfTypes mr_no_quant)
-
-             -- Finally, delete psig_qtvs
-             -- If the user has explicitly asked for quantification, then that
-             -- request "wins" over the MR.
-             --
-             -- What if a psig variable is also free in the environment
-             -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
-             -- in Step 2 of Note [Deciding quantification].
-             mono_tvs = mono_tvs1 `delVarSetList` psig_qtvs
+             mono_tvs_with_mr    = add_determined mono_tvs_accounting_for_mr
+             mono_tvs_without_mr = add_determined mono_tvs_ignoring_mr
 
              -- Do not quantify over any constraint mentioning a "newly-mono" tyvar
-             -- The "newly-mono" tyvars are the ones not free in the envt
-             -- nor forced to be promoted by the MR; but are deternmined by them
+             -- The "newly-mono" tyvars are the ones not free in the envt, nor
+             -- forced to be promoted by the MR; but are determined (via fundeps) by them
+             -- Example: class C a b | a -> b
+             --          [W] C Int beta[1],  tau = beta[1]->Int
+             -- We promote beta[1] to beta[0] since it is determined by fundep,
+             -- but we do not want to generate f :: (C Int beta[0]) => beta[0] -> Int
+             -- Rather, we generate f :: beta[0] -> Int, but leave [W] C Int beta[0]
+             -- in the residual constraints, which will probably cause a type errors
              newly_mono = mono_tvs `minusVarSet` mono_tvs0
              final_quant
                | isTopTcLevel tc_lvl = filterOut (predMentions newly_mono) post_mr_quant
@@ -1525,11 +1551,8 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
        -- Check if the Monomorphism Restriction has bitten
        ; warn_mr <- woptM Opt_WarnMonomorphism
        ; when (warn_mr && case infer_mode of { ApplyMR -> True; _ -> False}) $
-         do { let mono_tvs_wo_mr = closeWrtFunDeps post_mr_quant mono_tvs0
-                                   `delVarSetList` psig_qtvs
-
-            ; diagnosticTc (not (mono_tvs `subVarSet` mono_tvs_wo_mr)) $
-              TcRnMonomorphicBindings (map fst name_taus) }
+         diagnosticTc (not (mono_tvs `subVarSet` mono_tvs_wo_mr)) $
+              TcRnMonomorphicBindings (map fst name_taus)
              -- If there is a variable in mono_tvs, but not in mono_tvs_wo_mr
              -- then the MR has "bitten" and reduced polymorphism.
 


=====================================
testsuite/tests/typecheck/should_compile/T13785.hs
=====================================
@@ -2,15 +2,20 @@
 {-# OPTIONS_GHC -Wmonomorphism-restriction #-}
 module Bug where
 
-class Monad m => C m where
-  c :: (m Char, m Char)
+class Monad x => C x where
+  c :: (x Char, x Char)
 
 foo :: forall m. C m => m Char
-foo = bar >> baz >> bar2
+foo = bar >> baz >> bar1 >> bar2
   where
     -- Should not get MR warning
     bar, baz :: m Char
-    (bar, baz) = c
+    (bar, baz) = (c :: m Char, m Char)
+
+    -- Should not get MR warning
+    (bar1, baz1) = (c :: (m Char, m Char))
 
     -- Should get MR warning
+    -- Natural type for the "whole binding": forall x. C x => (x Char, x Char)
+    -- MR makes it less polymorphic => warning.
     (bar2, baz2) = c



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/423febc9d474cf3786f2491e9b9143c2e250ba4b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:38:02 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 14 Oct 2024 11:38:02 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] actualy probably like this
Message-ID: <670d3adaf189a_1a729f326338503dd@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
636cb80b by Hassan Al-Awwadi at 2024-10-14T16:37:50+01:00
actualy probably like this

- - - - -


5 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -38,7 +38,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
-import GHC.Data.BooleanFormula ( BooleanFormula, pprBooleanFormulaNormal )
+import GHC.Data.BooleanFormula ( BooleanFormula )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -34,7 +34,6 @@ import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
 import GHC.Data.BooleanFormula (BooleanFormula(..))
-import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -592,4 +591,4 @@ deriving instance Data XViaStrategyPs
 -- ---------------------------------------------------------------------
 
 deriving instance Data a => Data (BooleanFormula a)
----------------------------------------------------------------------
\ No newline at end of file
+---------------------------------------------------------------------


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -19,7 +19,7 @@ module GHC.Iface.Syntax (
         IfaceInfoItem(..), IfaceRule(..), IfaceAnnotation(..), IfaceAnnTarget,
         IfaceWarnings(..), IfaceWarningTxt(..), IfaceStringLiteral(..),
         IfaceDefault(..), IfaceClsInst(..), IfaceFamInst(..), IfaceTickish(..),
-        IfaceClassBody(..), IfaceBooleanFormula(..),
+        IfaceClassBody(..), IfaceBooleanFormula,
         IfaceBang(..),
         IfaceSrcBang(..), SrcUnpackedness(..), SrcStrictness(..),
         IfaceAxBranch(..),
@@ -100,7 +100,6 @@ import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
 import Data.Proxy
-import Data.List ( intersperse )
 
 infixl 3 &&&
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -126,13 +126,11 @@ import GHC.Types.Error
 import GHC.Fingerprint
 
 import Control.Monad
-import GHC.Parser.Annotation
 import GHC.Driver.Env.KnotVars
 import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
-import Data.List (nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3011,7 +3011,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula RdrName) where
+instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4697,7 +4697,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula RdrName)) where
+instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/636cb80b591f4c57aed71e34f98961fc8df64218

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:48:14 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 14 Oct 2024 11:48:14 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] actualy probably like this
Message-ID: <670d3d3e4ac95_216218ebd2022927@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
aabf3909 by Hassan Al-Awwadi at 2024-10-14T16:47:57+01:00
actualy probably like this

- - - - -


6 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -38,7 +38,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
-import GHC.Data.BooleanFormula ( BooleanFormula, pprBooleanFormulaNormal )
+import GHC.Data.BooleanFormula ( BooleanFormula )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -34,7 +34,6 @@ import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
 import GHC.Data.BooleanFormula (BooleanFormula(..))
-import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -592,4 +591,4 @@ deriving instance Data XViaStrategyPs
 -- ---------------------------------------------------------------------
 
 deriving instance Data a => Data (BooleanFormula a)
----------------------------------------------------------------------
\ No newline at end of file
+---------------------------------------------------------------------


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -32,23 +32,19 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-import GHC.Hs.Extension ( GhcPass )
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
 import GHC.Types.TyThing
-import GHC.Types.SrcLoc
 
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
 import GHC.Data.Maybe
-import GHC.Data.BooleanFormula
 
 import Data.List ( findIndex, mapAccumL )
-import Language.Haskell.Syntax.Extension (IdP, LIdP)
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -19,7 +19,7 @@ module GHC.Iface.Syntax (
         IfaceInfoItem(..), IfaceRule(..), IfaceAnnotation(..), IfaceAnnTarget,
         IfaceWarnings(..), IfaceWarningTxt(..), IfaceStringLiteral(..),
         IfaceDefault(..), IfaceClsInst(..), IfaceFamInst(..), IfaceTickish(..),
-        IfaceClassBody(..), IfaceBooleanFormula(..),
+        IfaceClassBody(..), IfaceBooleanFormula,
         IfaceBang(..),
         IfaceSrcBang(..), SrcUnpackedness(..), SrcStrictness(..),
         IfaceAxBranch(..),
@@ -100,7 +100,6 @@ import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
 import Data.Proxy
-import Data.List ( intersperse )
 
 infixl 3 &&&
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -126,13 +126,11 @@ import GHC.Types.Error
 import GHC.Fingerprint
 
 import Control.Monad
-import GHC.Parser.Annotation
 import GHC.Driver.Env.KnotVars
 import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
-import Data.List (nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3011,7 +3011,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula RdrName) where
+instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4697,7 +4697,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula RdrName)) where
+instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:56:27 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 11:56:27 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes 23479 (muted temporary))
Message-ID: <670d3f2b19e1a_2162181d4520236e7@gitlab.mail>



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


Commits:
2270360b by Serge S. Gulin at 2024-10-14T18:56:06+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


24 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- + testsuite/tests/javascript/T23479_3.hs
- + testsuite/tests/javascript/T23479_3.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,32 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    -- Test case T23479_3 (rewrite required)
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -7,3 +7,21 @@ T24495:
 	./T24495
 	# check that the optimization occurred
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	# check that the optimization occurred
+	grep -c "h\$$decodeUtf8z" T23479_2.dump-js
+
+T23479_3:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_3.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_3
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_3.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE MagicHash #-}
+
+import GHC.Prim
+
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## test_addr_1))
+  where
+    test_addr_1 :: Addr#
+    test_addr_1 = "test_val_1"#


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_1
+1


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,14 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+main :: IO ()
+main = do
+  js_log1 $ toJSString test_val_2


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_2
+1


=====================================
testsuite/tests/javascript/T23479_3.hs
=====================================
@@ -0,0 +1,14 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  js_log1 (toJSString test_val_3)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"


=====================================
testsuite/tests/javascript/T23479_3.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_3
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,6 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2270360b840c7d248f33e56df0c4dfb438afade7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:57:06 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 11:57:06 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] 4 commits: Consider Wanteds with
 rewriters as insoluble
Message-ID: <670d3f5272ad5_2162182493d4240c9@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
7326051e by Simon Peyton Jones at 2024-10-14T11:53:29-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

(cherry picked from commit 083703a12cd34369e7ed2f0efc4a5baee47aedab)

- - - - -
6b790e6c by Simon Peyton Jones at 2024-10-14T11:53:58-04:00
Wibbles

(cherry picked from commit 0dfaeb66fb8457e7339abbd44d5c53a81ad8ae3a)

- - - - -
454e2165 by Simon Peyton Jones at 2024-10-14T11:53:58-04:00
Spelling errors

(cherry picked from commit 09d24d828e48c2588a317e6dad711f8673983703)

- - - - -
a3a6da7e by Torsten Schmits at 2024-10-14T11:53:58-04:00
add test that runs MakeDepend on thousands of modules

(cherry picked from commit 7875e8cbe5d9b69a1a77354317b2bf9478172686)

- - - - -


9 changed files:

- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Types/Constraint.hs
- testsuite/driver/testlib.py
- + testsuite/tests/perf/compiler/large-project/all.T
- + testsuite/tests/perf/compiler/large-project/large-project.sh
- testsuite/tests/polykinds/T14172.stderr
- + testsuite/tests/typecheck/should_fail/T25325.hs
- + testsuite/tests/typecheck/should_fail/T25325.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -469,6 +469,8 @@ mkErrorItem ct
              flav = ctFlavour ct
 
        ; (suppress, m_evdest) <- case ctEvidence ct of
+         -- For this `suppress` stuff
+         -- see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
            CtGiven {} -> return (False, Nothing)
            CtWanted { ctev_rewriters = rewriters, ctev_dest = dest }
              -> do { rewriters' <- zonkRewriterSet rewriters


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -83,7 +83,7 @@ module GHC.Tc.Types.Constraint (
         ctEvExpr, ctEvTerm, ctEvCoercion, ctEvEvId,
         ctEvRewriters, ctEvUnique, tcEvDestUnique,
         mkKindEqLoc, toKindLoc, toInvisibleLoc, mkGivenLoc,
-        ctEvRole, setCtEvPredType, setCtEvLoc, arisesFromGivens,
+        ctEvRole, setCtEvPredType, setCtEvLoc,
         tyCoVarsOfCtEvList, tyCoVarsOfCtEv, tyCoVarsOfCtEvsList,
 
         -- RewriterSet
@@ -1312,25 +1312,51 @@ nonDefaultableTyVarsOfWC (WC { wc_simple = simples, wc_impl = implics, wc_errors
 insolubleWC :: WantedConstraints -> Bool
 insolubleWC (WC { wc_impl = implics, wc_simple = simples, wc_errors = errors })
   =  anyBag insolubleWantedCt simples
+       -- insolubleWantedCt: wanteds only: see Note [Given insolubles]
   || anyBag insolubleImplic implics
   || anyBag is_insoluble errors
-
-    where
+  where
       is_insoluble (DE_Hole hole) = isOutOfScopeHole hole -- See Note [Insoluble holes]
       is_insoluble (DE_NotConcrete {}) = True
 
 insolubleWantedCt :: Ct -> Bool
 -- Definitely insoluble, in particular /excluding/ type-hole constraints
 -- Namely:
---   a) an insoluble constraint as per 'insolubleCt', i.e. either
+--   a) an insoluble constraint as per 'insolubleIrredCt', i.e. either
 --        - an insoluble equality constraint (e.g. Int ~ Bool), or
 --        - a custom type error constraint, TypeError msg :: Constraint
 --   b) that does not arise from a Given or a Wanted/Wanted fundep interaction
+-- See Note [Insoluble Wanteds]
+insolubleWantedCt ct
+  | CIrredCan ir_ct <- ct
+      -- CIrredCan: see (IW1) in Note [Insoluble Wanteds]
+  , IrredCt { ir_ev = ev } <- ir_ct
+  , CtWanted { ctev_loc = loc, ctev_rewriters = rewriters }  <- ev
+      -- It's a Wanted
+  , insolubleIrredCt ir_ct
+      -- It's insoluble
+  , isEmptyRewriterSet rewriters
+      -- It has no rewriters; see (IW2) in Note [Insoluble Wanteds]
+  , not (isGivenLoc loc)
+      -- isGivenLoc: see (IW3) in Note [Insoluble Wanteds]
+  , not (isWantedWantedFunDepOrigin (ctLocOrigin loc))
+      -- origin check: see (IW4) in Note [Insoluble Wanteds]
+  = True
+
+  | otherwise
+  = False
+
+-- | Returns True of constraints that are definitely insoluble,
+--   as well as TypeError constraints.
+-- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
 --
--- See Note [Given insolubles].
-insolubleWantedCt ct = insolubleCt ct &&
-                       not (arisesFromGivens ct) &&
-                       not (isWantedWantedFunDepOrigin (ctOrigin ct))
+-- The function is tuned for application /after/ constraint solving
+--       i.e. assuming canonicalisation has been done
+-- That's why it looks only for IrredCt; all insoluble constraints
+-- are put into CIrredCan
+insolubleCt :: Ct -> Bool
+insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
+insolubleCt _                 = False
 
 insolubleIrredCt :: IrredCt -> Bool
 -- Returns True of Irred constraints that are /definitely/ insoluble
@@ -1360,18 +1386,6 @@ insolubleIrredCt (IrredCt { ir_ev = ev, ir_reason = reason })
   -- >   Assert 'True  _errMsg = ()
   -- >   Assert _check errMsg  = errMsg
 
--- | Returns True of constraints that are definitely insoluble,
---   as well as TypeError constraints.
--- Can return 'True' for Given constraints, unlike 'insolubleWantedCt'.
---
--- The function is tuned for application /after/ constraint solving
---       i.e. assuming canonicalisation has been done
--- That's why it looks only for IrredCt; all insoluble constraints
--- are put into CIrredCan
-insolubleCt :: Ct -> Bool
-insolubleCt (CIrredCan ir_ct) = insolubleIrredCt ir_ct
-insolubleCt _                 = False
-
 -- | Does this hole represent an "out of scope" error?
 -- See Note [Insoluble holes]
 isOutOfScopeHole :: Hole -> Bool
@@ -1415,6 +1429,31 @@ in GHC.Tc.Errors), so we may fail to report anything at all!  Yikes.
 Bottom line: insolubleWC (called in GHC.Tc.Solver.setImplicationStatus)
              should ignore givens even if they are insoluble.
 
+Note [Insoluble Wanteds]
+~~~~~~~~~~~~~~~~~~~~~~~~
+insolubleWantedCt returns True of a Wanted constraint that definitely
+can't be solved.  But not quite all such constraints; see wrinkles.
+
+(IW1) insolubleWantedCt is tuned for application /after/ constraint
+   solving i.e. assuming canonicalisation has been done.  That's why
+   it looks only for IrredCt; all insoluble constraints are put into
+   CIrredCan
+
+(IW2) We only treat it as insoluble if it has an empty rewriter set.  (See Note
+   [Wanteds rewrite Wanteds].)  Otherwise #25325 happens: a Wanted constraint A
+   that is /not/ insoluble rewrites some other Wanted constraint B, so B has A
+   in its rewriter set.  Now B looks insoluble.  The danger is that we'll
+   suppress reporting B because of its empty rewriter set; and suppress
+   reporting A because there is an insoluble B lying around.  (This suppression
+   happens in GHC.Tc.Errors.mkErrorItem.)  Solution: don't treat B as insoluble.
+
+(IW3) If the Wanted arises from a Given (how can that happen?), don't
+   treat it as a Wanted insoluble (obviously).
+
+(IW4) If the Wanted came from a  Wanted/Wanted fundep interaction, don't
+   treat the constraint as insoluble. See Note [Suppressing confusing errors]
+   in GHC.Tc.Errors
+
 Note [Insoluble holes]
 ~~~~~~~~~~~~~~~~~~~~~~
 Hole constraints that ARE NOT treated as truly insoluble:
@@ -2056,9 +2095,6 @@ tcEvDestUnique (HoleDest co_hole) = varUnique (coHoleCoVar co_hole)
 setCtEvLoc :: CtEvidence -> CtLoc -> CtEvidence
 setCtEvLoc ctev loc = ctev { ctev_loc = loc }
 
-arisesFromGivens :: Ct -> Bool
-arisesFromGivens ct = isGivenCt ct || isGivenLoc (ctLoc ct)
-
 -- | Set the type of CtEvidence.
 --
 -- This function ensures that the invariants on 'CtEvidence' hold, by updating


=====================================
testsuite/driver/testlib.py
=====================================
@@ -1538,6 +1538,9 @@ async def multi_compile( name, way, top_mod, extra_mods, extra_hc_opts ):
 async def multi_compile_fail( name, way, top_mod, extra_mods, extra_hc_opts ):
     return await do_compile( name, way, True, top_mod, extra_mods, [], extra_hc_opts)
 
+async def make_depend( name, way, mods, extra_hc_opts ):
+    return await do_compile( name, way, False,  ' '.join(mods), [], [], extra_hc_opts, mode = '-M')
+
 async def do_compile(name: TestName,
                way: WayName,
                should_fail: bool,
@@ -1804,7 +1807,9 @@ async def simple_build(name: Union[TestName, str],
                  addsuf: bool,
                  backpack: bool = False,
                  suppress_stdout: bool = False,
-                 filter_with: str = '') -> Any:
+                 filter_with: str = '',
+                 # Override auto-detection of whether to use --make or -c etc.
+                 mode: Optional[str] = None) -> Any:
     opts = getTestOpts()
 
     # Redirect stdout and stderr to the same file
@@ -1821,7 +1826,9 @@ async def simple_build(name: Union[TestName, str],
     else:
         srcname = Path(name)
 
-    if top_mod is not None:
+    if mode is not None:
+        to_do = mode
+    elif top_mod is not None:
         to_do = '--make '
         if link:
             to_do = to_do + '-o ' + name


=====================================
testsuite/tests/perf/compiler/large-project/all.T
=====================================
@@ -0,0 +1,21 @@
+# These tests are supposed to prevent severe performance regressions when
+# operating on projects with unusually large numbers of modules.
+# Inefficient algorithms whose complexity depends on the number of modules won't
+# be noticed when running the test suite or compiling medium size projects.
+
+def large_project_makedepend(num):
+    return test(
+        f'large-project-makedepend-{num}',
+        [
+            collect_compiler_stats('bytes allocated', 1),
+            pre_cmd(f'./large-project.sh {num}'),
+            extra_files(['large-project.sh']),
+            ignore_stderr,
+            when(windows,skip),
+        ],
+        make_depend,
+        [[f'Mod{i:04d}' for i in range(0, num - 1)], ''],
+        )
+
+large_project_makedepend(4000)
+large_project_makedepend(10000)


=====================================
testsuite/tests/perf/compiler/large-project/large-project.sh
=====================================
@@ -0,0 +1,22 @@
+#!/usr/bin/env bash
+
+set -eu
+
+total="$1"
+
+for ((i = 1; i < $total; i++))
+do
+  # Important to write directly to variables with `-v`, otherwise the script takes a second per 1000 modules
+  printf -v j "%04d" "$i"
+  printf -v k "%04d" "$(($i - 1))"
+  echo -e "module Mod${j} where
+import Mod${k}
+f_${j} :: ()
+f_${j} = f_$k" > "Mod${j}.hs"
+done
+
+echo "
+module Mod0000 where
+f_0000 :: ()
+f_0000 = ()
+" > "Mod0000.hs"


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,10 +1,7 @@
-
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'’
-      Where: ‘a'’ is a rigid type variable bound by
-               the inferred type of
-                 traverseCompose :: (a -> f b) -> g a -> f (h a')
-               at T14172.hs:8:1-46
+    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
+      Where: ‘k0’ is an ambiguous type variable
+             ‘a'1’ is an ambiguous type variable
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -13,17 +10,19 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
-        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
-                -> Compose f'0 g'1 a'0 -> f (h a')
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
+        Actual: (Unwrapped (Compose f'0 g'1 a'0)
+                 -> f (Unwrapped (h a'1)))
+                -> Compose f'0 g'1 a'0 -> f (h a'1)
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a')
+          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a')
+        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
           (bound at T14172.hs:8:1)
+


=====================================
testsuite/tests/typecheck/should_fail/T25325.hs
=====================================
@@ -0,0 +1,14 @@
+module T25325 where
+
+import Control.Monad.State
+
+data (f :+: g) a = Inl (f a) | Inr (g a)
+
+newtype Buggy f m = Buggy { thing :: m Int }
+
+class GhcBug f where
+  demo :: MonadState (Buggy f m) m => f (m Int) -> m Int
+
+instance (GhcBug f, GhcBug g) => GhcBug (f :+: g) where
+    demo (Inl l) = demo l
+    demo (Inr r) = demo r


=====================================
testsuite/tests/typecheck/should_fail/T25325.stderr
=====================================
@@ -0,0 +1,15 @@
+T25325.hs:14:20: error: [GHC-39999]
+    • Could not deduce ‘MonadState (Buggy g m) m’
+        arising from a use of ‘demo’
+      from the context: (GhcBug f, GhcBug g)
+        bound by the instance declaration at T25325.hs:12:10-49
+      or from: MonadState (Buggy (f :+: g) m) m
+        bound by the type signature for:
+                   demo :: forall (m :: * -> *).
+                           MonadState (Buggy (f :+: g) m) m =>
+                           (:+:) f g (m Int) -> m Int
+        at T25325.hs:13:5-8
+    • In the expression: demo r
+      In an equation for ‘demo’: demo (Inr r) = demo r
+      In the instance declaration for ‘GhcBug (f :+: g)’
+


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -702,3 +702,4 @@ test('T22684', normal, compile_fail, [''])
 test('T23776', normal, compile, ['']) # to become an error in GHC 9.12
 test('T17940', normal, compile_fail, [''])
 test('T24279', normal, compile_fail, [''])
+test('T25325', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/05152a5765a6a52fda14f1a1f2c8e735b86c7522...a3a6da7e757002a60553416ed61c299d504e3865

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/05152a5765a6a52fda14f1a1f2c8e735b86c7522...a3a6da7e757002a60553416ed61c299d504e3865
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:59:35 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 11:59:35 -0400
Subject: [Git][ghc/ghc][wip/T23479] 6 commits: hadrian: Handle broken symlinks
 properly when creating source dist directories
Message-ID: <670d3fe753d7b_21621822ede02442@gitlab.mail>



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


Commits:
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
d2504bf5 by Serge S. Gulin at 2024-10-14T18:58:13+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


30 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2270360b840c7d248f33e56df0c4dfb438afade7...d2504bf5e4364f0635c3cb6092b2b6a291c6bbf6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2270360b840c7d248f33e56df0c4dfb438afade7...d2504bf5e4364f0635c3cb6092b2b6a291c6bbf6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 15:59:38 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 11:59:38 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] Compatibility with 9.8.1 as boot
 compiler
Message-ID: <670d3fea264bc_2162182493ac24618@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
2e6704de by Matthew Pickering at 2024-10-14T11:59:27-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24605

(cherry picked from commit ef3d20f83499cf129b1cacac07906b8d6188fc17)

- - - - -


2 changed files:

- hadrian/cabal.project
- hadrian/hadrian.cabal


Changes:

=====================================
hadrian/cabal.project
=====================================
@@ -1,7 +1,7 @@
 packages: ./
 
 -- This essentially freezes the build plan for hadrian
-index-state: 2023-03-30T10:00:00Z
+index-state: 2024-05-01T10:00:00Z
 
 -- N.B. Compile with -O0 since this is not a performance-critical executable
 -- and the Cabal takes nearly twice as long to build with -O1. See #16817.


=====================================
hadrian/hadrian.cabal
=====================================
@@ -151,7 +151,7 @@ executable hadrian
                        , TypeOperators
     other-extensions:    MultiParamTypeClasses
                        , TypeFamilies
-    build-depends:       Cabal                >= 3.2     && < 3.9
+    build-depends:       Cabal                >= 3.2     && < 3.11
                        , base                 >= 4.11    && < 5
                        , bytestring           >= 0.10    && < 0.13
                        , containers           >= 0.5     && < 0.7



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e6704deebd2f9f6707cfde25d22146934a69ad3

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 16:18:24 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 12:18:24 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] Revert "NCG: Fix a bug in jump
 shortcutting."
Message-ID: <670d445015dea_216218436fac306fb@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
a5ce5c45 by Ben Gamari at 2024-10-14T12:18:06-04:00
Revert "NCG: Fix a bug in jump shortcutting."

This commit was wrong, as noted in the `master` revert cfeb70d3fed9c135295359296208bd800bab418f.
It appears to have ultimately been superceded by 0fe2b410ac0d8951f07ffcc9f3c6c97bc312df48
which is already present in `ghc-9.8`.

This reverts commit 44e119c9b7622f76b1b7e8d22548376b2591402d.

- - - - -


9 changed files:

- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -322,20 +322,15 @@ isJumpishInstr instr = case instr of
 -- | Checks whether this instruction is a jump/branch instruction.
 -- One that can change the flow of control in a way that the
 -- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [Maybe BlockId]
+jumpDestsOfInstr :: Instr -> [BlockId]
 jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i
-jumpDestsOfInstr i = case i of
-    (CBZ _ t) -> [ mkDest t ]
-    (CBNZ _ t) -> [ mkDest t ]
-    (J t) -> [ mkDest t ]
-    (B t) -> [ mkDest t ]
-    (BL t _ _) -> [ mkDest t ]
-    (BCOND _ t) -> [ mkDest t ]
-    _ -> []
-  where
-    mkDest (TBlock id) = Just id
-    mkDest TLabel{} = Nothing
-    mkDest TReg{} = Nothing
+jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (J t) = [id | TBlock id <- [t]]
+jumpDestsOfInstr (B t) = [id | TBlock id <- [t]]
+jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]]
+jumpDestsOfInstr _ = []
 
 canFallthroughTo :: Instr -> BlockId -> Bool
 canFallthroughTo (ANN _ i) bid = canFallthroughTo i bid


=====================================
compiler/GHC/CmmToAsm/BlockLayout.hs
=====================================
@@ -777,7 +777,6 @@ dropJumps :: forall a i. Instruction i => LabelMap a -> [GenBasicBlock i]
 dropJumps _    [] = []
 dropJumps info (BasicBlock lbl ins:todo)
     | Just ins <- nonEmpty ins --This can happen because of shortcutting
-    , [Just _dest] <- jumpDestsOfInstr (NE.last ins)
     , BasicBlock nextLbl _ : _ <- todo
     , canFallthroughTo (NE.last ins) nextLbl
     , not (mapMember nextLbl info)
@@ -876,7 +875,7 @@ mkNode edgeWeights block@(BasicBlock id instrs) =
               | length successors > 2 || edgeWeight info <= 0 -> []
               | otherwise -> [target]
           | Just instr <- lastMaybe instrs
-          , [one] <- jumpBlockDestsOfInstr instr
+          , [one] <- jumpDestsOfInstr instr
           = [one]
           | otherwise = []
 


=====================================
compiler/GHC/CmmToAsm/Instr.hs
=====================================
@@ -17,8 +17,6 @@ import GHC.Cmm.BlockId
 import GHC.CmmToAsm.Config
 import GHC.Data.FastString
 
-import Data.Maybe (catMaybes)
-
 -- | Holds a list of source and destination registers used by a
 --      particular instruction.
 --
@@ -75,18 +73,9 @@ class Instruction instr where
 
         -- | Give the possible *local block* destinations of this jump instruction.
         --      Must be defined for all jumpish instructions.
-        --      Returns Nothing for non BlockId destinations.
         jumpDestsOfInstr
-                :: instr -> [Maybe BlockId]
-
-        -- | Give the possible block destinations of this jump instruction.
-        --      Must be defined for all jumpish instructions.
-        jumpBlockDestsOfInstr
                 :: instr -> [BlockId]
 
-        jumpBlockDestsOfInstr = catMaybes . jumpDestsOfInstr
-
-
         -- | Check if the instr always transfers control flow
         -- to the given block. Used by code layout to eliminate
         -- jumps that can be replaced by fall through.


=====================================
compiler/GHC/CmmToAsm/PPC/Instr.hs
=====================================
@@ -522,15 +522,12 @@ canFallthroughTo instr bid
 -- | Checks whether this instruction is a jump/branch instruction.
 -- One that can change the flow of control in a way that the
 -- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [Maybe BlockId]
+jumpDestsOfInstr :: Instr -> [BlockId]
 jumpDestsOfInstr insn
   = case insn of
-        BCC _ id _       -> [Just id]
-        BCCFAR _ id _    -> [Just id]
-        BCTR targets _ _ -> targets
-        BCTRL{}          -> [Nothing]
-        BL{}             -> [Nothing]
-        JMP{}            -> [Nothing]
+        BCC _ id _       -> [id]
+        BCCFAR _ id _    -> [id]
+        BCTR targets _ _ -> [id | Just id <- targets]
         _                -> []
 
 


=====================================
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
=====================================
@@ -207,7 +207,7 @@ cleanForward platform blockId assoc acc (li : instrs)
 
         -- Remember the association over a jump.
         | LiveInstr instr _     <- li
-        , targets               <- jumpBlockDestsOfInstr instr
+        , targets               <- jumpDestsOfInstr instr
         , not $ null targets
         = do    mapM_ (accJumpValid assoc) targets
                 cleanForward platform blockId assoc (li : acc) instrs
@@ -386,7 +386,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs)
         --       it always does, but if those reloads are cleaned the slot
         --       liveness map doesn't get updated.
         | LiveInstr instr _     <- li
-        , targets               <- jumpBlockDestsOfInstr instr
+        , targets               <- jumpDestsOfInstr instr
         = do
                 let slotsReloadedByTargets
                         = IntSet.unions


=====================================
compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
=====================================
@@ -57,7 +57,7 @@ joinToTargets block_live id instr
         = return ([], instr)
 
         | otherwise
-        = joinToTargets' block_live [] id instr (jumpBlockDestsOfInstr instr)
+        = joinToTargets' block_live [] id instr (jumpDestsOfInstr instr)
 
 -----
 joinToTargets'


=====================================
compiler/GHC/CmmToAsm/Reg/Liveness.hs
=====================================
@@ -480,7 +480,7 @@ slurpReloadCoalesce live
 
                 -- if we hit a jump, remember the current slotMap
                 | LiveInstr (Instr instr) _     <- li
-                , targets                       <- jumpBlockDestsOfInstr instr
+                , targets                       <- jumpDestsOfInstr instr
                 , not $ null targets
                 = do    mapM_   (accSlotMap slotMap) targets
                         return  (slotMap, Nothing)
@@ -772,7 +772,7 @@ sccBlocks blocks entries mcfg = map (fmap node_payload) sccs
         sccs = stronglyConnCompG g2
 
         getOutEdges :: Instruction instr => [instr] -> [BlockId]
-        getOutEdges instrs = concatMap jumpBlockDestsOfInstr instrs
+        getOutEdges instrs = concatMap jumpDestsOfInstr instrs
 
         -- This is truly ugly, but I don't see a good alternative.
         -- Digraph just has the wrong API.  We want to identify nodes
@@ -849,7 +849,7 @@ checkIsReverseDependent sccs'
 
         slurpJumpDestsOfBlock (BasicBlock _ instrs)
                 = unionManyUniqSets
-                $ map (mkUniqSet . jumpBlockDestsOfInstr)
+                $ map (mkUniqSet . jumpDestsOfInstr)
                         [ i | LiveInstr i _ <- instrs]
 
 
@@ -1057,7 +1057,7 @@ liveness1 platform liveregs blockmap (LiveInstr instr _)
 
             -- union in the live regs from all the jump destinations of this
             -- instruction.
-            targets      = jumpBlockDestsOfInstr instr -- where we go from here
+            targets      = jumpDestsOfInstr instr -- where we go from here
             not_a_branch = null targets
 
             targetLiveRegs target


=====================================
compiler/GHC/CmmToAsm/X86/Instr.hs
=====================================
@@ -679,16 +679,13 @@ canFallthroughTo insn bid
 
 jumpDestsOfInstr
         :: Instr
-        -> [Maybe BlockId]
+        -> [BlockId]
 
 jumpDestsOfInstr insn
   = case insn of
-        JXX _ id        -> [Just id]
-        JMP_TBL _ ids _ _ -> [(mkDest dest) | Just dest <- ids]
+        JXX _ id        -> [id]
+        JMP_TBL _ ids _ _ -> [id | Just (DestBlockId id) <- ids]
         _               -> []
-    where
-      mkDest (DestBlockId id) = Just id
-      mkDest _ = Nothing
 
 
 patchJumpInstr


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -247,5 +247,3 @@ test('T23034', req_c, compile_and_run, ['-O2 T23034_c.c'])
 test('T24664a', normal, compile_and_run, ['-O'])
 test('T24664b', normal, compile_and_run, ['-O'])
 
-test('T24507', [req_cmm], multi_compile_and_run,
-                 ['T24507', [('T24507_cmm.cmm', '')], '-O2'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 16:20:28 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 12:20:28 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes 23479 (muted temporary))
Message-ID: <670d44cc8aee5_2162187a7f88310fe@gitlab.mail>



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


Commits:
63ff5e81 by Serge S. Gulin at 2024-10-14T19:19:58+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


24 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- + testsuite/tests/javascript/T23479_3.hs
- + testsuite/tests/javascript/T23479_3.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,32 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    -- Test case T23479_3 (rewrite required)
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -7,3 +7,21 @@ T24495:
 	./T24495
 	# check that the optimization occurred
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	# check that the optimization occurred
+	grep -c "h\$$decodeUtf8z" T23479_2.dump-js
+
+T23479_3:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_3.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_3
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_3.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE MagicHash #-}
+
+import GHC.Prim
+
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## test_addr_1))
+  where
+    test_addr_1 :: Addr#
+    test_addr_1 = "test_val_1"#


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_1
+1


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,14 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+main :: IO ()
+main = do
+  js_log1 $ toJSString test_val_2


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_2
+1


=====================================
testsuite/tests/javascript/T23479_3.hs
=====================================
@@ -0,0 +1,14 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  js_log1 (toJSString test_val_3)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"


=====================================
testsuite/tests/javascript/T23479_3.stdout
=====================================
@@ -0,0 +1,2 @@
+test_val_3
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,7 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])
+test('T23479_3', normal, makefile_test, ['T23479_3'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/63ff5e8157a9f845235016697fa318a7112d7f2f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 16:29:28 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 12:29:28 -0400
Subject: [Git][ghc/ghc][wip/T23479] test
Message-ID: <670d46e85e7fa_216218a48a5833870@gitlab.mail>



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


Commits:
502a6a23 by Serge S. Gulin at 2024-10-14T19:29:19+03:00
test

- - - - -


1 changed file:

- testsuite/tests/javascript/Makefile


Changes:

=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -18,7 +18,7 @@ T23479_2:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T23479_2
 	# check that the optimization occurred
-	grep -c "h\$$decodeUtf8z" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_2.dump-js
 
 T23479_3:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_3.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/502a6a236ccebe529f753023191a687726839192

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 16:36:59 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 12:36:59 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] hadrian: Update bootstrap plans
Message-ID: <670d48ab8e6ad_216218b42b0c364c1@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
1f43950e by Ben Gamari at 2024-10-14T12:36:03-04:00
hadrian: Update bootstrap plans

- - - - -


4 changed files:

- hadrian/bootstrap/plan-9_4_1.json
- hadrian/bootstrap/plan-9_4_2.json
- hadrian/bootstrap/plan-9_4_3.json
- hadrian/bootstrap/plan-9_4_4.json


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f43950e3e5198a1119441f7e3677a7cd20226ea

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 16:58:08 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 12:58:08 -0400
Subject: [Git][ghc/ghc][wip/T23479] test
Message-ID: <670d4da05006b_216218eacce83764f@gitlab.mail>



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


Commits:
e50ef194 by Serge S. Gulin at 2024-10-14T19:57:52+03:00
test

- - - - -


8 changed files:

- compiler/GHC/StgToJS/Apply.hs
- testsuite/tests/javascript/Makefile
- testsuite/tests/javascript/T23479_1.hs
- testsuite/tests/javascript/T23479_1.stdout
- − testsuite/tests/javascript/T23479_2.hs
- − testsuite/tests/javascript/T23479_2.stdout
- − testsuite/tests/javascript/T23479_3.hs
- − testsuite/tests/javascript/T23479_3.stdout


Changes:

=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -120,7 +120,6 @@ genApp ctx i args
     = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
 
     -- Test case T23479_1
-    -- Test case T23479_3 (rewrite required)
     | [StgLitArg (LitString bs)] <- args
     , Just d <- decodeModifiedUTF8 bs
     , idName i == unsafeUnpackJSStringUtf8ShShName


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -13,15 +13,7 @@ T23479_1:
 	./T23479_1
 	# check that the optimization occurred
 	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
-
-T23479_2:
-	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
-	./T23479_2
-	# check that the optimization occurred
-	grep -c "h\$$r1 = \"test_val_2\"" T23479_2.dump-js
-
-T23479_3:
-	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_3.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
-	./T23479_3
-	# check that the optimization occurred
-	grep -c "h\$$r1 = \"test_val_3\"" T23479_3.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -1,15 +1,33 @@
 {-# LANGUAGE MagicHash #-}
+module Main where
 
 import GHC.Prim
-
 import GHC.JS.Prim
 
 foreign import javascript "((x) => { console.log(x); })"
   js_log1 :: JSVal -> IO ()
 
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+test_val_80_global :: String
+test_val_80_global = "test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val"
+
 main :: IO ()
 main = do
-  js_log1 (JSVal (unsafeUnpackJSStringUtf8## test_addr_1))
+  -- Direct usage
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## "test_val_1"#))
+  -- Requires string sinker hit for strings shorter 80 symbols
+  js_log1 (toJSString test_val_2)
+  -- Requires rewrite hit "toJSString/literal"
+  js_log1 (toJSString test_val_3)
+  -- Locally defined strings become unfloatted at any length
+  js_log1 (toJSString test_val_80_local)
+  -- Globally defined strings with length >= 80 should not be unfloatted
+  js_log1 (toJSString test_val_80_global)
   where
-    test_addr_1 :: Addr#
-    test_addr_1 = "test_val_1"#
+    test_val_3 :: String
+    test_val_3 = "test_val_3"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -1,2 +1,10 @@
 test_val_1
+test_val_2
+test_val_3
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val
 1
+1
+1
+1
+0


=====================================
testsuite/tests/javascript/T23479_2.hs deleted
=====================================
@@ -1,14 +0,0 @@
-module Main where
-
-import GHC.Prim
-import GHC.JS.Prim
-
-foreign import javascript "((x) => { console.log(x); })"
-  js_log1 :: JSVal -> IO ()
-
-test_val_2 :: String
-test_val_2 = "test_val_2"
-
-main :: IO ()
-main = do
-  js_log1 $ toJSString test_val_2


=====================================
testsuite/tests/javascript/T23479_2.stdout deleted
=====================================
@@ -1,2 +0,0 @@
-test_val_2
-1


=====================================
testsuite/tests/javascript/T23479_3.hs deleted
=====================================
@@ -1,14 +0,0 @@
-module Main where
-
-import GHC.Prim
-import GHC.JS.Prim
-
-foreign import javascript "((x) => { console.log(x); })"
-  js_log1 :: JSVal -> IO ()
-
-main :: IO ()
-main = do
-  js_log1 (toJSString test_val_3)
-  where
-    test_val_3 :: String
-    test_val_3 = "test_val_3"


=====================================
testsuite/tests/javascript/T23479_3.stdout deleted
=====================================
@@ -1,2 +0,0 @@
-test_val_3
-1



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 17:30:30 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 13:30:30 -0400
Subject: [Git][ghc/ghc][wip/T23479] test
Message-ID: <670d553693711_2162181146abc44986@gitlab.mail>



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


Commits:
a49fed26 by Serge S. Gulin at 2024-10-14T20:30:21+03:00
test

- - - - -


3 changed files:

- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout


Changes:

=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -16,4 +16,12 @@ T23479_1:
 	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
 	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
 	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
-	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js || true
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local_once" T23479_2.dump-js
+	# check that the optimization occurred
+	grep -c "h\$$r1 = h\$$decodeUtf8z" T23479_2.dump-js


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  -- When long string (>= 80) used once it is unfloatted
+  js_log1 (toJSString test_val_80_local_once)
+
+  -- When long string (>= 80) used more than once no unfloatting happened
+  js_log1 (toJSString test_val_80_local)
+  js_log1 (toJSString (testFn80 "testFn80:"))
+
+  -- Even if short string used more than once it is unfloatted anyway
+  js_log1 (toJSString test_val_1)
+  js_log1 (toJSString (testFn "testFn:"))
+  where
+    test_val_80_local_once :: String
+    test_val_80_local_once = "test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"
+
+    testFn80 s = s ++ test_val_80_local
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn80 #-}
+
+    test_val_1 :: String
+    test_val_1 = "test_val_1"
+
+    testFn s = s ++ test_val_1
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn #-}


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,8 @@
+test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+testFn80:test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_1
+testFn:test_val_1
+1
+1
+1



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 18:51:10 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 14:51:10 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25374
Message-ID: <670d681ec47c1_79c317924c588bd@gitlab.mail>



Ben Gamari pushed new branch wip/T25374 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25374
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 18:54:11 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 14:54:11 -0400
Subject: [Git][ghc/ghc][wip/T23210] 5057 commits: [haddock @ 2002-04-04
 16:23:43 by simonmar]
Message-ID: <670d68d341bfc_79c3ed17063259@gitlab.mail>



Ben Gamari pushed to branch wip/T23210 at Glasgow Haskell Compiler / GHC


Commits:
2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00
[haddock @ 2002-04-04 16:23:43 by simonmar]
This is Haddock, my stab at a Haskell documentation tool.  It's not
quite ready for release yet, but I'm putting it in the repository so
others can take a look.

It uses a locally modified version of the hssource parser, extended
with support for GHC extensions and documentation annotations.

- - - - -
99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00
[haddock @ 2002-04-04 16:24:10 by simonmar]
forgot one file

- - - - -
8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00
[haddock @ 2002-04-05 13:58:15 by simonmar]
Remap names in the exported declarations to be "closer" to the current
module.  eg. if an exported declaration mentions a type 'T' which is
imported from module A then re-exported from the current module, then
links from the type or indeed the documentation will point to the
current module rather than module A.

This is to support better hiding: module A won't be referred to in the
generated output.

- - - - -
1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00
[haddock @ 2002-04-05 13:58:23 by simonmar]
update the TODO list

- - - - -
3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00
[haddock @ 2002-04-05 14:11:51 by simonmar]
Fix the anchor for a class declaration

- - - - -
c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00
[haddock @ 2002-04-05 14:18:41 by simonmar]
remove underlines on visited links

- - - - -
97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00
[haddock @ 2002-04-05 16:11:47 by simonmar]
- Update to generate more correct HTML.

- Use our own non-overloaded table combinators, as the overloaded
  versions were giving me a headache.  The improved type safety
  caught several errors in the HTML generation.

- - - - -
9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00
[haddock @ 2002-04-05 16:32:19 by simonmar]
Add width property to the title, and add TD.children for the module
contents page.

- - - - -
ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00
[haddock @ 2002-04-08 16:39:56 by simonmar]
Fix a problem with exports of the form T(..).

- - - - -
e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00
[haddock @ 2002-04-08 16:41:37 by simonmar]
- Add our own versions of Html & BlockTable for the time being.
- Add support for generating an index to the HTML backend

- - - - -
2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00
[haddock @ 2002-04-09 11:23:24 by simonmar]
Add '-- /' as a synonym for '-- |', for compatibility with IDoc.

- - - - -
3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00
[haddock @ 2002-04-09 11:33:54 by simonmar]
- add the <...> syntax for marking up URLs in documentation

- Make the output for data & class declarations more compact when
  there aren't any documentation annotations on the individual
  methods or constructors respectively.

- - - - -
5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00
[haddock @ 2002-04-09 11:36:04 by simonmar]
Update the TODO list

- - - - -
9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00
[haddock @ 2002-04-10 10:50:06 by simonmar]
Use explicit 'px' suffix on pixel sizes; IE seems to prefer them

- - - - -
052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00
[haddock @ 2002-04-10 13:23:13 by simonmar]
Lex URLs as a single token to avoid having to escape special
characters inside the URL string.

- - - - -
47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00
[haddock @ 2002-04-10 13:23:55 by simonmar]
Not sure why I made the constructor name for a record declaration into
a TyCls name, but change it back into a Var name anyhow.

- - - - -
3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00
[haddock @ 2002-04-10 13:26:09 by simonmar]
Lots of changes, including:

- add index support to the HTML backend
- clean up the renamer, put it into a monad
- propogate unresolved names to the top level and report them in a nicer way
- various bugfixes

- - - - -
c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00
[haddock @ 2002-04-10 13:32:39 by simonmar]
Skeleton documentation

- - - - -
50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00
[haddock @ 2002-04-10 13:37:23 by simonmar]
Update the TODO list, separate into pre-1.0 and post-1.0 items

- - - - -
f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00
[haddock @ 2002-04-10 14:30:58 by simonmar]
Add an introduction

- - - - -
cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00
[haddock @ 2002-04-10 14:59:51 by simonmar]
Sort the module tree

- - - - -
76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00
[haddock @ 2002-04-10 15:50:10 by simonmar]
Generate a little table of contents at the top of the module doc (only
if the module actually contains some section headings, though).

- - - - -
bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00
[haddock @ 2002-04-10 16:10:26 by simonmar]
Now we understand (or at least don't barf on) type signatures in
patterns such as you might find when scoped type variables are in use.

- - - - -
86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00
[haddock @ 2002-04-10 16:10:49 by simonmar]
more updates

- - - - -
1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00
[haddock @ 2002-04-10 16:28:05 by simonmar]
Parse errors in doc strings are now reported as warnings rather that
causing the whole thing to fall over.  It still needs cleaning up (the
warning is emitted with trace) but this will do for the time being.

- - - - -
ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00
[haddock @ 2002-04-10 16:38:03 by simonmar]
update again

- - - - -
69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00
[haddock @ 2002-04-11 13:38:02 by simonmar]
mention Opera

- - - - -
fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00
[haddock @ 2002-04-11 13:40:30 by simonmar]
- copy haddock.css into the same place as the generated HTML

- new option: --css <file>  specifies the style sheet to use

- new option:  -o <dir>  specifies the directory in which to
  generate the output.

- because Haddock now needs to know where to find its default stylesheet,
  we have to have a wrapper script and do the haddock-inplace thing
  (Makefile code copied largely from fptools/happy).

- - - - -
106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00
[haddock @ 2002-04-24 15:12:41 by simonmar]
Stop slurping comment lines when we see a row of dashes longer than
length 2: these are useful as separators.

- - - - -
995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00
[haddock @ 2002-04-24 15:14:11 by simonmar]
Grok the kind of module headers we use in fptools/libraries, and pass
the "portability", "stability", and "maintainer" strings through into
the generated HTML.  If the module header doesn't match the pattern,
then we don't include the info in the HTML.

- - - - -
e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00
[haddock @ 2002-04-24 15:16:57 by simonmar]
Done module headers now.

- - - - -
2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00
[haddock @ 2002-04-24 15:57:47 by simonmar]
Handle gcons in export lists (a common extension).

- - - - -
044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00
[haddock @ 2002-04-25 14:20:12 by simonmar]
Add the little lambda icon

- - - - -
63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00
[haddock @ 2002-04-25 14:40:05 by simonmar]
- Add support for named chunks of documentation which can be
  referenced from the export list.

- Copy the icon from $libdir to the destination in HTML mode.

- - - - -
36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00
[haddock @ 2002-04-25 16:48:36 by simonmar]
More keyboard bashing

- - - - -
7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00
[haddock @ 2002-04-26 08:43:33 by simonmar]
Package util reqd. to compile with 4.08.2

- - - - -
bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00
[haddock @ 2002-04-26 10:13:00 by simonmar]
Include $(GHC_HAPPY_OPTS) when compiling HsParser

- - - - -
31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00
[haddock @ 2002-04-26 11:18:56 by simonmar]
- support for fundeps (partially contributed by Brett Letner - thanks
  Brett).

- make it build with GHC 4.08.2

- - - - -
c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00
[haddock @ 2002-04-26 13:15:02 by simonmar]
Move the explicit formatting of the little table for the
stability/portability/maintainer info from the HTML into the CSS, and
remove the explicit table size (just right-align it).

- - - - -
520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00
[haddock @ 2002-04-26 16:01:44 by simonmar]
Yet more keyboard bashing - this is pretty much complete now.

- - - - -
2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00
[haddock @ 2002-04-26 16:02:14 by simonmar]
Add a couple of things I forgot about

- - - - -
b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00
[haddock @ 2002-04-29 15:28:12 by simonmar]
bugfix for declBinders on a NewTypeDecl

- - - - -
640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00
[haddock @ 2002-04-29 15:28:54 by simonmar]
Allow '-- |' style annotations on constructors and record fields.

- - - - -
393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00
[haddock @ 2002-04-29 15:37:32 by simonmar]
syntax fix

- - - - -
8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00
[haddock @ 2002-04-29 15:37:48 by simonmar]
Add an example

- - - - -
db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00
[haddock @ 2002-04-29 15:55:46 by simonmar]
remove a trace

- - - - -
2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00
[haddock @ 2002-04-29 15:56:19 by simonmar]
Fix for 'make install'

- - - - -
120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00
[haddock @ 2002-04-29 15:56:39 by simonmar]
Install the auxilliary bits

- - - - -
950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00
[haddock @ 2002-04-29 15:57:30 by simonmar]
Add BinDist bits

- - - - -
154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00
[haddock @ 2002-05-01 11:02:52 by simonmar]
update

- - - - -
ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00
[haddock @ 2002-05-01 11:03:26 by simonmar]
Add another item

- - - - -
bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00
[haddock @ 2002-05-03 08:50:00 by simonmar]
Fix some typos.

- - - - -
54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00
[haddock @ 2002-05-05 19:40:51 by panne]
As a temporary hack/workaround for a bug in GHC's simplifier, don't
pass Happy the -c option for generating the parsers in this
subdir. Furthermore, disable -O for HaddocParse, too.

- - - - -
e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00
[haddock @ 2002-05-06 09:51:10 by simonmar]
Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>)

- - - - -
7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00
[haddock @ 2002-05-06 12:29:26 by simonmar]
Add missing type signature (a different workaround for the bug in
GHC's simplifier).

- - - - -
cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00
[haddock @ 2002-05-06 12:30:09 by simonmar]
Remove workaround for simplifier bug in previous revision.

- - - - -
687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00
[haddock @ 2002-05-06 12:32:32 by simonmar]
Allow empty data declarations (another GHC extension).

- - - - -
8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00
[haddock @ 2002-05-06 12:49:21 by simonmar]
Fix silly bug in named documentation block lookup.

- - - - -
8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00
[haddock @ 2002-05-06 13:02:42 by simonmar]
Add another named chunk with a different name

- - - - -
68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00
[haddock @ 2002-05-06 13:32:32 by simonmar]
Be more lenient about extra paragraph breaks

- - - - -
65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00
[haddock @ 2002-05-07 15:36:36 by simonmar]
DocEmpty is a right and left-unit of DocAppend (remove it in the smart
constructor).

- - - - -
adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00
[haddock @ 2002-05-07 15:37:15 by simonmar]
Allow code blocks to be denoted with bird-tracks in addition to [...].

- - - - -
1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00
[haddock @ 2002-05-08 11:21:56 by simonmar]
Add a facility for specifying options that affect Haddock's treatment
of the module.  Options are given at the top of the module in a
comma-separated list, beginning with '-- #'.  eg.

	-- # prune, hide, ignore-exports

Options currently available, with their meanings:

  prune:
	ignore declarations which have no documentation annotations

  ignore-exports:
	act as if the export list were not specified (i.e. export
   	everything local to the module).

  hide:
	do not include this module in the generated documentation, but
 	propagate any exported definitions to modules which re-export
	them.

There's a slight change in the semantics for re-exporting a full
module by giving 'module M' in the export list: if module M does not
have the 'hide' option, then the documentation will now just contain a
reference to module M rather than the full inlined contents of that
module.

These features, and some other changes in the pipeline, are the result
of discussions between myself and Manuel Chakravarty
<chak at cse.unsw.edu.au> (author of IDoc) yesterday.

Also: some cleanups, use a Writer monad to collect error messages in
some places instead of just printing them with trace.

- - - - -
a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00
[haddock @ 2002-05-08 11:22:30 by simonmar]
Update to test new features.

- - - - -
6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00
[haddock @ 2002-05-08 13:37:25 by simonmar]
Change the markup for typewriter-font from [...] to @... at .  The
reasoning is that the '@' symbol is much less likely to be needed than
square brackets, and we don't want to have to escape square brackets
in code fragments.

This will be mildly painful in the short term, but it's better to get
the change out of the way as early as possible.

- - - - -
cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00
[haddock @ 2002-05-08 13:39:56 by simonmar]
Allow nested-style comments to be used as documentation annotations too. eg.

	{-| ... -}

is equivalent to

	-- | ...

An extra space can also be left after the comment opener: {- | ... -}.
The only version that isn't allowed is {-# ... -}, because this syntax
overlaps with Haskell pragmas;  use {- # ... -} instead.

- - - - -
db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00
[haddock @ 2002-05-08 14:48:39 by simonmar]
Add support for existential quantifiers on constructors.

- - - - -
adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00
[haddock @ 2002-05-08 15:43:25 by simonmar]
update

- - - - -
62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00
[haddock @ 2002-05-08 15:44:10 by simonmar]
Update to version 0.2

- - - - -
f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00
[haddock @ 2002-05-09 08:48:29 by simonmar]
typo

- - - - -
9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00
[haddock @ 2002-05-09 10:33:14 by simonmar]
oops, left out '/' from the special characters in the last change.

- - - - -
14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00
[haddock @ 2002-05-09 10:34:44 by simonmar]
Fix buglet

- - - - -
b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00
[haddock @ 2002-05-09 10:35:00 by simonmar]
Give a more useful instance of Show for Module.

- - - - -
f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00
[haddock @ 2002-05-09 10:37:07 by simonmar]
The last commit to Main.lhs broke the delicate balance of laziness
which was being used to avoid computing the dependency graph of
modules.

So I finally bit the bullet and did a proper topological sort of the
module graph, which turned out to be easy (stealing the Digraph module
from GHC - this really ought to be in the libraries somewhere).

- - - - -
b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00
[haddock @ 2002-05-09 10:37:25 by simonmar]
another item done

- - - - -
032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00
[haddock @ 2002-05-09 10:44:15 by simonmar]
Don't consider a module re-export as having documentation, for the
purposes of deciding whether we need a Synopsis section or not.

- - - - -
5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00
[haddock @ 2002-05-09 11:10:55 by simonmar]
Add a special case for list types in ppHsAType

- - - - -
1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00
[haddock @ 2002-05-09 12:43:06 by simonmar]
Type synonyms can accept a ctype on the RHS, to match GHC.

- - - - -
0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00
[haddock @ 2002-05-09 12:45:19 by simonmar]
Add 'stdcall' keyword

- - - - -
29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00
[haddock @ 2002-05-09 13:35:45 by simonmar]
Add System Requirements section

- - - - -
bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00
[haddock @ 2002-05-09 13:36:11 by simonmar]
Test existential types, amongst other things

- - - - -
502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00
[haddock @ 2002-05-09 13:37:35 by simonmar]
Print the module name in a doc-string parse error

- - - - -
ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00
[haddock @ 2002-05-09 13:38:04 by simonmar]
Add dependency

- - - - -
8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00
[haddock @ 2002-05-09 15:37:57 by simonmar]
Add the changelog/release notes

- - - - -
f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00
[haddock @ 2002-05-09 15:47:47 by simonmar]
mention the backquote-style of markup

- - - - -
089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00
[haddock @ 2002-05-09 15:59:45 by simonmar]
update

- - - - -
bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00
[haddock @ 2002-05-09 15:59:56 by simonmar]
Document changes since 0.1

- - - - -
00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00
[haddock @ 2002-05-10 08:22:48 by simonmar]
oops, update to version 0.2

- - - - -
a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00
[haddock @ 2002-05-10 16:05:08 by simonmar]
Only include a mini-contents if there are 2 or more sections

- - - - -
06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00
[haddock @ 2002-05-13 09:13:12 by simonmar]
fix typos

- - - - -
1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00
[haddock @ 2002-05-13 10:14:22 by simonmar]
Allow backquote as the right-hand quote as well as the left-hand
quote, as suggested by Dean Herrington.

Clean up the grammar a litte.

- - - - -
dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00
[haddock @ 2002-05-13 10:44:10 by simonmar]
a couple more things, prioritise a bit

- - - - -
a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00
[haddock @ 2002-05-13 15:19:03 by simonmar]
Cope with datatypes which have documentation on the constructor but
not the type itself, and records which have documentation on the
fields but not the constructor.  (Thanks to Ross Paterson for pointing
out the bugs).

- - - - -
a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00
[haddock @ 2002-05-13 15:20:54 by simonmar]
Fix one of the record examples

- - - - -
2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00
[haddock @ 2002-05-15 12:44:35 by simonmar]
Preserve the newline before a bird-track, but only within a paragraph.

- - - - -
1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00
[haddock @ 2002-05-15 13:03:01 by simonmar]
Reworking of the internals to support documenting function arguments
(the Most Wanted new feature by the punters).

The old method of keeping parsed documentation in a Name -> Doc
mapping wasn't going to cut it for anntations on type components,
where there's no name to attach the documentation to, so I've moved to
storing all the documentation in the abstract syntax.  Previously some
of the documentation was left in the abstract syntax by the parser,
but was later extracted into the mapping.

In order to avoid having to parameterise the abstract syntax over the
type of documentation stored in it, we have to parse the documentation
at the same time as we parse the Haskell source (well, I suppose we
could store 'Either String Doc' in the HsSyn, but that's clunky).  One
upshot is that documentation is now parsed eagerly, and documentation
parse errors are fatal (but have better line numbers in the error
message).

The new story simplifies matters for the code that processes the
source modules, because we don't have to maintain the extra Name->Doc
mapping, and it should improve efficiency a little too.

New features:

  - Function arguments and return values can now have doc annotations.

  - If you refer to a qualified name in a doc string, eg. 'IO.putStr',
    then Haddock will emit a hyperlink even if the identifier is not
    in scope, so you don't have to make sure everything referred to
    from the documentation is imported.

  - several bugs & minor infelicities fixed.

- - - - -
57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00
[haddock @ 2002-05-15 13:03:19 by simonmar]
Bump to version 0.3

- - - - -
b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00
[haddock @ 2002-05-15 13:03:41 by simonmar]
update

- - - - -
fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00
[haddock @ 2002-05-15 13:10:15 by simonmar]
Rename Foo.hs to Test.hs, and add a Makefile

- - - - -
b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00
[haddock @ 2002-05-15 13:16:07 by simonmar]
- Remove the note about function argument docs not being implemented

- Note that qualified identifiers can be used to point to entities
  that aren't in scope.

- - - - -
5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00
[haddock @ 2002-05-15 13:28:46 by simonmar]
Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson.

- - - - -
0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00
[haddock @ 2002-05-17 10:51:57 by simonmar]
Fix bugs in qualified name handling (A.B.f was returned as B.f)

- - - - -
10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00
[haddock @ 2002-05-21 10:24:52 by simonmar]
- Use an alternate tabular layout for datatypes, which is more compact
- Fix some problems with the function argument documentation

- - - - -
2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00
[haddock @ 2002-05-21 10:27:40 by simonmar]
add a few more test cases

- - - - -
01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00
[haddock @ 2002-05-21 10:28:33 by simonmar]
Rearrange a bit, and add support for tabular datatype rendering

- - - - -
a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00
[haddock @ 2002-05-27 09:03:51 by simonmar]
Lots of changes:

 - instances of a class are listed with the class, and
   instances involving a datatype are listed with that type.
   Derived instances aren't included at the moment: the calculation
   to find the instance head for a derived instance is non-trivial.

 - some formatting changes; use rows with specified height rather than
   cellspacing in some places.

 - various fixes (source file links were wrong, amongst others)

- - - - -
48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00
[haddock @ 2002-05-27 12:30:37 by simonmar]
- Put function arguments *before* the doc for the function, as suggested
  by Sven Panne.  This looks nicer when the function documentation is
  long.

- Switch to using bold for binders at the definition site, and use
  underline for keywords.  This makes the binder stand out more.

- - - - -
657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00
[haddock @ 2002-05-27 13:19:49 by simonmar]
Fix bug: we weren't renaming HsDocCommentNamed in renameDecl

- - - - -
592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00
[haddock @ 2002-05-27 14:10:27 by simonmar]
Fix some bugs in the rendering of qualified type signatures.

- - - - -
69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00
[haddock @ 2002-05-27 14:36:45 by simonmar]
warning message tweak

- - - - -
16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00
[haddock @ 2002-05-27 14:53:53 by simonmar]
hyperlinked identifiers should be in <tt>

- - - - -
8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00
[haddock @ 2002-05-27 15:56:45 by simonmar]
Do something sensible for modules which don't export anything (except
instances).

- - - - -
9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00
[haddock @ 2002-05-28 10:12:50 by simonmar]
Rename the module documentation properly (bug reported by Sven Panne).

- - - - -
ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00
[haddock @ 2002-05-28 10:13:04 by simonmar]
Add some more test cases

- - - - -
92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00
[haddock @ 2002-05-28 11:17:55 by simonmar]
If an identifier doesn't lex, then just replace it by a DocString.

- - - - -
a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00
[haddock @ 2002-05-28 16:16:19 by simonmar]
Only link to names in the current module which are actually listed in
the documentation.  A name may be exported but not present in the
documentation if it is exported as part of a 'module M' export
specifier.

- - - - -
31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00
[haddock @ 2002-05-28 16:17:11 by simonmar]
update

- - - - -
7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00
[haddock @ 2002-05-28 22:42:08 by sof]
Handle lone occurrences of '/', e.g.,

  -- | This/that.

[did this in the lexer rather than in the parser, as I couldn't
 see a way not to introduce an S/R conflict that way.]

- - - - -
093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00
[haddock @ 2002-05-29 09:09:49 by simonmar]
Back out previous change until we can find a better way to do this.

- - - - -
9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00
[haddock @ 2002-05-29 13:19:06 by simonmar]
Make the markup syntax a little more friendly:

  - single quotes are now interpreted literally unless they surround a
    valid Haskell identifier.  So for example now there's no need to
    escape a single quote used as an apostrophe.

  - text to the right of a bird track is now literal (if you want
    marked-up text in a code block, use @...@).

- - - - -
b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00
[haddock @ 2002-05-29 13:38:51 by simonmar]
Document recent changes to markup syntax

- - - - -
f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00
[haddock @ 2002-05-29 15:27:18 by simonmar]
Include the instances in abstract data types too

- - - - -
613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00
[haddock @ 2002-06-03 13:05:57 by simonmar]
Allow exporting of individual class methods and record selectors.  For
these we have to invent the correct type signature, which we do in the
simplest possible way (i.e. no context reduction nonsense in the class
case).

- - - - -
14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00
[haddock @ 2002-06-03 13:20:00 by simonmar]
Fix linking to qualified names again (thanks to Sven Panne for
pointing out the bug).

- - - - -
95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00
[haddock @ 2002-06-03 13:46:48 by simonmar]
Fix for exporting record selectors from a newtype declaration

- - - - -
272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00
[haddock @ 2002-06-03 13:56:38 by simonmar]
update to version 0.3

- - - - -
1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00
[haddock @ 2002-06-03 14:05:07 by simonmar]
Add changes in version 0.3

- - - - -
145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00
[haddock @ 2002-06-03 14:12:38 by simonmar]
Render class names as proper binders

- - - - -
052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00
[haddock @ 2002-06-03 14:15:10 by simonmar]
update, and separate into bugs, features, and cosmetic items.

- - - - -
854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00
[haddock @ 2002-06-03 14:16:13 by simonmar]
More test cases

- - - - -
466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00
[haddock @ 2002-06-03 14:16:56 by simonmar]
Example from the paper

- - - - -
9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00
[haddock @ 2002-06-03 14:17:49 by simonmar]
A debugging version of the style-sheet, which gives some tables
coloured backgrounds so we can see what's going on.

- - - - -
f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00
[haddock @ 2002-06-03 14:19:46 by simonmar]
typo

- - - - -
620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00
[haddock @ 2002-06-03 14:48:32 by simonmar]
oops, fix markup bugs

- - - - -
53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00
[haddock @ 2002-06-05 09:05:07 by simonmar]
Keep foreign imports when there is no export list (bug reported by
Sven Panne).

- - - - -
6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00
[haddock @ 2002-06-05 09:12:02 by simonmar]
Identifiers in single quotes can be symbol names too (bug reported by
Hal Daume).

- - - - -
001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00
[haddock @ 2002-06-08 14:03:36 by panne]
Tiny workaround for the fact that Haddock currently ignores
HsImportSpecs: Let the local_orig_env take precedence.
This is no real solution at all, but improves things sometimes,
e.g. in my GLUT documentation.  :-)

- - - - -
504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00
[haddock @ 2002-06-11 09:23:25 by simonmar]
portability nit

- - - - -
e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00
[haddock @ 2002-06-20 12:38:07 by simonmar]
Empty declaration fixes.

- - - - -
f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00
[haddock @ 2002-06-20 12:39:01 by simonmar]
Add support for a "prologue" - a description for the whole library,
placed on the contents page before the module list.

- - - - -
b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00
[haddock @ 2002-06-21 12:43:06 by simonmar]
When we have a single code block paragraph, don't place it in
<pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical
white space in some browsers.

- - - - -
4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00
[haddock @ 2002-06-21 15:50:42 by simonmar]
Add support for reading and writing interface files(!)

This turned out to be quite easy, and necessary to get decent
hyperlinks between the documentation for separate packages in the
libraries.

The functionality isn't quite complete yet: for a given package of
modules, you'd like to say "the HTML for these modules lives in
directory <dir>" (currently they are assumed to be all in the same
place).

Two new flags:

	--dump-interface=FILE   dump an interface file in FILE
	--read-interface=FILE	read interface from FILE

an interface file describes *all* the modules being processed.  Only
the exported names are kept in the interface: if you re-export a name
from a module in another interface the signature won't be copied.
This is a compromise to keep the size of the interfaces sensible.

Also, I added another useful option:

	--no-implicit-prelude

avoids trying to import the Prelude.  Previously this was the default,
but now importing the Prelude from elsewhere makes sense if you also
read in an interface containing the Prelude module, so Haddock imports
the Prelude implicitly according to the Haskell spec.

- - - - -
d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00
[haddock @ 2002-06-23 14:54:00 by panne]
Make it compile with newer GHCs

- - - - -
780c506b by Sven Panne at 2002-06-23T15:44:31+00:00
[haddock @ 2002-06-23 15:44:31 by panne]
Cleaned up build root handling and added more docs

- - - - -
45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00
[haddock @ 2002-06-24 14:37:42 by simonmar]
When reading an interface, allow a file path offset to be specified
which represents the path to the HTML files for the modules specified
by that interface.  The path may be either relative (to the location
of the HTML for this package), or absolute.

The syntax is

	--read-interface=PATH,FILE

where PATH is the path to the HTML, and FILE is the filename
containing the interface.

- - - - -
4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00
[haddock @ 2002-07-03 16:01:07 by simonmar]
Handle import specs properly, include 'hiding'.  Haddock now has a
complete implementation of the Haskell module system (more or less; I
won't claim it's 100% correct).

- - - - -
9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00
[haddock @ 2002-07-03 16:18:16 by simonmar]
Update

- - - - -
560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00
[haddock @ 2002-07-04 14:56:10 by simonmar]
Clean up the code that constructs the exported declarations, and fix a
couple of bugs along the way.  Now if you import a class hiding one of
the methods, then re-export the class, the version in the
documentation will correctly have the appropriate method removed.

- - - - -
2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00
[haddock @ 2002-07-04 15:26:13 by simonmar]
More bugfixes to the export handling

- - - - -
03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00
[haddock @ 2002-07-09 10:12:10 by simonmar]
Don't require that the list type comes from "Prelude" for it to be
treated as special syntax (sometimes it comes from Data.List or maybe
even GHC.Base).

- - - - -
44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00
[haddock @ 2002-07-09 10:12:51 by simonmar]
commented-out debugging code

- - - - -
97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00
[haddock @ 2002-07-09 16:33:31 by krasimir]
'Microsoft HTML Help' support

- - - - -
3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00
[haddock @ 2002-07-10 09:40:56 by simonmar]
Fix for rendering of the (->) type constructor, from Ross Paterson.

- - - - -
c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00
[haddock @ 2002-07-10 10:26:11 by simonmar]
Tweaks to the MS Help support: the extra files are now only generated
if you ask for them (--ms-help).

- - - - -
e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00
[haddock @ 2002-07-10 10:57:10 by simonmar]
Document all the new options since 0.3

- - - - -
8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00
[haddock @ 2002-07-10 10:58:31 by simonmar]
Sort the options a bit

- - - - -
abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00
[haddock @ 2002-07-15 09:19:38 by simonmar]
Fix a bug in mkExportItems when processing a module without an
explicit export list.  We were placing one copy of a declaration for
each binder in the declaration, which for a data type would mean one
copy of the whole declaration per constructor or record selector.

- - - - -
dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00
[haddock @ 2002-07-15 09:54:16 by simonmar]
merge rev. 1.35

- - - - -
bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00
[haddock @ 2002-07-15 10:14:30 by simonmar]
Be a bit more liberal in the kind of commenting styles we allow, as
suggested by Malcolm Wallace.  Mostly this consists of allowing doc
comments either side of a separator token.

In an export list, a section heading is now allowed before the comma,
as well as after it.  eg.

 	module M where (
	    T(..)
	  -- * a section heading
	  , f
	  -- * another section heading
	  , g
        )

In record fields, doc comments are allowed anywhere (previously a
doc-next was allowed only after the comma, and a doc-before was
allowed only before the comma).  eg.

	data R = C {
		-- | describes 'f'
		  f :: Int
		-- | describes 'g'
		, g :: Int
		}

- - - - -
8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00
[haddock @ 2002-07-15 10:21:56 by simonmar]
Mention alternative commenting styles.

- - - - -
fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00
[haddock @ 2002-07-15 16:16:50 by simonmar]
Allow multiple sections/subsections before and after a comma in the
export list.

Also at the same time I made the syntax a little stricter (multiple
commas now aren't allowed between export specs).

- - - - -
80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00
[haddock @ 2002-07-19 09:13:10 by simonmar]
Allow special id's ([], (), etc.) to be used in an import declaration.

- - - - -
a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00
[haddock @ 2002-07-19 09:59:02 by simonmar]
Allow special id's ([], (), etc.) to be used in an import declarations.

- - - - -
d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00
[haddock @ 2002-07-19 10:00:16 by simonmar]
Relax the restrictions which require doc comments to be followed by
semi colons - in some cases this isn't necessary.  Now you can write

	module M where {
 	  -- | some doc
	  class C where {}
 	}

without needing to put a semicolon before the class declaration.

- - - - -
e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00
[haddock @ 2002-07-23 08:24:09 by simonmar]
A new TODO list item

- - - - -
e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00
[haddock @ 2002-07-23 08:40:56 by simonmar]
- update the acknowledgements

- remove the paragraph that described how to use explicit layout with
  doc comments; it isn't relevant any more.

- - - - -
78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00
[haddock @ 2002-07-23 08:43:02 by simonmar]
more tests

- - - - -
5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00
[haddock @ 2002-07-23 08:43:26 by simonmar]
Updates for version 0.4

- - - - -
488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00
[haddock @ 2002-07-23 09:10:46 by simonmar]
Fix the %changelog (rpm complained that it wasn't in the right order)

- - - - -
a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00
[haddock @ 2002-07-23 09:12:38 by simonmar]
Another item for the TODO list

- - - - -
f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00
[haddock @ 2002-07-23 10:18:46 by simonmar]
Add a version banner when invoked with -v

- - - - -
1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00
[haddock @ 2002-07-24 09:28:19 by simonmar]
Remove ^Ms

- - - - -
4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00
[haddock @ 2002-07-24 09:42:17 by simonmar]
Patches to quieten ghc -Wall, from those nice folks at Galois.

- - - - -
d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00
[haddock @ 2002-07-25 14:37:28 by simonmar]
Patch to allow simple hyperlinking to an arbitrary location in another
module's documentation, from Volker Stolz.

Now in a doc comment:

  #foo#

creates

  <a name="foo"></a>

And you can use the form "M\#foo" to hyperlink to the label 'foo' in
module 'M'.  Note that the backslash is necessary for now.

- - - - -
b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00
[haddock @ 2002-08-02 09:08:22 by simonmar]
The <TT> and <PRE> environments seem to use a font that is a little
too small in IE.  Compensate.

(suggestion from Daan Leijen).

- - - - -
8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00
[haddock @ 2002-08-02 09:25:20 by simonmar]
Remove <P>..</P> from around list items, to reduce excess whitespace
between the items of bulleted and ordered lists.

(Suggestion from Daan Leijen).

- - - - -
c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00
[haddock @ 2002-08-05 09:03:49 by simonmar]
update

- - - - -
f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00
[haddock @ 2002-11-11 09:32:57 by simonmar]
Fix cut-n-pasto

- - - - -
12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00
[haddock @ 2002-11-13 09:49:46 by simonmar]
Small bugfix in the --read-interface option parsing from Brett Letner.

- - - - -
30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00
[haddock @ 2003-01-16 15:07:57 by ross]
Adjust for the new exception libraries (as well as the old ones).

- - - - -
871f65df by Sven Panne at 2003-02-20T21:31:40+00:00
[haddock @ 2003-02-20 21:31:40 by panne]
* Add varsyms and consyms to index
* Exclude empty entries from index

- - - - -
bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00
[haddock @ 2003-02-24 21:26:29 by panne]
Don't convert a "newtype" to a single-constructor "data" for
non-abstractly exported types, they are quite different regarding
strictness/pattern matching. Now a "data" without any constructors is
only emitted for an abstractly exported type, regardless if it is
actually a "newtype" or a "data".

- - - - -
0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00
[haddock @ 2003-03-08 19:02:38 by panne]
Fixed some broken/redirected/canonicalized links found by a very picky
link checker.

- - - - -
25459269 by Sven Panne at 2003-03-09T21:13:43+00:00
[haddock @ 2003-03-09 21:13:43 by panne]
Don't append a fragment to non-defining index entries, only documents
with a defining occurrence have a name anchor.

- - - - -
6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00
[haddock @ 2003-03-10 21:34:24 by panne]
Escape fragments. This fixes e.g. links to operators.

- - - - -
eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00
[haddock @ 2003-04-25 10:50:05 by ross]
An 80% solution to generating derived instances.  A complete solution
would duplicate the instance inference logic, but if a type variable
occurs as a constructor argument, then we can just propagate the derived
class to the variable.  But we know nothing of the constraints on any
type variables that occur elsewhere.  For example, the declarations

	data Either a b = Left a | Right b deriving (Eq, Ord)
	data Ptr a = Ptr Addr# deriving (Eq, Ord)
	newtype IORef a = IORef (STRef RealWorld a) deriving Eq

yield the instances

	(Eq a, Eq b) => Eq (Either a b)
	(Ord a, Ord b) => Ord (Either a b)
	Eq (Ptr a)
	Ord (Ptr a)
	(??? a) => Eq (IORef a)

The last example shows the limits of this local analysis.
Note that a type variable may be in both categories: then we know a
constraint, but there may be more, or a stronger constraint, e.g.

	data Tree a = Node a [Tree a] deriving Eq
yields
	(Eq a, ??? a) => Eq (Tree a)

- - - - -
de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00
[haddock @ 2003-04-25 11:17:55 by simonmar]
Some updates, including moving the derived instance item down to the
bottom of the list now that Ross has contributed some code that does
the job for common cases.

- - - - -
1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00
[haddock @ 2003-04-30 14:02:32 by simonmar]
When installing on Windows, run cygpath over $(HADDOCKLIB) so that
haddock (a mingw program, built by GHC) can understand it.

You still need to be in a cygwin environment to run Haddock, because
of the shell script wrapper.

- - - - -
d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00
[haddock @ 2003-05-06 10:04:47 by simonmar]
Catch another case of a paragraph containing just a DocMonospaced that
should turn into a DocCodeBlock.

- - - - -
4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00
[haddock @ 2003-05-06 10:11:44 by simonmar]
Add some more code-block tests.

- - - - -
4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00
[haddock @ 2003-05-06 10:14:52 by simonmar]
Don't turn a single DocCodeBlock into a DocMonospaced, because that
tends to remove the line breaks in the code.

- - - - -
ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00
[haddock @ 2003-05-21 15:07:21 by simonmar]
Only omit the module contents when there are no section headings at all.

- - - - -
bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00
[haddock @ 2003-05-30 16:50:45 by sof]
cygpath: for now, steer clear of --mixed

- - - - -
30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00
[haddock @ 2003-05-30 17:59:28 by sof]
oops, drop test defn from prev commit

- - - - -
b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00
[haddock @ 2003-06-03 09:55:26 by simonmar]
Two small fixes to make the output valid HTML 4.01 (transitional).

Thanks to Malcolm Wallace for pointing out the problems.

- - - - -
70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00
[haddock @ 2003-07-28 13:30:35 by simonmar]
Add tests for a couple of bugs.

- - - - -
122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00
[haddock @ 2003-07-28 13:31:25 by simonmar]
Add documentation for anchors.

- - - - -
0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00
[haddock @ 2003-07-28 13:31:46 by simonmar]
Update

- - - - -
08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00
[haddock @ 2003-07-28 13:32:12 by simonmar]
layout tweak.

- - - - -
13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00
[haddock @ 2003-07-28 13:33:03 by simonmar]
Differentiate links to types/classes from links to
variables/constructors with a prefix ("t:" and "v:" respectively).

- - - - -
d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00
[haddock @ 2003-07-28 13:35:16 by simonmar]
When a module A exports another module's contents via 'module B', then
modules which import entities from B re-exported by A should link to
B.foo rather than A.foo.  See examples/Bug2.hs.

- - - - -
d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00
[haddock @ 2003-07-28 13:36:14 by simonmar]
Update to version 0.5

- - - - -
dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00
[haddock @ 2003-07-28 14:02:43 by panne]
* Updated to version 0.5
* Automagically generate configure if it is not there

- - - - -
6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00
[haddock @ 2003-07-28 14:32:42 by simonmar]
Update to avoid using hslibs with GHC >= 5.04

- - - - -
a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00
[haddock @ 2003-07-28 14:33:37 by simonmar]
Update for 0.5

- - - - -
c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00
[haddock @ 2003-07-28 14:53:22 by simonmar]
Markup fix

- - - - -
6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00
[haddock @ 2003-07-28 16:40:45 by panne]
Make it compile with GHC >= 6.01

- - - - -
afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00
[haddock @ 2003-07-30 15:04:52 by simonmar]
Pay attention to import specs when building the the import env, as
well as the orig env.  This may fix some wrong links in documentation
when import specs are being used.

- - - - -
17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00
[haddock @ 2003-07-30 16:05:40 by simonmar]
Rename instances based on the import_env for the module in which they
are to be displayed.  This should give, in many cases, better links
for the types and classes mentioned in the instance head.

This involves keeping around the import_env in the iface until the
end, because instances are not collected up until all the modules have
been processed.  Fortunately it doesn't seem to affect performance
much.

Instance heads are now attached to ExportDecls, rather than the HTML
backend passing around a separate mapping for instances.  This is a
cleanup.

- - - - -
3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00
[haddock @ 2003-08-04 10:18:24 by panne]
Don't print parentheses around one-element contexts

- - - - -
9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00
[haddock @ 2003-08-04 12:59:47 by simonmar]
A couple of TODOs.

- - - - -
e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00
[haddock @ 2003-08-05 14:10:31 by simonmar]
I'm not sure why, but it seems that the index entries for non-defining
occurrences of entities did not have an anchor - the link just pointed
to the module.  This fixes it.

- - - - -
ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00
[haddock @ 2003-08-15 14:42:59 by simonmar]
Convert the lexer to Alex, and fix a bug in the process.

- - - - -
1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00
[haddock @ 2003-08-15 15:00:18 by simonmar]
Update

- - - - -
d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00
[haddock @ 2003-08-15 15:01:03 by simonmar]
wibbles

- - - - -
b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00
[haddock @ 2003-08-18 10:04:47 by simonmar]
Lex the 'mdo' keyword as 'do'.

- - - - -
8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00
[haddock @ 2003-08-18 11:48:24 by simonmar]
Two bugs from Sven.

- - - - -
ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00
[haddock @ 2003-08-18 11:48:46 by simonmar]
Fixes to the new lexer.

- - - - -
d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00
[haddock @ 2003-08-19 09:09:03 by simonmar]
Further wibbles to the syntax.

- - - - -
6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00
[haddock @ 2003-08-26 18:45:35 by panne]
Use autoreconf instead of autoconf

- - - - -
32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00
[haddock @ 2003-08-26 19:01:18 by panne]
Made option handling a bit more consistent with other tools, in
particular: Every program in fptools should output
   * version info on stdout and terminate successfully when -V or --version
   * usage info on stdout and terminate successfully when -? or --help
   * usage info on stderr and terminate unsuccessfully when an unknown option
is given.

- - - - -
5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00
[haddock @ 2003-08-26 19:20:55 by panne]
Make it *very* clear that we terminate when given a -V/--version flag

- - - - -
e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00
[haddock @ 2003-08-27 07:50:02 by panne]
* Made -D a short option for --dump-interface.
* Made -m a short option for --ms-help.
* Made -n a short option for --no-implicit-prelude.
* Made -c a short option for --css.
* Removed DocBook options from executable (they didn't do anything),
  but mark them as reserved in the docs. Note that the short option
  for DocBook output is now -S (from SGML) instead of -d. The latter
  is now a short option for --debug.
* The order of the Options in the documentation now matches the order
  printed by Haddock itself.

Note: Although changing the names of options is often a bad idea, I'd
really like to make the options for the programs in fptools more
consistent and compatible to the ones used in common GNU programs.

- - - - -
d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00
[haddock @ 2003-09-10 08:23:48 by simonmar]
Add doc subdir.

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00
[haddock @ 2003-09-10 08:24:32 by simonmar]
Install these files in $(datadir), not $(libdir), since they're
architecture independent.

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00
[haddock @ 2003-09-10 08:25:31 by simonmar]
Haddock's supplementary HTML bits now live in $(datadir), not
$(libdir).

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00
[haddock @ 2003-09-22 10:34:38 by simonmar]
Allow installing of docs.

- - - - -
d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00
[haddock @ 2003-10-11 08:10:44 by panne]
Include architecture-independent files in file list

- - - - -
187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00
[haddock @ 2003-10-20 17:19:22 by sof]
support for i-parameters + zip comprehensions

- - - - -
b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00
[haddock @ 2003-11-03 14:24:24 by simonmar]
Update TODO file.

- - - - -
58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00
[haddock @ 2003-11-05 11:22:04 by simonmar]
Remove the last of the uses of 'trace' to emit warnings, and tidy up a
couple of places where duplicate warnings were being emitted.

- - - - -
33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00
[haddock @ 2003-11-05 11:30:52 by simonmar]
- Suppress warnings about unknown imported modules by default.
- Add a -v/--verbose flag to re-enable these warnings.

The general idea is to suppress the "Warning: unknown module: Prelude"
warnings which most Haddock users will see every time, and which
aren't terribly useful.

- - - - -
a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00
[haddock @ 2003-11-05 12:30:28 by simonmar]
- Remove the emboldening of index entries for defining locations.
  This isn't useful, and breaks abstractions.

- If an entity is re-exported by a module but the module doesn't
  include documentation for that entity (perhaps because it is
  re-exported by 'module M'), then don't attempt to hyperlink to
  the documentation from the index.  Instead, just list that module
  in the index, to indicate that the entity is exported from there.

- - - - -
f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00
[haddock @ 2003-11-05 15:15:59 by simonmar]
Index overhaul:

  - no more separate type/class and variable/function indices

  - the index now makes a distinction between different entities
    with the same name.  One example is a type constructor with
    the same name as a data constructor, but another example is
    simply a function with the same name exported by two different
    modules.  For example, the index entry for 'catch' now looks like
    this:

    catch
      1 (Function)	Control.Exception
      2 (Function)	GHC.Exception, Prelude, System.IO, System.IO.Error

    making it clear that there are two different 'catch'es, but one
    of them is exported by several modules.

  - Each index page now has the index contents (A B C ...) at the top.

Please let me know if you really hate any of this.

- - - - -
01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00
[haddock @ 2003-11-05 15:16:38 by simonmar]
Update

- - - - -
1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00
[haddock @ 2003-11-05 17:16:04 by simonmar]
Support for generating a single unified index for several packages.

  --use-index=URL  turns off normal index generation, causes Index
 		   links to point to URL.

  --gen-index      generates an combined index from the specified
                   interfaces.

Currently doesn't work exactly right, because the interfaces don't
contain the iface_reexported info.  I'll need to fix that up.

- - - - -
a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00
[haddock @ 2003-11-06 10:44:52 by simonmar]
Include iface_reexported in the .haddock file.  This unfortunately
bloats the file (40% for base).  If this gets to be a problem we can
always apply the dictionary trick that GHC uses for squashing .hi
files.

- - - - -
0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00
[haddock @ 2003-11-06 12:39:46 by simonmar]
- Add definition lists, marked up like this:

	-- | This is a definition list:
	--
	--   [@foo@] The description of @foo at .
	--
	--   [@bar@] The description of @bar at .

  Cunningly, the [] characters are not treated specially unless a [ is
  found at the beginning of a paragraph, in which case the ] becomes
  special in the following text.


- Add --use-contents and --gen-contents, along the lines of
  --use-index and --gen-index added yesterday.  Now we can generate a
  combined index and contents for the whole of the hierarchical
  libraries, and in theory the index/contents on the system could
  be updated as new packages are added.

- - - - -
fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00
[haddock @ 2003-11-06 14:47:36 by simonmar]
Remove the 'Parent' button - it is of dubious use, and often points
into thin air.

- - - - -
db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00
[haddock @ 2003-11-06 16:48:11 by simonmar]
- Include the OptHide setting in the interface, so we don't include
  hidden modules in the combined index/contents.

- Add a -k/--package flag to set the package name for the current set
  of modules.  The package name for each module is now shown in the
  right-hand column of the contents, in a combined contents page.

- - - - -
7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00
[haddock @ 2003-11-06 16:50:28 by simonmar]
Add -k/--package docs

- - - - -
ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00
[haddock @ 2003-11-06 16:51:23 by simonmar]
Bump to 0.6

- - - - -
1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00
[haddock @ 2003-11-06 16:51:50 by simonmar]
update

- - - - -
69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00
[haddock @ 2003-11-10 14:41:05 by simonmar]
Re-exporting names from a different package is problematic, because we
don't have access to the full documentation for the entity.  Currently
Haddock just ignores entities with no documentation, but this results
in bogus-looking empty documentation for many of the modules in the
haskell98 package.  So:

  - the documentation will now just list the name, as a link
    pointing to the location of the actual documentation.

  - now we don't attempt to link to these re-exported entities if
    they are referred to by the current module.

Additionally:

  - If there is no documentation in the current module, include
    just the Synopsis section (rather than just the documentation
    section, as it was before).  This just looks nicer and was on
    the TODO list.

- - - - -
3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00
[haddock @ 2003-11-10 14:51:59 by simonmar]
Fix for getReExports: take into account names which are not visible
because they are re-exported from a different package.

- - - - -
31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00
[haddock @ 2003-11-10 15:10:53 by simonmar]
Version 0.6 changes

- - - - -
a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00
[haddock @ 2003-11-10 15:15:58 by simonmar]
getReExports: one error case that isn't

- - - - -
00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00
[haddock @ 2003-11-10 16:15:18 by simonmar]
copyright update

- - - - -
ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00
[haddock @ 2003-11-11 09:57:25 by simonmar]
Version 0.6

- - - - -
3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00
[haddock @ 2003-11-11 12:10:44 by simonmar]
Go back to producing just the documentation section, rather than just
the synopsis section, for a module with no documentation annotations.

One reason is that the synopsis section tries to link each entity to
its documentation on the same page.  Also, the doc section anchors
each entity, and it lists instances which the synopsis doesn't.

- - - - -
6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00
[haddock @ 2003-11-12 10:03:39 by simonmar]
2002 -> 2003

- - - - -
090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00
[haddock @ 2003-11-28 12:08:00 by simonmar]
update

- - - - -
8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00
[haddock @ 2003-11-28 12:09:58 by simonmar]
Fix some of the problems with Haddock generating pages that are too
wide.  Now we only specify 'nowrap' when it is necessary to avoid a
code box getting squashed up by the text to the right of it.

- - - - -
35294929 by Sven Panne at 2003-12-29T17:16:31+00:00
[haddock @ 2003-12-29 17:16:31 by panne]
Updated my email address

- - - - -
cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00
[haddock @ 2004-01-08 10:14:24 by simonmar]
Add instructions for using GHC to pre-process source for feeding to Haddock.

- - - - -
8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00
[haddock @ 2004-01-09 12:45:46 by simonmar]
Add -optP-P to example ghc command line.

- - - - -
ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00
[haddock @ 2004-02-03 11:02:03 by simonmar]
Fix bug in index generation

- - - - -
f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00
[haddock @ 2004-02-10 11:51:16 by simonmar]
Don't throw away whitespace at the beginning of a line (experimental fix).

- - - - -
68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00
[haddock @ 2004-02-10 12:10:08 by simonmar]
Fix for previous commit: I now realise why the whitespace was stripped
from the beginning of the line.  Work around it.

- - - - -
e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00
[haddock @ 2004-02-10 18:38:45 by panne]
Make Haddock link with the latest relocated monad transformer package

- - - - -
992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00
[haddock @ 2004-02-16 10:21:35 by simonmar]
Add a TODO

- - - - -
1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00
[haddock @ 2004-03-12 11:33:39 by simonmar]
Add an item.

- - - - -
0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00
[haddock @ 2004-03-15 12:24:05 by simonmar]
Add an item.

- - - - -
6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00
[haddock @ 2004-03-18 14:21:29 by simonmar]
Fix URL

- - - - -
19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00
[haddock @ 2004-03-22 14:09:03 by simonmar]
getReExports was bogus: we should really look in the import_env to
find the documentation for an entity which we are re-exporting without
documentation.

Suggested by: Ross Paterson (patch modified by me).

- - - - -
5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00
[haddock @ 2004-03-24 09:42:10 by simonmar]
hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs)

- - - - -
1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00
[haddock @ 2004-03-24 10:10:50 by simonmar]
mkExportItems fix & simplification: we should be looking at the actual
exported names (calculated earlier) to figure out which subordinates
of a declaration are exported.

This means that if you export a record, and name its fields separately
in the export list, the fields will still be visible in the
documentation for the constructor.

- - - - -
90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00
[haddock @ 2004-03-24 10:12:08 by simonmar]
Make restrictCons take into account record field names too (removing a ToDo).

- - - - -
2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00
[haddock @ 2004-03-24 10:16:17 by simonmar]
Record export tests.

- - - - -
6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00
[haddock @ 2004-03-25 09:35:14 by simonmar]
restrictTo: fix for restricting a newtype with a record field.

- - - - -
dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00
[haddock @ 2004-03-25 10:01:42 by simonmar]
Fix duplicate instance bug

- - - - -
f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00
[haddock @ 2004-03-25 10:02:41 by simonmar]
Duplicate instance bug.

- - - - -
7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00
[haddock @ 2004-03-25 10:29:56 by simonmar]
If a name is imported from two places, one hidden and one not, choose
the unhidden one to link to.  Also, when there's only a hidden module
to link to, don't try linking to it.

- - - - -
40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00
[haddock @ 2004-03-25 15:17:23 by simonmar]
Add support for collaspible parts of the page, with a +/- button and a
bit of JavaScript.  Make the instances collapsible, and collapse them
by default.

This makes documentation with long lists of instances (eg. the
Prelude) much easier to read.  Maybe we should give other
documentation sections the same treatment.

- - - - -
9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00
[haddock @ 2004-03-25 15:20:55 by simonmar]
Update

- - - - -
c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00
[haddock @ 2004-03-25 15:45:10 by simonmar]
Eliminate some unnecessary spaces in the HTML rendering

- - - - -
b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00
[haddock @ 2004-03-25 16:00:36 by simonmar]
Remove all that indentation in the generated HTML to keep the file sizes down.

- - - - -
da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00
[haddock @ 2004-03-27 09:57:57 by panne]
Added the new-born haddock.js to the build process and the documentation.

- - - - -
b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00
[haddock @ 2004-03-27 10:32:20 by panne]
"type" is a required attribute of the "script" element

- - - - -
562b185a by Sven Panne at 2004-03-27T12:52:34+00:00
[haddock @ 2004-03-27 12:52:34 by panne]
Add a doctype for the contents page, too.

- - - - -
f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00
[haddock @ 2004-04-14 10:03:25 by simonmar]
fix for single-line comment syntax

- - - - -
de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00
[haddock @ 2004-04-20 13:08:04 by simonmar]
Allow a 'type' declaration to include documentation comments.  These
will be ignored by Haddock, but at least one user (Johannes Waldmann)
finds this feature useful, and it's easy to add.

- - - - -
fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00
[haddock @ 2004-05-07 15:14:56 by simonmar]
- update copyright
- add version to abstract

- - - - -
59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00
[haddock @ 2004-05-09 14:39:53 by panne]
Fix the fix for single-line comment syntax,
-------------------------------------------
is now a valid comment line again.

- - - - -
8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00
[haddock @ 2004-05-10 10:11:51 by simonmar]
Update

- - - - -
225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00
[haddock @ 2004-05-19 13:10:23 by ross]
Make the handling of "deriving" slightly smarter, by ignoring data constructor
arguments that are identical to the lhs.  Now handles things like

data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ...

- - - - -
37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00
[haddock @ 2004-05-21 06:38:14 by mthomas]
Windows exe extensions (bin remains for Unix).

- - - - -
cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00
[haddock @ 2004-05-25 09:34:54 by simonmar]
Add some TODO items

- - - - -
4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00
[haddock @ 2004-05-25 10:41:46 by simonmar]
Complain if -h is used with --gen-index or --gen-contents, because
it'll overwrite the new index/contents.

- - - - -
2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00
[haddock @ 2004-05-28 20:17:55 by mthomas]
Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg.

- - - - -
8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00
[haddock @ 2004-06-05 16:53:34 by panne]
Misc. rpm spec file cleanup, including:
* make BuildRoot handling more consistent
* added default file attributes
* consistent defines and tags

- - - - -
59974349 by Sven Panne at 2004-06-05T18:01:00+00:00
[haddock @ 2004-06-05 18:01:00 by panne]
More rpm spec file cleanup, including:
* added some BuildRequires
* changed packager to me, so people can complain at the right place :-]
* consistently refer to haskell.org instead of www.haskell.org

- - - - -
b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00
[haddock @ 2004-07-01 11:08:57 by simonmar]
Update to the +/- buttons: use a resized image rather than a <button>.
Still seeing some strange effects in Konqueror, so might need to use a
fixed-size image instead.

- - - - -
d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00
[haddock @ 2004-07-04 15:15:55 by panne]
Install pictures for +/- pictures, too (JPEG is a strange format for graphics
like this, I would have expected GIF or PNG here.)

Things look fine with Konqueror and Netscape on Linux now, the only downside is
that the cursor doesn't change when positioned above the "button".

- - - - -
46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00
[haddock @ 2004-07-13 17:59:28 by panne]
A quote is a valid part of a Haskell identifier, but it would interfere with an
ECMA script string delimiter, so escape it there.

- - - - -
1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00
[haddock @ 2004-07-22 08:54:06 by simonmar]
Add single quote to $ident, so you can say eg. 'foldl'' to refer to
foldl' (the longest match rule is our friend).

Bug reported by Adrian Hey <ahey at iee.org>

- - - - -
f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00
[haddock @ 2004-07-27 22:58:23 by krasimir]
Add basic support for Microsoft HTML Help 2.0

- - - - -
d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00
[haddock @ 2004-07-27 23:02:36 by krasimir]
escape names in the index

- - - - -
a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00
[haddock @ 2004-07-27 23:05:21 by krasimir]
Add jsFile, plusFile and minusFile to the file list

- - - - -
c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00
[haddock @ 2004-07-28 22:12:09 by krasimir]
bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to
HaddockUtil.hs module to make them accessible from HaddockHH2.hs

- - - - -
64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00
[haddock @ 2004-07-30 22:15:45 by krasimir]
more stuffs

  - support for separated compilation of packages
  - the contents page now uses DHTML TreeView
  - fixed copyFile bug

- - - - -
133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00
[haddock @ 2004-07-31 12:04:37 by krasimir]
make the DHtmlTree in contents page more portable. The +/- buttons are replaced
with new images which looks more beatiful.

- - - - -
79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00
[haddock @ 2004-07-31 13:10:20 by krasimir]
Make DHtmlTree compatible with Mozila browser

- - - - -
1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00
[haddock @ 2004-07-31 14:52:55 by krasimir]
fix

- - - - -
85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00
[haddock @ 2004-07-31 14:53:28 by krasimir]
HtmlHelp 1.x

- - - - -
3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00
[haddock @ 2004-07-31 20:35:21 by krasimir]
Added support for DevHelp

- - - - -
d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00
[haddock @ 2004-07-31 21:17:51 by krasimir]
Document new features in HtmlHelp

- - - - -
790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00
[haddock @ 2004-08-01 15:14:02 by krasimir]
add missing imports

- - - - -
fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00
[haddock @ 2004-08-01 19:52:06 by krasimir]
fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format.

- - - - -
94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00
[haddock @ 2004-08-01 19:53:50 by krasimir]
I forgot to add the new +/- images

- - - - -
f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00
[haddock @ 2004-08-02 16:25:53 by krasimir]
Add root node to the table of contents. All modules in tree are not children of
the root

- - - - -
f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00
[haddock @ 2004-08-02 18:17:46 by panne]
Mainly DocBook fixes

- - - - -
09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00
[haddock @ 2004-08-02 20:02:29 by panne]
Fixed -o/--odir handling. Generating the output, especially the
directory handling, is getting a bit convoluted nowadays...

- - - - -
c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00
[haddock @ 2004-08-02 20:31:13 by panne]
Warning police

- - - - -
37830bff by Sven Panne at 2004-08-02T20:32:29+00:00
[haddock @ 2004-08-02 20:32:28 by panne]
Nuked dead code

- - - - -
13847171 by Sven Panne at 2004-08-02T21:12:27+00:00
[haddock @ 2004-08-02 21:12:25 by panne]
Use pathJoin instead of low-level list-based manipulation for FilePaths

- - - - -
c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00
[haddock @ 2004-08-02 21:16:02 by panne]
Removed WinDoze CRs

- - - - -
b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00
[haddock @ 2004-08-03 19:35:59 by panne]
Fixed spelling of "http-equiv" attribute

- - - - -
dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00
[haddock @ 2004-08-03 19:44:03 by panne]
Pacify W3C validator:
* Added document encoding (currently UTF-8, not sure if this is completely correct)
* Fixed syntax of `id' attributes
* Added necessary `alt' attribute for +/- images

Small layout improvement:
* Added space after +/- images (still not perfect, but better than before)

- - - - -
919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00
[haddock @ 2004-08-03 19:45:11 by sof]
make it compile with <= ghc-6.1

- - - - -
4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00
[haddock @ 2004-08-03 19:45:30 by sof]
ffi wibble

- - - - -
4770643a by Sven Panne at 2004-08-03T20:47:46+00:00
[haddock @ 2004-08-03 20:47:46 by panne]
Fixed CSS for button style. Note that only "0" is a valid measure without a unit!

- - - - -
14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00
[haddock @ 2004-08-03 21:07:58 by panne]
Improved spacing of dynamic module tree

- - - - -
97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00
[haddock @ 2004-08-09 11:03:04 by simonmar]
Add FormatVersion

Patch submitted by: George Russell <ger at informatik.uni-bremen.de>

- - - - -
af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00
[haddock @ 2004-08-09 11:55:05 by simonmar]
Add support for a short description for each module, which is included
in the contents.

The short description should be given in a "Description: " field of
the header.  Included in this patch are changes that make the format
of the header a little more flexible.  From the comments:

-- all fields in the header are optional and have the form
--
-- [spaces1][field name][spaces] ":"
--    [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")*
-- where each [spaces2] should have [spaces1] as a prefix.
--
-- Thus for the key "Description",
--
-- > Description : this is a
-- >    rather long
-- >
-- >    description
-- >
-- > The module comment starts here
--
-- the value will be "this is a .. description" and the rest will begin
-- at "The module comment".

The header fields must be in the following order: Module, Description,
Copyright, License, Maintainer, Stability, Portability.

Patches submitted by: George Russell <ger at informatik.uni-bremen.de>,
with a few small changes be me, mostly to merge with other recent
changes.

ToDo: document the module header.

- - - - -
7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00
[haddock @ 2004-08-10 14:09:57 by simonmar]
Fixes for DevHelp/HtmlHelp following introduction of short module description.

- - - - -
814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00
[haddock @ 2004-08-10 14:33:45 by simonmar]
Fixes to installation under Windows.

- - - - -
39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00
[haddock @ 2004-08-12 12:08:23 by simonmar]
Avoid using string-gap tricks.

- - - - -
b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00
[haddock @ 2004-08-13 10:53:21 by simonmar]
Update

- - - - -
eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00
[haddock @ 2004-08-13 10:53:50 by simonmar]
Test for primes in quoted links

- - - - -
68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00
[haddock @ 2004-08-16 19:59:36 by panne]
XMLification

- - - - -
7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00
[haddock @ 2004-08-18 16:42:54 by panne]
Re-added indices + minor fixes

- - - - -
8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00
[haddock @ 2004-08-25 17:15:42 by sof]
backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw

- - - - -
4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00
[haddock @ 2004-08-26 20:08:49 by panne]
SGML is dead, long live DocBook XML!

Note: The BuildRequires tags in the spec files are still incomplete
and the documentation about the DocBook tools needs to be updated,
too. Stay tuned...

- - - - -
8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00
[haddock @ 2004-08-26 21:03:19 by panne]
Updated BuildRequires tags. Alas, there seems to be no real standard here, so
your mileage may vary... At least the current specs should work on SuSE Linux.

- - - - -
e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00
[haddock @ 2004-08-30 15:44:59 by sof]
escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x

- - - - -
b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00
[haddock @ 2004-08-31 13:09:42 by simonmar]
Avoid GHC/shell versionitis and create Version.hs

- - - - -
c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00
[haddock @ 2004-09-05 19:12:32 by panne]
* HTML documentation for "foo.xml" goes into directory "foo" again,
  not "foo-html". This is nicer and consistent with the behaviour for
  building the docs from SGML.

* Disabled building PostScript documentation in the spec files for
  now, there are some strange issues with the FO->PS conversion for
  some files which have to be clarified first.

- - - - -
c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00
[haddock @ 2004-09-24 07:04:38 by panne]
Switched the default state for instances and the module hierarchy to
non-collapsed. This can be reversed when we finally use cookies from
JavaScript to have a more persistent state. Previously going back and forth
in the documentation was simply too annoying because everything was
collapsed again and therefore the documentation was not easily navigatable.

- - - - -
dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00
[haddock @ 2004-09-30 08:21:29 by simonmar]
Add a feature request

- - - - -
45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00
[haddock @ 2004-10-23 19:54:00 by panne]
Improved the Cygwin/MinGW chaos a little bit. There is still confusion
about host platform vs. target platform...

- - - - -
5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00
[haddock @ 2004-10-28 16:01:51 by krasimir]
update for ghc-6.3+

- - - - -
92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00
[haddock @ 2004-11-01 16:39:01 by panne]
Revert previous commit: It's Network.URI which should be changed, not Haddock.

- - - - -
05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00
[haddock @ 2005-01-04 16:15:51 by simonmar]
parser fix: allow qualified specialids.

- - - - -
47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00
[haddock @ 2005-01-04 16:16:54 by simonmar]
Add a test

- - - - -
ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00
[haddock @ 2005-01-10 19:18:22 by ross]
Render non-ASCII characters using numeric character references, to simplify
charset issues.  There's a META tag saying the charset is UTF-8, but GHC
outputs characters as raw bytes.

Ideally we need an encoding on the input side too, primarily in comments,
because source files containing non-ASCII characters aren't portable between
locales.

- - - - -
eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00
[haddock @ 2005-01-11 10:44:37 by simonmar]
Remove string gap

- - - - -
b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00
[haddock @ 2005-01-13 11:41:33 by ross]
recognize SGML-style numeric character references &#ddd; or &#xhhhh; and
translate them into Chars.

- - - - -
106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00
[haddock @ 2005-01-13 14:43:41 by ross]
also allow uppercase X in hexadecimal character references (like SGML)

- - - - -
e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00
[haddock @ 2005-01-13 14:44:24 by ross]
Describe numeric character references.

- - - - -
914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00
[haddock @ 2005-01-15 18:44:45 by panne]
Make Haddock compile again after the recent base package changed. The Map/Set
legacy hell has been factored out, so that all modules can simply use the new
non-deprecated interfaces. Probably a lot of things can be improved by a little
bit of Map/Set/List algebra, this can be done later if needed.

Small note: Currently the list of instances in HTML code is reversed. This will
hopefully be fixed later.

- - - - -
6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00
[haddock @ 2005-01-16 12:18:26 by panne]
Trim imports

- - - - -
efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00
[haddock @ 2005-01-16 12:58:03 by panne]
Correctly handle the new order of arguments for the combining function
given to fromListWith.

- - - - -
e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00
[haddock @ 2005-01-16 14:14:39 by panne]
Data.Map.unions is left-biased.

- - - - -
dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00
[haddock @ 2005-01-16 14:22:44 by panne]
Added the last missing "flip" to get identical HTML output as previous versions.

- - - - -
951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00
[haddock @ 2005-01-16 14:37:10 by panne]
Refactored Text.PrettyPrint legacy hell into a separate module.

- - - - -
f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00
[haddock @ 2005-01-16 15:41:21 by panne]
Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway.

- - - - -
60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00
[haddock @ 2005-01-18 10:02:48 by simonmar]
Add a TODO

- - - - -
a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00
[haddock @ 2005-01-28 23:19:39 by krasimir]
import Foreign/Foreign.C are required for Windows

- - - - -
d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00
[haddock @ 2005-02-02 16:23:00 by simonmar]
Revamp the linking strategy in Haddock.

Now name resolution is done in two phases:

 - first resolve everything to original names, like a Haskell compiler
   would.

 - then, figure out the "home" location for every entity, and point
   all the links to there.  The home location is the lowest non-hidden
   module in the import hierarchy that documents the entity.  If there
   are multiple candidates, one is chosen at random.

Also:

 - Haddock should not generate any HTML with dangling links any more.
   Unlinked references are just rendered as plain text.

 - Error reporting is better: if we can't find a link destination for
   an entity reference, we now emit a warning.

- - - - -
1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00
[haddock @ 2005-02-03 13:42:19 by simonmar]
- add --ignore-all-exports flag, which behaves as if every module
  has the ignore-exports attribute (requested by Chris Ryder).

- add --hide option to hide a module on the command line.

- add --use-package option to get Haddock info for a package from
  ghc-pkg (largely untested).

- remove reexports from the .haddock file, they aren't used any more.

- - - - -
767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00
[haddock @ 2005-02-03 16:17:37 by ross]
fix typo for < 6.3

- - - - -
0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00
[haddock @ 2005-02-04 12:03:31 by simonmar]
Fix bug in renameExportItems that meant links in instances weren't
being renamed properly.

- - - - -
ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00
[haddock @ 2005-02-04 12:15:52 by simonmar]
Add attribute #not-home, to indicate that the current module should
not be considered to be a home module for the each entity it exports,
unless there is no other module that exports the entity.

- - - - -
fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00
[haddock @ 2005-02-04 12:40:02 by simonmar]
Update the documentation w.r.t. home modules and the not-home attribute.

- - - - -
26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00
[haddock @ 2005-02-04 13:36:05 by ross]
sort lists of instances by
- arity of the type constructors (so higher-kinded instances come first)
- name of the class
- argument types

- - - - -
26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00
[haddock @ 2005-02-23 15:57:12 by simonmar]
Fix documentation regarding the module attributes.

- - - - -
9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00
[haddock @ 2005-02-28 16:18:17 by simonmar]
version 0.7

- - - - -
a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00
[haddock @ 2005-02-28 16:22:08 by simonmar]
Attempt to fix the layout of the package names in the contents.

Having tried just about everything, the only thing I can get to work
reliably is to make the package names line up on a fixed offset from
the left margin.  This obviously isn't ideal, so anyone else that
would like to have a go at improving it is welcome.  One option is to
remove the +/- buttons from the contents list and go back to a plain
table.

The contents page now uses CSS for layout rather than tables.  It
seems that most browsers have different interpretations of CSS layout,
so only the simplest things lead to consistent results.

- - - - -
905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00
[haddock @ 2005-03-01 17:16:40 by simonmar]
Another attempt at lining up the package names on the contents page.
Now, they line up with Konqueror, and almost line up with Firefox & IE
(different layout in each case).

- - - - -
a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00
[haddock @ 2005-03-09 08:28:39 by wolfgang]
Hack haddock's lexer to accept the output from Apple's broken version of
cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output).

- - - - -
9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00
[haddock @ 2005-04-22 14:27:15 by simonmar]
Add a TODO item

- - - - -
23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00
[haddock @ 2005-05-18 12:41:59 by ross]
fix 3 bugs in --use-package, and document it.

- - - - -
00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00
[haddock @ 2005-05-21 12:35:29 by panne]
Warning/versionitis police

- - - - -
341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00
[haddock @ 2005-06-15 15:43:21 by simonmar]
Allow "licence" as an alternate spelling of "license"

- - - - -
3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00
[haddock @ 2005-06-16 08:14:12 by simonmar]
wibble

- - - - -
abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00
[haddock @ 2005-06-27 14:46:40 by simonmar]
name hierarchical HTML files as A-B-C.html instead of A.B.C.html.  The
old way confused Apache because the extensions are sometimes
interpreted as having special meanings.

- - - - -
a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00
[haddock @ 2005-08-04 13:59:40 by simonmar]
0.7 changes

- - - - -
170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00
[haddock @ 2005-08-04 15:08:03 by simonmar]
spec file from Jens Peterson

- - - - -
7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00
[haddock @ 2005-08-04 15:59:30 by simonmar]
replace mingw tests with $(Windows)

- - - - -
a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00
[haddock @ 2005-08-05 07:01:12 by panne]
Reverted to previous version (but with bumped version number), the last
commit broke RPM building on SuSE systems due to differently named
dependencies.

As a clarification: All .spec files in the repository have to work at least
on SuSE, because that's the system I'm using. And as "Mr. Building Police",
I reserve me the right to keep them that way... >:-) It might very well be
the case that we need different .spec files for different platforms, so
packagers which are unhappy with the current .spec files should contact me,
stating the actual problems.

- - - - -
4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00
[haddock @ 2005-10-05 10:51:45 by simonmar]
Add a bug

- - - - -
60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00
[haddock @ 2005-10-05 12:52:03 by simonmar]
Document new behaviour of -s option

- - - - -
f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00
[haddock @ 2005-10-10 15:02:55 by simonmar]
extractRecSel: ignore non-record constructors (fixes a crash when
using datatypes with a mixture of record and non-record style
constructors).

- - - - -
b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00
Start CHANGES for 0.8
- - - - -
21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00
First cut of Cabal build system
- - - - -
766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00
Add configure script and Makefile for the docs

Add a separate configure script and build system for building the
documentation.  The configure and Makefile code is stolen from
fptools.  This is left as a separate build system so that the main
Cabal setup doesn't require a Unix build environment or DocBook XML
tools.


- - - - -
aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00
Add a --wiki=URL flag to add a per-module link to a correspondng wiki page.
So each html page gets an extra link (placed next to the source code and
contents links) to a corresponding wiki page. The idea is to let readers
contribute their own notes, examples etc to the documentation.

Also slightly tidy up the code for the --source option.

- - - - -
e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00
TODO: documnet --wiki
- - - - -
17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00
Add an optional wiki link for each top level exported name.
In each module, for each "top level" exported entity we add a hyper link to a
corresponding wiki page. The link url gets the name of the exported entity as
a '#'-style anchor, so if there is an anchor in the page with that name then
the users browser should jump directly to it. By "top level" we mean functions,
classes, class members and data types (data, type, newtype), but not data
constructors, class instances or data type class membership.

The link is added at the right of the page and in a small font. Hopefully this
is the right balance of visibility/distraction.

We also include a link to the wiki base url in the contents and index pages.

- - - - -
f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00
Rewrite pathJoin to only add a path separator when necessary.
When the path ends in a file seperator there is no need to add another.
Now using "--wiki=http://blah.com/foo/" should do the right thing.
(Code snippet adapted from Isaac's FilePath package.)

- - - - -
43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00
Teach haddock about line pragmas and add accurate source code links
Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's
source location tracking to include the file name as well as line/column. This
way each AST item that is tagged with a SrcLoc gets the original file name too.

Use this original file name to add source links to each exported item, in the
same visual style as the wiki links. Note that the per-export source links are
to the defining module rather than whichever module haddock pretends it is
exported from. This is what we want for source code links. The source code link
URL can also contain the name of the export so one could implement jumping to
the actual location of the function in the file if it were linked to an html
version of the source rather than just plain text. The name can be selected
with the %N wild card.

So for linking to the raw source code one might use:
--source=http://darcs/haskell.org/foo/%F

Or for linking to html syntax highlighted code:
--source=http://darcs/haskell.org/foo/%M.html#%N

- - - - -
edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00
Extend URL variable expansion syntax and add source links to the contents page
Like the wiki link on the contents and index page, add a source code link too.
Extend the wiki & source URL variable expansion syntax.

The original syntax was:
%F for the source file name (the .hs version only, not the .lhs or .hs.pp one)
%M for the module name (with '.' replaced by '/')

The new syntax is:
%F or %{FILE} for the original source file name
%M or %{MODULE} for the module name (no replacements)
%N or %{NAME} for the function/type export name
%K or %{KIND} for a type/value flag "t" or "v"

with these extensions:
%{MODULE/./c} to replace the '.' module seperator with any other char c

%{VAR|some text with the % char in it} which means if the VAR is not in use in
this URL context then "" else replace the given text with the '%' char
replaced by the string value of the VAR. This extension allows us to construct
URLs wit optional parts, since the module/file name is not available for the
URL in the contents/index pages and the value/type name is not available for
the URL at the top level of each module.

- - - - -
eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00
Remove the complex substitutions and add more command line flags instead.
Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now
use three seperate command line flags for the top level, per-module and
per-entity source and wiki links. They are:
--source-base, --source-module, --source-entity
--comments-base, --comments-module, --comments-entity

We leave -s, --source as an alias for --source-module which is how that option
behaved previously.

The long forms of the substitutions are still available, ${FILE} ${MODULE} etc
and the only non-trivial substitution is ${MODULE/./c} to replace the '.'
characters in the module name with any other character c. eg ${MODULE/./-}

Seperating the source and wiki url flags has the added bonus that they can
be turned on or off individually. So users can have per-module links for
example without having to also have per-entity links.`

- - - - -
a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00
Make the --help output fit in 80 columns.
This is a purely cosmetic patch, feel free to ignore it.
The only trickery going on is that we don't display the deprecated -s, --source
flags in the help message, but we do still accept them.

- - - - -
2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00
Add documentation for the new --source-* and --comments-* command line options
- - - - -
1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00
fix markup
- - - - -
100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00
remove a couple TODO items that have been done
The --wiki, or rather the --comment-* options are now documented.
There is probably no need to have haddock invoke unlit or cpp itself since
it can now pick up the line pragmas to get the source locations right. Tools
like Cabal will arrange for preprocessors to be run so there is less of a need
for tools like haddock to do it themselves.

- - - - -
3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00
add a test I had lying around
- - - - -
98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00
add scabal-version field
- - - - -
c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00
Add Hoogle output option
- - - - -
f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00
add haskell.vim
Contributed by Brad Bowman <bsb at bereft.net>, thanks!

- - - - -
35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00
fixed libdir (/html was missing)
- - - - -
4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00
add PatternGuards extension
- - - - -
3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00
bug fixes from Brad Bowman
- - - - -
8610849d by Sven Panne at 2006-03-19T17:02:56+00:00
Fixed Cabal/RPM build
- - - - -
34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00
Avoid pattern guards

Due to the use of pattern guards in Haddock, GHC was called with
-fglasgow-exts. This in turn enables bang patterns, too, which broke the
Haddock build. Removing some unnecessary pattern guards seemed to be the
better way of fixing this instead of using a pragma to disable pattern
guards.

- - - - -
bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00
extend 'deriving' heuristic a little
If an argument of a data constructor has a type variable head, it is
irreducible and the same type class can be copied into the constraint.
(Formerly we just did this for type variable arguments.)

- - - - -
dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00
record an idea
- - - - -
748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00
add section about deriving
- - - - -
11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00
replace a fatal error in lexChar with a parseError
- - - - -
382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00
add a bug
- - - - -
b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00
add a bug report
- - - - -
912edf65 by David Waern at 2006-07-10T19:09:23+00:00
Initial modifications -- doesn't compile
- - - - -
a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00
More porting work -- doesn't compile
- - - - -
0a173d19 by David Waern at 2006-07-11T11:30:03+00:00
Make the repos temporarily compile and illustrate a problem
- - - - -
bad316de by David Waern at 2006-07-11T15:43:47+00:00
Progress on the porting process 
- - - - -
bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00
More progress on the porting -- first pass starting to shape up
- - - - -
de580ba2 by David Waern at 2006-07-20T17:48:30+00:00
More progress -- still on phase1
- - - - -
75a917a2 by David Waern at 2006-07-23T18:22:43+00:00
More work on pass1 -- mostly done
- - - - -
6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00
More work, started working on the renaming phase -- this code will need a cleanup soon :)
- - - - -
82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00
Add instances, build renaming environment, start on the renamer
- - - - -
c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00
Complete the renamer
- - - - -
7e00d464 by David Waern at 2006-07-30T21:01:57+00:00
Start porting the Html renderer
- - - - -
f04ce121 by David Waern at 2006-08-09T20:04:56+00:00
More Html rendering progress
- - - - -
20c21b53 by David Waern at 2006-08-10T17:37:47+00:00
More progress
- - - - -
d7097e0d by David Waern at 2006-08-11T20:31:51+00:00
Cleanup
- - - - -
a7351e86 by David Waern at 2006-08-12T11:44:47+00:00
Render H98 Data declarations
- - - - -
3fb2208e by David Waern at 2006-08-12T17:15:34+00:00
Perfect rendering of Test.hs
- - - - -
454fd062 by David Waern at 2006-08-13T21:57:08+00:00
Misc fixes and interface load/save
- - - - -
7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00
Some refactoring
- - - - -
a7d3efef by David Waern at 2006-08-19T20:07:55+00:00
Adapt to latest GHC 
- - - - -
5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00
Move interface read/write to its own module + some cleanup
- - - - -
037e011c by David Waern at 2006-08-20T21:38:24+00:00
Small cleanup
- - - - -
da3a1023 by David Waern at 2006-09-03T16:05:22+00:00
Change mode to BatchCompile to avoid GHC API bug
- - - - -
3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00
Starting work on GADT rendering
- - - - -
94506037 by David Waern at 2006-09-03T20:02:48+00:00
Compensate for change of export list order in GHC
- - - - -
c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00
Rename a function
- - - - -
9a9735ba by David Waern at 2006-09-05T15:51:21+00:00
Change version number to 2.0
- - - - -
3758a714 by David Waern at 2006-09-05T15:51:49+00:00
Align comment properly
- - - - -
68478d9e by David Waern at 2006-09-15T18:03:00+00:00
Remove interface reading/writing code and use the GHC api for creating package environments instead
- - - - -
d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00
Change the executable name to haddock-ghc-nolib
- - - - -
fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00
Small source code cleanup
- - - - -
d08eb017 by David Waern at 2006-09-15T18:06:21+00:00
Remove handling of --package flag
- - - - -
b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00
Remove commented-out code
- - - - -
bef0a684 by David Waern at 2006-09-15T18:37:57+00:00
Don't warn about missing links to ()
- - - - -
e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00
Remove Interface and Binary2 modules 
- - - - -
9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00
Remove debug printing from HaddockHtml
- - - - -
a0e7455d by David Waern at 2006-09-16T00:16:29+00:00
Comments only
- - - - -
d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00
Refactor PackageData creation code and start on building the doc env propery (unfinished)
- - - - -
06aaa779 by David Waern at 2006-09-16T00:19:25+00:00
Better comments in Main.hs
- - - - -
1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00
Comments and spacing change
- - - - -
e5a97767 by David Waern at 2006-09-21T17:02:45+00:00
Remove unnecessary fmapM import in Main
- - - - -
9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00
Make import list in HaddockHtml prettier
- - - - -
3452f662 by David Waern at 2006-09-22T18:08:47+00:00
Refactor context rendering
- - - - -
12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00
Do proper HsType rendering (inser parentheses correctly)
- - - - -
2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00
Fix a bug in Main.toHsType
- - - - -
c5396443 by David Waern at 2006-09-22T18:11:16+00:00
Skip external package modules sort for now
- - - - -
3fb95547 by David Waern at 2006-09-22T20:35:40+00:00
Take away trailin "2" on all previously clashing type names
- - - - -
2174755f by David Waern at 2006-09-22T20:51:43+00:00
Remove unused imports in Main
- - - - -
1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00
Fix a comment in Main
- - - - -
32d9e028 by David Waern at 2006-10-05T16:40:11+00:00
Merge with changes to ghc HEAD
- - - - -
3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00
Comment fixes
- - - - -
b9c217ec by David Waern at 2006-10-05T16:49:59+00:00
Filter out more builtin type constructors from warning messages
- - - - -
67e7d252 by David Waern at 2006-10-05T19:38:22+00:00
Refactoring -- better structured pass1
- - - - -
cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00
Remove read/dump interface flags
- - - - -
313f9e69 by David Waern at 2006-10-05T19:49:26+00:00
Remove unused pretty printing
- - - - -
480f09d1 by David Waern at 2006-12-28T13:22:24+00:00
Update to build with latest GHC HEAD
- - - - -
63dccfcb by David Waern at 2007-01-05T01:38:45+00:00
Fixed a bug so that --ghc-flag works correctly
- - - - -
3117dadc by David Waern at 2006-12-29T18:53:39+00:00
Automatically get the GHC lib dir
- - - - -
9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00
Comments
- - - - -
0b0237cc by David Waern at 2007-01-05T16:48:30+00:00
Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC
- - - - -
a962c256 by David Waern at 2007-01-05T17:02:47+00:00
Add tabs in haddock.cabal
- - - - -
0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00
Add GHCUtils.hs
- - - - -
c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00
Change package name to haddock-ghc, version 0.1
- - - - -
38e18b27 by David Waern at 2007-01-12T12:03:52+00:00
No binder name for foreign exports
- - - - -
d18587ab by David Waern at 2007-01-12T12:08:15+00:00
Temp record
- - - - -
ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00
Remove read/dump-interface (again)
- - - - -
f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00
Remove DocOption, use the GHC type
- - - - -
511be8bd by David Waern at 2007-01-12T18:32:41+00:00
Use exceptions instead of Either when loading package info
- - - - -
0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00
Small type change
- - - - -
77507eb7 by David Waern at 2007-01-12T18:33:59+00:00
Remove interface file read/write
- - - - -
0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00
Add trace_ppr to GHCUtils
- - - - -
3878b493 by David Waern at 2007-01-17T21:40:53+00:00
Sort external package modules and build a doc env
- - - - -
8dc323fc by David Waern at 2007-01-17T21:42:41+00:00
Remove comment
- - - - -
f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00
Add haddock-ghc.cabal and remove ghc option pragma in source file
- - - - -
da242b2c by David Waern at 2007-01-18T23:22:46+00:00
Remove some tabs
- - - - -
288ed096 by David Waern at 2007-01-18T23:39:28+00:00
Moved the defaultErrorHandler to scope only over sortAndCheckModules for now
- - - - -
4dd150fe by David Waern at 2007-02-03T21:23:56+00:00
Let restrictCons handle infix constructors
- - - - -
97893442 by David Waern at 2007-02-04T16:26:00+00:00
Render infix data constructors
- - - - -
da89db72 by David Waern at 2007-02-04T16:26:33+00:00
CHange project name to Haddock-GHC
- - - - -
e93d48af by David Waern at 2007-02-04T16:59:08+00:00
Render infix type constructors properly
- - - - -
357bc99b by David Waern at 2007-02-04T17:37:08+00:00
Insert spaces around infix function names
- - - - -
ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00
Do not list entities without documentation
- - - - -
04249c7e by David Waern at 2007-02-04T19:16:25+00:00
Add GADT support (quite untested)
- - - - -
2c223f8d by David Waern at 2007-02-04T19:25:10+00:00
Add package file write/save again!
- - - - -
b07ed218 by David Waern at 2007-02-04T19:33:02+00:00
Comment out minf_iface based stuff
- - - - -
953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00
Solve conflicts
- - - - -
593247fc by David Waern at 2007-02-06T19:48:48+00:00
Remove -package flag, GHC's can be used instead
- - - - -
f658ded2 by David Waern at 2007-02-06T20:50:44+00:00
Start for support of ATs
- - - - -
97f9e913 by David Waern at 2007-02-06T20:52:27+00:00
Wibble
- - - - -
2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00
Add the DocOptions change
- - - - -
dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00
Wibble
- - - - -
7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00
Change version to 2.0 and executable name to haddock
- - - - -
c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00
Go back to -B flag 
- - - - -
3a349201 by David Waern at 2007-03-09T13:31:59+00:00
Better exception handling and parsing of GHC flags
- - - - -
05a69b71 by David Waern at 2007-03-09T17:45:44+00:00
Remove commented-out DocEntity printing
- - - - -
755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00
Remove a file that shouldn't be here
- - - - -
a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00
Remove an import
- - - - -
6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00
Start work on Haddock API
- - - - -
f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00
Prettify some comments
- - - - -
f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00
Remove ppr in HaddockTypes
- - - - -
bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00
Remove commented out doc env inference
- - - - -
11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00
De-flatten the namespace
- - - - -
f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00
Add missing stuff to API
- - - - -
9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00
Wibble
- - - - -
7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00
Avoid a GHC bug with parseStaticFlags []
- - - - -
4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00
Add fall-through case to mkExportItem
- - - - -
6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00
Add shebang line to Setup.lhs
- - - - -
80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00
Fix stupid compile error
- - - - -
1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00
Do save/read of interface files properly
- - - - -
0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00
Add version to ghc dependency
- - - - -
b0499b63 by David Waern at 2007-04-10T21:37:08+00:00
Change package name to haddock
- - - - -
9d50d27e by David Waern at 2007-04-24T00:22:14+00:00
Use filepath package instead of FilePath
- - - - -
87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00
Add new package dependencies
- - - - -
4768709c by David Waern at 2007-07-11T20:37:11+00:00
Follow changes to record constructor representation
- - - - -
b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00
update to compile with the latest GHC & Cabal
- - - - -
c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00
Fix conflicts
- - - - -
97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00
Follow changes to the GHC API
- - - - -
a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00
Call parseStaticFlags before newSession
- - - - -
f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00
Better indentation in haddock.cabal
- - - - -
d84e52ad by David Waern at 2007-08-02T00:08:18+00:00
Wibble
- - - - -
a23f494a by David Waern at 2007-08-02T00:08:24+00:00
Be better at trying to load all module dependencies (debugging)
- - - - -
ee917f13 by David Waern at 2007-08-03T18:48:08+00:00
Load all targets explicitly (checkModule doesn't chase dependencies anymore)
- - - - -
5182d631 by David Waern at 2007-08-16T16:48:55+00:00
Finalize support for links to other packages
- - - - -
dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00
Fix haddock comment errors in Haddock.Types
- - - - -
50c0d83e by David Waern at 2007-08-16T16:51:37+00:00
Remove a debug import
- - - - -
d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00
Rename PackageData to HaddockPackage
- - - - -
3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00
Simplify some comments
- - - - -
66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00
Comment the HaddockPackage definition
- - - - -
8674c761 by David Waern at 2007-08-16T17:25:54+00:00
Improve code layout in Main
- - - - -
571a3a0b by David Waern at 2007-08-16T17:32:13+00:00
Remove explict module imports in Main
- - - - -
d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00
Correct comments
- - - - -
7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00
Fix layout problems in Haddock.Types
- - - - -
9f421d7f by David Waern at 2007-08-17T11:16:48+00:00
Move options out of Main into Haddock.Options
- - - - -
80042b63 by David Waern at 2007-08-17T11:26:59+00:00
Small comment/layout fixes
- - - - -
b141b982 by David Waern at 2007-08-17T11:28:28+00:00
Change project name from Haddock-GHC to Haddock
- - - - -
dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00
Add top module comment to all files
- - - - -
ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00
Factor out typechecking phase into Haddock.Typecheck
- - - - -
6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00
Factor out package code to Haddock.Packages
- - - - -
b396db37 by David Waern at 2007-08-29T22:40:23+00:00
Major refactoring
- - - - -
3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00
Rename HaddockModule to Interface and a few more refactorings
- - - - -
c55326db by David Waern at 2007-08-29T23:48:03+00:00
Some comment cleanup
- - - - -
9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00
Add some modules that I forgot to add earlier
- - - - -
4536dce2 by David Waern at 2007-08-29T23:55:24+00:00
Wibble
- - - - -
9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00
Wibble
- - - - -
c52c050a by David Waern at 2007-08-30T16:30:37+00:00
Rename HaddockModule to Interface
- - - - -
eae2995f by David Waern at 2007-08-30T16:42:59+00:00
Simplify createInterfaces
- - - - -
53f99caa by David Waern at 2007-09-29T00:04:31+00:00
Add build-type: Simple to the cabal file
- - - - -
0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00
Add containers and array dependency
- - - - -
6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00
Prettify the cabal file
- - - - -
87c1e378 by David Waern at 2007-09-29T13:16:39+00:00
FIX: consym data headers with more than two variables
- - - - -
b67fc16a by David Waern at 2007-09-29T14:01:32+00:00
FIX: prefix types used as operators should be quoted
- - - - -
a8f925bc by David Waern at 2007-09-29T14:02:26+00:00
Use isSymOcc from OccName instead of isConSym
- - - - -
fc330701 by David Waern at 2007-09-29T14:15:37+00:00
Use isLexConSym/isLexVarSym from OccName
- - - - -
e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00
FIX: do not quote varsym type operators
- - - - -
402207d2 by David Waern at 2007-09-29T15:01:50+00:00
Wibble
- - - - -
f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00
Take care when pp tyvars - add parens on syms
- - - - -
849e2a77 by David Waern at 2007-10-01T21:56:39+00:00
Go back to using a ModuleMap instead of LookupMod - fixes a bug
- - - - -
549dbac6 by David Waern at 2007-10-02T01:05:19+00:00
Improve parsing of doc options
- - - - -
a36021b8 by David Waern at 2007-10-02T23:05:00+00:00
FIX: double arrows in constructor contexts
- - - - -
d03bf347 by David Waern at 2007-10-09T16:14:05+00:00
Add a simple test suite
- - - - -
c252c140 by David Waern at 2007-10-17T16:02:28+00:00
Add --optghc=.. style flag passing to GHC
- - - - -
cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00
Add support for --read-interface again
- - - - -
33d059c0 by David Waern at 2007-10-18T22:30:18+00:00
Refactoring -- get rid of Haddock.Packages
- - - - -
f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00
Name changes
- - - - -
8a1c816f by David Waern at 2007-10-20T14:24:23+00:00
Add --ghc-version option
- - - - -
4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00
Add some Outputable utils
- - - - -
69e7e47f by David Waern at 2007-10-21T14:35:49+00:00
FIX: Ord for OrdName was not comparing modules
- - - - -
5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00
Wibble
- - - - -
03d48e20 by David Waern at 2007-10-24T15:52:56+00:00
Remove Main from "other modules"
- - - - -
c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00
Make it possible to run haddock on itself
- - - - -
21d156d8 by David Waern at 2007-10-25T14:02:14+00:00
Don't set boot modules as targets
- - - - -
f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00
Add optimisation flags
- - - - -
7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00
Go back to loading only targets (seems to work now)
- - - - -
4862aae1 by David Waern at 2007-11-05T22:24:57+00:00
Do full compilation of modules -- temporary fix for GHC API problem
- - - - -
697e1517 by David Waern at 2007-11-05T22:25:50+00:00
Don't warn about not being able to link to wired/system/builtin-names
- - - - -
892186da by David Waern at 2007-11-06T00:49:21+00:00
Filter out instances with TyCons that are not exported
- - - - -
9548314c by David Waern at 2007-11-06T09:37:14+00:00
Wibble
- - - - -
5cafd627 by David Waern at 2007-11-08T01:43:07+00:00
Filter out all non-vanilla type sigs
- - - - -
04621830 by David Waern at 2007-11-08T01:45:13+00:00
Synch loading of names from .haddock files with GHC's name cache
- - - - -
88d37f77 by David Waern at 2007-11-08T01:46:21+00:00
Remove commented-out code
- - - - -
6409c911 by David Waern at 2007-11-08T01:56:00+00:00
Small bugfix and cleanup in getDeclFromTyCls
- - - - -
af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00
Remove OrdName stuff
- - - - -
3a615e2e by David Waern at 2007-11-08T02:13:41+00:00
Update runtests.hs following changes to haddock
- - - - -
01f3314e by David Waern at 2007-11-08T02:33:01+00:00
Complain if we can't link to wired-in names
- - - - -
fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00
Don't exit when there are no file arguments
- - - - -
194bc332 by David Waern at 2007-11-09T02:55:37+00:00
Wibble
- - - - -
dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00
Wibble
- - - - -
82869fda by David Waern at 2007-11-10T17:01:43+00:00
Introduce InstalledInterface structure and add more stuff to the .haddock files

We introduce InstalledInterface capturing the part of Interface that is stored
in the interface files. We change the ppHtmlContents and ppHtmllIndex to take
this structure instead of a partial Interface. We add stuff like the doc map
and exported names to the .haddock file (via InstalledInterface).

- - - - -
d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00
FIX: contents and index should include external package modules when --gen-contents/--gen-index
- - - - -
e8814716 by David Waern at 2007-11-11T00:29:27+00:00
Remove lDocLinkName and its use in Html backend
- - - - -
6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00
Do some refactoring in the html backend
This also merges an old patch by Augustsson:
  
  Wed Jul 12 19:54:36 CEST 2006  lennart.augustsson at credit-suisse.com
    * Print type definitions like signatures if given arrows.



- - - - -
09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00
mention HsColour in the docs, next to option flags for linking to source code
- - - - -
24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00
change doc references to CVS to give darcs repository location instead
- - - - -
74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00
Update copyright
- - - - -
fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00
Eliminate dep on network by doing a little cut'n'paste
haddock depending on the network causes a circular dependency
at least if you want to build the network lib with haddock docs.

- - - - -
10cc9bda by David Waern at 2007-11-11T02:09:41+00:00
Fix conflicts
- - - - -
4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00
Manual merge of a patch from Duncan Coutts that removes the dependency on mtl 
- - - - -
fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00
Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01
- - - - -
d7431c85 by David Waern at 2007-11-11T02:28:50+00:00
Fix conflicts
- - - - -
f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00
changes for 0.8
- - - - -
db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00
fix the name of the source file


- - - - -
8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00
Rename haddock.js to haddock-util.js
haddock.js will be run automatically by Windows when you type
'haddock' if it is found on the PATH, so rename to avoid confusion.
Spotted by Adrian Hey.

- - - - -
6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00
Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones
- - - - -
d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00
add todo item for --maintainer
- - - - -
2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00
TODO: do something better about re-exported symbols from another package
- - - - -
42d85549 by David Waern at 2007-11-11T02:30:59+00:00
Fix conflicts
- - - - -
5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00
Never do spliting index files into many
- - - - -
f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00
Add searching on the index page
- - - - -
bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00
Delete dead code, now there is only one index page
- - - - -
cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00
Delete more stuff that is no longer required
- - - - -
e2806646 by David Waern at 2007-11-11T02:41:53+00:00
Fix conflicts
- - - - -
a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00
Make the index be in case-insensitive alphabetic order
- - - - -
8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00
Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance
- - - - -
036b8120 by David Waern at 2007-11-11T02:56:58+00:00
Fix conflicts
- - - - -
f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00
added substitution %{FILE///c}
- - - - -
402e166a by David Waern at 2007-11-11T03:35:46+00:00
Manual merge of old patch:

Sat Apr 21 04:36:43 CEST 2007  Roberto Zunino <zunrob at users.sf.net>
  * URL expansion for %%, %L, %{LINE}


- - - - -
2f264fbd by David Waern at 2007-11-11T03:40:33+00:00
Manual merge of an old patch:
  Thu Apr 19 20:23:40 CEST 2007  Wolfgang Jeltsch <g9ks157k at acme.softbase.org>
    * bug fix
    When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for 
  non-exported names.
  
    This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional
  OptIgnoreExports option for every module) but at least the bug seems to be resolved now.

- - - - -
7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00
Install LICENSE in the correct place
- - - - -
66eaa924 by David Waern at 2007-11-11T19:02:46+00:00
Fix a bug that made haddock loop
- - - - -
4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00
Rename java-script file (this wasn't merge correctly)
- - - - -
d569534a by David Waern at 2007-11-11T19:06:44+00:00
Don't require -B <ghc-libdir> when no argument files
Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B 
<ghc-libdir> to Haddock when there're no source files to process. This is nice when 
computing contents/index for external packages.

- - - - -
373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00
Change from tabs to spaces in the ppHtmlIndex function
- - - - -
6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00
Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n))
- - - - -
bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00
Fix conflicts
- - - - -
cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00
Make the max number of results 75 instead of 50, to allow map searching in the base library to work
- - - - -
3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00
Make the search box in a form so that enter does the default search
- - - - -
142103e5 by David Waern at 2007-11-12T00:03:18+00:00
Merge patch from the old branch:

Fri Aug 31 13:21:45 CEST 2007  Duncan Coutts <duncan at haskell.org>
  * Add category: Development to .cabal file
  Otherwise it appears on the hackage website in the "Unclassified" category.


- - - - -
22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00
A a list of small improvements to the TODO file
- - - - -
eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00
addition of type equality support (at least for HTML generation)
- - - - -
816a7e22 by David Waern at 2007-12-08T15:46:26+00:00
Handle class operators correctly when rendering predicates
- - - - -
68baaad2 by David Waern at 2007-12-08T16:15:54+00:00
Code layout changes
- - - - -
09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00
Handle infix operators correctly in the Type -> HsType translation
- - - - -
31c36da2 by David Waern at 2007-12-08T16:24:27+00:00
Add ppLParendTypes/ppLParendType
- - - - -
b17cc818 by David Waern at 2007-12-08T16:26:12+00:00
Use ppParendType when printing types args in predicates
- - - - -
ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00
Fix rendering of instance heads to handle infix operators
This is also a refactoring to share this code for rendering predicates.


- - - - -
ff886d45 by David Waern at 2007-12-08T17:27:46+00:00
Fix rendering of class operators
- - - - -
e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00
Fix a bug (use ppTyName instead of ppName to print names in type apps)
- - - - -
79a1056e by David Waern at 2007-12-08T21:25:18+00:00
Update tests
- - - - -
867741ac by David Waern at 2007-12-08T21:25:49+00:00
Give a diff on test failure
- - - - -
7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00
Add DrIFT commands
- - - - -
3656454d by David Waern at 2008-01-05T20:26:00+00:00
Add "cabal-version: >= 1.2" to the cabal file
- - - - -
77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00
add an item
- - - - -
f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00
Source links must point to the original module, not the referring module
- - - - -
eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00
Manual merge of a patch to the 0.8 branch

  Thu Dec  6 15:00:10 CET 2007  Simon Marlow <simonmar at microsoft.com>
    * Source links must point to the original module, not the referring 
      module


- - - - -
378f4085 by David Waern at 2008-01-06T16:03:45+00:00
Change stability from stable to experimental
- - - - -
8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00
Add haskell.vim (it had been removed somehow)
- - - - -
ea34d02e by David Waern at 2008-01-06T16:36:57+00:00
Change version to 2.0.0.0
- - - - -
34631ac0 by David Waern at 2008-01-06T16:44:57+00:00
Add missing modules to the cabal file
- - - - -
9e142935 by David Waern at 2008-01-06T17:25:42+00:00
Depend on ghc >= 6.8.2 && < 6.9
- - - - -
59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00
add build scripts
- - - - -
1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00
update version number
- - - - -
fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00
update version
- - - - -
f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00
doc updates
- - - - -
ce71b611 by David Waern at 2008-01-07T13:46:32+00:00
Change version in docs and spec
- - - - -
03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00
Manually merge over changes to CHANGES for 0.9
- - - - -
39f1b042 by David Waern at 2008-01-07T15:17:41+00:00
Remove the -use-package flag, we don't support it anyway
- - - - -
7274a544 by David Waern at 2008-01-07T15:33:05+00:00
Update CHANGES for 2.0.0.0
- - - - -
96594f5d by David Waern at 2008-01-07T15:46:49+00:00
Wibble
- - - - -
f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00
Change url to repo in documentation
- - - - -
8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00
Update CHANGES
- - - - -
cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00
Documentation fix
- - - - -
d8e45539 by David Waern at 2008-01-07T16:12:00+00:00
Update docs to say that Haddock accets .lhs files and module names
- - - - -
4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00
Document -B option
- - - - -
47274262 by David Waern at 2008-01-07T16:23:07+00:00
Update CHANGES
- - - - -
7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00
Remove --use-package, --package & --no-implicit.. flags from docs
- - - - -
6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00
Remove --no-implicit-prelide flag
- - - - -
1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00
Update the "Using literate or pre-processed source" section
- - - - -
0117f620 by David Waern at 2008-01-07T16:41:55+00:00
Document the --optghc flag
- - - - -
087ab1cf by David Waern at 2008-01-07T16:42:10+00:00
Remove the documenation section on derived instances
The problem mentioned there doesn't exist in Haddock 2.0.0.0

- - - - -
7253951e by David Waern at 2008-01-07T16:48:40+00:00
Document OPTIONS_HADDOCK
- - - - -
3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00
Wibble
- - - - -
3025adf9 by David Waern at 2008-01-07T17:08:14+00:00
Wibble
- - - - -
5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00
Change synopsis field to description
- - - - -
1673f54b by David Waern at 2008-01-07T17:18:21+00:00
Change my email address in the cabal file
- - - - -
55aa9808 by David Waern at 2008-01-07T18:18:02+00:00
Add documentation for readInterfaceFile
- - - - -
eaea417f by David Waern at 2008-01-07T18:21:30+00:00
Export necessary stuff from Distribution.Haddock
- - - - -
7ea18759 by David Waern at 2008-01-07T18:31:49+00:00
Remove dep on Cabal
- - - - -
7b79c74e by David Waern at 2008-01-07T18:33:49+00:00
Remove dep on process
- - - - -
ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00
Add feature-requsts from Henning Thielemann to TODO
- - - - -
0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00
Record a bug in TODO
- - - - -
b04605f3 by David Waern at 2008-01-23T16:59:06+00:00
Add a bug reported by Ross to TODO
- - - - -
5b17c030 by David Waern at 2008-01-23T18:05:53+00:00
A a bug report to TODO
- - - - -
1c993b0d by David Waern at 2008-01-25T16:30:25+00:00
Accept test output
- - - - -
c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00
Accept test output
- - - - -
4b795811 by David Waern at 2008-01-25T16:38:37+00:00
Change Hidden.hs (test) to use OPTIONS_HADDOCK
- - - - -
c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00
Accept test output
- - - - -
ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00
Add Hidden.html.ref to tests
- - - - -
1dc9610c by David Waern at 2008-02-02T20:50:51+00:00
Add a comment about UNPACK bug in TODO
- - - - -
2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00
Change the representation of DocNames

Ross Paterson reported a bug where links would point to the defining module
instead of the "best" module for an identifier (e.g Int pointing to GHC.Base
instead of Data.Int). This patch fixes this problem by refactoring the way
renamed names are represented. Instead of representing them by:

> data DocName = Link Name | NoLink Name

they are now represented as such:

> data DocName = Documented Name Module | Undocumented Name

and the the link-env looks like this:

> type LinkEnv = Map Name Module

There are several reasons for this. First of all, the bug was caused by
changing the module part of Names during the renaming process, without changing
the Unique field. This caused names to be overwritten during the loading of
.haddock files (which caches names using the NameCache of the GHC session).
So we might create new Uniques during renaming to fix this (but I'm not
sure that would be problem-free). Instead, we just keep the Name and add the
Module where the name is best documented, since it can be useful to keep
the original Name around (for e.g. source-code location info and for users of
the Haddock API).

Also, the names Link/NoLink don't really make sense, since wether to use
links or not is entirely up to the users of DocName.

In the process of following this change into H.Backends.Html I removed the
assumption that binder names are Undocumented (which was just an unnecessary
assumption, the OccName is the only thing needed to render these). This will
probably make it possible to get rid of the renamer and replace it with a
traversal from SYB or Uniplate.

Since DocName has changed, InterfaceFile has changed so this patch also
increments the file-format version. No backwards-compatibility is implemented.

- - - - -
0f28c921 by David Waern at 2008-02-09T23:00:36+00:00
H.GHC.Utils: remove unused imports/exports
- - - - -
0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00
H.GHC.Utils: add some functions that were removed by mistake
- - - - -
e3452f49 by David Waern at 2008-02-10T00:28:48+00:00
Fix some trivial warnings in H.InterfaceFile
- - - - -
a6d74644 by David Waern at 2008-02-10T00:48:06+00:00
Update the version message to fit in small terminals
- - - - -
76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00
Remove bugs from TODO that don't apply anymore since the port
- - - - -
5e10e090 by David Waern at 2008-02-10T15:22:47+00:00
Remove bugs from TODO that weren't actual bugs
- - - - -
fef70878 by David Waern at 2008-02-10T15:23:44+00:00
Remove yet another item from TODO that was not an actual bug
- - - - -
e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00
Bump the version number to 2.1.0

Since the exported datatype DocName has changed, we need to bump the
major version number.

Let's also drop the fourth version component, it's not that useful.

- - - - -
e3be7825 by David Waern at 2008-04-11T14:29:04+00:00
Add a bug to TODO
- - - - -
cb6574be by David Waern at 2008-04-11T16:00:45+00:00
Use the in-place haddock when running tests
- - - - -
c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00
Turn off GHC warnings when running tests
- - - - -
7f61b546 by David Waern at 2008-04-11T17:24:00+00:00
Add a flag for turning off all warnings
- - - - -
883b8422 by David Waern at 2008-04-12T14:02:18+00:00
Fix printing of data binders
- - - - -
2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00
Fix missing parenthesis in constructor args bug
- - - - -
1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00
Simplify test suite and add tests
I move all tests into one single directory to simplify things, and add a test
for the last bug that was fixed.

- - - - -
8f178376 by David Waern at 2008-04-12T19:00:15+00:00
Add a script for copying test output to "expected" output
- - - - -
193e3a03 by David Waern at 2008-04-12T19:16:37+00:00
Remove two fixed bugs from TODO
- - - - -
ddc9130c by David Waern at 2008-04-12T19:37:06+00:00
Update test README
- - - - -
956069c0 by David Waern at 2008-05-01T12:16:14+00:00
Update version number in spec and docs
- - - - -
5478621c by David Waern at 2008-05-01T12:28:12+00:00
 Remove claim of backwards compatibility from docs for readInterfaceFile
- - - - -
4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00
Update CHANGES
- - - - -
804216fb by David Waern at 2008-05-01T12:43:16+00:00
Add a synopsis
- - - - -
fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00
Add Haddock.DocName to the cabal file
- - - - -
9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00
Remove -fglasgow-exts and -fasm
- - - - -
aee7c145 by David Waern at 2008-05-01T12:54:01+00:00
Add LANGUAGE pragmas to source files
- - - - -
9a58428b by David Waern at 2008-05-01T12:54:19+00:00
Add extensions to cabal file
- - - - -
494f1bee by David Waern at 2008-05-01T13:12:09+00:00
Export DocName in the API
- - - - -
c938196b by David Waern at 2008-05-01T13:12:19+00:00
Add hide options to some source files
- - - - -
236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00
Rewrite the --hoogle flag support
- - - - -
6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00
Simplify the newtype/data outputting in Hoogle, as haddock does it automatically
- - - - -
f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00
Add initial structure for outputting documentation as well, but does not yet output anything
- - - - -
7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00
Remove <document comment> from the Hoogle output
- - - - -
9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00
Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info
- - - - -
4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00
Change packageName to packageStr, as it better reflects the information stored in it
- - - - -
7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00
Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info
- - - - -
8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00
Change Hoogle to take the package name and package version separately
- - - - -
a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00
In Hoogle do not list things that are not local to this module
- - - - -
974b76b7 by David Waern at 2008-06-19T18:40:13+00:00
Be more consistent with GHC API naming in H.GHC.Utils
- - - - -
2facb4eb by David Waern at 2008-06-19T19:03:03+00:00
Update test output
- - - - -
c501de72 by David Waern at 2008-06-26T20:26:49+00:00
Use ghc-paths to get the lib dir

The path can still be overridden using the -B flag. It's not longer
required to pass the lib dir to the program that runs the test suite.

- - - - -
ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00
Update CHANGES
- - - - -
9d21c60a by David Waern at 2008-06-26T20:34:53+00:00
Update README
- - - - -
741448f0 by David Waern at 2008-06-26T21:12:57+00:00
Improve wording in the help message
- - - - -
b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00
Rename ForeignType
- - - - -
6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00
Rename TyFamily
- - - - -
8d1125ed by David Waern at 2008-06-30T10:37:21+00:00
Rename type patterns
- - - - -
7610a4cb by David Waern at 2008-06-30T10:45:07+00:00
Rename associated types
- - - - -
8eeba14c by David Waern at 2008-06-30T10:47:41+00:00
Remove the TODO file now that we have a trac
- - - - -
1af5b25b by David Waern at 2008-07-02T18:19:28+00:00
Render type family declarations (untested)
- - - - -
ceb99797 by David Waern at 2008-07-02T18:24:06+00:00
Remove redundant check for summary when rendering data types
- - - - -
b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00
More support for type families and associated types
Now we just need to render the instances

- - - - -
78784879 by David Waern at 2008-07-07T22:13:58+00:00
Remove filtering of instances
We were filtering out all instances for types with unknown names. This was probably an
attempt to filter out instances for internal types. I am removing the filtering for the
moment, and will try to fix this properly later.


- - - - -
3e758dad by David Waern at 2008-06-30T18:50:30+00:00
Run haddock in-place during testing
- - - - -
d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00
Remove index.html and doc-index.html from output, they should not be versioned
- - - - -
3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00
Update test output following change to instance filtering
- - - - -
e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00
Stop using the map from exported names to declarations

During creation of the interface, we were using two maps: one from 
exported names to declarations, and one from all defined names in the 
module to declarations. The first contained subordinate names while the 
second one didn't. The first map was never used to look up names not 
defined in the associated module, so if we add subordinate names to the
second map, we could use it everywhere. That's that this patch does.

This simplifies code because we don't have to pass around two maps 
everywhere.

We now store the map from locally defined things in the interface
structure instead of the one from exported names.

- - - - -
2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00
Get the all locally defined names from GHC API

We previously had some code to compute all locally defined names in 
a module including subordinate names. We don't need it since we can
get the names from modInfoTyThings in the GHC API.

- - - - -
bf637994 by David Waern at 2008-07-13T13:09:16+00:00
Refactoring in H.Interface.Create

We were creating a doc map, a declaration map and a list of entities
separately by going through the HsGroup. These structures were all used
to build the interface of a module.

Instead of doing this, we can start by creating a list of declarations
from the HsGroup, then collect the docs directly from this list 
(instead of using the list of entities), creating a documentation map.

We no longer need the Entity data type, and we can store a single
map from names to declarations and docs in the interface, instead of
the declaration map and the doc map.

This way, there is only one place where we filter out the declarations
that we don't want, and we can remove a lot of code.

Another advantage of this is that we can create the exports directly
out of the list of declarations when we export the full module contents.
(Previously we did a look up for each name to find the declarations).
This is faster and removes another point where we depend on names to
identify exported declarations, which is good because it eliminates
problems with instances (which don't have names).

- - - - -
547e410e by David Waern at 2008-07-13T13:34:51+00:00
Remove FastString import and FSLIT macro in H.I.Create -- they were unused
- - - - -
693759d1 by David Waern at 2008-07-13T13:36:23+00:00
Remove unused import from H.I.Create
- - - - -
cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00
Small touches
- - - - -
96de8f1d by David Waern at 2008-07-20T11:21:46+00:00
Preparation for rendering instances as separate declarations

We want to be able to render instances as separate declarations. So we remove
the Name argument of ExportDecl, since instances are nameless.

This patch also contains the first steps needed to gather type family instances 
and display them in the backend, but the implementation is far from complete.
Because of this, we don't actually show the instances yet.

- - - - -
b0f824fb by David Waern at 2008-07-20T15:53:08+00:00
Follow changes to ExportDecl in Hoogle
- - - - -
1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00
Change how the Hoogle backend outputs classes, adding the context in
- - - - -
7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00
Remove the indent utility function from Hoogle backend
- - - - -
3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00
Add support for Hoogle writing ForeignImport/ForeignExport properly
- - - - -
795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00
Flesh out the Hoogle code to render documentation
- - - - -
23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00
Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u>
- - - - -
db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00
Remove any white space around a <li> element
- - - - -
f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00
Remove the TODO in the Hoogle HTML generation, was already done
- - - - -
693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00
Put brackets round operators in more places in the Hoogle output
- - - - -
842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00
Print type signatures with brackets around the name
- - - - -
cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00
Bump version number to 2.2.0
- - - - -
30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00
Resolve conflicts in H.B.Hoogle
- - - - -
1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00
Add "all" command to runtests.hs that runs all tests despite failures
- - - - -
f2723023 by David Waern at 2008-07-23T23:08:39+00:00
Update tests/README
- - - - -
c0304a11 by David Waern at 2008-07-23T23:21:15+00:00
Be compatible with GHC 6.8.3
    
The cabal file is converted to use the "new" syntax with explicit Library
and Executable sections.

We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field
in the cabal file. (Ideally, Cabal would define the symbol for us, like it does
for __GLASGOW_HASKELL__).

We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3.
    
Previously, we only supported GHC 6.8.2 officially but the dependencies field
said "ghc <= 6.9". This was just for convenience when testing against the (then 
compatible) HEAD version of GHC, and was left in the release by mistake.
  
Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field
correctly reflects this.

- - - - -
88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00
Depend on the currently available ghc-paths versions only
- - - - -
8738d97b by David Waern at 2008-07-24T10:50:44+00:00
FIX haskell/haddock#44: Propagate parenthesis level when printing documented types
- - - - -
05339119 by David Waern at 2008-07-24T16:06:18+00:00
Drop unnecessary parenthesis in types, put in by the user
 
We were putting in parenthesis were the user did. Let's remove this since
it just clutters up the types. The types are readable anyway since we print
parens around infix operators and do not rely on fixity levels.
  
When doing this I discovered that we were relying on user parenthesis when
printin types like (a `O` b) c. This patchs fixes this problem so that
parenthesis are always inserted around an infix op application in case it
is applied to further arguments, or if it's an arguments to a type constructor.

Tests are updated.

- - - - -
b3a99828 by David Waern at 2008-07-24T10:19:43+00:00
Print parenthesis around non-atomic banged types

Fixes half of haskell/haddock#44

- - - - -
ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00
Add a reference file for the TypeFamilies test
- - - - -
1941cc11 by David Waern at 2008-07-25T17:15:53+00:00
Simplify definition of pretty and trace_ppr
- - - - -
e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00
Warning messages

Output a warning when filtering out data/type instances and associated types
in instances. We don't show these in the documentation yet, and we need to
let the user know.

- - - - -
9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00
Doc: Mention Hoogle in the Introduction
- - - - -
afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00
Doc: update -B description
- - - - -
584c0c91 by David Waern at 2008-07-25T18:11:38+00:00
Doc: describe -w flag
- - - - -
77619c24 by David Waern at 2008-07-28T12:29:07+00:00
Remove TODO from cabal file
- - - - -
96717d5f by David Waern at 2008-07-28T12:29:27+00:00
Support type equality predicates
- - - - -
c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00
Move unL from H.B.Hoogle to H.GHC.Utils

I like Neil's shorter unL better than unLoc from the GHC API.

- - - - -
c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00
Do not export ATs when not in list of subitems
- - - - -
bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00
Filter out ForeignExports
- - - - -
df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00
Filter out more declarations

The previous refactorings in H.I.Create introduced a few bugs. Filtering
of some types of declarations that we don't handle was removed. This patch
fixes this.

- - - - -
2f8a958b by David Waern at 2008-08-03T15:24:07+00:00
Move reL to H.GHC.Utils so we can use it everywhere
- - - - -
8ec15efd by David Waern at 2008-08-03T15:25:00+00:00
 Use isVanillaLSig from GHC API instead of home brewn function
- - - - -
300f93a2 by David Waern at 2008-08-03T15:25:27+00:00
Filter out separately exported ATs

This is a quick and dirty hack to get rid of separately exported ATs.
We haven't decided how to handle them yet. No warning message is given.

- - - - -
8776d1ec by David Waern at 2008-08-03T16:21:21+00:00
Filter out more declarations and keep only vanilla type sigs in classes
- - - - -
ea07eada by David Waern at 2008-08-03T16:48:00+00:00
Fix layout
- - - - -
dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00
Move some utility functions from H.I.Create to H.GHC.Utils
- - - - -
4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00
Do not filter out doc declarations
- - - - -
0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00
Filter out separately exported ATs (take two)
- - - - -
af970fe8 by David Waern at 2008-08-03T22:39:17+00:00
Update CHANGES
- - - - -
5436ad24 by David Waern at 2008-08-03T22:40:20+00:00
Bump version number to 2.2.1
- - - - -
d66de448 by David Waern at 2008-08-05T19:00:32+00:00
Remove version restriction on ghc-paths
- - - - -
534b1364 by David Waern at 2008-08-05T19:04:35+00:00
Bump version to 2.2.2 and update CHANGES
- - - - -
549188ff by David Waern at 2008-08-05T19:16:49+00:00
Fix CHANGES
- - - - -
0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00
invoking haddock clarification and help
- - - - -
748295cc by David Waern at 2008-08-11T18:56:37+00:00
Doc: say that the --hoogle option is functional
- - - - -
43301db4 by David Waern at 2008-08-05T19:26:08+00:00
Change ghc version dependency to >= 6.8.2
- - - - -
3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00
Make H.GHC.Utils build with GHC HEAD
- - - - -
7568ace0 by David Waern at 2008-08-11T19:41:54+00:00
Import Control.OldException instead of C.Exception when using ghc >= 6.9

We should really test for base version instead, but I don't currently
know which version to test for.

- - - - -
b71ae991 by David Waern at 2008-08-12T22:40:39+00:00
Make our .haddock file version number depend on the GHC version

We need to do this, since our .haddock format can potentially
change whenever GHC's version changes (even when only the patchlevel
changes).

- - - - -
6307ce3f by David Waern at 2008-08-12T22:49:57+00:00
Remove matching on NoteTy in AttachInstances, it has been removed
- - - - -
2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00
Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9
- - - - -
c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00
Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3
- - - - -
69a44ebb by David Waern at 2008-08-12T23:11:12+00:00
Follow changes to parseDynamic/StaticFlags
- - - - -
5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00
Add __GHC_PATCHLEVEL__ symbol also when building the library
- - - - -
8574dc11 by David Waern at 2008-08-13T21:44:17+00:00
Follow move of package string functions from PackageConfig to Module
- - - - -
c9baa77f by David Waern at 2008-08-13T21:45:29+00:00
Follow extensible exceptions changes
- - - - -
9092de15 by David Waern at 2008-08-13T21:46:20+00:00
Update test following Haddock version change
- - - - -
ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00
Follow changes to parseDynamic- parseStaticFlags in GHC
- - - - -
b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00
Follow changes to Binary in GHC 6.9
- - - - -
edfda1cc by David Waern at 2008-08-13T21:50:17+00:00
Change ghc version dependency to >= 6.8.2 && <= 6.9
- - - - -
d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00
Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base
- - - - -
dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00
Add support for type synonyms to Hoogle, was accidentally missing before (woops!)
- - - - -
b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00
Generalise Hoogle.doc and add a docWith
- - - - -
415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00
Make Hoogle add documentation to a package
- - - - -
790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00
Use the same method to put out signatures as class methods in the Hoogle backend
- - - - -
ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00
Remove Explicit top-level forall's when pretty-printing signatures
- - - - -
6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00
Simplify the code by removing not-to-important use of <.> in the Hoogle back end
- - - - -
788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00
In the hoogle back end, markup definition lists using <i>, not <b>
- - - - -
77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00
Add a Makefile for GHC's build system. Still won't work yet, but we're closer
- - - - -
920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00
Add haddock.wrapper
- - - - -
bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00
Add a manual Cabal flag to control the ghc-paths dependency
- - - - -
04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00
Update extensions in Cabal file
Use ScopedTypeVariables instead of PatternSignatures

- - - - -
12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00
Increase the upper bound on the GHC version number
- - - - -
b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00
Fix some warnings
- - - - -
aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00
Fixes for using haddock in a GHC build tree
- - - - -
ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00
Don't use Cabal wrappers on Windows
- - - - -
35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00
Fix in-tree haddock on Windows
- - - - -
c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00
follow library changes
- - - - -
2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00
bindist fixes
- - - - -
3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00
We need to tell haddock that its datasubdir is . or it can't find package.conf
- - - - -
388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00
Fix haddock inplace on Windows
- - - - -
70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00
Fix installed haddock on Windows
- - - - -
83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00
Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better
- - - - -
b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00
Add a LANGUAGE ForeignFunctionInterface pragma
- - - - -
afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00
Wibble imports
- - - - -
547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00
Add a "#!/bin/sh" to haddock.wrapper
- - - - -
f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00
Use "exec" when calling haddock in the wrapper
- - - - -
2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00
Port Haddock.Interface to new GHC API.

This required one bigger change: 'readInterfaceFile' used to take an
optional 'Session' argument.  This was used to optionally update the
name cache of an existing GHC session.  This does not work with the
new GHC API, because an active session requires the function to return
a 'GhcMonad' action, but this is not possible if no session is
provided.

The solution is to use an argument of functions for reading and
updating the name cache and to make the function work for any monad
that embeds IO, so it's result type can adapt to the calling context.

While refactoring, I tried to make the code a little more
self-documenting, mostly turning comments into function names.

- - - - -
3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00
Reflect GHC API changes.
- - - - -
2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00
Port Haddock.GHC.Typecheck to new GHC API.
- - - - -
9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00
Port Haddock.GHC to new GHC API.
- - - - -
caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00
Port Main to new GHC API.
- - - - -
069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00
Fix paths used on Windows frmo a GHC tree: There is no whare directory
- - - - -
7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00
Fix the in-tree haddock on Windows
- - - - -
0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00
Increase the GHC upper bound from 6.11 to 6.13
- - - - -
f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00
Do not wrap __ in brackets
- - - - -
036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00
Fix building haddock when GhcProfiled=YES
- - - - -
01434a89 by David Waern at 2008-09-24T20:24:21+00:00
Add PatternSignatures LANGUAGE pragma to Main and Utils
- - - - -
1671a750 by David Waern at 2008-10-02T22:57:25+00:00
For source links, get original module from declaration name instead of environment.

Getting it from the environment must have been a remnant from the
times when we were using unqualified names (versions 0.x).

- - - - -
a25dde99 by David Waern at 2008-10-02T22:59:57+00:00
Remove ifaceEnv from Interface - it's no longer used
- - - - -
610993da by David Waern at 2008-10-02T23:04:58+00:00
Write a comment about source links for type instance declarations
- - - - -
5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00
Follow GHC API change of parseModule.
- - - - -
5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00
TAG 2008-10-03
- - - - -
76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00
Only load modules once when typechecking with GHC.
  
This still doesn't fix the memory leak since the typechecked source is
retained and then processed separately.  To fix the leak, modules must
be processed directly after typechecking.

- - - - -
7074d251 by David Waern at 2008-10-09T23:53:54+00:00
Interleave typechecking with interface creation

At the same time, we fix a bug where the list of interfaces were
processed in the wrong order, when building the links and renaming
the interfaces.

- - - - -
4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00
Add some strictness annotations in Interface

We add some strictness annotations to the fields of Interface,
so that less GHC data is hold on to during processing.

- - - - -
22035628 by David Waern at 2008-10-10T20:02:31+00:00
Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck
- - - - -
be637ad3 by David Waern at 2008-10-10T20:33:38+00:00
Make Haddock build with GHC 6.8.2
- - - - -
523b3404 by David Waern at 2008-10-10T21:08:09+00:00
Fix documentation for createInterfaces
- - - - -
e1556702 by David Waern at 2008-10-10T21:26:19+00:00
Hide H.Utils in library
- - - - -
a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00
Add back .haddock file versioning based on GHC version

It was accidentally removed in the patch for GHC 6.8.2 compatibility

- - - - -
06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00
Bump version number to 2.3.0
- - - - -
ff087fce by David Waern at 2008-10-10T22:35:49+00:00
Add support for DocPic

The support for DocPic was merged into the GHC source long ago,
but the support in Haddock was forgotten. Thanks Peter Gavin for
submitting this fix!

- - - - -
3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00
Update tests
- - - - -
0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00
no need for handleErrMsg now, we don't throw any ErrMsgs
- - - - -
f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00
Compile with wrapper but remove it for dist-install
- - - - -
7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00
Remove interface from LinksInfo

It was there to know the documentation home module when creating
a wiki link, but we already know this since we have the DocName.

- - - - -
e5729e6a by David Waern at 2008-10-15T20:49:18+00:00
Wibble
- - - - -
b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00
Use type synonyms for declarations and docs in H.I.Create
- - - - -
be71a15b by David Waern at 2008-10-15T21:12:17+00:00
Comment out unused type family stuff completely
- - - - -
91aaf075 by David Waern at 2008-10-15T21:49:04+00:00
Wibble
- - - - -
42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00
Move convenient type synonym to H.Types
- - - - -
db11b723 by David Waern at 2008-10-15T22:14:07+00:00
Add DeclInfo to H.Types
- - - - -
193552b6 by David Waern at 2008-10-15T22:15:01+00:00
Add subordinates with docs to the declaration map

The only place in the code where we want the subordinates for a declaration is
right after having looked up the declaration in the map.

And since we include subordinates in the map, we might as well take the
opportunity to store those subordinates that belong to a particular declaration
together with that declaration.

We also store the documentation for each subordinate.

- - - - -
31e6eebc by David Waern at 2008-10-16T17:18:47+00:00
Wibble
- - - - -
0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00
Fix haskell/haddock#61

We were not getting docs for re-exported class methods. This was because we
were looking up the docs in a map made from the declarations in the current
module being rendered. Obviously, re-exported class methods come from another
module.

Class methods and ATs were the only thing we were looking up using the doc map,
everything else we found in the ExporItems. So now I've put subordinate docs
in the ExportItem's directly, to make things a bit more consistent.

To do this, I added subordinates to the the declarations in the declaration
map. This was easy since we were computing subordinates anyway, to store
stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we
call what is now stored in the map. 

This little refactoring removes duplicate code to retrieve subordinates and
documentation from the HsGroup.

- - - - -
de47f20a by David Waern at 2008-10-16T22:06:35+00:00
Document function and improve its layout
- - - - -
e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00
Force interface more aggressively.

For running Haddock on GHC this reduces memory usage by about 50 MB on
a 32 bit system.  A heap profile shows total memory usage peak at
about 100 MB, but actual usage is at around 300 MB even with
compacting GC (+RTS -c).

- - - - -
b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00
Make renamer consistent

Instead of explicitly making some binders Undocumented, treat all names the
same way (that is, try to find a Documented name).

- - - - -
f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00
TAG GHC 6.10 fork
- - - - -
74599cd0 by David Waern at 2008-10-20T21:13:24+00:00
Do not save hidden modules in the .haddock file

We were saving interfaces of all processed modules including those hidden using
{-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links
when generating the index for the libraries that come with GHC.

This patch excludes modules with hidden documentation when writing .haddock
files. It should fix the above problem. 

- - - - -
7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00
Do not save hidden modules in the .haddock file (also for ghc >= 6.9)

When writing the first patch, I forgot to do the fix in both branches of an #if
macro.

- - - - -
b99b1951 by David Waern at 2008-10-22T20:04:18+00:00
Remove subordinate map and its usage

It is not needed now that we store subordinate names in the DeclInfo map.

- - - - -
da97cddc by David Waern at 2008-10-22T20:11:46+00:00
Tidy up code in H.I.Create a little

Remove commented out half-done type instance support, and remove DeclWithDoc
synonym.

- - - - -
6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00
Fix warnings in H.GHC.Utils
- - - - -
171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00
Fix warnings in H.Utils
- - - - -
c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00
Wibble
- - - - -
767fa06a by David Waern at 2008-10-27T19:59:04+00:00
Make named doc comments into ExportDoc instead of ExportDecl

Fixes a crash when processing modules without export lists containing named
docs.

- - - - -
e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00
Add HCAR entry
- - - - -
92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00
Update CHANGES
- - - - -
84d4da6e by David Waern at 2008-11-03T11:25:04+00:00
Add failing test for template haskell crash
- - - - -
2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00
Add tests/TH.hs
- - - - -
8a59348e by David Waern at 2008-11-04T21:30:26+00:00
TAG 2.3.0
- - - - -
54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00
Enable framed view of the HTML documentation.

This patch introduces:

 - A page that displays the documentation in a framed view.  The left
   side will show a full module index.  Clicking a module name will
   show it in the right frame.  If Javascript is enabled, the left
   side is split again to show the modules at the top and a very short
   synopsis for the module currently displayed on the right.

 - Code to generate the mini-synopsis for each module and the mini
   module index ("index-frames.html").

 - CSS rules for the mini-synopsis.

 - A very small amount of javascript to update the mini-synopsis (but
   only if inside a frame.)

Some perhaps controversial things:

 - Sharing code was very difficult, so there is a small amount of code
   duplication.

 - The amount of generated pages has been doubled, since every module
   now also gets a mini-synopsis.  The overhead should not be too
   much, but I haven't checked.  Alternatively, the mini-synopsis
   could also be generated using Javascript if we properly annotate
   the actual synopsis.

- - - - -
5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00
Follow change to ExportDecl in frames code
- - - - -
60e16308 by David Waern at 2008-11-04T23:35:26+00:00
Update CHANGES
- - - - -
d63fd26d by David Waern at 2008-11-04T23:37:43+00:00
Bump version number
- - - - -
c1660c39 by David Waern at 2008-11-04T23:44:46+00:00
Update CHANGES
- - - - -
995ab384 by David Waern at 2008-11-04T23:55:21+00:00
Remove .ref files from tests/output/
- - - - -
1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00
Output version info before running tests
- - - - -
649b182f by David Waern at 2008-11-05T22:45:37+00:00
Add ANNOUNCE message
- - - - -
c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00
Update ANNOUNCE
- - - - -
9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00
Wibble
- - - - -
5aac87ce by David Waern at 2008-11-06T21:07:48+00:00
Depend on base 4.* when using GHC >= 6.9, otherwise 3.*
- - - - -
b9796a74 by David Waern at 2008-11-06T21:13:40+00:00
Bump version to 2.4.1 and update CHANGES
- - - - -
d4b26baa by David Waern at 2008-11-06T21:26:33+00:00
Depend on base 4.0.* instead of 4.*
- - - - -
2cb0903c by David Waern at 2008-11-06T21:46:53+00:00
Fix warnings in H.B.HH and H.B.HH2
- - - - -
e568e89a by David Waern at 2008-11-06T21:47:12+00:00
Fix warnings in Haddock.ModuleTree
- - - - -
9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00
Fix warnings in Haddock.Version
- - - - -
02ac197c by David Waern at 2008-11-06T21:51:31+00:00
Fix warnings in H.InterfaceFile and H.Options
- - - - -
63e7439a by David Waern at 2008-11-06T21:59:45+00:00
Fix warnings in H.GHC.Typecheck
- - - - -
4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00
Set HscTarget to HscNothing instead of HscAsm

There used to be a bug in the GHC API that prevented us from setting this
value.

- - - - -
07357aec by David Waern at 2008-11-09T22:27:00+00:00
Re-export NameCache and friends from Distribution.Haddock
- - - - -
ea554b5a by David Waern at 2008-11-09T23:14:10+00:00
Add Haddock.GHC.Utils to other-modules in library
- - - - -
74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00
Export DocName in the library
- - - - -
241a58b3 by David Waern at 2008-11-10T01:19:18+00:00
Document the functions in H.DocName
- - - - -
edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00
Export H.DocName in the library
- - - - -
4f588d55 by David Waern at 2008-11-10T01:29:14+00:00
Make DocName an instance of NamedThing
- - - - -
b4647244 by David Waern at 2008-11-15T22:58:18+00:00
Reflect version bump in test suite
- - - - -
4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00
Update tests

For unknown reasons, test output for Bug1 and Test has changed for the better.

- - - - -
1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00
Store hidden modules in .haddock files

We store documentation for an entity in the 'InstalledInterface' of the
definition site module, and never in the same structure for a module which
re-exports the entity. So when a client of the Haddock library wants to look up
some documentation, he/she might need to access a hidden module. But we
currently don't store hidden modules in the .haddock files.

So we add the hidden modules and the Haddock options to the .haddock files.
The options will be used to filter the module list to obtain the visible
modules only, which is necessary for generating the contents and index for
installed packages.

- - - - -
8add6435 by David Waern at 2008-11-16T14:35:50+00:00
Bump major version number due to .haddock file format change
- - - - -
48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00
Update tests to account for version number bump
- - - - -
0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00
HADDOCK_DATA_DIR changed to haddock_datadir
- - - - -
5088b78c by David Waern at 2008-11-23T17:13:21+00:00
FIX haskell/haddock#45: generate two anchors for each name

We generate two anchor tags for each name, one where we don't escape the name
and one where we URI-encode it. This is for compatibility between IE and Opera.
Test output is updated.

- - - - -
5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00
Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584)
- - - - -
51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00
Allow referring to a specific section within a module in a module link
Fixes haskell/haddock#65

- - - - -
4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00
Update tests following anchor change
- - - - -
f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00
Haddock really shouldn't try to overwrite files.
- - - - -
98127499 by David Waern at 2008-12-07T14:09:15+00:00
Solve conflict
- - - - -
319356c5 by David Waern at 2008-10-22T21:16:55+00:00
Add -Wall -Werror to ghc-options
- - - - -
3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00
TAG 2.4.0
- - - - -
4b21e003 by David Waern at 2008-11-06T21:14:04+00:00
TAG 2.4.1
- - - - -
8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00
Remove -Werror
- - - - -
299d6deb by David Waern at 2008-12-07T14:25:18+00:00
Remove -Wall, we'll focus on warnings after 6.10.2 is out
- - - - -
5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00
Resolve conflict properly
- - - - -
67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00
Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a}
- - - - -
61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00
Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library
- - - - -
2fab8554 by David Waern at 2008-12-08T23:19:48+00:00
Make visible names from ExportItems

Instead of a complicated calculation of visible names out of GHC's export
items, we can get them straight out of the already calculated ExportItems.  The
ExportItems should represent exactly those items that are visible in an
interface. 

If store all the exported sub-names in ExportDecl instead of only those with
documentation, the calculation becomes very simple. So we do this change as
well (should perhaps have been a separate patch).
 
This should fix the problem with names from ghc-prim not appearing in the link
environment.

- - - - -
7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00
Wrap the GHC usage with defaultCleanupHandler
This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned.

- - - - -
7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00
Show re-exported names from external packages again

This fixes GHC ticket 2746.

In order to also link to the exported subordinate names of a declaration, we
need to re-introduce the sub map in the .haddock files.

- - - - -
119e4e05 by David Waern at 2009-01-06T23:34:17+00:00
Do not process boot modules

We should of course not try to produce documentation for boot modules! The
reason this has worked in the past is that the output of "real" modules
overwrites the output of boot modules later in the process. However, this
causes a subtle link environment problem. So let's get rid of this stupid
behaviour.
  
We avoid processing boot modules, but we continue to typecheck them.

- - - - -
c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00
Export modules also when coming from external packages

This seems to have regressed since a refactoring that was
part of the 2.3.0 release.

- - - - -
24031c17 by David Waern at 2009-01-10T15:26:26+00:00
Change version to 2.4.2 - no need to go to 2.5.0
- - - - -
864d1c3f by David Waern at 2009-01-10T15:35:20+00:00
Update tests to account for version number change
- - - - -
524ba886 by David Waern at 2009-01-10T18:29:17+00:00
Add test for Template Haskell splicing
- - - - -
05e6e003 by David Waern at 2009-01-10T19:35:42+00:00
Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages

We can't use HscNothing if we need to run code coming from modules inside
the processed package during typechecking, which is the case for some packages
using Template Haskell. This could be improved, to e.g. use HscInterpreted and
HscNothing where possible, instead of using HscC for all modules in the
package.

- - - - -
2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00
Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above
- - - - -
bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00
Fix the location of INPLACE_PKG_CONF; fixes the build
Spotted by Conal Elliott

- - - - -
943107c8 by David Waern at 2009-01-20T19:27:39+00:00
Document H.I.Create.collectDocs better
- - - - -
c6252e37 by David Waern at 2009-01-20T19:29:51+00:00
Fix Trac haskell/haddock#59: TH-generated declarations disappearing

This patch was contributed by Joachim Breitner (nomeata).

- - - - -
3568a6af by David Waern at 2009-01-21T21:41:48+00:00
Do not indicate that a constructor argument is unboxed

We only show the strictness annotation for an unboxed constructor argument. The
fact that it is unboxed is an implementation detail and should not be part of
the module interface.

- - - - -
562a4523 by David Waern at 2009-01-22T18:53:49+00:00
Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations

We now filter out everything that is not a proper Haskell declaration before
collecting the docs and attaching them to declarations.

- - - - -
6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00
Add test for quasi quotation. No reference output yet.
- - - - -
dc4100fd by David Waern at 2009-01-22T19:57:47+00:00
Improve quasi-quotation test and add reference output
- - - - -
908b74bb by David Waern at 2009-01-23T23:22:03+00:00
Filter out separately exported associated types in a smarter way
- - - - -
f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00
Correct spelling mistake in error message
- - - - -
24e4245d by David Waern at 2009-01-24T17:48:03+00:00
Correct comment
- - - - -
b5e8462f by David Waern at 2009-02-07T13:22:29+00:00
Do not show a subordinate at the top level if its parent is also exported

See note in the source code for more info.

- - - - -
4b09de57 by David Waern at 2009-02-07T13:53:53+00:00
Update test following change to top level subordinates
- - - - -
76379896 by David Waern at 2009-02-07T13:58:04+00:00
Remove html files in the tests/output/ directory which have been accidentally added
- - - - -
1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00
Typo in comment
- - - - -
fec367d0 by David Waern at 2009-02-24T20:21:17+00:00
Fix small bug

The rule is to prefer type constructors to other things when an identifier in a
doc string can refer to multiple things. This stopped working with newer GHC
versions (due to a tiny change in the GHC renamer). We implement this rule
in the HTML backend for now, instead of fixing it in GHC, since we will move
renaming of doc strings to Haddock in the future anyway. 

- - - - -
9b4172eb by David Waern at 2009-02-25T20:04:38+00:00
Fix bad error handling with newer GHCs

When support for GHC 6.10 was added, an error handler was installed only around
the typechecking phase. This had the effect that errors thrown during
dependency chasing were caught in the top-level exception handler and not
printed with enough detail.  With this patch we wrap the error handler around
all our usage of the Ghc monad. 

- - - - -
de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00
Hide funTyConName, now exported by TypeRep
- - - - -
4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00
Don't build the library when building in the GHC tree
- - - - -
1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00
Add a ghc.mk
- - - - -
3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00
do .depend generation for haddock with the stage1 compiler
This is a bit of a hack. We mkdepend with stage1 as if .depend
depends on the stage2 compiler then make goes wrong: haddock's
.depend gets included, which means that make won't reload until
it's built, but we can't build it without the stage2 compiler. We
therefore build the stage2 compiler before its .depend file is
available, and so compilation fails.

- - - - -
b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00
Give haddock a wrapper on unix in the new GHC build system
- - - - -
9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00
Create inplace/lib/html in the new GHC build system
- - - - -
93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00
TAG GHC 6.10.1 release
- - - - -
06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00
Define __GHC_PATCHLEVEL__ for recent version of GHC (stable).
- - - - -
680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00
'needsTemplateHaskell' is not defined in current stable GHC.
- - - - -
6c5619df by David Waern at 2009-02-25T22:15:23+00:00
Hide fynTyConName only for recent GHC versions
- - - - -
6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00
Add the module to one of haddocks warnings
- - - - -
e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00
Bug fix
We tried to filter out subordinates that were already exported through their parent.

This didn't work properly since we were in some cases looking at the
grand-parent and not the parent.  We now properly compute all the parent-child
relations of a declaration, and use this information to get the parent of a
subordinate.

We also didn't consider record fields with multiple parents. This is now
handled correctly.

We don't currently support separately exported associated types. But when we
do, they should be handled correctly by this process too.

Also slightly improved the warning message that we give when filtering out
subordinates.

- - - - -
10a79a60 by David Waern at 2009-02-27T22:08:08+00:00
Fix error message conflict

The module name is already written in the beginning of the message, as
seems to be the convention in Haddock. Perhaps not so clear, but we
should change it everywhere in that case. Leaving it as it is for now.

- - - - -
c5055c7f by David Waern at 2009-02-27T22:15:17+00:00
Shorten warning message
- - - - -
a72fed3a by David Waern at 2009-02-28T00:53:55+00:00
Do not show package name in warning message
- - - - -
a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00
Install haddock in the new GHC build system
- - - - -
dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00
Relax base dependency to < 4.2, not < 4.1
- - - - -
5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00
Bump .haddock file version number (due to change of format)
- - - - -
f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00
Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1
- - - - -
23f78831 by David Waern at 2009-03-21T16:40:52+00:00
Update CHANGES
- - - - -
7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00
Update ANNOUNCE
- - - - -
0771e00a by David Waern at 2009-03-21T16:54:40+00:00
Update ANNOUNCE, again
- - - - -
81a6942a by David Waern at 2009-03-21T17:50:06+00:00
Don't be too verbose in CHANGES
- - - - -
29861dcf by David Waern at 2009-03-21T18:03:31+00:00
TAG 2.4.2
- - - - -
a585f285 by David Waern at 2009-03-21T19:20:29+00:00
Require Cabal >= 1.2.3
- - - - -
7c611662 by David Waern at 2009-03-21T19:21:48+00:00
TAG 2.4.2 with cabal-version >= 1.2.3
- - - - -
23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00
new GHC build system: use shell-wrappers macro
- - - - -
25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00
Fix (with a hack?) haddock in teh new build system
- - - - -
6a29a37e by David Waern at 2009-03-24T22:10:15+00:00
Remove unnecessary LANGUAGE pragma
- - - - -
954da57d by David Waern at 2009-03-24T22:21:23+00:00
Fix warnings in H.B.DevHelp
- - - - -
1619f1df by David Waern at 2009-03-26T23:20:44+00:00
-Wall police in H.B.Html
- - - - -
b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00
install Haddock's html stuff
- - - - -
78e0b107 by David Waern at 2008-12-07T19:58:53+00:00
Add verbosity flag and utils, remove "verbose" flag
- - - - -
913dae06 by David Waern at 2008-12-07T20:01:05+00:00
Add some basic "verbose" mode logging in H.Interface
- - - - -
1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00
Fix conflicts
- - - - -
22f82032 by David Waern at 2009-03-27T21:15:11+00:00
Remove H.GHC.Typecheck
- - - - -
81557804 by David Waern at 2009-03-27T21:19:22+00:00
Remove docNameOrig and use getName everywhere instead
- - - - -
d8267213 by David Waern at 2009-03-27T21:21:46+00:00
Use docNameOcc instead of nameOccName . getName
- - - - -
5d55deab by David Waern at 2009-03-27T21:33:04+00:00
Remove H.DocName and put DocName in H.Types
- - - - -
8ba72611 by David Waern at 2009-03-27T22:06:26+00:00
Document DocName
- - - - -
605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00
-Wall police
- - - - -
e4da93ae by David Waern at 2009-03-27T23:12:53+00:00
-Wall police in H.B.Hoogle
- - - - -
bb255519 by David Waern at 2009-03-27T23:41:28+00:00
Define Foldable and Traversable instances for Located
- - - - -
f1195cfe by David Waern at 2009-03-27T23:51:34+00:00
Wibble
- - - - -
23818d7c by David Waern at 2009-03-28T00:03:55+00:00
-Wall police in H.I.Rename
- - - - -
0f050d67 by David Waern at 2009-03-28T00:15:15+00:00
-Wall police in H.I.AttachInstances
- - - - -
0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00
Wibble
- - - - -
275d4865 by David Waern at 2009-03-28T21:27:06+00:00
Layout fix
- - - - -
54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00
-Wall police in H.I.Create
- - - - -
7f58b117 by David Waern at 2009-03-28T22:10:19+00:00
-Wall police in H.Interface
- - - - -
f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00
-Wall police in Main
- - - - -
29da355c by David Waern at 2009-03-28T22:23:39+00:00
Turn on -Wall -Werror
- - - - -
446d3060 by David Waern at 2009-04-01T20:40:30+00:00
hlint police
- - - - -
3867c9fc by David Waern at 2009-04-01T20:48:42+00:00
hlint police
- - - - -
bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00
hlint police
- - - - -
e0e90866 by David Waern at 2009-04-05T12:42:53+00:00
Move H.GHC.Utils to H.GhcUtils
- - - - -
9cbd426b by David Waern at 2009-04-05T12:57:21+00:00
Remove Haddock.GHC and move its (small) contents to Main
- - - - -
b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00
Fix whitespace and stylistic issues in Main
- - - - -
3c04aa56 by porges at 2008-12-07T08:22:19+00:00
add unicode output
- - - - -
607918da by David Waern at 2009-04-26T15:09:43+00:00
Resolve conflict
- - - - -
4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00
fix markup
- - - - -
436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00
clean up
- - - - -
bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00
new GHC build system: add $(exeext)
- - - - -
9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00
update for new GHC build system layout
- - - - -
d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00
GHC new build system fixes
- - - - -
5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00
Tweak new build system
- - - - -
9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00
add build instructions for GHC
- - - - -
66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00
Quote program paths in ghc.mk
- - - - -
bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00
Use a bang pattern on an unlifted binding
- - - - -
3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00
Include haddock in GHC bindists
- - - - -
ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00
Delete Haddock.Exception and move contents to Haddock.Types

Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types.

- - - - -
4464fb9b by David Waern at 2009-06-24T22:23:23+00:00
Add Haddock module headers

Add a proper Haddock module header to each module, with a more finegrained
copyright. If you feel mis-accreditted, please correct any copyright notice!

The maintainer field is set to haddock at projects.haskell.org.

Next step is to add a brief description to each module.

- - - - -
5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00
Fix spelling error
- - - - -
6d074cdb by David Waern at 2009-06-25T21:53:56+00:00
Document Interface and InstalledInterface better
- - - - -
d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00
Remove misplaced whitespace in H.I.Rename
- - - - -
fa381c49 by David Waern at 2009-06-27T13:26:03+00:00
Fix haskell/haddock#104 - create output directory if missing
- - - - -
91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00
TAG 2009-06-25
- - - - -
0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00
Follow extra field in ConDecl
- - - - -
b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00
Update Makefile for the new GHC build system
- - - - -
df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00
Resolve conflicts
- - - - -
1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00
Remove the -Wwarn hack in the GHC build system
- - - - -
7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00
Fix warnings
- - - - -
5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00
Bump version number
Cabal needs to distinguish between haddocks having a --verbose and
--verbosity flag

- - - - -
6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00
Wibble
- - - - -
2308b66f by David Waern at 2009-07-06T20:24:20+00:00
Clearer printing of versions by runtests.hs
- - - - -
d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00
Fix (invisible) bug introduced by unicode patch
- - - - -
2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00
Use HscAsm instead of HscC when using TH
- - - - -
18f3b755 by David Waern at 2009-07-06T22:10:22+00:00
Update HCAR entry (by Janis)
- - - - -
a72ac9db by David Waern at 2009-07-06T23:01:35+00:00
Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611
- - - - -
549135d2 by David Waern at 2009-07-06T23:11:41+00:00
Remove unused functions from Haddock.Utils
- - - - -
b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00
revert to split-index for large indices
- remove the search-box, because browsers have search-for-text
abilities anyway.
- pick 150 items in index as the arbitrary time at which to split it
- notice the bug that identifiers starting with non-ASCII characters
won't be listed in split-index, but don't bother to fix it yet (see
ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 )

- - - - -
78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00
Implement GADT records in HTML backend
- - - - -
4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00
add test for GADT records
- - - - -
79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00
Update test suite following version bump
- - - - -
5932c011 by David Waern at 2009-08-02T10:25:39+00:00
Fix documentation bug
- - - - -
a6970fca by David Waern at 2009-08-12T23:08:53+00:00
Remove support for ghc 6.8.* from .cabal file
- - - - -
c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00
Fix unused import warnings
- - - - -
fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00
Use cProjectVersion directly rather than going through compilerInfo
Fixes the build after changes in GHC

- - - - -
548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00
follow changes in GHC's ForeignType
- - - - -
9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00
Switch from PatternSignatures to ScopedTypeVariables in Main
- - - - -
eebf39bd by David Waern at 2009-08-14T17:14:28+00:00
Version .haddock files made with GHC 6.10.3/4 correclty
- - - - -
58f3e735 by David Waern at 2009-08-14T17:19:37+00:00
Support GHC 6.10.* and 6.11.* only
- - - - -
5f63cecc by David Waern at 2009-08-14T22:03:20+00:00
Do not version .haddock file based on GHC patchlevel version

We require that the instances of Binary that we use from GHC will not change
between patchlevel versions.

- - - - -
d519de9f by David Waern at 2009-08-14T23:50:00+00:00
Update CHANGES
- - - - -
35dccf5c by David Waern at 2009-08-14T23:51:38+00:00
Update version number everywhere
- - - - -
6d363fea by David Waern at 2009-08-15T09:46:49+00:00
Update ANNOUNCE
- - - - -
c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00
Remove -Werror

Forgot that Hackage doesn't like it.

- - - - -
a125c12b by David Waern at 2009-08-15T09:49:50+00:00
Require Cabal >= 1.6
- - - - -
adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00
Cross-Package Documentation version 4
- - - - -
3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00
Put all the IN_GHC_TREE stuff inside getGhcLibDir
- - - - -
56624097 by David Waern at 2009-08-15T23:52:03+00:00
Add --print-ghc-libdir
- - - - -
f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00
Read base.haddock when running tests

We can now test cross-package docs.

- - - - -
283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00
Update test output - we now have more links
- - - - -
673d1004 by David Waern at 2009-08-16T01:26:08+00:00
Read process.haddock when running tests
- - - - -
0d127f82 by David Waern at 2009-08-16T01:43:04+00:00
Add a test for cross-package documentation
- - - - -
f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00
Follow GHC build system changes
- - - - -
5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00
make cross-package list types look nicer
- - - - -
c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00
Haddock.Convert: export more functions
This lets us remove some code in Haddock.Interface.AttachInstances

- - - - -
2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00
switch AttachInstances to use synify code
It changed an instance from showing ((,) a b) to (a, b)
because my synify code is more sophisticated; I hope the latter
is a good thing rather than a bad thing aesthetically, here.

But this definitely reduces code duplication!

- - - - -
b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00
Find instances using GHC, which is more complete.
In particular, it works cross-package.

An intermediate patch also moved the instance-finding into
createInterface, but that move turned out not to be necessary,
so if we want to do that, it'd go in a separate patch.
(Is that possible? Or will we need GHC to have loaded all the modules
first, before we can go searching for the instances (e.g. if the
modules are recursive or something)?)

- - - - -
6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00
fix preprocessor conditional sense
- - - - -
942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00
remove ghc 6.8 conditionals from Haddock.Interface
- - - - -
4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00
Fix GHC 6.11 build in Haddock.Convert
- - - - -
0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00
hacks to make it compile without fnArgDocsn
- - - - -
7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00
less big-Map-based proper extraction of constructor subdocs
- - - - -
b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00
Html: remove unnecessary+troublesome GHC. qualifications
- - - - -
96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00
Move doc parsing/lexing into Haddock for ghc>=6.11
- - - - -
e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00
get rid of unused DocMap parameter in Html
- - - - -
66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00
fix horrible named-docs-disappearing bug :-)
- - - - -
a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00
re-implement function-argument docs
..on top of the lexParseRn work.
This patch doesn't change the InstalledInterface format, and thus,
it does not work cross-package, but that will be easy to add
subsequently.

- - - - -
8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00
cross-package fnArgDocs. WARNING: changes .haddock binary format
While breaking the format, I took the opportunity to unrename the
DocMap that's saved to disk, because there's really no reason that
we want to know what *another* package's favorite place to link a
Name to was.  (Is that true? Or might we want to know, someday?)

Also, I added instance Binary Map in InterfaceFile.
It makes the code a little simpler without changing anything of
substance.  Also it lets us add another Map hidden inside another
Map (fnArgsDocs in instDocMap) without having really-convoluted
serialization code.  Instances are neat!
I don't understand why this change to InterfaceFile seemed to
subtly break binary compatibility all by itself, but no matter,
I'll just roll it into the greater format-changing patch. Done!

- - - - -
30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00
Improve behavior for unfindable .haddock
- - - - -
aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00
add comment for FnArgsDoc type
- - - - -
49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00
bugfix: restore fnArgDocs for type-synonyms
- - - - -
f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00
Backends.Hoogle: eliminate warnings
- - - - -
a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00
Haddock.Convert: eliminate warnings
- - - - -
5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00
Haddock.Interface.Rename: eliminate warnings
- - - - -
0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00
Main.hs: remove ghc<6.9 conditionals
- - - - -
e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00
Main.hs: eliminate warnings (except for OldException)
- - - - -
61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00
move get*LibDir code in Main.hs, to +consistent code, -duplication
- - - - -
948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00
Main.hs: OldException->Exception: which eliminates warnings
- - - - -
3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00
GhcUtils: ghc >= 6.10
- - - - -
2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00
InterfaceFile: ghc >= 6.10
- - - - -
d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00
Types: ghc >= 6.10
- - - - -
ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00
ModuleTree: ghc >= 6.10
- - - - -
883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00
Backends.DevHelp: ghc >= 6.10
- - - - -
04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00
Backends.Html: ghc >= 6.10
- - - - -
a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00
Utils: ghc >= 6.10
- - - - -
b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00
eliminate haskell98 dependency, following GHC's example
It turns out I/we already had, and it was only a matter of
deleting it from the cabal file.

- - - - -
292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00
refactor out subordinatesWithNoDocs
dep of inferenced-decls fix

- - - - -
c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00
Eradicate wrong runtime warning for type-inferenced exported-functions
see the long comment in the patch for why I did it this way :-)

- - - - -
4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00
Clean up tyThingToHsSynSig a little

Factor out noLoc and use the case construct. Also rename the function to
tyThingToLHsDecl, since it doesn't just create type signatures.

- - - - -
28ab9201 by David Waern at 2009-09-04T22:58:50+00:00
Wibble
- - - - -
0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00
Add more copyright owners to H.I.AttachInstances
- - - - -
122441b1 by David Waern at 2009-09-06T18:44:12+00:00
Style police
- - - - -
1fa79463 by David Waern at 2009-09-06T18:57:45+00:00
Move toHsInstHead to Haddock.Convert and call it synifyInstHead
- - - - -
0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00
Use colordiff to display test results if available
- - - - -
ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00
Follow changes in GHC's interface file format
Word32 instead of Int for FastString and Name offsets

- - - - -
537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00
define unpackPackageId (it was removed from GHC)
- - - - -
50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00
Remove commented-out code
- - - - -
511631fe by David Waern at 2009-09-09T23:19:05+00:00
Correct copyright in H.I.ParseModuleHeader
- - - - -
898ec768 by David Waern at 2009-09-11T11:22:29+00:00
Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps
  
This fixes the missing docs problem. The Eq and Ord instances for Name uses the
unique number in Name. This number is created at deserialization time by GHC's
magic Binary instance for Name, and it is random. Thus, fromAscList can't be used
at deserialization time, even though toAscList was used at serialization time.

- - - - -
37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00
Track change in HsType
- - - - -
eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00
Allow building with base 4.2
- - - - -
bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00
Loosen the GHC dependency
- - - - -
5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00
Fix building with GHC >= 6.12
- - - - -
fb131481 by David Waern at 2009-09-11T11:24:48+00:00
Update runtests.hs to work with GHC 6.11
- - - - -
ac3a419d by David Waern at 2009-09-11T11:25:14+00:00
Update CrossPackageDocs test
- - - - -
ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00
Add reference output for CrossPackageDocs
- - - - -
520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00
Fix installation in the GHC build system
- - - - -
28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00
GHC build system: Make *nix installation work in paths containing spaces
- - - - -
5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00
Track change in HsType for the right compiler version
- - - - -
905097ce by David Waern at 2009-11-14T12:10:47+00:00
hlint police
- - - - -
04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00
Use defaultObjectTarget rather than HscAsm
This fixes haddock when we don't have a native code generator

- - - - -
966eb079 by David Waern at 2009-11-15T12:32:21+00:00
Remove commented-out code
- - - - -
37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00
Make runtests.hs strip links before diffing

Generates easier to read diffs when tests fail. The content of the links
is not important anyway since it is not taken into account by the tests.

- - - - -
3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00
Follow findProgramOnPath signature change in runtests.hs
- - - - -
b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00
Follow removal of GHC.MVar from base in CrossPackageDocs 
- - - - -
f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00
Make copy.hs strip link contents before copying

No more updating of reference files when URLs in links changes.

- - - - -
4c9c420d by David Waern at 2009-11-22T15:26:41+00:00
Update test reference output

* More links (Int, Float etc)
* Stripped link contents 

- - - - -
a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00
Update CrossPackageDocs reference output

- Remove GHC.MVar import (removed from base)
- Strip link contents

- - - - -
43491394 by David Waern at 2009-11-23T23:20:00+00:00
Update test reference files with comments on instances
- - - - -
0d370a0b by David Waern at 2009-11-23T23:25:16+00:00
Bump version number
- - - - -
2293113e by David Waern at 2009-11-24T20:55:49+00:00
Comments on instances

Implementing this was a little trickier than I thought, since we need to match
up instances from the renamed syntax with instances represented by
InstEnv.Instance. This is due to the current design of Haddock, which matches
comments with declarations from the renamed syntax, while getting the list of
instances of a class/family directly using the GHC API.

- Works for class instances only (Haddock has no support for type family
  instances yet)
- The comments are rendered to the right of the instance head in the HTML output
- No change to the .haddock file format
- Works for normal user-written instances only. No comments are added on
  derived or TH-generated instances

- - - - -
bf586f29 by David Waern at 2009-11-27T22:05:15+00:00
Whitespace police
- - - - -
b8f03afa by David Waern at 2009-11-27T22:11:46+00:00
Remove bad whitespace and commented-out pieces
- - - - -
90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00
Whitespace police
- - - - -
b5ede900 by David Waern at 2009-11-27T22:15:50+00:00
Whitespace police
- - - - -
e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00
Remove Name from DocInstance

It's not used.

- - - - -
9502786c by David Waern at 2009-11-28T13:56:54+00:00
Require at least GHC 6.12

While regression testing Haddock, I found a bug that happens with GHC 6.10.3,
but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it
down.

I think we should just always require the latest major GHC version. The time
spent on making Haddock work with older versions is too high compared to the
time spent on bugfixing, refactoring and features.

- - - - -
8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00
Remove cruft due to compatibility with older GHCs
- - - - -
46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00
Add a documentation header to Haddock.Convert
- - - - -
c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00
Remove unused H.Utils.FastMutInt2
- - - - -
490aba80 by David Waern at 2009-11-28T15:36:36+00:00
Rename Distribution.Haddock into Documentation.Haddock
- - - - -
33ee2397 by David Waern at 2009-11-28T15:36:47+00:00
Fix error message
- - - - -
a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00
Add a test flag that brings in QuickCheck
- - - - -
fa049e13 by David Waern at 2009-11-28T19:32:18+00:00
Say that we want quickcheck 2
- - - - -
f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00
Add an Arbitrary instance for HsDoc
- - - - -
da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00
Rename HsDoc back into Doc
- - - - -
edb60101 by David Waern at 2009-11-28T22:16:16+00:00
Move H.Interface.Parse/Lex to H.Parse/Lex

These are not just used to build Interfaces.

- - - - -
0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00
Update version number in test suite
- - - - -
5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00
Improve doc of DocName
- - - - -
7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00
TAG GHC 6.12-branch created
- - - - -
0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00
TAG GHC 6.12.1 release
- - - - -
65e9be62 by David Waern at 2009-12-21T16:58:58+00:00
Update CHANGES
- - - - -
145cee32 by David Waern at 2009-12-21T16:59:09+00:00
TAG 2.6.0
- - - - -
3c552008 by David Waern at 2009-12-22T17:11:14+00:00
Update ANNOUNCE
- - - - -
931f9db4 by David Waern at 2010-01-22T19:57:17+00:00
Convert haddock.vim to use unix newlines
- - - - -
4e56588f by David Waern at 2010-01-22T22:11:17+00:00
Remove unnecessary (and inexplicable) uses of nub
- - - - -
744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00
Follow move of parser and lexer
- - - - -
e34bab14 by David Waern at 2010-01-22T22:49:13+00:00
Use findProgramLocation instead of findProgramOnPath in runtests.hs
- - - - -
8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00
fix html arg-doc off-by-one and silliness
- - - - -
9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00
Create a test for function argument docs
- - - - -
507a82d7 by David Waern at 2010-01-22T23:24:47+00:00
Put parenthesis around type signature arguments of function type
- - - - -
8a305c28 by David Waern at 2010-01-23T17:26:59+00:00
Add reference file for the FunArgs test
- - - - -
1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00
Improve FunArg test and update Test.html.ref
- - - - -
2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00
Do not generate illegal character in HTML ID attribute.
- - - - -
c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00
Fix Haddock markup error in comment
- - - - -
c6416a73 by David Waern at 2010-02-24T22:55:08+00:00
Large additions to the Haddock API

Also improved and added more doc comments.

- - - - -
57d289d7 by David Waern at 2010-02-24T22:58:02+00:00
Remove unused ifaceLocals
- - - - -
80528d93 by David Waern at 2010-02-25T21:05:09+00:00
Add HaddockModInfo to the API
- - - - -
82806848 by David Waern at 2010-02-25T21:05:27+00:00
Wibble
- - - - -
744cad4c by David Waern at 2010-02-25T23:30:59+00:00
Make it possible to run a single test
- - - - -
6a806e4c by David Waern at 2010-03-14T14:19:39+00:00
Bump version number
- - - - -
a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00
Update ANNOUNCE
- - - - -
6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00
Add missing dependencies for 'library' in haddock.cabal
- - - - -
faefe2bd by David Waern at 2010-03-15T22:29:37+00:00
Solve conflicts
- - - - -
9808ad52 by David Waern at 2010-03-15T22:51:21+00:00
Bump version number
- - - - -
eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00
Update CHANGES
- - - - -
f95cd891 by David Waern at 2010-03-15T23:01:06+00:00
Add Paths_haddock to other-modules of library
- - - - -
65997b0a by David Waern at 2010-03-15T23:14:59+00:00
Update CHANGES
- - - - -
7e251731 by David Waern at 2010-03-15T23:15:30+00:00
Bump version number
- - - - -
c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00
Fix warning
- - - - -
1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00
Fix imports for new location of splitKindFunTys
- - - - -
474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00
Update Haddock for quasiquotes
- - - - -
0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00
Track changes in HsTyVarBndr
- - - - -
2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00
Track HsSyn chnages
- - - - -
9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00
Resolve conflicts
- - - - -
a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00
Track change in HsUtils; and use a nicer function not an internal one
- - - - -
27994854 by David Waern at 2010-03-18T22:22:27+00:00
Fix build with GHC 6.12.1
- - - - -
11f6e488 by David Waern at 2010-03-18T22:24:09+00:00
Bump version in test reference files
- - - - -
0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00
Fix library part of cabal file when in ghc tree
- - - - -
3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00
First, experimental XHTML rendering
    switch to using the xhtml package

    copied Html.hs to Xhtml.hs
        and split into sub-modules under Haddock/Backends/Xhtml
        and detabify

    moved footer into div, got ready for iface change
    headers converted to semantic markup
    contents in semantic markup
    summary as semantic markup
    description in semantic markup, info block in header fixed

    factored out rendering so during debug it can be readable
        (see renderToString)


- - - - -
b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00
apply changes to Html.hs to Xhtml/*.hs
	incorporate changes that were made between the time Html.hs
	was copied and split into Xhtml.hs and Xhtml/*.hs
	includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1"

- - - - -
73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00
Follow LazyUniqFM->UniqFM in GHC
- - - - -
db4f602b by David Waern at 2010-03-29T22:00:01+00:00
Fix build with GHC 6.12
- - - - -
d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00
Add missing dependencies to cabal file
- - - - -
e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00
Add markup support for interactive examples
- - - - -
e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00
Add tests for interactive examples
- - - - -
5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00
Propagate source positions from Lex.x to Parse.y
- - - - -
6493b46f by David Waern at 2010-04-07T21:48:57+00:00
Let runtests.hs die when haddock has not been built
- - - - -
5e34423e by David Waern at 2010-04-07T22:01:13+00:00
Make runtests.hs slightly more readable
- - - - -
321d59b3 by David Waern at 2010-04-07T22:13:27+00:00
Fix haskell/haddock#75

Add colons to the $ident character set. 

- - - - -
37b08b8d by David Waern at 2010-04-08T00:32:52+00:00
Fix haskell/haddock#118

Avoid being too greedy when lexing URL markup (<..>), in order to allow
multiple URLs on the same line. Do the same thing with <<..>> and #..#.

- - - - -
df8feac9 by David Waern at 2010-04-08T00:57:33+00:00
Make it easier to add new package deps to test suite

This is a hack - we should use Cabal to get the package details instead.

- - - - -
1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00
Add ghc-prim to test suite deps
- - - - -
27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00
Let parsing fails on paragraphs that are immediately followed by an
example

This is more consistent with the way we treat code blocks.

- - - - -
83096e4a by David Waern at 2010-04-08T21:20:00+00:00
Improve function name
- - - - -
439983ce by David Waern at 2010-04-10T10:46:14+00:00
Fix haskell/haddock#112

No link was generated for 'Addr#' in a doc comment. The reason was simply that
the identifier didn't parse. We were using parseIdentifier from the GHC API,
with a parser state built from 'defaultDynFlags'. If we pass the dynflags of
the module instead, the right options are turned on on while parsing the
identifer (in this case -XMagicHash), and the parse succeeds.

- - - - -
5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00
Rename startGhc into withGhc
- - - - -
dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00
Add documentation for interactive examples
- - - - -
c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00
Slight fix to the documentation of examples
- - - - -
06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00
Rename Interactive Examples into Examples (and simplify explanation)
- - - - -
264830cb by David Waern at 2010-05-10T20:07:27+00:00
Update CHANGES with info about 2.6.1
- - - - -
8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00
Add unit tests for parser
- - - - -
68297f40 by David Waern at 2010-05-10T21:53:37+00:00
Improve testsuite README
- - - - -
f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00
Re-organise the testsuite structure
- - - - -
a360f710 by David Waern at 2010-05-11T19:18:03+00:00
Shorten function name
- - - - -
1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00
Update runtests.hs following testsuite re-organisation
- - - - -
ffebe217 by David Waern at 2010-05-11T21:40:10+00:00
Update runtests.hs to use base-4.2.0.1
- - - - -
635de402 by David Waern at 2010-05-11T21:41:11+00:00
Update runparsetests.hs following testsuite reorganisation
- - - - -
72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00
Fix build
- - - - -
1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00
Remove redundant import
- - - - -
1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00
Minor wibbles to HsBang stuff
- - - - -
dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00
GHC build system: Follow "rm" variable changes
- - - - -
7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00
Fix build with GHC 6.12.2
- - - - -
7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00
Fixes to comments only
- - - - -
8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00
ModuleMap -> IfaceMap
- - - - -
1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00
Fix whitespace style issues
- - - - -
e96783c0 by David Waern at 2010-05-13T19:08:53+00:00
Fix comment
- - - - -
c998a78b by David Waern at 2010-05-13T19:39:00+00:00
Position the module header the same way everywhere
Silly, but nice with some consistency :-)

- - - - -
b48a714e by David Waern at 2010-05-13T19:41:32+00:00
Position of module header, this time in the HTML backends
- - - - -
f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00
Two newlines between declarations in Main
- - - - -
071d44c7 by David Waern at 2010-05-13T19:44:21+00:00
Newlines in Convert
- - - - -
036346db by David Waern at 2010-05-13T19:46:47+00:00
Fix a few stylistic issues in H.InterfaceFile
- - - - -
f0b8379e by David Waern at 2010-05-13T19:47:53+00:00
Add newlines to H.ModuleTree
- - - - -
27409f8e by David Waern at 2010-05-13T19:51:10+00:00
Fix stylistic issues in H.Utils
- - - - -
24774a11 by David Waern at 2010-05-13T20:00:43+00:00
Structure H.Types better
- - - - -
7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00
Remove bad Arbitrary instance
- - - - -
fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00
Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead
- - - - -
fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00
Export a couple of more types from the API
- - - - -
b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00
Improve doc comment for Interface
- - - - -
c585f2ce by David Waern at 2010-05-13T21:30:14+00:00
Improve documentation of Haddock.Interface
- - - - -
e6791db2 by David Waern at 2010-05-13T22:07:35+00:00
Remove meaningless comments
- - - - -
7801b390 by David Waern at 2010-05-14T17:53:33+00:00
Remove unused modules
- - - - -
f813e937 by David Waern at 2010-05-14T17:55:17+00:00
Re-direct compilation output to a temporary directory
Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of
writing compilation files to GHC's output directory (default ".").

- - - - -
e56737ec by David Waern at 2010-05-14T18:06:11+00:00
Wibble
- - - - -
e40b0447 by David Waern at 2010-05-14T19:01:52+00:00
Move flag evaluation code from Main to Haddock.Options
Determining the value of "singular" flags (by e.g. taking the last occurrence
of the flag) and other flag evaluation should done in Haddock.Options which is
the module that is supposed to define the command line interface. This makes
Main a bit easier on the eyes as well.

- - - - -
27091f57 by David Waern at 2010-05-14T19:05:10+00:00
Wibble
- - - - -
c658cf61 by David Waern at 2010-05-14T19:06:49+00:00
Re-order things in Haddock.Options a bit
- - - - -
8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00
De-tabify Haddock.Options and fix other whitespace issues
- - - - -
0df16b62 by David Waern at 2010-05-14T19:25:07+00:00
Improve comments
- - - - -
80b38e2b by David Waern at 2010-05-14T19:26:42+00:00
Whitespace police
- - - - -
fe580255 by David Waern at 2010-05-14T19:31:23+00:00
Wibbles to comments
- - - - -
a2b43fad by David Waern at 2010-05-14T20:24:32+00:00
Move some more flag functions to Haddock.Options
- - - - -
3f895547 by David Waern at 2010-05-14T20:37:12+00:00
Make renderStep a top-level function in Main
- - - - -
5cdca11d by David Waern at 2010-05-14T20:39:27+00:00
Spelling in comment
- - - - -
ad98d14c by David Waern at 2010-05-14T20:40:26+00:00
Comment fixes
- - - - -
0bb9218f by David Waern at 2010-05-14T20:49:01+00:00
Whitespace police
- - - - -
0f0a533f by David Waern at 2010-05-15T16:42:29+00:00
Improve description of --dump-interface
- - - - -
5b2833ac by David Waern at 2010-05-15T17:16:53+00:00
Document --no-tmp-comp-dir
- - - - -
8160b170 by David Waern at 2010-05-15T17:18:59+00:00
Wibble
- - - - -
570dbe33 by David Waern at 2010-05-18T21:15:38+00:00
HLint police
- - - - -
204e425f by David Waern at 2010-05-18T21:16:30+00:00
HLint police
- - - - -
6db657ac by David Waern at 2010-05-18T21:16:37+00:00
Wibble
- - - - -
b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00
Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100)
- - - - -
3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00
Allow base-4.3
- - - - -
c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00
Fix compilation with GHC 6.13
- - - - -
6181296c by David Waern at 2010-06-08T21:09:05+00:00
Display name of prologue file when parsing it fails
- - - - -
7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00
Remove redundant imports
- - - - -
980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00
isLocalAndTypeInferenced: fix for local module names overlapping package modules
- - - - -
d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00
Unresolved identifiers in Doc get replaced with DocMonospaced
rather than plain strings

- - - - -
d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00
LaTeX backend (new options: --latex, --latex-style=<style>)
- - - - -
437afa9e by David Waern at 2010-07-01T12:02:44+00:00
Fix a few stylistic whitespace issues in LaTeX backend
- - - - -
85bc1fae by David Waern at 2010-07-01T15:42:45+00:00
Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this)
- - - - -
7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00
Update test following Simon's patch to render unresolved names in monospaced font
- - - - -
08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00
Warning police
- - - - -
d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00
Fix a bug in attachInstances

We didn't look for instance docs in all the interfaces of the package. This had
the effect of instance docs not always showing up under a declaration. I took
the opportunity to clean up the code in H.I.AttachInstances a bit as well. More
cleanup is needed, however.

- - - - -
d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00
Add missing dependencies to cabal file
- - - - -
24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00
add exports to Xhtml modules
- - - - -
84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00
clean up Doc formatting code
- add CSS for lists 
- renderToString now uses showHtml since prettyHtml messes up <pre> sections

- - - - -
bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00
tweak list css
- - - - -
0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00
all decls now generate Html not HtmlTable
	- ppDecl return Html, and so now do all of the functions it calls
	- added some internal tables to some decls, which is wrong, and will have
		to be fixed
	- decl "Box" functions became "Elem" functions to make clear they aren't
		in a table anymore (see Layout.hs)
	- docBox went away, as only used in one place (and its days are numbered)
	- cleaned up logic in a number of places, removed dead code
	- added maybeDocToHtml which simplified a number of places in the code

- - - - -
dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00
clean up processExport and place a div around each decl
- - - - -
e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00
data decls are now a sequence of paragraphs, not a table
- - - - -
89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00
removed commented out code that can't be maintained
- - - - -
d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00
removed declWithDoc and cleaned up data decls in summary
- - - - -
ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00
merge in markupExample changes
- - - - -
c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00
made record fields be an unordList, not a table
- - - - -
ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00
fixed surround of instance and constructor tables
- - - - -
0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00
fix class member boxes in summary
- - - - -
5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00
remove unused bodyBox
- - - - -
e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00
fixed javascript quoting/escpaing issue
- - - - -
f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00
adjust css for current markup
- - - - -
e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00
added assoicated types and methods back into class decls
- - - - -
84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00
merge in changes from the big-whitespace cleanup
- - - - -
3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00
adjust synopsis and bottom bar spacing
- - - - -
3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00
fix missing space in "module" lines in synoposis
- - - - -
9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00
changed tt elements to code elements
- - - - -
50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00
factored out ppInstances
- - - - -
3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00
push single constructors (newtype) onto line with decl
- - - - -
e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00
remove <++> connector
- - - - -
56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00
change to new page structure
- - - - -
04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00
constructors and args as dl lists, built in Layout.hs
- - - - -
65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00
better interface to subDecls
- - - - -
72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00
made subDecl tables looks just so
- - - - -
b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00
convert args to SubDecl format
- - - - -
cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00
convert instances to SubDecl
- - - - -
34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00
removing old table cruft from Layout.hs
- - - - -
d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00
methods and associated types in new layout scheme
- - - - -
65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00
clean up synopsis lists
- - - - -
e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00
clean up of anchors
- - - - -
1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00
added two new themes and rough css switcher
- - - - -
7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00
fixed package catpion, added style menu
- - - - -
0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00
new output for mini_ pages
- - - - -
64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00
reformat index-frames
- - - - -
3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00
convert index to new markup
- - - - -
b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00
convert index.html to new markup, adjust module markup
- - - - -
8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00
classing styling of ancillary pages
- - - - -
2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00
clean up Layout.hs: no more vanillaTable
- - - - -
87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00
clean up Util.hs
- - - - -
d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00
qualify import of XHtml as XHtml
- - - - -
7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00
factored out head element generation
- - - - -
9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00
refactored out main page body generation
- - - - -
8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00
moved footer into only place that used it
- - - - -
efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00
styling auxillary pages for tibbe and snappy themes
- - - - -
81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00
fixed alphabet on index page, and styling of it and packages in module lists
- - - - -
20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00
cleaned up div functions in Layout.hs
- - - - -
60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00
added content div to main pages
- - - - -
ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00
add .doc class to documentation blocks
- - - - -
f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00
refactoring of anchor ID and fragment handling
- - - - -
a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00
remove an explicit bold tag - replace with .def class
- - - - -
d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00
rename Haddock.Backends.Xhtml.Util to Utils
- - - - -
5a58c0da by David Waern at 2010-07-21T13:30:54+00:00
Remove trailing whitespace in Haddock.Backends.Xhtml
- - - - -
0652aa17 by David Waern at 2010-07-21T13:33:21+00:00
Align a few comments
- - - - -
785776c3 by David Waern at 2010-07-21T13:39:04+00:00
Remove trailing whitespace in H.B.X.Decl
- - - - -
71a30710 by David Waern at 2010-07-21T13:44:27+00:00
Remove more trailing whitespace
- - - - -
38750394 by David Waern at 2010-07-21T13:50:43+00:00
Style police
- - - - -
3023d940 by David Waern at 2010-07-21T14:01:22+00:00
Style police in H.B.X.Decl
- - - - -
df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00
Style police in H.B.X.DocMarkup
- - - - -
6020e321 by David Waern at 2010-07-21T14:17:32+00:00
More style police
- - - - -
86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00
Style police in H.B.Xhtml
- - - - -
aea27d03 by David Waern at 2010-07-21T14:42:03+00:00
Fix warnings in LaTeX backend
- - - - -
2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00
Style police in LaTeX backend (mainly more newlines)
- - - - -
e517162d by David Waern at 2010-07-21T15:05:47+00:00
Doc sections in Main
- - - - -
b971aa0c by David Waern at 2010-07-21T15:06:17+00:00
Trailing whitespace in Documentation.Haddock
- - - - -
f11628fb by David Waern at 2010-07-21T15:07:06+00:00
Trailing whitespace in Haddock.Convert
- - - - -
cbaf284c by David Waern at 2010-07-21T15:08:11+00:00
Style police in Haddock.GhcUtils
- - - - -
71feb77b by David Waern at 2010-07-21T15:09:06+00:00
Style police in Haddock.InterfaceFile
- - - - -
0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00
Whitespace police
- - - - -
6168376c by David Waern at 2010-07-21T15:16:35+00:00
Style police in Haddock.Utils
- - - - -
9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00
Add -fwarn-tabs
- - - - -
a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00
move CSS Theme functions into Themes.hs
- - - - -
b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00
add Thomas Schilling's theme
- - - - -
e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00
correct icon used with Snappy theme
- - - - -
ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00
apply Tibbe's updates to his theme
- - - - -
7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00
space between "Style" and the downward triangle
- - - - -
7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00
merge with David's source cleanups
- - - - -
ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00
Fix a bug where we allowed --hoogle, --latex, etc without input files
- - - - -
e413ff7a by David Waern at 2010-07-22T17:21:58+00:00
Improve function name
- - - - -
a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00
fix warnings
- - - - -
31f73d2a by David Waern at 2010-07-22T19:29:41+00:00
Solve conflicts
- - - - -
d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00
fix warning
- - - - -
412b6469 by David Waern at 2010-07-22T19:31:28+00:00
Solve conflict
- - - - -
35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00
Follow mkPState argument order change
- - - - -
b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00
common up code for instance rendering
- - - - -
d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00
fix warnings
- - - - -
a6d88695 by David Waern at 2010-07-24T15:33:33+00:00
Fix build with ghc < 6.13
- - - - -
94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00
Remove conflict left-over
- - - - -
313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00
reorganization of nhaddock.css with tibbe
- - - - -
9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00
further cleanup of nhaddock.css, float TOC, support aux. pages
- - - - -
6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00
remove old HTML backend
- - - - -
b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00
remove --html-help support - it was old, out-of-date, and mostly missing
- - - - -
d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00
tweaks to nhaddock.css
- - - - -
f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00
command like processing for theme selection
  The bulk of the change is threadnig the selected theme set through functions
  in Xhtml.hs so that the selected themes can be used when generating the page
  output. There isn't much going on in most of these changes, just passing it
  along. The real work is all done in Themes.hs.

- - - - -
8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00
drop --themes support, add named theme support
  decided that --themes was silly - no one would do that, just use
    multiple --theme arguments
  made --theme a synonym for --css and -c
  made those arguments, if no file is found, look up the argument as the
    name of a built in theme

  all of this let's haddock be invoked with "--theme=classic" for example.

- - - - -
20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00
rename --default-themes to --built-in-themes
- - - - -
0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00
tweaks to theme for info table, headings, and tables
- - - - -
cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00
tweaks for dl layout, though still not used
- - - - -
463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00
tweak look of mini pages, keywords, and preblocks
- - - - -
5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00
slide out Synopsis drawer
- - - - -
9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00
extend package header and footer to edges of page
- - - - -
a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00
fields are def lists, tweak css for style menu, mini pages, arguments
- - - - -
ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00
excisting last vestiges of the --xhtml flag
- - - - -
71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00
change how collapsing sections are done
  make whole .caption be the target
  improve javascript for class toggling
  have plus/minus images come from .css, not img tags

- - - - -
c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00
reorganize files in the html lib data dir
- - - - -
93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00
cleaned up Themes.hs
- - - - -
ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00
make module list use new collapsers
- - - - -
1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00
remove Tibbe theme
- - - - -
8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00
move themes into html dir with .theme and .std-theme extensions
- - - - -
a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00
give a class to empty dd elements so they can be hidden
- - - - -
a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00
remove custom version of copyFile in Xhtml.hs
- - - - -
b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00
apply margin changes to pre and headings as per group decision, and small cleanups
- - - - -
e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00
make info block and package bar links be floatable by placing them first in the dom tree
- - - - -
c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00
styling source links on declarations
- - - - -
88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00
styling tweaks
	don't generate an empty li for absent style menu in links area
	update css for Classic and Snappy to handle:
		dl lists
		links in package header and in declarations
		floating of links and info block in package and module headers

- - - - -
8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00
Fix build in GHC tree
- - - - -
ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00
Adapt paths to data files in cabal file
- - - - -
9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00
Add missing dependency to cabal file
- - - - -
01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00
improved synopsis drawer: on click, not hover
- - - - -
7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00
put the synopsis back in the other themes
- - - - -
7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00
close arrows on expanded synopsis drawer
- - - - -
ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00
width and font changes
	removed the max width restrictions on the page as a whole and the synopsis
	made the main font size smaller (nominally 14pt) and then tweaked most
	font sizes (relative) to be more consistent

- - - - -
5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00
implemented YUI's CSS font approach
- - - - -
2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00
adjusted margin to 2em, 1 wasn't enough
- - - - -
58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00
removed underlining on hover for named anchors
	headings in interface lost thier a element, no need, just put id on heading
	css for a elements now only applies to those with href attribute

- - - - -
7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00
more space between elements
- - - - -
5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00
adjusted font sizes of auxilary pages per new scheme
- - - - -
487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00
add Frames button and clean up frames.html
- - - - -
c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00
move frames button to js 
- - - - -
b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00
build style menu in javascript
	moved to javascript, so as to not polute the content with the style menu
	removed menu building code in Themes.hs
	removed onclick in Utils.hs
changed text of button in header from "Source code" to "Source"
	more consistent with links in rest of page

- - - - -
43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00
font size and margin tweaks
- - - - -
c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00
clean up collapser logics
	javascript code for collapasble sections cleaned up
	rewrote class utilities in javascript to be more robust
	refactored utilities for generating collapsable sections
made toc be same color as synopsis
module list has needed clear attribute in CSS

- - - - -
5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00
don't collapse entries in module list when clicking on links
- - - - -
8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00
add missing data file to .cabal
- - - - -
414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00
remove synopsis when in frames
- - - - -
ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00
layout tweeks - mini page font size, toc color, etc.
- - - - -
63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00
margin fiddling
- - - - -
c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00
better synopsis handling logic - no flashing
- - - - -
f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00
fix small layout issues
	mini frames should have same size top heading
	give info block dts some padding so they don't collide in some browsers

- - - - -
0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00
made style changing and cookies storage robust
- - - - -
1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00
Make synopsis frame behave properly in Firefox.

In Firefox, pressing the back button first reverted the synopsis
frame, and only clicking the back button a second time would update
the main frame.

- - - - -
dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00
remove Snappy theme
- - - - -
2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00
fix occasional v.scroll bars on pre blocks (I think)
- - - - -
459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00
Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API
- - - - -
b1b68675 by David Waern at 2010-08-26T20:31:58+00:00
Follow recent API additions with some refactorings

Simon Hegel's patch prompted me to do some refactorings in Main,
Haddock.Documentation and Haddock.Interface. 

- - - - -
264d4d67 by David Waern at 2010-08-26T21:40:59+00:00
Get rid of GhcModule and related cruft

We can get everything we need directly from TypecheckedModule.

- - - - -
0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00
fixed CSS for ordered lists and def lists in doc blocks
- - - - -
2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00
support both kinds of enumerated lists in doc markup
	The documentation for Haddock says enumerated lists can use either of
		(1) first item
		2. second item
	The second form wasn't actually supported


- - - - -
5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00
fix broken header link margins
- - - - -
614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00
fix table of contents CSS
- - - - -
03f329a2 by David Waern at 2010-08-28T16:36:09+00:00
Update tests following switch to the Xhtml backend
- - - - -
ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00
fix def lists
- - - - -
18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00
push footer to bottom of window
- - - - -
b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00
Whitespace police
- - - - -
2d217977 by David Waern at 2010-08-29T12:44:45+00:00
Remove Snappy data files
- - - - -
01e27d5f by David Waern at 2010-08-29T13:03:28+00:00
Add source entity path to --read-interface

You can now use this flag like this:

  --read-interface=<html path>,<source entity path>,<.haddock file> 

By "source entity path" I mean the same thing that is specified with the
--source-entity flag. The purpose of this is to be able to specify the source
entity path per package, to allow source links to work in the presence of
cross-package documentation.

When given two arguments or less the --read-interface flag behaves as before.

- - - - -
20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00
Naming wibbles
- - - - -
ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00
make portability block be a table - solves layout issues
- - - - -
97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00
update golden test for Test due to portability box change
- - - - -
d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00
move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs
- - - - -
acf52501 by David Waern at 2010-08-29T17:32:36+00:00
Allow building with ghc < 6.16
- - - - -
1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00
Flatten the dynflags before parsing
- - - - -
b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00
Follow flattenLanguageFlags -> flattenExtensionFlags rename
- - - - -
7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00
Use flattenExtensionFlags with ghc >= 6.13 only
- - - - -
13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00
Make the main haddock script versioned, and make plain "haddock" a symlink
- - - - -
495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00
Fix installation in the GHC build system
Data-files are now in subdirectories, so we need to handle that

- - - - -
88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00
GHC build system: Add all the data files to BINDIST_EXTRAS
- - - - -
65837172 by David Waern at 2010-08-29T20:12:34+00:00
Update Test
- - - - -
094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00
Revert update to Test
- - - - -
a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00
Bump version number
- - - - -
1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00
Update ANNOUNCE
- - - - -
ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00
Update CHANGES
- - - - -
394cc854 by David Waern at 2010-08-31T22:33:23+00:00
Update interface file versioning to work with ghc 6.14/15
- - - - -
7d03b79b by David Waern at 2010-08-31T22:36:00+00:00
Update test output following version change
- - - - -
a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00
sort options in doc to match --help output
	removed --html-help option, as it is no longer supported

- - - - -
06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00
update options documentation
	rewrote doc for --html
	added doc for --theme and --built-in-themes
	added --use-contents and --gen-contents

- - - - -
57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00
slight wording change about Frames mode
- - - - -
fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00
Update doc configure script to find docbook stylesheets on arch linux
- - - - -
addff770 by David Waern at 2010-09-01T11:02:29+00:00
Wibble
- - - - -
8399006d by David Waern at 2010-09-01T11:19:21+00:00
Replace ghci> with >>> in example syntax
- - - - -
35074cf8 by David Waern at 2010-09-01T19:03:27+00:00
Improve docs for --no-tmp-comp-dir
- - - - -
0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00
Add a list of contributors to the user guide

Break out everyone thanked in the `Acknowledgements` chapter into a
separate contributor list and add everyone from `darcs show authors`.
We consider everyone who is thanked to be a contributor as a conservative
estimation :-)

I have added some more contributors that I know about, who were not in the
darcs history, but others may be missing. So please add anyone that you think 
is missing from the list.

- - - - -
42ccf099 by David Waern at 2010-09-02T11:29:22+00:00
Update copyright years in license
- - - - -
0d560479 by David Waern at 2010-09-02T11:38:52+00:00
Update release instructions
- - - - -
72ab7796 by David Waern at 2010-09-02T19:27:08+00:00
Add a note to ANNOUNCE
- - - - -
bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00
H.Utils needs FFI on Win+MinGW 
- - - - -
048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00
make TOC group header identifiers validate
- - - - -
8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00
add hints for cleaner darcs show authors output
- - - - -
9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00
print haddock coverage info on stdout when generating docs
A module's haddockable items are its exports and the module itself.
The output is lightly formatted so you can align the :'s and sort
for readability.

- - - - -
6da72171 by David Waern at 2010-10-03T21:31:24+00:00
Style wibble
- - - - -
2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00
adding the option to fully qualify identifiers
- - - - -
833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00
adding support for local and relative name qualification
- - - - -
df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00
corrected qualification help message
- - - - -
449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00
Solve conflicts
- - - - -
3469bda5 by David Waern at 2010-10-16T18:42:40+00:00
Use "qual" as an abbreviation for qualification instead of "quali" for consistency
- - - - -
97c2d728 by David Waern at 2010-10-16T18:47:07+00:00
Style police
- - - - -
ce14fbea by David Waern at 2010-10-16T21:15:25+00:00
Style police
- - - - -
fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00
Add a pointer to the style guide
- - - - -
8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00
Change to index pages: include an 'All' option even when subdividing A-Z.
- - - - -
755b131c by David Waern at 2010-11-14T19:39:36+00:00
Bump version
- - - - -
d0345a04 by David Waern at 2010-11-14T19:41:59+00:00
TAG 2.8.1
- - - - -
f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00
Adapt to minor changes in internal GHC functions
- - - - -
1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00
Remove duplicate Outputable instance for Data.Map.Map
- - - - -
87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00
Bump GHC dep upper bound
- - - - -
af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00
Fix up __GLASGOW_HASKELL__ tests
- - - - -
ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00
Don't build haddock is HADDOCK_DOCS is NO
- - - - -
63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00
Fixes for when HADDOCK_DOCS=NO
- - - - -
e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00
Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353
- - - - -
66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00
Tidy up haddock symlink installation
In particular, it now doesn't get created if we aren't installing
haddock.

- - - - -
549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00
Follow extension-flattening change in GHC
- - - - -
d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00
Bump version to 2.8.2
- - - - -
6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00
Solve conflict
- - - - -
055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00
Bump GHC dep
- - - - -
c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00
follow changes in the GHC API
- - - - -
45907129 by David Waern at 2010-11-07T14:00:58+00:00
Update the HCAR entry
- - - - -
61940b95 by David Waern at 2010-11-07T14:07:34+00:00
Make the HCAR entry smaller
- - - - -
aa590b7d by David Waern at 2010-11-14T21:30:59+00:00
Update HCAR entry with November 2010 version
- - - - -
587f9847 by David Waern at 2010-11-14T23:48:17+00:00
Require ghc >= 7.0
- - - - -
ff5c647c by David Waern at 2010-11-14T23:49:09+00:00
TAG 2.8.2
- - - - -
937fcb4f by David Waern at 2010-11-14T23:49:45+00:00
Solve conflict
- - - - -
8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00
Remove code for ghc < 7
- - - - -
3d47b70a by David Waern at 2010-11-15T21:11:06+00:00
Fix bad merge
- - - - -
7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00
Remove more ghc < 7 code
- - - - -
9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00
Match all AsyncExceptions in exception handler
- - - - -
42849c70 by David Waern at 2010-11-15T21:35:31+00:00
Just say "internal error" instead of "internal Haddock or GHC error"
- - - - -
c88c809b by David Waern at 2010-11-15T21:44:19+00:00
Remove docNameOcc under the motto "don't name compositions"
- - - - -
b798fc7c by David Waern at 2010-11-15T23:27:13+00:00
Wibble
- - - - -
2228197e by David Waern at 2010-11-15T23:28:24+00:00
Rename the HCAR entry file
- - - - -
8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00
Remove Haskell 2010 extensions from .cabal file
- - - - -
c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00
Style wibbles
- - - - -
cde707a5 by David Waern at 2010-11-16T00:12:00+00:00
Remove LANGUAGE ForeignFunctionInterface pragmas
- - - - -
1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00
Make a little more use of DoAndIfThenElse
- - - - -
4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00
hlint police
- - - - -
d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00
hlint police
- - - - -
99876e97 by David Waern at 2010-11-20T19:06:00+00:00
Haddock documentation updates
- - - - -
65ce6987 by David Waern at 2010-11-20T19:42:51+00:00
Follow the style guide closer in Haddock.Types and improve docs
- - - - -
28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00
add full qualification for undocumented names
- - - - -
d61341e3 by David Waern at 2010-11-20T20:04:15+00:00
Re-structure qualification code a little
- - - - -
0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00
Re-order functions
- - - - -
d7279afd by David Waern at 2010-11-21T03:39:54+00:00
Add BangPatterns to alex and happy source files
- - - - -
629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00
documentation for qualification
- - - - -
37031cee by David Waern at 2010-11-23T21:06:44+00:00
Update CHANGES - don't mention 2.8.2, we won't release it
- - - - -
f2489e19 by David Waern at 2010-12-01T21:57:11+00:00
Update deps of runtests.hs to work with ghc 7.0.1
- - - - -
d3657e9a by David Waern at 2010-12-01T22:04:57+00:00
Make tests compile with ghc 7.0.1
- - - - -
a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00
Update tests following version bump
- - - - -
50883ebb by David Waern at 2010-12-06T14:09:18+00:00
Update tests following recent changes
- - - - -
fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00
Add a flag --pretty-html for rendering indented html with newlines
- - - - -
30832ef2 by David Waern at 2010-12-06T14:17:35+00:00
Use --pretty-html when running the test suite. Makes it easier to compare output
- - - - -
a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00
Wibble
- - - - -
3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00
Haddockify ppHtml comments
- - - - -
24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00
Remove --debug. It was't used, and --verbosity should take its place
- - - - -
6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00
Rename golden-tests into html-tests. "golden tests" sounds strange
- - - - -
53301e55 by David Waern at 2010-12-06T14:26:26+00:00
QUALI -> QUAL in the description --qual for consistency
- - - - -
98b6affb by David Waern at 2010-12-06T21:54:02+00:00
Bump version
- - - - -
371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00
Update tests following version bump
- - - - -
25be762d by David Waern at 2010-12-06T22:21:03+00:00
Update CHANGES
- - - - -
7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00
Update ANNOUNCE
- - - - -
30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00
Alex generates BangPatterns, so make Lex.x accept them

(It'd be better for Alex to generate this pragma.)

- - - - -
605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00
Add {-# LANGUAGE BangPatterns #-} to mollify GHC
- - - - -
a46607ba by David Waern at 2010-12-07T14:08:10+00:00
Solve conflicts
- - - - -
b28cda66 by David Waern at 2010-12-09T20:41:35+00:00
Docs: Mention that \ is a special character in markup
- - - - -
a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00
TAG GHC 7.0.1 release
- - - - -
5a15a05a by David Waern at 2010-12-11T17:51:19+00:00
Fix indentation problem
- - - - -
4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00
Revise haddock.cabal given that we now require ghc-7
default-language should be Haskell2010, slight new semantics for extensions.
Rewrite into clearer dependencies of base and Cabal.

- - - - -
a36302dc by David Waern at 2010-12-19T17:12:37+00:00
Update CHANGES
- - - - -
7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00
Bump version
- - - - -
cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00
Write hoogle output in utf8; fixes GHC build on Windows
- - - - -
c7e762ea by David Waern at 2011-01-22T00:00:35+00:00
Put title outside doc div when HTML:fying title+prologue

Avoids indenting the title, and makes more sense since the title
is not a doc string anyway.

- - - - -
5f639054 by David Waern at 2011-01-22T16:09:44+00:00
Fix spelling error - contributed by Marco Silva
- - - - -
c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00
Follow GHC build system changes
- - - - -
101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00
Bump version
- - - - -
af62348b by David Waern at 2011-01-08T14:07:07+00:00
TAG 2.9.2
- - - - -
4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00
Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882
"7.0.2" looked like a haddock version number before

- - - - -
8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00
Update Haddock to reflect change in hs_tyclds field of HsGroup
- - - - -
06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00
TAG GHC 7.0.2 release
- - - - -
7de0667d by David Waern at 2011-03-10T22:47:13+00:00
Update CHANGES
- - - - -
33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00
Fix build with ghc 7.0.1
- - - - -
4616f861 by David Waern at 2011-03-10T22:47:50+00:00
TAG 2.9.2-actual
- - - - -
0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00
Set shell script for unit tests back to work
- - - - -
85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00
Set unit tests back to work

Here "ghci>" was still used instead of ">>>".

- - - - -
1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00
Update runtests.hs for GHC 7.0.2
- - - - -
8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00
Update Haddock version in *.html.ref
- - - - -
2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00
Add support for blank lines in the result of examples

Result lines that only contain the string "<BLANKLINE>" are treated as a blank
line.

- - - - -
adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00
Add documentation for "support for blank lines in the result of examples"
- - - - -
c51352ca by David Waern at 2011-05-21T23:57:56+00:00
Improve a haddock comment
- - - - -
7419cf2c by David Waern at 2011-05-22T15:41:52+00:00
Use cabal's test suite support to run the test suite

This gives up proper dependency tracking of the test script.

- - - - -
7770070c by David Waern at 2011-05-22T01:45:44+00:00
We don't need to send DocOptions nor a flag to mkExportItems
- - - - -
9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00
Fix a bug
- - - - -
1f93699b by David Waern at 2011-05-22T21:40:21+00:00
Break out fullContentsOf, give it a better name and some documentation

The documentation describes how we want this function to eventually behave,
once we have fixed a few problems with the current implementation.

- - - - -
9a86432f by David Waern at 2011-05-22T21:53:52+00:00
Fix some stylistic issues in mkExportItems
- - - - -
c271ff0c by David Waern at 2011-05-22T22:09:11+00:00
Indentation
- - - - -
93e602b1 by David Waern at 2011-06-10T01:35:31+00:00
Add git commits since switchover:

  darcs format (followed by a conflict resolution):

  commit 6f92cdd12d1354dfbd80f8323ca333bea700896a
  Merge: f420cc4 28df3a1
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Thu May 19 17:54:34 2011 +0100

      Merge remote branch 'origin/master' into ghc-generics

  commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0
  Author: Max Bolingbroke <batterseapower at hotmail.com>
  Date:   Sat May 14 22:37:02 2011 +0100

      Unicode fix for getExecDir on Windows

  commit 89813e729be8bce26765b95419a171a7826f6d70
  Merge: 6df3a04 797ab27
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 9 11:55:17 2011 +0100

      Merge branch 'ghc-new-co'

  commit 6df3a040da3dbddee67c6e30a892f87e6b164383
  Author: Ian Lynagh <igloo at earth.li>
  Date:   Sun May 8 17:05:50 2011 +0100

      Follow changes in SDoc

  commit f420cc48b9259f0b1afd2438b12f9a2bde57053d
  Author: Jose Pedro Magalhaes <jpm at cs.uu.nl>
  Date:   Wed May 4 17:31:52 2011 +0200

      Adapt haddock to the removal of HsNumTy and TypePat.

  commit 797ab27bdccf39c73ccad374fea265f124cb52ea
  Merge: 1d81436 5a91450
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 2 12:05:03 2011 +0100

      Merge remote branch 'origin/master' into ghc-new-co

  commit 1d8143659a81cf9611668348e33fd0775c7ab1d2
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 2 12:03:46 2011 +0100

      Wibbles for ghc-new-co branch

  commit 5a91450e2ea5a93c70bd3904b022445c9cc82488
  Author: Ian Lynagh <igloo at earth.li>
  Date:   Fri Apr 22 00:51:56 2011 +0100

      Follow defaultDynFlags change in GHC

- - - - -
498da5ae by David Waern at 2011-06-11T00:33:33+00:00
* Merge in git patch from Michal Terepeta

>From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001
From: Michal Terepeta <michal.terepeta at gmail.com>
Date: Sat, 14 May 2011 19:18:22 +0200
Subject: [PATCH] Follow the change of TypeSig in GHC.

This follows the change in GHC to make TypeSig take a list
of names (instead of just one); GHC ticket haskell/haddock#1595. This
should also improve the Haddock output in case the user
writes a type signature that refers to many names:
  -- | Some comment..
  foo, bar :: ...
will now generate the expected output with one signature for
both names.

- - - - -
094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00
Fix build

- - - - -
8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00
Bump GHC dep to allow 7.2

- - - - -
e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00
Relax base dep

- - - - -
b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00
GHC build system: Don't install the datafiles twice

- - - - -
f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00
Hack this to make it work with both Alex 2.x and Alex 3.x.  Unicode in
documentation strings is (still) mangled.  I don't think it's possible
to make it so that we get the current behaviour with Alex 2.x but
magic Unicode support if you use Alex 3.x.  At some point we have to
decide that Alex 3.x is a requirement, then we can do Unicode.

- - - - -
b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00
Fix compilation with no-pred-ty GHC

- - - - -
30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00
Remaining fixes for PredTy removal

- - - - -
0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00
Rename factKind to constraintKind

- - - - -
a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00
Deal with change to IParam handling in GHC

- - - - -
f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00
Adapt Haddock for the ConstraintKind extension changes

- - - - -
8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00
Ignore associated type defaults (just as we ignore default methods)

- - - - -
31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00
Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty

- - - - -
dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00
Merge branch 'no-pred-ty'

Conflicts:
	src/Haddock/Convert.hs

- - - - -
5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00
Replace FactTuple with ConstraintTuple

- - - - -
cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00
Bump to version 2.9.3

- - - - -
4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00
Follow changes to BinIface Name serialization

- - - - -
92257d90 by David Waern at 2011-09-30T23:45:07+02:00
Fix problem with test files not added to distribution tarball

- - - - -
00255bda by David Waern at 2011-09-30T23:48:24+02:00
Merge branch 'development'

- - - - -
5421264f by David Waern at 2011-10-01T01:25:39+02:00
Merge in darcs patch from Simon Meier:

  Wed Jun  1 19:41:16 CEST 2011  iridcode at gmail.com
    * prettier haddock coverage info
    The new coverage info rendering uses less horizontal space. This reduces the
    number of unnecessary line-wrappings. Moreover, the most important information,
    how much has been documented already, is now put up front. Hopefully, this
    makes it more likely that a library author is bothered by the low coverage of
    his modules and fixes that issue ;-)

- - - - -
07d318ef by David Waern at 2011-10-01T01:34:10+02:00
Use printException instead of deprecated printExceptionAndWarnings

- - - - -
40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00
Merge in darcs pach:

  Mon Apr 11 18:09:54 JST 2011  Liyang HU <haddock at liyang.hu>
    * Remember collapsed sections in index.html / haddock-util.js

- - - - -
279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00
Merge in darcs patch:

  Joachim Breitner <mail at joachim-breitner.de>**20110619201645
  Ignore-this: f6c51228205b0902ad5bfad5040b989a

  As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301,
  generating the global index takes much too long if type-level (with lots of
  auto-generated types) is installed. The patch avoids a quadratic runtime in the
  subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s.

- - - - -
d1612383 by David Waern at 2011-10-01T01:56:48+02:00
Merge branch 'development'

- - - - -
347520c1 by David Waern at 2011-10-01T01:56:54+02:00
Merge branch 'master' of http://darcs.haskell.org/haddock

- - - - -
9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00
Improve .cabal file

- - - - -
6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00
Follow changes to ForeignImport/ForeignExport in GHC

- - - - -
565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00
Hack this to make it work with both Alex 2.x and Alex 3.x.  Unicode in
documentation strings is (still) mangled.  I don't think it's possible
to make it so that we get the current behaviour with Alex 2.x but
magic Unicode support if you use Alex 3.x.  At some point we have to
decide that Alex 3.x is a requirement, then we can do Unicode.

- - - - -
8b74f512 by David Waern at 2011-10-04T00:18:17+02:00
Requre ghc >= 7.2

- - - - -
271d360c by David Waern at 2011-10-04T00:22:50+02:00
Bump version to 2.9.4

- - - - -
37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00
Add alex and happy to build-tools.

- - - - -
7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00
Add safe haskell indication to haddock output

- - - - -
42c91a47 by David Terei at 2011-10-12T14:06:03-07:00
Fix CSS issue with info table not being contained in module header

- - - - -
0eddab6c by David Terei at 2011-10-12T14:06:58-07:00
Add safe haskell indication to haddock output

- - - - -
3df058eb by David Terei at 2011-10-12T14:07:07-07:00
Fix CSS issue with info table not being contained in module header

- - - - -
a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00
Bump .haddock file version since the format has changed recently

- - - - -
8a6254be by David Waern at 2011-10-22T11:30:42+02:00
Merge branch 'development'

- - - - -
642e3e02 by David Waern at 2011-10-23T21:23:39+02:00
Sort import list

- - - - -
36371cf8 by David Waern at 2011-10-23T22:48:18+02:00
Remove NEW_GHC_LAYOUT conditional.

- - - - -
5604b499 by David Waern at 2011-10-27T00:15:03+02:00
Add --print-ghc-path.

- - - - -
463499fa by David Waern at 2011-10-27T00:16:22+02:00
Make testsuite able to find its dependencies automatically.

- - - - -
a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00
Improved declNames internal error.  Added a case to handle DocD.

- - - - -
001b8baf by David Waern at 2011-11-05T20:37:29+01:00
Rename copy.hs -> accept.hs.

- - - - -
55d808d3 by David Waern at 2011-11-05T23:30:02+01:00
Fix build.

- - - - -
deb5c3be by David Waern at 2011-11-06T00:01:47+01:00
Merge branch 'master' of http://darcs.haskell.org/haddock

- - - - -
9b663554 by David Waern at 2011-11-06T00:03:45+01:00
Merge https://github.com/rrnewton/haddock

- - - - -
1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00
Use getDeclMainBinder instead of declNames.

- - - - -
4b005c01 by David Waern at 2011-11-06T19:09:53+01:00
Fix build.

- - - - -
c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00
Remove -DNEW_GHC_LAYOUT in ghc.mk

- - - - -
f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00
New kind-polymorphic core

This big patch implements a kind-polymorphic core for GHC. The current
implementation focuses on making sure that all kind-monomorphic programs still
work in the new core; it is not yet guaranteed that kind-polymorphic programs
(using the new -XPolyKinds flag) will work.

For more information, see http://haskell.org/haskellwiki/GHC/Kinds

- - - - -
7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00
Follow changes to tuple sorts in master

- - - - -
8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00
Remove redundant imports

- - - - -
d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00
Follow GHC build system change to the way we call rm

- - - - -
9e2230ed by David Waern at 2011-11-24T15:00:24+01:00
Fix a bug in test runner and get rid of regex-compat dependency.

- - - - -
52039b21 by David Waern at 2011-11-24T23:55:36+01:00
Avoid haskell98 dependency in test

- - - - -
92e1220d by David Waern at 2011-11-25T00:03:33+01:00
Avoid depency on regex-compat also in accept.hs.

- - - - -
ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00
Accept test output.

- - - - -
5a720455 by David Waern at 2011-11-25T02:16:20+01:00
Some more changes to test scripts.

- - - - -
170a9004 by David Waern at 2011-11-25T02:30:41+01:00
Add flag --interface-version.

- - - - -
d225576c by David Waern at 2011-11-25T02:39:26+01:00
Remove #ifs for older compiler versions.

- - - - -
f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00
Give preference to type over data constructors for doc comment links at renaming time.

Previously this was done in the backends.

Also, warn when a doc comment refers to something that is in scope but which we
don't have the .haddock file for.

These changes mean we can make DocIdentifier [a] into DocIdentifier a.

- - - - -
eef0e776 by David Waern at 2011-11-26T17:01:06+01:00
Allow doc comments to link to out-of-scope things (#78).

(A bug that should have been fixed long ago.)

- - - - -
565ad529 by David Waern at 2011-11-26T19:56:21+01:00
Update tests.

- - - - -
fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00
Cleanup.

- - - - -
d0328126 by David Waern at 2011-11-26T22:10:28+01:00
Fix module reference bug.

- - - - -
c03765f8 by David Waern at 2011-12-03T05:20:20+01:00
Slightly better behaviour on top-levels without type signatures.

- Docs don't get attached to the next top-level with signature by
mistake.

- If there's an export list and the top-level is part of it,
its doc comment shows up in the documentation.

- - - - -
48461d31 by David Waern at 2011-12-03T05:38:10+01:00
Add a test for Unicode doc comments.

- - - - -
549c4b4e by David Waern at 2011-12-03T19:07:55+01:00
Cleanup.

- - - - -
7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00
More cleanup.

- - - - -
14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00
Update dependencies and binaryInterfaceVersion

- - - - -
469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00
Fix (untested) building from source tarball without alex/happy

haddock's .cabal file was declaring that it needed alex and happy to
build, but in the GHC source tarballs it doesn't.

- - - - -
895c9a8c by David Waern at 2011-12-27T12:57:43+01:00
Go back to having a doc, sub and decl map instead of one big decl map.

This setup makes more sense since when we add value bindings to the
processed declarations (for type inference), we will have multiple
declarations which should share documentation. Also, we already have
a separate doc map for instances which we can now merge into the
main doc map. Another benefit is that we don't need the DeclInfo
type any longer.

- - - - -
736767d9 by David Waern at 2011-12-27T13:33:41+01:00
Merge ../../../haddock

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
20016f79 by David Waern at 2011-12-27T13:57:23+01:00
Bump version.

- - - - -
31f276fb by David Waern at 2011-12-27T13:57:32+01:00
Merge ../ghc/utils/haddock

- - - - -
95b367cd by David Waern at 2011-12-27T14:57:29+01:00
Update tests following version bump.

- - - - -
fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00
Get rid of quite unnecessary use of different lists.

- - - - -
9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00
Cleanup.

- - - - -
2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00
Wibbles.

- - - - -
3757d09b by David Waern at 2011-12-27T20:50:26+01:00
Complete support for inferring types for top-level bindings.

- - - - -
53418734 by David Waern at 2011-12-28T15:02:13+01:00
Minor fixes and cleanup.

- - - - -
0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00
Follow rename of Instance to ClsInst in GHC

- - - - -
c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00
Make sure that generated xhtml is valid (close haskell/haddock#186)

Thanks to Phyx.

- - - - -
836a0b9a by David Waern at 2012-02-01T02:30:05+01:00
Fix bug introduced in my recent refactoring.

- - - - -
c7d733eb by David Waern at 2012-02-01T02:30:26+01:00
Cleanup mkMaps and avoid quadratic behaviour.

- - - - -
da3cda8f by David Waern at 2012-02-01T02:56:56+01:00
Require ghc >= 7.4.

- - - - -
83a3287e by David Waern at 2012-02-01T02:57:36+01:00
Update CHANGES.

- - - - -
93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00
Add reference renderings

- - - - -
49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00
Set unit tests for parser back to work

- - - - -
eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00
Add .gitignore

- - - - -
a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00
Add .ghci file

- - - - -
8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00
tests/html-tests/copy.hs: Use mapM_ instead of mapM

So we do net get a list of () on stdout when running with runhaskell.

- - - - -
b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00
Remove index files from golden tests

- - - - -
9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00
Add /tests/html-tests/tests/*index*.ref to .gitignore

- - - - -
a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00
Add DocWarning to Doc

The Xhtml backend has special markup for that, Hoogle and LaTeX reuse
what we have for DocEmphasis.

- - - - -
de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00
Add support for module warnings

- - - - -
0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00
Add tests for module warnings

- - - - -
30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00
Add support for warnings

- - - - -
bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00
Add tests for warnings

- - - - -
6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00
Expand type signatures in export list (fixes haskell/haddock#192)

- - - - -
a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00
Expand type signatures for modules without explicit export list

- - - - -
57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00
Remove obsolete TODO

- - - - -
270c3253 by David Waern at 2012-02-04T00:51:24+01:00
Fix issues in support for warnings.

* Match against local names only.
* Simplify (it's OK to map over the warnings).

- - - - -
683634bd by David Waern at 2012-02-04T00:55:11+01:00
Some cleanup and make sure we filter warnings through exports.

- - - - -
210cb4ca by David Waern at 2012-02-04T03:01:30+01:00
Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4

- - - - -
e8db9031 by David Waern at 2012-02-04T03:07:51+01:00
Style police.

- - - - -
261f9462 by David Waern at 2012-02-04T03:20:16+01:00
Update tests.

- - - - -
823cfc7c by David Waern at 2012-02-04T03:21:12+01:00
Use mapM_ in accept.hs as well.

- - - - -
873dd619 by David Waern at 2012-02-04T03:21:33+01:00
Remove copy.hs - use accept.hs instead.

- - - - -
0e31a14a by David Waern at 2012-02-04T03:47:33+01:00
Use <> instead of mappend.

- - - - -
2ff7544f by David Waern at 2012-02-04T03:48:55+01:00
Remove code for older ghc versions.

- - - - -
dacf2786 by David Waern at 2012-02-04T15:52:51+01:00
Clean up some code from last SoC project.

- - - - -
00cbb117 by David Waern at 2012-02-04T21:43:49+01:00
Mostly hlint-inspired cleanup.

- - - - -
7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00
Track changes in HsDecls

- - - - -
f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00
Follow changes in GHC caused by the CAPI CTYPE pragma

- - - - -
a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00
Follow changes in GHC

- - - - -
b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00
Follow changes in data representation from the big PolyKinds commit

- - - - -
43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00
Save/restore global state for static flags when running GHC actions

This is necessary if we want to run createInterfaces (from
Documentation.Haddock) multiple times in the same process.

- - - - -
9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00
Update .gitignore.

- - - - -
a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00
Follow changes to tcdKindSig (Trac haskell/haddock#5937)

- - - - -
fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00
Add support for type-level literals.

- - - - -
2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00
Follow changes to tcdKindSig (Trac haskell/haddock#5937)

- - - - -
93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00
Merge branch 'master' of http://darcs.haskell.org//haddock

Conflicts:
	src/Haddock/Convert.hs

- - - - -
d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00
Merge remote-tracking branch 'origin/master' into type-nats

- - - - -
fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00
Add a missing case for type literals.

- - - - -
fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00
Rename variable to avoid shadowing warning.

- - - - -
9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00
Follow refactoring of TyClDecl/HsTyDefn

- - - - -
38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00
Merge branch 'master' of http://darcs.haskell.org//haddock

- - - - -
4324ac0f by David Waern at 2012-04-01T01:51:19+02:00
Disable unicode test.

- - - - -
3165b750 by David Waern at 2012-04-01T01:51:34+02:00
Take reader environment directly from TypecheckedSource.

- - - - -
213b644c by David Waern at 2012-04-01T01:55:20+02:00
Cleanup.

- - - - -
3118b4ba by David Waern at 2012-04-01T02:16:15+02:00
Don't filter out unexported names from the four maps - fixes a regression.

- - - - -
d6524e17 by David Waern at 2012-04-01T02:40:34+02:00
Fix crash when using --qual. Naughty GHC API!

- - - - -
ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00
add QualOption type for distinction between qualification argument given by the user
and the actual qualification for a concrete module
- - - - -
5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00
emit an error message when the --qual option is used incorrectly
- - - - -
026e3404 by David Waern at 2012-04-01T18:10:30+02:00
Don't crash on unicode strings in doc comments.

- - - - -
ce006632 by David Waern at 2012-04-01T20:13:35+02:00
Add test for --ignore-all-exports flag/ignore-exports pragma.

- - - - -
6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00
Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4

- - - - -
734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00
'abbreviate' qualification style - basic support
Currently we ignore the package a module is imported from.
This means that a module import would shadow another one
with the same module name from a different package.
- - - - -
c85314ef by David Waern at 2012-04-01T22:05:12+02:00
Check qualification option before processing modules.

- - - - -
ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00
abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to
- - - - -
60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00
qualification style 'abbreviated' -> 'aliased'

- - - - -
f4192a64 by David Waern at 2012-04-02T01:05:47+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
7ba09067 by David Terei at 2012-04-04T15:08:21-07:00
Fix reporting of modules safe haskell mode (#5989)

- - - - -
d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00
Fix reporting of modules safe haskell mode (#5989)

- - - - -
6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00
Track changes in HsSyn

- - - - -
22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00
Follow changes to LHsTyVarBndrs

- - - - -
d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00
Update CHANGES.

- - - - -
8e181d29 by David Waern at 2012-05-16T02:27:56+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
e358210d by David Waern at 2012-05-16T02:35:33+02:00
Mention the new aliased --qual mode in CHANGES.

- - - - -
efd36a28 by David Waern at 2012-05-16T21:33:13+02:00
Bump version number.

- - - - -
d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00
Add test for deprecated record field

- - - - -
927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00
Use >>= instead of fmap and join

- - - - -
048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00
newtype-wrap Doc nodes for things that may have warnings attached

- - - - -
e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00
Attach warnings to `Documentation` type

- - - - -
5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00
Simplify lookupWarning

- - - - -
cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00
Add test for haskell/haddock#205

- - - - -
cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00
Follow changes in LHsTyVarBndrs

- - - - -
2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00
Add Applicative instance for (GenRnM a)

- - - - -
e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00
Use a map for warnings, as suggested by @waern

- - - - -
597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00
Add an optional label to URLs

- - - - -
ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00
Add support for hyperlink labels to parser

- - - - -
41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00
Add golden test for hyperlinks

- - - - -
83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00
Use LANGUAGE pragmas instead of default-extensions in cabal file

- - - - -
ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00
Fix typo in comment

- - - - -
110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00
Add a type signature for a where-binding

- - - - -
7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00
Follow changes in GHC

- - - - -
47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00
Follow changes in GHC

- - - - -
e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00
Follow changes for the implementation of implicit parameters

- - - - -
69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00
Follow changes in base

- - - - -
9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00
Use right docMap to get decl documentation.

- - - - -
e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00
Follow changes in GHC

- - - - -
ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00
Fix haddock following some GHC changes

Passing _|_ as the Settings for defaultDynFlags no longer works well
enough

- - - - -
9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00
Forward port changes from stable.

- - - - -
572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00
Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock

- - - - -
9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00
Update dependencies.

- - - - -
33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00
Build with GHC 7.7

- - - - -
925a2cea by David Waern at 2012-07-23T16:50:40+02:00
Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
d710ef97 by David Waern at 2012-07-23T16:52:07+02:00
Bump version number.

- - - - -
eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00
Update CHANGES.

- - - - -
b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00
Hide "internal" instances

This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37)

Precisely, we show an instance iff its class and all the types are exported by
non-hidden modules.

- - - - -
a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00
Tests for hiding instances (#37)

- - - - -
c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00
Add an other test for hiding instances (#37)

- - - - -
a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00
Follow changes in GHC

- - - - -
0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00
Improve haddock memory usage

- - - - -
0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00
Improve haddock memory usage

- - - - -
659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00
Remove some temporary pragmas I accidentally recorded

- - - - -
d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00
Add missing dependency to library

- - - - -
4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00
Move .ghci to project root

- - - - -
fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00
accept.hs: Ignore some files

- - - - -
1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00
Update reference renderings (bump version)

- - - - -
980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00
Update reference renderings (remove links for ())

- - - - -
33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00
Update documentation of `runInteractiveProcess` in reference rendering

- - - - -
7ab25078 by David Waern at 2012-09-07T10:38:50+02:00
Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6

- - - - -
c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00
Follow changes in GHC.

- - - - -
298c43ac by David Waern at 2012-09-07T14:59:24+02:00
Update CHANGES.

- - - - -
e797993a by David Waern at 2012-09-07T15:21:30+02:00
Update ANNOUNCE.

- - - - -
d0b44790 by David Waern at 2012-09-07T15:22:43+02:00
Merge branch 'hidden-instances' into ghc-7.6

- - - - -
41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00
Update doc/README

- - - - -
71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00
Add documentation for URL labels

- - - - -
9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00
Follow data type changes in the tc-untouchables branch

Relating entirely to SynTyConRhs

- - - - -
b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00
Disable Unicode test for now

- - - - -
a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00
Update TypeOperators test for GHC 7.6.1

Type operators can't be used as type variables anymore!

- - - - -
6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00
Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs

I do not really understand why the behavior changed, so I'll open a
ticket, so that we can further investigate.

- - - - -
b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00
Follow changes in GHC build system

- - - - -
b98eded0 by David Waern at 2012-09-27T15:37:02+02:00
Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6

- - - - -
76cc2051 by David Waern at 2012-09-27T15:48:19+02:00
Update hidden instances tests.

- - - - -
aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00
Make API buildable with GHC 7.6.

- - - - -
d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00
Merge remote-tracking branch 'origin/master' into tc-untouchables

- - - - -
a1922af8 by David Waern at 2012-09-28T19:50:20+02:00
Fix spurious superclass constraints bug.

- - - - -
bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00
Remove old examples

- - - - -
bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00
Adapt parsetests for GHC 7.6.1

- - - - -
dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00
Add test-suite section for parsetests to cabal file

+ get rid of HUnit dependency

- - - - -
1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00
Remove test flag from cabal file

This was not really used.

- - - - -
4beee98b by David Waern at 2012-09-28T23:42:28+02:00
Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6

- - - - -
11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00
Follow change in GHC build system

- - - - -
fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00
Remove redundant dependency from cabal file

- - - - -
09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00
Fix typo

- - - - -
93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00
Remove trailing whitespace from cabal file

- - - - -
c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00
Export Haddock's main entry point from library

- - - - -
b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00
Depend on library for executable

The main motivation for this is to increase build speed.  In GHC's
source tree the library is not build, but all modules are now required
for the executable, so that GHC's validate will now detect build
failures for the library.

- - - - -
f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00
Set executable flag for Setup.lhs

- - - - -
dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00
Extend rather than set environment when running HTML tests

On some platforms (e.g. ppc64) GHC requires gcc in the path.

- - - - -
7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00
cross-package test: re-export IsString instead of Monad

There is a monad instance for Q, which is not available on platforms
that do not have GHCi support.  This caused CrossPackageDocs to fail on
those platforms.  Re-exporting IsString should test the same thing, but
it works on all platforms.

- - - - -
0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Fix some warnings

- - - - -
f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Make -Wall proof

- - - - -
6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe

- - - - -
44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00
Follow changes in GHC

- - - - -
6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00
Update .ghci

- - - - -
9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00
Add markup support for properties

- - - - -
1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00
Simplify lexing/parsing of properties

In contrast to what we do for examples, we do not really need to capture
the "prompt" here.

- - - - -
bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00
Add HTML test for properties

- - - - -
2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00
Add unit tests for properties

- - - - -
874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00
Bump interface version

- - - - -
2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00
Fix parser bug

- - - - -
743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00
Allow to load interface files with compatible versions

- - - - -
981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00
Export more types from Documentation.Haddock (fixes haskell/haddock#216)

- - - - -
dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00
Update ANNOUNCE and CHANGES

- - - - -
edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00
Bump version

- - - - -
5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00
Fix typo in documentation

- - - - -
e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00
Add documentation for properties

- - - - -
9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00
Remove redundant if-defs, more source documentation

- - - - -
87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00
Adapt cabal file

- - - - -
c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00
Require ghc 7.6

- - - - -
8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00
Bump version

- - - - -
1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00
Update ANNOUNCE and CHANGES

- - - - -
74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00
Improve note about `binaryInterfaceVersion` (thanks David)

- - - - -
ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00
Update version in html tests, rpm spec file, and user manual

- - - - -
f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00
Remove unused MonadFix constraint

- - - - -
dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00
Minor code simplification

- - - - -
4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00
Increase code locality

- - - - -
f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00
Minor code simplification

- - - - -
e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00
Handle HsExplicitListTy in renameer (fixes haskell/haddock#213)

- - - - -
c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00
Better error messages

- - - - -
14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00
Simplify RnM type

- - - - -
6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00
Simplify lookupRn

- - - - -
bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00
Organize unite tests hierarchically

- - - - -
2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00
Handle more cases in renameType

- - - - -
8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00
Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref

- - - - -
3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00
Add /tests/html-tests/output/ to .gitignore

- - - - -
db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00
Allow haddock markup in deprecation messages

- - - - -
e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00
If parsing of deprecation message fails, include it verbatim

- - - - -
242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00
Add description for PruneWithWarning test

- - - - -
43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00
Minor formatting change

- - - - -
22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00
Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220)

- - - - -
cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00
Add build artifacts for documentation to .gitignore

- - - - -
854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00
unit-tests: Improve readability

Add IsString instance for (Doc RdrName) + use <> instead of DocAppend.

- - - - -
c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00
unit-tests: Minor refactoring

Rename parse to parseParas.

- - - - -
04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00
Fix typo

- - - - -
3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00
Add description for DeprecatedReExport test

- - - - -
84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00
Move resources to /resources directory

- - - - -
a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00
Move HTML tests to directory /html-test/

- - - - -
e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00
Move HTML reference renderings to /html-test/ref/

- - - - -
3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00
Copy css, images, etc. on accept

- - - - -
40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00
Move unit tests to /test directory

- - - - -
99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00
Fix Setup.lhs

/usr/bin/runhaskell is not installed on all systems.

- - - - -
95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00
Make test management scripts more robust

 * They are now independent from the current directory, and hence can be
   called from everywhere

 * On UNIX/Linux they can now be run as scripts

- - - - -
027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00
Add 'dev' flag to cabal file, that builds without -O2

That way --disable-optimization can be used, which decreases build time
considerably.

- - - - -
e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00
Add test case for "spurious superclass constraints bug"

- - - - -
52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00
Adapt accept.lhs, so that it ignores more index files

- - - - -
53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00
Rename html-test/runtests.lhs to html-test/run.lhs

- - - - -
84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00
Move source files for HTML tests to html-test/src

- - - - -
a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00
Adapt output directory for HTML tests

- - - - -
d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00
Follow dopt->gopt rename

- - - - -
956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00
Update html-test/README

- - - - -
903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00
Use markdown for html-test/README

- - - - -
150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00
Follow changes in GHC: 'flags' has been renamed 'generalFlags'

- - - - -
41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00
Export missing types from Documentation.Haddock

- - - - -
9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00
Update dependencies

- - - - -
e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00
Bump version

- - - - -
e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00
Add missing test files to cabal file (fixes haskell/haddock#230)

- - - - -
ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00
Update CHANGES

- - - - -
51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00
Track changes in UNPACK pragma stuff

- - - - -
f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00
Implement overlapping type family instances.

An ordered, overlapping type family instance is introduced by 'type
instance
where', followed by equations. See the new section in the user manual
(7.7.2.2) for details. The canonical example is Boolean equality at the
type
level:

type family Equals (a :: k) (b :: k) :: Bool
type instance where
  Equals a a = True
  Equals a b = False

A branched family instance, such as this one, checks its equations in
order
and applies only the first the matches. As explained in the note
[Instance
checking within groups] in FamInstEnv.lhs, we must be careful not to
simplify,
say, (Equals Int b) to False, because b might later unify with Int.

This commit includes all of the commits on the overlapping-tyfams
branch. SPJ
requested that I combine all my commits over the past several months
into one
monolithic commit. The following GHC repos are affected: ghc, testsuite,
utils/haddock, libraries/template-haskell, and libraries/dph.

Here are some details for the interested:

- The definition of CoAxiom has been moved from TyCon.lhs to a
  new file CoAxiom.lhs. I made this decision because of the
  number of definitions necessary to support BranchList.

- BranchList is a GADT whose type tracks whether it is a
  singleton list or not-necessarily-a-singleton-list. The reason
  I introduced this type is to increase static checking of places
  where GHC code assumes that a FamInst or CoAxiom is indeed a
  singleton. This assumption takes place roughly 10 times
  throughout the code. I was worried that a future change to GHC
  would invalidate the assumption, and GHC might subtly fail to
  do the right thing. By explicitly labeling CoAxioms and
  FamInsts as being Unbranched (singleton) or
  Branched (not-necessarily-singleton), we make this assumption
  explicit and checkable. Furthermore, to enforce the accuracy of
  this label, the list of branches of a CoAxiom or FamInst is
  stored using a BranchList, whose constructors constrain its
  type index appropriately.

I think that the decision to use BranchList is probably the most
controversial decision I made from a code design point of view.
Although I provide conversions to/from ordinary lists, it is more
efficient to use the brList... functions provided in CoAxiom than
always to convert. The use of these functions does not wander far
from the core CoAxiom/FamInst logic.

BranchLists are motivated and explained in the note [Branched axioms] in
CoAxiom.lhs.

- The CoAxiom type has changed significantly. You can see the new
  type in CoAxiom.lhs. It uses a CoAxBranch type to track
  branches of the CoAxiom. Correspondingly various functions
  producing and consuming CoAxioms had to change, including the
  binary layout of interface files.

- To get branched axioms to work correctly, it is important to have a
  notion
  of type "apartness": two types are apart if they cannot unify, and no
  substitution of variables can ever get them to unify, even after type
family
  simplification. (This is different than the normal failure to unify
because
  of the type family bit.) This notion in encoded in tcApartTys, in
Unify.lhs.
  Because apartness is finer-grained than unification, the tcUnifyTys
now
  calls tcApartTys.

- CoreLinting axioms has been updated, both to reflect the new
  form of CoAxiom and to enforce the apartness rules of branch
  application. The formalization of the new rules is in
  docs/core-spec/core-spec.pdf.

- The FamInst type (in types/FamInstEnv.lhs) has changed
  significantly, paralleling the changes to CoAxiom. Of course,
  this forced minor changes in many files.

- There are several new Notes in FamInstEnv.lhs, including one
  discussing confluent overlap and why we're not doing it.

- lookupFamInstEnv, lookupFamInstEnvConflicts, and
  lookup_fam_inst_env' (the function that actually does the work)
  have all been more-or-less completely rewritten. There is a
  Note [lookup_fam_inst_env' implementation] describing the
  implementation. One of the changes that affects other files is
  to change the type of matches from a pair of (FamInst, [Type])
  to a new datatype (which now includes the index of the matching
  branch). This seemed a better design.

- The TySynInstD constructor in Template Haskell was updated to
  use the new datatype TySynEqn. I also bumped the TH version
  number, requiring changes to DPH cabal files. (That's why the
  DPH repo has an overlapping-tyfams branch.)

- As SPJ requested, I refactored some of the code in HsDecls:

 * splitting up TyDecl into SynDecl and DataDecl, correspondingly
   changing HsTyDefn to HsDataDefn (with only one constructor)

 * splitting FamInstD into TyFamInstD and DataFamInstD and
   splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl

 * making the ClsInstD take a ClsInstDecl, for parallelism with
   InstDecl's other constructors

 * changing constructor TyFamily into FamDecl

 * creating a FamilyDecl type that stores the details for a family
   declaration; this is useful because FamilyDecls can appear in classes
but
   other decls cannot

 * restricting the associated types and associated type defaults for a
 * class
   to be the new, more restrictive types

 * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts,
   according to the new types

 * perhaps one or two more that I'm overlooking

None of these changes has far-reaching implications.

- The user manual, section 7.7.2.2, is updated to describe the new type
  family
  instances.

- - - - -
f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00
Track changes in HsBang

- - - - -
ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00
Merge branch 'master' of http://darcs.haskell.org//haddock

- - - - -
f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00
Use InstEnv.instanceSig rather than instanceHead (name change)

- - - - -
88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00
Track change to HsBang type

- - - - -
e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00
Merge branch 'ghc-7.6' into ghc-7.6-merge-2

Conflicts:
	haddock.cabal
	src/Haddock/Interface/AttachInstances.hs
	src/Haddock/Interface/Create.hs
	src/Haddock/Interface/LexParseRn.hs
	src/Haddock/InterfaceFile.hs
	src/Haddock/Types.hs

Only GHC HEAD can compile this. GHC 7.6.x cannot compile this.

Some test fail.

- - - - -
62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00
Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.)

- - - - -
013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00
Refactoring instanceHead'.

- - - - -
3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00
Using new syntax in html-test/src/GADTRecords.hs.

- - - - -
626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00
Typo

- - - - -
1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00
Follow changes in base

- - - - -
3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00
Follow changes in GHC's build system

- - - - -
1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00
Follow changes in GHC build system

- - - - -
69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00
Use Alex 3's Unicode support to properly lex source files as UTF-8

Signed-off-by: David Waern <david.waern at gmail.com>

- - - - -
ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00
Adapt to tcRnGetInfo returning family instances too

This API change was part of the fix to Trac haskell/haddock#4175.  But it offers new
information to Haddock: the type-family instances, as well as the
class instances, of this type.

This patch just drops the new information on the floor, but there's an
open opportunity to use it in the information that Haddock displays.

- - - - -
971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00
Fix for haskell/haddock#7879.

Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory.

- - - - -
31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00
Use "cp -L" when making $(INPLACE_LIB)/latex too

- - - - -
e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00
Add -itest to .ghci

- - - - -
b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00
Workaround for a failing build with --enable-tests.

- - - - -
e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00
Fix broken test

- - - - -
0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00
Updates to reflect changes in HsDecls to support closed type families.

- - - - -
7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00
Fix failing test

- - - - -
53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00
Fix failing test

- - - - -
931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00
Remove (error "synifyKind") to use WithinType, to allow haddock to process base.

- - - - -
55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00
Changes to reflect changes in GHC's type HsTyVarBndr

- - - - -
b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00
Output Copright and License keys in Xhtml backend.

This information is as relevant in the documentation as it is in the
source files themselves.

Signed-off-by: David Waern <david.waern at gmail.com>

- - - - -
4c66028a by David Waern at 2013-08-04T15:27:36-07:00
Bump interface file version.

- - - - -
67340163 by David Waern at 2013-08-09T16:12:51-07:00
Update tests.

- - - - -
2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00
Add spec tests.

This adds tests for all elements we can create during regular
parsing. This also adds tests for text with unicode in it.

- - - - -
97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00
Fix ticket haskell/haddock#247.

I do the same thing that the XHTML backend does: give these no special
treatment and just act as if they are regular functions.

- - - - -
60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00
LaTeX tests setup

- - - - -
fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00
Fixes haskell/haddock#253

- - - - -
1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00
Use Hspec instead of nanospec

This is motivated by the fact that Haddock tests are not ran by the
GHC's ‘validate’ script so we're pretty liberal on dependencies in that
area. Full Hspec gives us some nice features such as Quickcheck integration.

- - - - -
8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00
Fix AMP warnings

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00
Update Git repo URL in `.cabal` file

- - - - -
16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00
Revision to reflect new role annotation syntax in GHC.

- - - - -
4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00
Add missing `traverse` method for `GenLocated`

As `Traversable` needs at least one of `traverse` or `sequenceA` to be
overridden.

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00
Add test helper

- - - - -
4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00
Fixes haskell/haddock#231

- - - - -
435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00
Fixes haskell/haddock#256

We inject -dynamic-too into flags before we run all our actions in the
GHC monad.

- - - - -
b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Add new field to DynFlags

- - - - -
49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00
Fallback to ./resources when Cabal data is not found

(so that themes are found during development)

- - - - -
bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Fixes haskell/haddock#5

- - - - -
e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Print missing documentation. Fixes haskell/haddock#258.

- - - - -
02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00
Don't consider StaticFlags when parsing arguments.

Instead, discard any static flags before parsing the command line using
GHC's DynFlags parser.

See http://ghc.haskell.org/trac/ghc/ticket/8276

Based off a patch from Simon Hengel.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00
Update HTML tests

- - - - -
f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00
Bump version

- - - - -
97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00
Track changes in HsSpliceTy data constructor

- - - - -
59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00
Adapt to small change in Pretty's exports

- - - - -
8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00
Some code simplification by using traverse

- - - - -
fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00
Fix warnings in test helper

- - - - -
6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Add ByteString version of Attoparsec

- - - - -
968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
One pass parser and tests.

We remove the HTML test as it is no longer necessary. We cover the
test case in spec tests and other HTML tests but keeping this around
fails: this is because the new parser has different semantics there.
In fact, I suspect the original behaviour was a bug that wasn't
caught/fixed but simply included as-is during the testing.

- - - - -
37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00
Rename Haddock.ParseSpec to Haddock.ParserSpec

- - - - -
f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00
Don't append newline to parseString input

We also check that we have parsed everything with endOfInput.

- - - - -
95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00
Fix totality, unicode, examples, paragraph parsing

Also simplify specs and parsers while we're at it. Some parsers were
made more generic.

This commit is a part of GHC pre-merge squash, email
fuuzetsu at fuuzetsu.co.uk if you need the full commit history.

- - - - -
7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00
Update acceptance tests

- - - - -
d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Support for bold.

Conflicts:
	src/Haddock/Backends/Hoogle.hs
	src/Haddock/Interface/Rename.hs
	src/Haddock/Parser.hs

- - - - -
4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Allow for headings inside function documentation.

LaTeX will treat the h3-h6 headings the same as we'd have to hack the
style file heavily otherwise and it would make the headings tiny
anyway.

Hoogle upstream said they will put in the functionality on their end.

Conflicts:
	src/Haddock/Interface/Rename.hs
	src/Haddock/Types.hs
	test/Haddock/ParserSpec.hs

- - - - -
fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Per-module extension flags and language listing.

Any extensions that are not enabled by a used language (Haskell2010
&c) will be shown. Furthermore, any implicitly enabled are also going
to be shown. While we could eliminate this either by using the GHC API
or a dirty hack, I opted not to: if a user doesn't want the implied
flags to show, they are recommended to use enable extensions more
carefully or individually. Perhaps this will encourage users to not
enable the most powerful flags needlessly. Enabled with show-extensions.

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Bump interface version

There were some breaking changes over the last few patches so we bump
the interface version. This causes a big problem with testing:

1. To generate cross package docs, we first need to generate docs for
the package used.
2. To generate package docs with new interface version, we need to use
Haddock which has the version bumped.
3. To get Haddock with the version bump, we first need to test cross
package docs
4. GOTO 1

So the problem is the chicken and the egg problem. It seems that the
only solution would be to generate some interface files on the fly but
it is non-trivial.

To run this test, you'll have to:

* build Haddock without the test (make sure everything else passes)
* rebuild the packages used in the test with your shiny new binary
  making sure they are visible to Haddock
* remove the ‘_hidden’ suffix and re-run the tests

Note: because the packages currently used for this test are those
provided by GHC, it's probably non-trivial to just re-build them.
Preferably something less tedious to rebuild should be used and
something that is not subject to change.

- - - - -
124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Allow for nesting of paragraphs under lists.

The nesting rules are similar to Markdown's with the exception that we
can not simply indent the first line of a hard wrapped indented
paragraph and have it treated as if it was fully indented. The reason is
differences in markup as some of our constructs care about whitespace
while others just swallow everything up so it's just a lot easier to not
bother with it rather than making arbitrary rules.

Note that we now drop trailing for string entities inside of lists. They
weren't needed and it makes the output look uniform whether we use a
single or double newline between list elements.

Conflicts:
	src/Haddock/Parser.hs
	test/Haddock/ParserSpec.hs

- - - - -
c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Allow escaping in URLs and pictures.

Some tests were moved under parseString as they weren't about paragraph
level markup.

Conflicts:
	src/Haddock/Parser.hs
	test/Haddock/ParserSpec.hs

- - - - -
32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Update documentation.

- - - - -
fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Update maintainer

- - - - -
b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00
Fixes haskell/haddock#271

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00
Support for -XPatternSynonyms

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00
Update CPP check for __GLASGOW_HASKELL__

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00
<+>: Don't insert a space when concatenating empty nodes

- - - - -
a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00
Fix @ code blocks

In cases where we had some horizontal space before the closing ‘@’, the
parser would not accept the block as a code block and we'd get ugly
output.

- - - - -
0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00
Update tests

This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of
TypeHoles as an extension from GHC.

- - - - -
157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00
Handle infix vs prefix names correctly everywhere, by explicitly specifying the context

The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)"  or "`a`" and "+"

- - - - -
aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00
Correct whitespace in ‘hidden’ test for <+> change

- - - - -
121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00
Document module header.

Fixes Haddock Trac haskell/haddock#270.

- - - - -
e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00
Insert a space between module link and description

Fixes Haddock Trac haskell/haddock#277.

- - - - -
771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00
Ensure a space between type signature and ‘Source’

This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the
suggested fix _but_ it doesn't actually fix the reported issue. This
commit simply makes copying the full line a bit less of a pain.

- - - - -
8cda9eff by nand at 2014-02-11T15:48:30+00:00
Add support for type/data families

This adds support for type/data families with their respective
instances, as well as closed type families and associated type/data
families.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
3f22c510 by nand at 2014-02-11T15:53:50+00:00
Improve display of poly-kinded type operators

This now displays them as (==) k a b c ... to mirror GHC's behavior,
instead of the old (k == a) b c ... which was just wrong.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
effb2d6b by nand at 2014-02-11T15:56:50+00:00
Add test case for PatternSynonyms

This just tests various stuff including poly-kinded patterns and
operator patterns to make sure the rendering isn't broken.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00
Get rid of re-implementation of sortBy

I have no idea what this was doing lying around here, and due to the
usage of tuples it's actually slower, too.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00
Only warn about missing docs when docs are missing

This fixes the ‘Missing documentation for…’ message for modules with
100% coverage.

- - - - -
cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00
Add test case for inter-module type/data family instances

These should show up in every place where the class is visible, and
indeed they do right now.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00
Use a bespoke data type to indicate fixity

This deals with what I imagine was an ancient TODO and makes it much
clearer what the argument actually does rather than having the user
chase down the comment.

- - - - -
5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00
Strip a single leading space from bird tracks (#201)

This makes bird tracks in the form

> foo
> bar
> bat

parse as if they had been written as

>foo
>bar
>bat

ie. without the leading whitespace in front of every line.

Ideally we also want to look into how leading whitespace affects code
blocks written using the @ @ syntax, which are currently unaffected by
this patch.

- - - - -
5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00
Turn a source code comment into specs

- - - - -
784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00
Update test case for lifted GADT type rendering

The parsing of these seems to have been fixed by GHC folk and it now
renders differently. IMHO it now renders in a better way so I'm updating
the test to reflect this.

- - - - -
c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00
Don't shadow ‘strip’.

-Wall complains

- - - - -
293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00
Make ImplicitParams render correctly (#260)

This introduces a new precedence level for single contexts (because
implicit param contexts always need parens around them, but other types
of contexts don't necessarily, even when alone)

- - - - -
4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00
Lower precedence of equality constraints

This drops them to the new precedence pREC_CTX, which makes single
eqaulity constraints show up as (a ~ b) => ty, in line with GHC's
rendering. Additional tests added to make sure other type operators
render as intended. Current behavior matches GHC

- - - - -
b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00
Add RankNTypes test case to ImplicitParams.hs

This test actually tests what haskell/haddock#260 originally reported - I omitted the
RankNTypes scenario from the original fix because I realized it's not
relevant to the underlying issue and indeed, this renders as intended
now. Still good to have more tests.

- - - - -
c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00
Fix rendering of Contents when links are present

Fixes Haddock Trac haskell/haddock#267.

- - - - -
9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00
Fix wording in the docs

- - - - -
4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00
Change rendering of duplicate record field docs

See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering
the documentation attached to the first instance of a duplicate field.

Perhaps we could improve this by rendering the first instance that has
documentation attached to it but for now, we'll stick with this.

- - - - -
ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00
Render fixity information

Affects functions, type synonyms, type families, class names, data type
names, constructors, data families, associated TFs/DFs, type synonyms,
pattern synonyms and everything else I could think of.

- - - - -
6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00
Reorder topDeclElem to move the source/wiki links to the top

They appear in the same position due to the float: right attribute but
now they're always at the top of the box instead of at the bottom.

- - - - -
2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00
Use optLast instead of listToMaybe for sourceUrls/wikiUrls

This lets you override them using eg. cabal haddock --haddock-options,
which can come in handy if you want to use a different layout or URL for
your source code links than cabal-install generates.

- - - - -
0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00
Differentiate between TH splices (line-links) and regular names

This adds a new type of source code link, to a specific line rather than
a specific declaration/name - this is used to link to the location of a
TH splice that defines a certain name.

Rather hefty changes throughout and still one unresolved issue (the line
URLs aren't parsed from the third form of --read-interface which means
they're currently restricted to same-interface links). Not sure if
this issue is really worth all the hassle, especially since we could
just use line links in general.

This commit also contains some cleanup/clarification of the types in
Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the
process. Notably, the Bool parameter was replaced by a Unicode type
synonym to help clarify its presence in type signatures.

- - - - -
66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00
Group similar fixities together

Identical fixities declared for the same line should now render using
syntax like: infix 4 <, >=, >, <=

- - - - -
6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00
Update changelog

- - - - -
7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00
Include fixity information in the Interface file

This resolves fixity information not appearing across package borders.

The binary file version has been increased accordingly.

- - - - -
ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00
Update changelog

- - - - -
565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00
Update appearance of fixity annotations

This moves them in-line with their corresponding lines, similar to a
presentation envision by @hvr and described in #ghc.

Redundant operator names are also omitted when no ambiguity is present.

- - - - -
5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00
Filter family instances of hidden types

Currently, this check does not extend to hidden right hand sides,
although it probably should hide them in that case.

- - - - -
ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00
Add documentation for --source-entity-line

- - - - -
0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00
Revert "Reorder topDeclElem to move the source/wiki links to the top"

This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d.

This change is no longer needed with the new rendering style, and it
messes with copy/pasting lines.

- - - - -
30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00
Bump version to 2.15.0

- - - - -
adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00
Fix up some whitespace

- - - - -
8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00
Hide RHS of TFs with non-exported right hand sides

Not sure what to do about data families yet, since technically it would
not make a lot of sense to display constructors that cannot be used by
the user.

- - - - -
5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00
Add UnicodeSyntax alternatives for * and ->

I could not find a cleaner way to do this other than checking for
string equality with the given built-in types. But seeing as it's
actually equivalent to string rewriting in GHC's implementation of
UnicodeSyntax, it's probably fitting.

- - - - -
b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00
Display minimal complete definitions for type classes

This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+.
I also cleaned up some of the places in which ExportDecl is used to make
adding fields easier in the future.

Lots of test cases have been updated since they now render with
minimality information.

- - - - -
a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00
Strip links from recently added html tests

These were accidentally left there when the tests were originally added

- - - - -
d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00
Update changelog

- - - - -
d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00
Always read in prologue files as UTF8 (#286).

- - - - -
54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00
Style only

- - - - -
fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00
Add Fuuzetsu maintainers field in cabal file

- - - - -
f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00
Hide minimal definition for only-method classes

Previously this was not covered by the All xs check since here it is not
actually an All, rather a single Var n.

This also adds the previously missing html-test/src/Minimal.hs.

- - - - -
0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00
Fix issue haskell/haddock#281

This is a regression from the data family instances change. Data
instances are now distinguished from regular lists by usage of the new
class "inst", and the style has been updated to only apply to those.

I've also updated the appropriate test case to test this a bit better,
including GADT instances with GADT-style records.

- - - - -
1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00
Please cabal sdist

- - - - -
75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00
Drop needless --split-objs which slows us down.

Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292.

- - - - -
31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00
Fix a few typos

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00
Print kind signatures on GADTs

- - - - -
2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00
Add default for new PlatformConstraints field

- - - - -
42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00
Drop leading whitespace in @-style blocks.

Fixes haskell/haddock#201.

- - - - -
98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00
Crash when exporting record selectors of data family instances

This fixes bug haskell/haddock#294.

This also fixes a related but never-before-mentioned bug about the
display of GADT record selectors with non-polymorphic type signatures.

Note: Associated data type constructors fail to show up if nothing is
exported that they could be attached to. Exporting any of the data types
in the instance head, or the class + data family itself, causes them to
show up, but in the absence of either of these, exporting just the
associated data type with the constructor itself will result in it
being hidden.

The only scenario I can come up that would involve this kind of
situation involved OverlappingInstances, and even then it can be
mitigated by just exporting the class itself, so I'm not going to solve
it since the logic would most likely be very complicated.

- - - - -
3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00
Make CHANGES consistent with what's now in 2.14.2

- - - - -
c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00
Actually bundle extra spec tests in sdist

- - - - -
bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00
Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188

The order of signature groups has been corrected upstream. Here we add a
test case and update some existing test-cases to reflect this change. We
remove grouped signature in test cases that we can (Minimal,
BugDeprecated &c) so that the test is as self-contained as possible.

- - - - -
708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00
Enforce strict GHC version in cabal file

This stops people with 7.6.3 trying to install 2.15.x which clearly
won't work. Unfortunately we shipped 2.14.x without realising this.

- - - - -
60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00
Initialise some new PlatformConstants fields

- - - - -
ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00
We don't actually want unicode here

- - - - -
0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00
Parse identifiers with ^ and ⋆ in them.

Fixes haskell/haddock#298.

- - - - -
e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00
Ignore version string during HTML tests.

- - - - -
de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00
Update CHANGES to follow 2.14.3

- - - - -
beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00
remove Origin flag from LHsBindsLR

- - - - -
cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00
Replace local `die` by new `System.Exit.die`

Starting with GHC 7.10, System.Exit exports the new `die`
which is essentially the same as Haddock.Util.die, so this
commit changes Haddock.Util.die to be a simple re-export
of System.Exit.die. See also

  https://ghc.haskell.org/trac/ghc/ticket/9016

for more details.

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00
Disambiguate ‘die’ in test runners.

- - - - -
5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00
Prepare modules for parser split.

We have to generalise the Doc (now DocH) slightly to remove the
dependency on GHC-supplied type.

- - - - -
d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00
Move parser + parser tests out to own package.

We move some types out that are necessary as well and then
re-export and specialise them in the core Haddock.

Reason for moving out spec tests is that if we're working on the parser,
we can simply work on that and we can ignore the rest of Haddock. The
downside is that it's a little inconvenient if at the end of the day we
want to see that everything passes.

- - - - -
522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00
Move out Show and Eq instances to Types

They are much more useful to the users here.

- - - - -
11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00
Remove no longer necessary parser error handling.

We can now drop some Maybe tests and even lets us strip an error
handling monad away in a few places.

- - - - -
6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00
Please the GHC build-system.

As I can not figure out how to do this properly, if we're in GHC tree,
we treat the library as being the same package. If we're not in the
tree, we require that the library be installed separately.

- - - - -
7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00
Update issue tracker URL

- - - - -
f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00
Update issue tracker URL for haddock-library

- - - - -
66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00
Accomodate change in PatSyn representation

- - - - -
0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00
Revert "Accomodate change in PatSyn representation"

This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am
reverting this because I pushed it to master when it was meant to stay
on a wip-branch. Sorry Gergo and everyone who had trouble due to this.

- - - - -
e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00
Revert "Revert "Accomodate change in PatSyn representation""

This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295.

Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5
this was actually intended. Embarrasing for me.

- - - - -
5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00
Clear up highlighting of identifiers with ‘'’s.

- - - - -
d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00
Follow change in patSynSig

- - - - -
938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00
Slightly update the readme.

Style-sheets are no longer a recent thing, dead links, old maintainers,
different formats.

- - - - -
c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00
Update cabal files

Update repository urls, use subdir property for haddock-library and use
a separate versioning scheme for haddock-library in preparation for release.

- - - - -
a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00
Compatibility with older versions of base and bytestring

- - - - -
009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00
Enable travis-ci for haddock-library

- - - - -
9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00
haddock-library: Do not depend on haddock-library in test suite

I think you either add src to hs-source-dirs or the library to
build-depends.  But doing both does not make sense (AFAICT).

- - - - -
fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00
haddock-library: Use -Wall for specs

- - - - -
649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00
Use Travis with multiple GHC versions

When using HEAD, we build haddock-library directly from repository as a
dependency (and thanks to --enable-tests, the tests get ran anyway). In
all other cases, we manually run the tests on haddock-library only and
don't test the main project.

- - - - -
d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00
Comment improvements + few words in cabal file

- - - - -
0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00
Use doctest to check examples in documentation

- - - - -
2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00
Remove doctest dependency

(so that we can use haddock-library with doctest)

- - - - -
626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00
Travis tweaks

- - - - -
41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00
Don't actually forget to install specified GHC.

- - - - -
c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00
Removed reliance on LambdaCase (which breaks build with ghc 7.4).

- - - - -
b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00
Fixed haddock warnings.

- - - - -
a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00
Update Travis, bump version

- - - - -
864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00
Fix anchors. Closes haskell/haddock#308.

- - - - -
53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00
Drop DocParagraph from front of headers

I can not remember why they were wrapped in paragraphs to begin with and
it seems unnecessary now that I test it. Closes haskell/haddock#307.

- - - - -
29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00
Don't mangle append order for nested lists.

The benefit of this is that the ‘top-level’ element of such lists is
properly wrapped in <p> tags so any CSS working with these will be
applied properly. It also just makes more sense.

Pointed out at jgm/pandoc#1346.

- - - - -
05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00
Bump haddock-library to 1.1.0 for release

- - - - -
70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00
Propagate overloading-mode for instance declarations in haddock (#9242)

- - - - -
d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00
Adapt to new definition of HsDecls.TyFamEqn

This is a knock-on from the refactoring from Trac haskell/haddock#9063.
I'll push the corresponding changes to GHC shortly.

- - - - -
f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00
Track GHC PackageId to PackageKey renaming.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	src/Haddock/Interface/Create.hs

- - - - -
b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00
Track changes for module reexports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	src/Haddock/Interface/Create.hs

- - - - -
8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00
Catch mid-line URLs. Fixes haskell/haddock#314.

- - - - -
4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00
Track type signature change of lookupModuleInAllPackages

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00
If GhcProfiled, also build Haddock profiled.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00
Ignore TAGS files.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00
Update to attoparsec-0.12.1.1

There seems to be memory and speed improvement.

- - - - -
5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00
Fix forgotten src

- - - - -
3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00
Bump down the version for master to 2.14.4

- - - - -
dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00
Revert "Track type signature change of lookupModuleInAllPackages"

This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f.

- - - - -
3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00
Revert "Track changes for module reexports."

This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d.

- - - - -
56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00
Revert "Track GHC PackageId to PackageKey renaming."

This reverts commit 8ac42d3327473939c013551750425cac191ff0fd.

- - - - -
726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00
Revert "Adapt to new definition of HsDecls.TyFamEqn"

This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd.

- - - - -
61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00
Revert "Propagate overloading-mode for instance declarations in haddock (#9242)"

This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c.

- - - - -
a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00
Revert "Disambiguate ‘die’ in test runners."

This reverts commit dba02d6df32534aac5d257f2d28596238d248942.

- - - - -
f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00
Revert "Replace local `die` by new `System.Exit.die`"

This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5.

- - - - -
107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00
Merge branch 'reverts'

This reverts any changes that were made to have Haddock compile with
7.9. When 7.10 release comes, we can simply re-apply all the patches and
any patches that occur on ghc-head branch from now on.

This allows us to build master with 7.8.3

- - - - -
b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00
Fix haskell/haddock#313 by doing some list munging.

I get rid of the Monoid instance because we weren't satisfying the laws.
Convenience of having <> didn't outweigh the shock-factor of having it
behave badly.

- - - - -
e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00
Stop testing haskell/haddock#188.

Because the change is in GHC 7.9 and we now work against 7.8.3, this
test no longer makes sense. We revert it until 7.10 becomes the standard
version. If anything, there should be a test for this in GHC itself.

- - - - -
54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00
Add haskell/haddock#313 to CHANGES

- - - - -
9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00
Fix warning

- - - - -
ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00
Fix travis builds

- - - - -
384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00
Require GHC 7.8.3

- - - - -
d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00
Move Haddock API to a separate package

- - - - -
80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00
Bump version to 2.15.0 and add version constraints

- - - - -
309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00
Add deprecated compatibility module

- - - - -
4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00
export things to allow customizing how the Ghc session is run

- - - - -
47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00
ghc 7.8.2 compatibility

- - - - -
5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00
install dependencies for haddock-api on travis

- - - - -
9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00
Move sources under haddock-api/src

- - - - -
85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00
Remove compat stuff

- - - - -
151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00
Fix extra whitespace on signatures and update all test cases

This was long overdue, now running ./accept.lhs on a clean test from
master will not generate a bunch of changes.

- - - - -
d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00
Omit unnecessary foralls and fix haskell/haddock#315

This also fixes haskell/haddock#86.

- - - - -
bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00
Update CHANGES

- - - - -
fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00
Delete few unused/irrelevant/badly-place files.

- - - - -
3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00
Changes due to ghc api changes in package representation

Also fix a bug with finding the package name and version given a
module. This had become wrong due to the package key changes (it was
very hacky in the first place). We now look up the package key in the
package db to get the package info properly.

- - - - -
539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00
Import Data.Word w/o import-list

This is needed to keep the compilation warning free (and thus pass GHC's
./validate) regardless of whether Word is re-exported from Prelude or not

See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details

- - - - -
9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00
Bump version in doc

- - - - -
4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00
Bump haddock-library version

- - - - -
f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00
Remove references to deleted files

- - - - -
5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00
Make the doc parser not complain

- - - - -
2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00
CONTRIBUTING file for issues

- - - - -
88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00
Mention --print-missing-docs

- - - - -
42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00
Follow changes to TypeAnnot in GHC HEAD

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00
Fix import of 'empty' due to AMP.

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00
Bump `base` constraint for AMP

- - - - -
0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00
Delete stale ANNOUNCE

- - - - -
cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00
Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426)

- - - - -
4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00
Properly render package ID (not package key) in index, fixes haskell/haddock#329.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00
Disambiguate string-literals

GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem`
otherwise.

- - - - -
c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00
Revert "Followup changes to addition of -fwarn-context-quantification"

This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily
as the respective feature hasn't landed in GHC HEAD yet, but this commit
blocks later commits from being referenced in GHC HEAD.

- - - - -
38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00
Revert "Revert "Followup changes to addition of -fwarn-context-quantification""

This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc.
It's in HEAD now.

- - - - -
f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00
Revert "Fix import of 'empty' due to AMP."

This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since
it turns out we don't need to re-export `empty` from Control.Monad after
all.

- - - - -
467050f1 by David Feuer at 2014-10-09T20:07:36-04:00
Fix improper lazy IO use

Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results.
- - - - -
cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00
Fix use-after-close lazy IO bug

Make `getPrologue` force `parseParas dflags str` before returning. Without this,
it will attempt to read from the file after it is closed, with unspecified and
generally bad results.

Signed-off-by: David Feuer <David.Feuer at gmail.com>
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00
Add an .arcconfig file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00
Add .arclint file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00
Experimental support for collapsable headers

Closes haskell/haddock#335

- - - - -
849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00
Experimental support for collapsable headers

(cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc)

- - - - -
a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00
Collapse user-defined section by default (re haskell/haddock#335)

- - - - -
9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00
reflect ForeignType constructore removal

Reviewers: austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D358

- - - - -
c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00
Remove overlapping pattern match

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00
Remove -fobject-code from .ghci

(this slows down reloads on modifications)

- - - - -
d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00
Get rid of StandaloneDeriving

- - - - -
a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00
Derive more instances

- - - - -
8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00
Remove unused language extensions

- - - - -
3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00
Minor refactoring

- - - - -
4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00
parser: Try to parse definition lists right before text paragraphs

- - - - -
8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00
Add support for markdown links (closes haskell/haddock#336)

- - - - -
a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00
Allow markdown links at the beginning of a paragraph

- - - - -
53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00
Update documentation

- - - - -
652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00
Add support for markdown images

- - - - -
9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00
Allow an optional colon after the closing bracket of definition lists

This is to disambiguate them from markdown links and will be require
with a future release.

- - - - -
8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00
whitespace only

- - - - -
3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00
Fix re-exports of built-in type families

Fixes haskell/haddock#310

- - - - -
edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00
Turn some uses of error into recoverable warnings

This should at the very least not abort when something weird happens. It
does feel like we should have a type that carries these errors until the
end however as the user might not see them unless they are printed at
the end.

- - - - -
0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00
Fix warnings

- - - - -
d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00
Fix parsing of identifiers written in infix way

- - - - -
1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00
Minor code simplification

- - - - -
6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00
newtype-wrap parser monad

- - - - -
dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00
Make compatible with `deepseq-1.4.0.0`

...by not relying on the default method implementation of `rnf`

- - - - -
fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00
State intention rather than implementation details in Haddock comment

- - - - -
97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00
(wip) Add support for @since (closes haskell/haddock#26)

- - - - -
34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00
Update Haddock to new pattern synonym type signature syntax

- - - - -
304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00
Follow changes from haskell/haddock#9812

- - - - -
920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00
Changes to reflect refactoring in GHC as part of haskell/haddock#7484

- - - - -
0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00
Follow API changes in D426

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00
Support for PartialTypeSignatures

- - - - -
5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00
For pattern synonyms, render "pattern" as a keyword

- - - - -
fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00
List new module in cabal file

- - - - -
b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00
Allow the parser to spit out meta-info

Currently we only use it only for ‘since’ annotations but with these
patches it should be fairly simple to add new attributes if we wish to.

Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the
chance to do more exhaustive testing right now. The way the meta is
output (emphasis at the end of the whole comment) is fairly arbitrary
and subject to bikeshedding.

Note that this makes test for Bug310 fail due to interface version bump:
it can't find the docs for base with this interface version so it fails.
There is not much we can do to help this because it tests for ’built-in’
identifier, not something we can provide ourselves.

- - - - -
765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00
Update doctest parts of comments

- - - - -
8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00
header could contain several lines

Closes haskell/haddock#348

- - - - -
4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00
Revert "Merge branch 'reverts'"

This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing
changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06.

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00
Changes due to ghc api changes in package representation

Also fix a bug with finding the package name and version given a
module. This had become wrong due to the package key changes (it was
very hacky in the first place). We now look up the package key in the
package db to get the package info properly.

Conflicts:
	haddock-api/src/Haddock.hs

- - - - -
2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00
Import Data.Word w/o import-list

This is needed to keep the compilation warning free (and thus pass GHC's
./validate) regardless of whether Word is re-exported from Prelude or not

See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details

- - - - -
1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00
Follow changes to TypeAnnot in GHC HEAD

Signed-off-by: Austin Seipp <aseipp at pobox.com>

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00
Bump ‘base’ constraint

Follows the similar commit made on ghc-head branch

- - - - -
466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00
Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426)

- - - - -
97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00
Properly render package ID (not package key) in index, fixes haskell/haddock#329.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	haddock-api/src/Haddock/ModuleTree.hs

- - - - -
20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00
Disambiguate string-literals

GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem`
otherwise.

Conflicts:
	haddock-library/src/Documentation/Haddock/Parser.hs

- - - - -
b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00
Add an .arcconfig file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00
Add .arclint file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00
Collapse user-defined section by default (re haskell/haddock#335)

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs

- - - - -
f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00
reflect ForeignType constructore removal

Reviewers: austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D358

- - - - -
753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00
Remove overlapping pattern match

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00
Make compatible with `deepseq-1.4.0.0`

...by not relying on the default method implementation of `rnf`

- - - - -
d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00
Update Haddock to new pattern synonym type signature syntax

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs

- - - - -
1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00
Follow changes from haskell/haddock#9812

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00
Changes to reflect refactoring in GHC as part of haskell/haddock#7484

- - - - -
8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00
Follow API changes in D426

Signed-off-by: Austin Seipp <aseipp at pobox.com>

Conflicts:
	haddock-api/src/Haddock/Backends/LaTeX.hs
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs

- - - - -
95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00
Support for PartialTypeSignatures

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs
	haddock-api/src/Haddock/Interface/Create.hs

- - - - -
45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00
For pattern synonyms, render "pattern" as a keyword

- - - - -
a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00
Various fixups and bumps for next release

- - - - -
22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00
Remove redundant wild-card pattern match

(this would otherwise cause a build-failure with `-Werror`)

- - - - -
1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00
Treat GHC 7.10 the same as GHC 7.9

...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway

- - - - -
f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00
Fixup ghc.mk (follow-up to 1739375eb23342)

This makes the GHC build-system aware of the data-files to be copied
into the bindist (as haddock.cabal doesn't list those anymore)

- - - - -
6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00
Only keep one Version instead of blindly appending

- - - - -
40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00
Fix dependency version

- - - - -
8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00
Print missing docs by default

Adds --no-print-missing-docs

- - - - -
59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00
update changelog

- - - - -
aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00
Update docs for @since

- - - - -
2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00
hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion

- - - - -
aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00
Add missing import for standalone haddock-api package

- - - - -
9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00
Reset ghc-head with master's tree

(this is an overwriting git merge of master into ghc-head)

- - - - -
fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00
Bump versions for ghc-7.11

- - - - -
525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00
travis-ci: test with HEAD

- - - - -
cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00
Eliminate instanceHead' in favour of GHC's instanceSig

This is made possible by the elimination of "silent superclass
parameters" in GHC

- - - - -
50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00
Make travis use 7.10.x

- - - - -
475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00
Turn the README into GitHub Markdown format.

Closes haskell/haddock#354

- - - - -
8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00
bump haddock-api ghc dependency to allow release candidate and first release

- - - - -
6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00
Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints

- - - - -
8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00
Track naming change in DataCon

- - - - -
23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00
Follow API changes in D538

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00
Ignore warnings, install Cabal 1.22

- - - - -
86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00
solve dataDir ambiguity

- - - - -
5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00
support GHC 7.10: no Safe-Inferred, Foldable instance

- - - - -
6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00
Update test files

Test: a correct behaviour for fields comma-separating values. I'm
surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders
now but I doubt.

Operators: Seems GHC is giving us a new order for operators, something
must have changed on their side again. cc @haasn , this makes the fixity
to the side not match the order on the LHS which is a bit unpleasant.
Maybe the fixity can be made to match the GHC order?

Bug335: We expand examples by default now.

Bug310: Now inferred safe.

- - - - -
708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00
Links to source location of class instance definitions

- - - - -
5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00
Filter '\r' from comments due to Windows problems.

On Windows this was causing newline to be rendered twice in code blocks.
Closes haskell/haddock#359, fixes haskell/haddock#356.

- - - - -
1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00
Changelog only

- - - - -
c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00
--package-name and --package-version flags

Used for --hoogle amongst other things. Now we need to teach cabal to
use it. The situation is still a bit sub-par because if the flags aren't
passed in, the crash will occur. Closes haskell/haddock#353.

- - - - -
14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00
Sort out some module import warnings

- - - - -
d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00
Track naming change in DataCon

(cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b)

- - - - -
d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00
Follow API changes in D538

Signed-off-by: Austin Seipp <aseipp at pobox.com>
(cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6)

- - - - -
4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00
Track changes in HsSyn for quasi-quotes

- - - - -
775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00
--package-name and --package-version flags

Used for --hoogle amongst other things. Now we need to teach cabal to
use it. The situation is still a bit sub-par because if the flags aren't
passed in, the crash will occur. Closes haskell/haddock#353.

(cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4)

- - - - -
f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00
Prevent Synopsis from using up too much horizontal space

When long type signatures occur in the Synopsis, the element is
stretched beyond the width of the window.  Scrollbars don't appear, so
it's impossible to read anything when this happens.

- - - - -
cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00
Update changelog

Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc

- - - - -
b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00
Make the error encountered when a package can't be found more
user-friendly

Closes haskell/haddock#369

- - - - -
b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00
Remove now redundant imports

- - - - -
5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00
Update test to account for \r filtering

- - - - -
6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00
Test for anchor defaulting

I delete the old tests because it turns out that:

* test runner would never put them in scope of each other even with
  imports so just one would suffice
* test runner actually needed some hacking to keep links so in the end
  we would end up with no anchors making them useless

- - - - -
1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00
Clearly default to variables in out of scope case

- - - - -
7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00
Fix Hoogle display of constructors

Fixes haskell/haddock#361

- - - - -
6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00
Fully qualify names in Hoogle instances output

Closes haskell/haddock#263

- - - - -
52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00
Update changelog

- - - - -
ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00
Output method documentation in Hoogle backend

One thing of note is that we no longer preserve grouping of methods and
print each method on its own line. We could preserve it if no
documentation is present for any methods in the group if someone asks
for it though.

Fixes haskell/haddock#259

- - - - -
a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00
Don't print instance safety information in Hoogle

Fixes haskell/haddock#168

- - - - -
df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00
Post-release version bumps and changelog

- - - - -
dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00
Loosen bounds on haddock-*

- - - - -
de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00
Expand response files in arguments

Closes haskell/haddock#285

- - - - -
1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00
Do not insert anchor for section headings in contents box

- - - - -
860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00
Track change in API of TyCon

- - - - -
a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00
Track API changes to support empty closed type familes

- - - - -
77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00
Ignore doc/haddock.{ps,pdf}

- - - - -
663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00
Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00
Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385

Signed-off-by: Austin Seipp <aseipp at pobox.com>
(cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899)

- - - - -
bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00
haddock-library: require GHC >= 7.4

`Data.Monoid.<>` was added in base-4.5/GHC-7.4

Closes haskell/haddock#394

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00
Track the new location of setRdrNameSpace

- - - - -
1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00
ApiAnnotations : strings in warnings do not return SourceText

The strings used in a WARNING pragma are captured via

strings :: { Located ([AddAnn],[Located FastString]) }
    : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) }
..

The STRING token has a method getSTRINGs that returns the original
source text for a string.

A warning of the form

{-# WARNING Logic
          , mkSolver
          , mkSimpleSolver
          , mkSolverForLogic
          , solverSetParams
          , solverPush
          , solverPop
          , solverReset
          , solverGetNumScopes
          , solverAssertCnstr
          , solverAssertAndTrack
          , solverCheck
          , solverCheckAndGetModel
          , solverGetReasonUnknown
          "New Z3 API support is still incomplete and fragile: \
          \you may experience segmentation faults!"
  #-}

returns the concatenated warning string rather than the original source.

- - - - -
ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00
Create simple method for indentation parsing.
- - - - -
7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00
Make nested lists count indentation according to first item.
- - - - -
d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00
Add simple test case for arbitrary-depth list nesting.
- - - - -
2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00
Add arbitrary-indent spec test for parser.
- - - - -
9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00
Update docs with info on new list nesting rule

Fixes haskell/haddock#278 through commits from PR haskell/haddock#401

- - - - -
12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00
Update some meta data at the top of the docs

- - - - -
765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00
Add some Hacking docs for getting started

- - - - -
19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00
Fix markdown

- - - - -
2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00
Refine hacking instructions slightly

- - - - -
0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00
Update after wild card renaming refactoring in D613

Summary:
* Move `Post*` type instances to `Haddock.Types` as other modules than
  `Haddock.Interface.Rename` will rely on these type instances.
* Update after wild card renaming refactoring in D613.

Reviewers: simonpj, austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D954

GHC Trac Issues: haskell/haddock#10098

- - - - -
10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00
Build executable with '-threaded' (fixes haskell/haddock#399)

- - - - -
7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00
Update changelog for -threaded

Closes haskell/haddock#400

- - - - -
d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00
Fix haddock: internal error: spliceURL UnhelpfulSpan (#207)

Inferred type signatures don't have SrcSpans, so let's use the one from
the declaration.

I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at
trying to run the test-suite.

- - - - -
b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00
Changelog for haskell/haddock#207

Fixes haskell/haddock#207, closes haskell/haddock#402

- - - - -
841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00
Attach to instance location the name that has the same location file

Fixes haskell/haddock#383

- - - - -
98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00
Update changelog

Closes haskell/haddock#398

- - - - -
7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00
Fix alignment of Source links in instance table in Firefox

Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the
parent element with 'float: right' on the inner element can cause the
floated element to be displaced downwards for no apparent reason.

To work around this, the left side is wrapped in its own <span> and set
to 'float: left'.  As a precautionary measure to prevent the parent
element from collapsing entirely, we also add the classic "clearfix"
hack.  The latter is not strictly needed but it helps prevent bugs if
the layout is altered again in the future.

Fixes haskell/haddock#384.

Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to
        prevent confusion over the operator precedence of (<+>) vs (<<).

[1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725

- - - - -
cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00
Update tests for the CSS changes

- - - - -
2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create scaffolding for Haskell source parser module.

- - - - -
29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement function for tagging parsed chunks with source spans.
- - - - -
6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement simple string chunking based on HsColour library.
- - - - -
6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create basic token classification method.
- - - - -
da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Adapt source span tagging to work with current whitespace handling.
- - - - -
4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add record accessors to exports of hyperlinker parser module.
- - - - -
a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Make parser module export all types and associated accessors.
- - - - -
fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create simple HTML renderer for parsed source file.
- - - - -
80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for specifying the CSS file path in HTML source renderer.
- - - - -
994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix identifier recognition in Haskell source parser.
- - - - -
b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix comment recognition in Haskell source parser.
- - - - -
11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for recognizing compiler pragmas in source parser.
- - - - -
736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create scaffolding of module for associating tokens with AST names.

- - - - -
7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement utility method for extracting variable identifiers from AST.

- - - - -
32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create simple mechanism for associating tokens with AST names.

- - - - -
d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add dummy support for hyperlinking named tokens.
- - - - -
2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix span matcher bug causing wrong items being hyperlinked.
- - - - -
2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Constrain elements exported by hyperlinker modules.
- - - - -
9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for type token recognition.
- - - - -
8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for binding token recognition.
- - - - -
d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement go-to-definition mechanism for local bindings.
- - - - -
f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement module export- and import-list item hyperlinking.
- - - - -
c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix span matching to allow parenthesized operators hyperlinking.
- - - - -
03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix weird hyperlinking of parenthesized operators.
- - - - -
b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for type declaration anchors.
- - - - -
7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for top-level function declaration anchors.
- - - - -
dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix external anchors to contain HTML file extension.
- - - - -
a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Refactor the way AST names are handled within detailed tokens.
- - - - -
c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement hyperlinking of imported module names.
- - - - -
2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix parsing of single line comments with broken up newlines.
- - - - -
11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix bug with improper newline handling.
- - - - -
8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix issues with escaped newlines in comments.
- - - - -
34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for parsing C preprocessor macros.
- - - - -
09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add some documentation for parser module of source hyperlinker.
- - - - -
709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add some documentation for AST module of source hyperlinker.
- - - - -
4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add command line option for generating hyperlinked source.
- - - - -
7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Extend module interface with rich source token stream field.
- - - - -
494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement source tokenization during interface creation process.
- - - - -
5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Create hyperlinker module and plug it into the Haddock pipeline.
- - - - -
0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for providing custom CSS files for hyperlinked source.
- - - - -
a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for fancy highlighting upon hovering over identifier.
- - - - -
d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make source hyperlinker generate output in apropriate directory.
- - - - -
ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Create module with hyperlinker utility functions.
- - - - -
6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make external hyperlinks point to locations specified by source URLs.
- - - - -
8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Rewrite source generation to fixed links and directory structure.
- - - - -
ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add basic support for cross-package hyperlink generation.
- - - - -
7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Disable generating hyperlinks for module references.
- - - - -
a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make Haddock generate source for all interfaces (also hidden ones).
- - - - -
f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Prevent source parser from throwing exception when lexing fails.
- - - - -
db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement workaround for Chrome highlighting issues.
- - - - -
0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make hyperlinker generate correct anchors for data constructors.
- - - - -
c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make hyperlinker generate anchors for record field declarations.
- - - - -
063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix issue with hyperlink highlight styling in Chrome browser.
- - - - -
880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking constructor names in patters.
- - - - -
c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking field names in record patterns.
- - - - -
17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking field names in record expressions.
- - - - -
0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Make hyperlinker respect pretty-printer flag and add documentation.
- - - - -
f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Unexpose hyperlinker modules in Cabal configuration.
- - - - -
4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Setup HSpec framework for Haddock API package.
- - - - -
4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add basic tests related to comment parsing.
- - - - -
6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add tests related to parsing basic language constructs.

- - - - -
87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add simple tests for do-notation parsing.

- - - - -
e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add very simple QuickCheck properties for source parser spec.
- - - - -
c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Create simple test runner for hyperlinker tests.
- - - - -
76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for basic identifier hyperlinking.
- - - - -
0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for operator hyperlinking.
- - - - -
731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for constructor hyperlinking.
- - - - -
995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for record expressions and patterns hyperlinking.
- - - - -
3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for literal syntax highlighting.
- - - - -
68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Add hyperlinker test runner to .cabal and .gitignore files. 
- - - - -
aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Adapt hyperlinker test runner to have the same interface as HTML one.
- - - - -
ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Fix hyperlinker test runner file paths and add pretty-printing option.
- - - - -
0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Add reference files for hyperlinker test cases.
- - - - -
efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00
Make hyperlinker test runner strip local links from generated source.
- - - - -
3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00
Create simple script for accepting hyperlinker test case references.
- - - - -
526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00
Re-accept hyperlinker test cases with local references stripped out.
- - - - -
892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00
Fix bug with diffing wrong files in hyperlinker test runner.
- - - - -
9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00
Remove unused dependencies in Haddock API spec configuration.
- - - - -
47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00
Add support for hyperlinking synonyms in patterns.
- - - - -
a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00
Create test case for hyperlinking @-patterns.
- - - - -
c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00
Add support for hyperlinking universally quantified type variables.
- - - - -
68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00
Create hyperlinker test case with quantified type variables.
- - - - -
51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00
Add scoped type variables test for polymorphism test case.
- - - - -
13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00
Add record wildcards test for records hyperlinking test case.
- - - - -
991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00
Document some functions in XHTML utlity module.
- - - - -
98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00
Make hyperlinker render qualified names as one entity.
- - - - -
75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00
Add qualified name test for identifiers hyperlinking test case.
- - - - -
de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00
Fix crash happening when hyperlinking type family declarations.
- - - - -
7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00
Add support for anchoring data family constructor declarations.
- - - - -
3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00
Improve support for hyperlinking type families.
- - - - -
59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00
Add hyperlinker test case for checking type and type family declarations.
- - - - -
d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00
Fix issue with operators being recognized as preprocessor directives.
- - - - -
da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00
Fix broken tests for parsing and hyperlinking hash operators.
- - - - -
53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00
Add support for anchoring signatures in type class declarations.
- - - - -
1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00
Make hyperlinker generate anchors only to top-level value bindings.
- - - - -
a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00
Create hyperlinker test case for type classes.
- - - - -
b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00
Update docs with information about source hyperlinking.
- - - - -
9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00
Update docs on using `--read-interface` option.
- - - - -
9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00
Remove potentially dangerous record access in hyperlinker AST module.
- - - - -
fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00
Make Haddock generate warnings about potential misuse of hyperlinker.
- - - - -
a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00
Fix incorrect specification of source style option in doc file.
- - - - -
3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00
Refactor source path mapping to use modules as indices.
- - - - -
ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00
Fix bug where not all module interfaces were added to source mapping.
- - - - -
f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00
Extract main hyperlinker types to separate module.
- - - - -
43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00
Move source paths types to hyperlinker types module.
- - - - -
3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00
Add support for hyperlinking modules in import lists.
- - - - -
58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00
Add short documentation for hyperlinker source map type.
- - - - -
14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00
Fix bug with module name being hyperlinked to `Prelude`.
- - - - -
8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00
Fix problem with spec build in Haddock API configuration.
- - - - -
e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00
StrictData: print correct strictness marks

- - - - -
e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00
Update changelog

- - - - -
0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00
Relax upper bound on GHC a bit

- - - - -
7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00
Delete trailing whitespace

- - - - -
50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00
StrictData: changes in HsBang type

- - - - -
83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00
Fix expansion icon for user-collapsible sections

Closes haskell/haddock#412

- - - - -
b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00
Make some version changes after 2.16.1 release

- - - - -
a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00
Merge pull request haskell/haddock#422 from adamse/adamse-D1033

Merge for GHC D1033
- - - - -
c0173f17 by randen at 2015-07-30T14:49:08-07:00
Break the response file by line termination rather
than spaces, since spaces may be within the parameters.
This simple approach avoids having the need for any
quoting and/or escaping (although a newline char will
not be possible in a parameter and has no escape
mechanism to allow it).

- - - - -
47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00
Replace (SourceText,FastString) with WithSourceText data type

Phab:D907 introduced SourceText for a number of data types, by replacing
FastString with (SourceText,FastString). Since this has an Outputable
instance, no warnings are generated when ppr is called on it, but
unexpected output is generated. See Phab:D1096 for an example of this.

Replace the (SourceText,FastString) tuples with a new data type

data WithSourceText = WithSourceText SourceText FastString

Trac ticket: haskell/haddock#10692

- - - - -
45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00
Update changelog

- - - - -
347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00
Avoid JavaScript error during page load in non-frame mode

In non-frame mode, parent.window.synopsis refers to the synopsis div
rather than the nonexistent frame.  Unfortunately, the script wrongly
assumes that if it exists it must be a frame, leading to an error where
it tries to access the nonexistent attribute 'replace' of an undefined
value (synopsis.location).

Closes haskell/haddock#406

- - - - -
54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00
Link to the definitions to themselves

Currently, the definitions already have an anchor tag that allows URLs
with fragment identifiers to locate them, but it is rather inconvenient
to obtain such a URL (so-called "permalink") as it would require finding
the a link to the corresponding item in the Synopsis or elsewhere.  This
commit adds hyperlinks to the definitions themselves, allowing users to
obtain links to them easily.

To preserve the original aesthetics of the definitions, we alter the
color of the link so as to be identical to what it was, except it now
has a hover effect indicating that it is clickable.

Additionally, the anchor now uses the 'id' attribute instead of the
(obsolete) 'name' attribute.

Closes haskell/haddock#407

- - - - -
02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00
Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis

Closes haskell/haddock#408

- - - - -
2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00
Fix record field alignment when name is too long

Change <dl> to <ul> and use display:table rather than floats to layout
the record fields.  This avoids bug haskell/haddock#301 that occurs whenever the field
name gets too long.

Slight aesthetic change: the entire cell of the field's source code is
now shaded gray rather than just the area where text exists.

Fixes haskell/haddock#301. Closes haskell/haddock#421

- - - - -
7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00
Add some utility definitions for generating line anchors.

- - - - -
e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Make hyperlinked source renderer generate line anchors.
- - - - -
24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Re-accept test cases after adding line anchors for each of them.
- - - - -
0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Override source line flags when source hyperlinker is enabled.
- - - - -
a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00
Update tests to follow HTML changes

- - - - -
d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00
Fix quote syntax for promoted types.
- - - - -
668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00
Apply promoted type quoting to type-level consing.
- - - - -
89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00
Extend advanced types test case with other examples.
- - - - -
86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00
Rename advanced types test case and accept new output.
- - - - -
dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00
HsBang is split into HsSrcBang and HsImplBang

With recent changes in GHC handling of strictness annotations in Haddock
is simplified.

- - - - -
2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00
Merge pull request haskell/haddock#433 from adamse/split-hsbang

HsBang is split into HsSrcBang and HsImplBang
- - - - -
891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00
Follow changes in GHC build system

- - - - -
b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00
Make Travis use 7.10.2

- - - - -
97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Move SYB utilities to standalone module.
- - - - -
748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Implement `everywhere` transformation in SYB module.
- - - - -
011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Implement generic transformation constructor.
- - - - -
b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Create simple utility module for type specialization.
- - - - -
43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Make type of type specialization function more general.
- - - - -
fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Add basic HTML test case for checking instance specialization.
- - - - -
6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Make HTML class instance printer take optional signature argument.
- - - - -
65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Refactor instance head type to record instead of a meaningless tuple.
- - - - -
3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Add expandable method section for each class instance declaration.
- - - - -
99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Move dummy post-family instances for `DocName` to `Types` module.
- - - - -
e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create convenience functions for type specialization module.
- - - - -
b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Hook type specialization logic with HTML pretty-printer.
- - - - -
dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create stub functions for sugaring specialized types.
- - - - -
fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement list syntax sugaring logic for specialized types.
- - - - -
e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement tuple syntax sugaring logic for specialized types.
- - - - -
68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Get rid of code duplication in type specialization module.
- - - - -
4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create scaffolding of a framework for renaming specialized types.
- - - - -
271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fill in missing cases in specialized type renaming function.
- - - - -
bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Remove code duplication in specialized type renamer.
- - - - -
ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Change state of the type renaming monad.
- - - - -
77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement simple mechanism for generating new type names.
- - - - -
91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fill in stub behaviour with actual environment renaming.
- - - - -
d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fix logic behind binder type renaming.
- - - - -
f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Add SYB-like utility function for performing stateful queries.
- - - - -
eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create function for retrieving free variables from given type.
- - - - -
a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fix compilation error caused by incorrect type signature.
- - - - -
8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Move `SetName` class definition to types module.
- - - - -
5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Hook type renamer with instance method HTML pretty-printer.
- - - - -
6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add some test cases for type renamer.
- - - - -
839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make specialized signatures refer to original signature declaration.
- - - - -
4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make specialized methods be nicely formatted again.
- - - - -
ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Attach source locations to the specialized class methods.
- - - - -
43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Extend instances test case to also test multi-name type signatures.
- - - - -
59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix tab-based indentation in instances test case.
- - - - -
c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Improve placement of instance methods expander button.
- - - - -
0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add new data type declaration to instance specialization test case. 
- - - - -
5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make type renamer first try single-letter names as  alternatives.
- - - - -
7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix type renamer bug with incorrect names being generated.
- - - - -
0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add some documentation and refactor type specialization module.
- - - - -
da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix another bug where type renamer was generating incorrect names.
- - - - -
cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Refactor type renamer to rebinding and pure renaming phases.
- - - - -
850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix unwitting compilation bug.
- - - - -
e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Integrate instance specification type into class instance definition.
- - - - -
825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Get rid of no longer neccessary instance specification type.
- - - - -
cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix declaration converter to use more appropriate mode for methods.
- - - - -
bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix bug with types not being specialized at all.
- - - - -
5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix bug where instance expander was opening wrong section.
- - - - -
6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix another type renamer bug where not all names were rebound.
- - - - -
5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix yet another renamer bug where some names were not unique.
- - - - -
8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Split instance subsection layout method to top-level declarations.
- - - - -
e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Rearrange layout of instance methods in generated documentation.
- - - - -
a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Get rid of no longer used layout method.
- - - - -
2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Attach section title to the instance methods block.
- - - - -
7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Add basic tests for associated types in instances test case.
- - - - -
db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Attach associated types information to instance header.
- - - - -
71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Make instance details section contain associated types information.
- - - - -
deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Improve look of rendered associated families in instance details.
- - - - -
839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Introduce alternative type for family declarations.
- - - - -
d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Make instance details record use new type for family declarations.
- - - - -
2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Split printer of type family header to separate functions.
- - - - -
c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Implement HTML renderer for pseudo-family declarations.
- - - - -
c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Apply type specializer to associated type family declarations. 
- - - - -
2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Create helper method for specializing type signatures.
- - - - -
475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Refactor specializer module to be independent from XHTML backend.
- - - - -
f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add some documentation for instance head specializer.
- - - - -
a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix bug with missing space in documentation for associated types.
- - - - -
50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix issue with incorrect instance details sections being expanded.
- - - - -
e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Accept tests affected by adding instance details section.
- - - - -
75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Make section identifier of instance details more GHC-independent.
- - - - -
add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Re-accept tests after applying deterministic section identifiers.
- - - - -
878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Make identifier generation also architecture-independent.
- - - - -
48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix issue with instance expander hijacking type hyperlink click.
- - - - -
47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Get rid of dreadful hashing function for generating identifiers.
- - - - -
956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Move `InstOrigin` type declaration to more appropriate module.
- - - - -
bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Accept tests affected by changes related to instance expander.
- - - - -
8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add examples with type operators to the instances test case.
- - - - -
64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add basic support for sugaring infix type operators.
- - - - -
747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00
Add support for sugaring built-in function syntax.
- - - - -
d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Remove default methods from Hoogle class output.
- - - - -
bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Add fixity declarations in Hoogle backend output.
- - - - -
90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Fix bug with incorrect fixities being generated in Hoogle backend.
- - - - -
48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Improve class type family declarations output in Hoogle backend.
- - - - -
661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Add missing default family equations in Hoogle output.
- - - - -
e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Improve formatting of class details output in Hoogle backend.
- - - - -
490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Fix weird-looking Hoogle output for familyless classes.
- - - - -
ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Create script file for new HTML test runner.
- - - - -
609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Set default behaviour if no arguments given.
- - - - -
dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add support for providing optional arguments for test runner.
- - - - -
d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Improve output of test runner error messages.
- - - - -
0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add support for executing Haddock process in test runner.
- - - - -
4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add GHC path to test runner configuration.
- - - - -
d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make GHC path a test runner command-line argument.
- - - - -
c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Extend test runner configuration with Haddock arguments.
- - - - -
fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Refactor test runner and create stub functions.
- - - - -
ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make test runner actually run Haddock executable.
- - - - -
391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Fix bug with test runner not producing any output files.
- - - - -
81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Setup skeleton of framework for running tests.
- - - - -
f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Fix bug with modules not being found in global search mode.
- - - - -
7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make Haddock standard output redirection be more configurable.
- - - - -
53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Incorporate old, ugly functions for comparing output files.
- - - - -
8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Refactor architecture of test runner output checking functions.
- - - - -
587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Implement actual diffing mechanism.
- - - - -
9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Improve code style to match popular guidelines.
- - - - -
14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make it possible to choose alternative diff tool.
- - - - -
5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Create stub methods for processing test output as XML documents.
- - - - -
7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Implement link-stripping logic as simple SYB transformation.
- - - - -
8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Incorporate link stripping to output diffing mechanism.
- - - - -
37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement footer-stripping logic.
- - - - -
9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Add missing dependencies in Cabal configuration file.
- - - - -
e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix issue with output being printed in incorrect order.
- - - - -
0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make it possible to run tests without generating diff.
- - - - -
76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Refactor HTML test suite boilerplate to external package.
- - - - -
af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create utilities for storing directory configuration.
- - - - -
d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Move IO-dependent config of HTML test suite to test package.
- - - - -
17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Enable all compiler warnings in Haddock test package configuration.
- - - - -
9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Move Haddock runner of HTML test suite to Haddock test package.
- - - - -
4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make Haddock test package more generic.
- - - - -
03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create convenience wrappers to simplify in test entry points.
- - - - -
27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adjust module visibility and items they export.
- - - - -
c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Remove no longer useful test option.
- - - - -
55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Change extension of test files used for diffing.
- - - - -
136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Refactor and simplify XHTML helper module of test package.
- - - - -
69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix typo in link stripper of HTML test suite runner.
- - - - -
0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create convenience script for running specific HTML tests.
- - - - -
489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement utility functions for conditional link stripping.
- - - - -
0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adapt `hypsrc-test` module to work with new testing framework.
- - - - -
927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement output accepting mechanism in test package.
- - - - -
8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create utility function for recursive obtaining directory contents.
- - - - -
cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make Haddock test package more generic.
- - - - -
019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix path handling in test runner.
- - - - -
399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make it possible to specify ignored files for test output.
- - - - -
41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adapt HTML test runner to use new ignoring functionality.
- - - - -
e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix bug with not all test output files being checked.
- - - - -
b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Specify ignored files for hyperlinker source test runner.
- - - - -
3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Copy test runner script for hyperlinked source case.
- - - - -
d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with test runner invoking Haddock in incorrect mode.
- - - - -
f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix path handling in test module loader.
- - - - -
10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Make test runner ignore test packages with no modules.
- - - - -
5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create test runner entry points for LaTeX test suite.
- - - - -
58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with unnecessary checking old test output.
- - - - -
c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Re-implement test acceptance functionality.
- - - - -
13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix warning about no longer needed definition.
- - - - -
958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Adapt Cabal configuration to execute LaTeX suite with new runner.
- - - - -
550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Setup test suite for Hoogle backend.
- - - - -
3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Make Hoogle backend create output directory if needed.
- - - - -
eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Add appropriate .gitignore entry and configure Hoogle test suite.
- - - - -
a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with test runner failing when run on multiple test packages.
- - - - -
bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create simple test cases for Hoogle backend.
- - - - -
6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create helper function for conversion between XML and XHTML.
- - - - -
cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Refactor existing code to use XHTML printer instead of XML one.
- - - - -
e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Improve portability of test runner scripts.
- - - - -
9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00
Remove redundant import statement.
- - - - -
55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00
Fix bug with accepting to non-existing directory.
- - - - -
00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00
Accept output for Hoogle and LaTeX backends.
- - - - -
29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00
Get rid of obsolete testing utilities.
- - - - -
bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00
Update sandbox setup guide to work with Haddock test package.
- - - - -
cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00
Make Travis aware of Haddock test package.
- - - - -
74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00
Fix test suite failure when used with Stack.
- - - - -
18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00
Add sample Stack setup to the hacking guide.

- - - - -
22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00
Fix Markdown formatting of README file.
- - - - -
b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00
Setup Haddock executable path in Travis configuration.
- - - - -
5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00
account for changes to ipClass

- - - - -
f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00
Merge pull request haskell/haddock#443 from bgamari/ghc-head

account for changes to ipClass
- - - - -
a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00
Follow changes from haskell/haddock#6018

- - - - -
2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00
React to refactoring CoAxiom branch lists.

- - - - -
ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00
Track msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00
Create Process: removed PhaseFailed

- - - - -
7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00
Generate docs for orphan instances

- - - - -
32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00
Have source links for orphan instances

- - - - -
c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00
Print orphan instances header only if required

- - - - -
ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00
Add orphan instances link to contents box

- - - - -
d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00
Fix orphan instance collapsing

- - - - -
25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00
Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive

Remove PhaseFailed
- - - - -
1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00
s/PackageKey/UnitId/g and s/packageKey/unitId/g

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00
Roughly fix up haddock for DuplicateRecordFields changes

This compiles, but will probably need more work to produce good
documentation when the DuplicateRecordFields extension is used.

- - - - -
60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00
Track wip/spj-wildcard-refactor on main repo

- - - - -
4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00
Track change to PatSyn.patSynSig

- - - - -
25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00
Follow changes to HsTYpe

Not yet complete (but on a wip/ branch)

- - - - -
693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00
Account for Typeable changes

The treatment of type families changed.

- - - - -
cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00
Work on updating Haddock to wip/spj-wildard-recactor

Still incomplete

- - - - -
712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00
Relax upper bound on `base` to allow base-4.9

- - - - -
0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00
More adaption to wildcard-refactor

- - - - -
0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00
Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00
Matching change GHC haskell/haddock#11017 BooleanFormula located

- - - - -
42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00
Change for IEThingWith

- - - - -
f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00
Eliminate support for deprecated GADT syntax

Follows from GHC D1460.

- - - - -
e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00
Merge with origin/head

- - - - -
ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00
Undo msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00
Wibbles to Haddock

- - - - -
2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00
Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor

- - - - -
695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00
Update to match GHC wip/T11019

- - - - -
bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00
merge with origin/ghc-head

- - - - -
3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00
Wibble

- - - - -
e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00
Canonicalise Monad instances

- - - - -
a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00
Matching changes for haskell/haddock#11028

- - - - -
cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00
Placeholder for record style GADT declaration

A GADT Declaration is now presented as

    CmmCondBranch :: {..} -> CmmNode O C
        cml_pred :: CmmExpr
        cml_true, cml_false :: !Label
        cml_likely :: Maybe Bool
for

    CmmCondBranch :: {              -- conditional branch
        cml_pred :: CmmExpr,
        cml_true, cml_false :: ULabel,
        cml_likely :: Maybe Bool    -- likely result of the conditional,
                                    -- if known
    } -> CmmNode O C

- - - - -
95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00
Update for type=kinds

- - - - -
cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00
Bump versions for ghc-7.11

- - - - -
4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00
Eliminate instanceHead' in favour of GHC's instanceSig

This is made possible by the elimination of "silent superclass
parameters" in GHC

- - - - -
13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints

- - - - -
098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track changes in HsSyn for quasi-quotes

- - - - -
716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track change in API of TyCon

- - - - -
77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00
Track API changes to support empty closed type familes

- - - - -
f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track the new location of setRdrNameSpace

- - - - -
ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00
ApiAnnotations : strings in warnings do not return SourceText

The strings used in a WARNING pragma are captured via

strings :: { Located ([AddAnn],[Located FastString]) }
    : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) }
..

The STRING token has a method getSTRINGs that returns the original
source text for a string.

A warning of the form

{-# WARNING Logic
          , mkSolver
          , mkSimpleSolver
          , mkSolverForLogic
          , solverSetParams
          , solverPush
          , solverPop
          , solverReset
          , solverGetNumScopes
          , solverAssertCnstr
          , solverAssertAndTrack
          , solverCheck
          , solverCheckAndGetModel
          , solverGetReasonUnknown
          "New Z3 API support is still incomplete and fragile: \
          \you may experience segmentation faults!"
  #-}

returns the concatenated warning string rather than the original source.

- - - - -
a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00
Update after wild card renaming refactoring in D613

Summary:
* Move `Post*` type instances to `Haddock.Types` as other modules than
  `Haddock.Interface.Rename` will rely on these type instances.
* Update after wild card renaming refactoring in D613.

Reviewers: simonpj, austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D954

GHC Trac Issues: haskell/haddock#10098

- - - - -
25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
StrictData: print correct strictness marks

- - - - -
6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
StrictData: changes in HsBang type

- - - - -
ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00
Replace (SourceText,FastString) with WithSourceText data type

Phab:D907 introduced SourceText for a number of data types, by replacing
FastString with (SourceText,FastString). Since this has an Outputable
instance, no warnings are generated when ppr is called on it, but
unexpected output is generated. See Phab:D1096 for an example of this.

Replace the (SourceText,FastString) tuples with a new data type

data WithSourceText = WithSourceText SourceText FastString

Trac ticket: haskell/haddock#10692

- - - - -
abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
HsBang is split into HsSrcBang and HsImplBang

With recent changes in GHC handling of strictness annotations in Haddock
is simplified.

- - - - -
3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00
Follow changes in GHC build system

- - - - -
6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00
account for changes to ipClass

- - - - -
ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00
Follow changes from haskell/haddock#6018

- - - - -
ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00
React to refactoring CoAxiom branch lists.

- - - - -
d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00
Track msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00
Create Process: removed PhaseFailed

- - - - -
3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00
s/PackageKey/UnitId/g and s/packageKey/unitId/g

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00
Roughly fix up haddock for DuplicateRecordFields changes

This compiles, but will probably need more work to produce good
documentation when the DuplicateRecordFields extension is used.

- - - - -
79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00
Track wip/spj-wildcard-refactor on main repo

- - - - -
959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00
Follow changes to HsTYpe

Not yet complete (but on a wip/ branch)

- - - - -
e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00
Work on updating Haddock to wip/spj-wildard-recactor

Still incomplete

- - - - -
aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00
More adaption to wildcard-refactor

- - - - -
8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00
Track change to PatSyn.patSynSig

- - - - -
cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00
Account for Typeable changes

The treatment of type families changed.

- - - - -
63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00
Relax upper bound on `base` to allow base-4.9

- - - - -
a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00
Matching change GHC haskell/haddock#11017 BooleanFormula located

- - - - -
2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00
Change for IEThingWith

- - - - -
593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00
Eliminate support for deprecated GADT syntax

Follows from GHC D1460.

- - - - -
b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00
Undo msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00
Update to match GHC wip/T11019

- - - - -
14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00
Wibble

- - - - -
10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00
Canonicalise Monad instances

- - - - -
ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00
Matching changes for haskell/haddock#11028

- - - - -
3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00
Placeholder for record style GADT declaration

A GADT Declaration is now presented as

    CmmCondBranch :: {..} -> CmmNode O C
        cml_pred :: CmmExpr
        cml_true, cml_false :: !Label
        cml_likely :: Maybe Bool
for

    CmmCondBranch :: {              -- conditional branch
        cml_pred :: CmmExpr,
        cml_true, cml_false :: ULabel,
        cml_likely :: Maybe Bool    -- likely result of the conditional,
                                    -- if known
    } -> CmmNode O C

- - - - -
6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00
Update for type=kinds

- - - - -
193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00
Changes to compile with 8.0

- - - - -
add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00
Warnings

- - - - -
223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00
Update for D1200

- - - - -
d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00
Types: Add Outputable[Bndr] DocName instances

- - - - -
62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00
Fix fallout from wildcards refactoring

The wildcard refactoring was introduced a new type of signature,
`ClassOpSig`, which is carried by typeclasses. The original patch
adapting Haddock for this change missed a few places where this
constructor needed to be handled, resulting in no class methods
in documentation produced by Haddock.

Additionally, this moves and renames the `isVanillaLSig` helper from
GHC's HsBinds module into GhcUtils, since it is only used by Haddock.

- - - - -
ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00
Update for D1200

- - - - -
cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00
Types: Add Outputable[Bndr] DocName instances

- - - - -
d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00
Fix fallout from wildcards refactoring

The wildcard refactoring was introduced a new type of signature,
`ClassOpSig`, which is carried by typeclasses. The original patch
adapting Haddock for this change missed a few places where this
constructor needed to be handled, resulting in no class methods
in documentation produced by Haddock.

Additionally, this moves and renames the `isVanillaLSig` helper from
GHC's HsBinds module into GhcUtils, since it is only used by Haddock.

- - - - -
ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00
Fix Hyperlinker

GHC.con_names is now GHC.getConNames

- - - - -
a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00
Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head

- - - - -
f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00
test: Compatibility with Cabal 1.23

- - - - -
88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00
Merge remote-tracking branch 'phadej/orphans' into ghc-head

- - - - -
4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00
Add html-test for orphan instances output

- - - - -
87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00
Update for GHC trac#11258

Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc

- - - - -
6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00
Merge pull request haskell/haddock#1 from haskell/ghc-head

Ghc head
- - - - -
229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00
Handle inline math with mathjax.

- - - - -
57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00
Fix the documentation for haddock itself.

Change notation and add support for inline math.

Allow newlines in display math.

Add a command line option for the mathjax url (you might want to use a
locally installed version).

Rebase tests because of extra url and version change.

Respond to (some of the) comments.

Fix warnings in InterfaceFile.hs

- - - - -
0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00
Fix-up left-over assumptions of GHC 7.12 into GHC 8.0

- - - - -
c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00
Follow removal of NamedWildCard from HsType

- - - - -
da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00
html-test/Operators: Clear up ambiguous types

For reasons that aren't entirely clear a class with ambiguous types was
accepted by GHC <8.0. I've added a functional dependency to clear up
this ambiguity.

- - - - -
541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00
hoogle-test/AssocTypes: Allow AmbiguousTypes

GHC 8.0 complains otherwise

- - - - -
25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00
OrphanInstances: Accept test output

- - - - -
841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00
Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head

- - - - -
358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00
Add missing import

- - - - -
a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00
travis: Use Travis containers

- - - - -
85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00
tweak version bounds for GHC-8.1

- - - - -
672a5f75 by randen at 2016-01-01T23:45:25-08:00
The Haddock part for fully gcc-like response files

" driver/Main.hs
  * Moved the response file handling into ResponseFile.hs,
    updating import section as appropriate.
* driver/ResponseFile.hs
  * New file. In anticipation that maybe some day this could
    be provided by another library, and to make it possible
    to unit test, this functionality is pulled out of the
    Main.hs module, and expanded to support the style/format
    of response files which gcc uses.
  * The specification for the format of response files which
    gcc generates and consumes, seems to be best derived from
    the gcc code itself (libiberty/argv.c), so that is what
    has been done here.
  * This is intended to fix haskell/haddock#379
* driver-test/Main.hs
  * New file for testing code in the driver source tree
* driver-test/ResponseFileSpec.hs
  * Tests, adapted/adopted from the same gcc code where the
    escaping/unescaping is from, in the hspec style of unit
    tests
* haddock.cabal
  * Add the driver-test test-suite.  Introduces a new library
    dependency (upon hspec) for the haddock driver target in
    the haddock.cabal file, but practically, this should not
    be a problem as the haddock-api tests already depend on
    hspec.

- - - - -
498781df by Ben Gamari at 2016-01-06T13:41:04+01:00
Version bumps and changelog

- - - - -
8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00
Merge remote-tracking branch 'randen/bug468'

- - - - -
fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00
Add ResponseFile to OtherModules

- - - - -
2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00
Merge branch 'master' into ghc-head

- - - - -
913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00
deal with un-wiring of IP class

- - - - -
c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00
Update to match wip/T11430 in GHC

- - - - -
3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00
Update to match wip/T11430 in GHC

- - - - -
c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00
Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head

- - - - -
9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00
deal with un-wiring of IP class

(cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f)

- - - - -
b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00
Make sure --mathjax affects all written HTML files

This fixes haskell/haddock#475.

- - - - -
af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00
Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473)

- - - - -
b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00
Merge pull request haskell/haddock#477 from haskell/issue-475

Make sure --mathjax affects all written HTML files
- - - - -
adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00
Merge branch 'master' into ghc-head

- - - - -
d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00
doc: Switch to Sphinx

- - - - -
acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00
Document --use-unicode flag

- - - - -
c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00
Fix GHC and haddock-library dependency bounds

- - - - -
8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00
testsuite: Rework handling of output sanitization

Previously un-cleaned artifacts were kept as reference output, making
it difficult to tell what has changed and causing spurious changes in
the version control history. Here we rework this, cleaning the output
during acceptance. To accomplish this it was necessary to move to strict
I/O to ensure the reference handle was closed before accept attempts to
open the reference file.

- - - - -
c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00
test: Compare on dump

For reasons I don't understand the Xml representations differ despite
their textual representations being identical.

- - - - -
1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00
html-test: Accept test output

- - - - -
eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00
hypsrc-test: Accept test output

And fix impredicative Polymorphism testcase.

- - - - -
d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00
Merge branch 'fix-up-testsuite'

- - - - -
206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00
Move the permalinks to "#" on the right side

Since pull request haskell/haddock#407, the identifiers have been permalinked to
themselves, but this makes it difficult to copy the identifier by
double-clicking.  To work around this usability problem, the permalinks
are now placed on the far right adjacent to "Source", indicated by "#".

Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete).

- - - - -
6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00
Update tests for previous commit

- - - - -
effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00
Merge branch 'anchors-redux'

- - - - -
9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00
Use -fprint-unicode-syntax when --use-unicode is enabled

This allows GHC to render `*` as its Unicode representation, among other
things.

- - - - -
28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00
Merge pull request haskell/haddock#480 from bgamari/sphinx

Move documentation to ReStructuredText
- - - - -
222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00
Collapse type/data family instances by default

- - - - -
a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00
Ensure expanded family instances render correctly

- - - - -
7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Various cleanups

- - - - -
79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Show kind signatures for type family variables

Addresses GHC haskell/haddock#11588.

- - - - -
b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Show 'where ...' after closed type family

Seems like we should ideally show the actual equations as well but that
seems like it would be a fair amount of work

- - - - -
cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00
Merge pull request haskell/haddock#483 from bgamari/T11588

Fix GHC haskell/haddock#11588

This fixes GHC haskell/haddock#11588:
  * Show where ... after closed type families
  * Show kind signatures on type family type variables


- - - - -
256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00
Follow-on changes to support RuntimeRep

- - - - -
2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00
Remove unused functions

- - - - -
eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00
Follow-on changes to support RuntimeRep

(cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c)

- - - - -
8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00
Changes due to fix for GHC#11648.

- - - - -
0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00
Changes due to fix for GHC#11648.

(cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1)

- - - - -
ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00
Fix printing of pattern synonym types

Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this
function will be removed from GHC. Instead, we use the function `patSynSig`
and build the `HsDecl` manually. This also fixes the printing of the two
contexts and the quantified type variables in a pattern synonym type.

Reviewers: goldfire, bgamari, mpickering

Differential Revision: https://phabricator.haskell.org/D2048

- - - - -
d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00
Fix printing of pattern synonym types

Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this
function will be removed from GHC. Instead, we use the function `patSynSig`
and build the `HsDecl` manually. This also fixes the printing of the two
contexts and the quantified type variables in a pattern synonym type.

Reviewers: goldfire, bgamari, mpickering

Differential Revision: https://phabricator.haskell.org/D2048

(cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb)

- - - - -
236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00
doc: Fix option references

(cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197)

- - - - -
692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00
doc: Only install if BUILD_SPHINX_HTML==YES

Fixes GHC haskell/haddock#11818.

- - - - -
79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00
doc: Only install if BUILD_SPHINX_HTML==YES

Fixes GHC haskell/haddock#11818.

(cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5)

- - - - -
3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00
doc: Fix option references

(cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197)

- - - - -
264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00
Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head

Collapse type/data family instances by default
- - - - -
478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00
Merge pull request haskell/haddock#489 from mpickering/unused-functions

Remove some unused functions
- - - - -
c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00
Collapse type/data family instances by default

(cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088)

- - - - -
31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00
Ensure expanded family instances render correctly

(cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103)

- - - - -
03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00
Remove unused functions

(cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0)

- - - - -
ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00
ghc: Install files for needed --hyperlinked-source

- - - - -
0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00
ghc: Install files for needed --hyperlinked-source

(cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6)

- - - - -
4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00
Track change to HsGroup

This relates to a big GHC patch for Trac haskell/haddock#11348

- - - - -
1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00
doc: At long last fix ghc.mk

The variable reference was incorrectly escaped, meaning that Sphinx
documentation was never installed.

- - - - -
0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00
doc: At long last fix ghc.mk

The variable reference was incorrectly escaped, meaning that Sphinx
documentation was never installed.

(cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9)

- - - - -
af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00
Render Haddocks for derived instances

Currently, one can document top-level instance declarations, but derived
instances (both those in `deriving` clauses and standalone `deriving`
instances) do not enjoy the same privilege. This makes the necessary
changes to the Haddock API to enable rendering Haddock comments for
derived instances.

This is part of a fix for Trac haskell/haddock#11768.

- - - - -
76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00
haddock-test: A bit of refactoring for debuggability

- - - - -
7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00
Create: Mark a comment as TODO

- - - - -
2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00
html-test: Update reference output

- - - - -
bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00
hypsrc-test: Fix reference file path in cabal file

It appears the haddock insists on prefixing --hyperlinked-sourcer output
with directory which the source appeared in.

- - - - -
c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00
doc: Update extra-source-files in Cabal file

- - - - -
41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00
Bump versions

- - - - -
ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00
Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head

- - - - -
a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00
doc: Add clean targets

- - - - -
f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00
doc: Add html as an all-target for ghc

Otherwise the html documentation won't be installed for binary-dist.

- - - - -
388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00
Update CHANGES

- - - - -
bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00
Version bump

- - - - -
c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00
Revert "Version bump"

This bump was a bit premature.

This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8.

- - - - -
7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00
doc: Fix GHC clean rule

Apparently GHC's build system doesn't permit wildcards in clean paths.

- - - - -
5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00
Version bump to 2.17.2

- - - - -
b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00
doc: Use `$(MAKE)` instead of `make`

This is necessary to ensure we use gmake.

- - - - -
8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00
Fix haskell/haddock#303. Hide footer when printing

The "Produced by Haddock" footer was overlapping the page's body when printing.
This patch hides the footer with a css media rule.

- - - - -
b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00
Fix haskell/haddock#280. Parsing of module header

The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines

- - - - -
ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00
doc: Vendorize alabaster Sphinx theme

Alabaster is now the default sphinx theme and is a significant
improvement over the previous default that it's worthproviding it when
unavailable (e.g. Sphinx <1.3).

- - - - -
c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00
Merge pull request haskell/haddock#502 from Helkafen/master

Fix haskell/haddock#303. Hide footer when printing
- - - - -
33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00
Revert "doc: Vendorize alabaster Sphinx theme"

This ended up causes far too many issues to be worthwhile. We'll just
have to live with inconsistent haddock documentation.

This reverts commit cec21957001143794e71bcd9420283df18e7de40.

- - - - -
93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00
cabal: Fix README path

- - - - -
c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00
doc: Use whichever theme sphinx deems appropriate

- - - - -
857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00
Create: Remove redundant imports

- - - - -
132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00
Create: Better debug output

For tracking down haskell/haddock#505

- - - - -
2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00
Don't consider default class ops when looking for decls

When we are looking for an operation within a class we don't care about
`default`-type declarations. This was the cause of haskell/haddock#505.

- - - - -
4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00
UnfelpfulSpan line number omitted

Kind of resolves https://github.com/haskell/haddock/issues/508

- - - - -
a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00
Change Hyperlinked lexer to know about DataKinds ticks

- - - - -
f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00
Make parser state a newtype

Previously, it was `data` wrapping a `Maybe`, which seems a bit
silly. Obviously, this can be changed back if anyone wants to add
more fields some day.

- - - - -
05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00
remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274)

Frames are a bit broken, ignored by Hackage, and considered obsolete in general.
This patch disables frames generation. The mini_*.html files are still used in the synopsis.

- - - - -
b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00
Merge pull request haskell/haddock#507 from bgamari/T505

Fix haskell/haddock#505
- - - - -
ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00
Update CHANGES

- - - - -
eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00
Merge pull request haskell/haddock#514 from Helkafen/frames

remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274)
- - - - -
0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00
Remove misplaced haddock comment

- - - - -
a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00
Merge pull request haskell/haddock#515 from alexbiehl/master

Remove misplaced haddock comment
- - - - -
9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00
Merge pull request haskell/haddock#513 from treeowl/newtype-since

Make parser state a newtype
- - - - -
74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00
Merge pull request haskell/haddock#504 from Helkafen/issue-280

Fix haskell/haddock#280. Parsing of module header
- - - - -
37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00
Matching changes for haskell/haddock#12105

- - - - -
7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00
Version bumps (2.17.3, 1.4.2)

- - - - -
85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00
Merge pull request haskell/haddock#521 from Helkafen/master

Version bumps (2.17.3, 1.4.2)
- - - - -
e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00
publish haddock-test library

- - - - -
4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00
Merge pull request haskell/haddock#512 from phadej/oleg-fixes

Fixes for haskell/haddock#508 and haskell/haddock#510
- - - - -
ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00
Documentation for LaTeX markup.

- - - - -
697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00
Fix spelling mistake.

- - - - -
246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00
Camel case MathJax.

- - - - -
4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00
Fix math typo and add link.

- - - - -
f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00
Follow changes to LHsSigWcType

- - - - -
0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00
Follow GHC re-adding FunTy

- - - - -
401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00
Merge pull request haskell/haddock#525 from idontgetoutmuch/master

Documentation for LaTeX markup.
- - - - -
92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00
Merge pull request haskell/haddock#522 from Helkafen/master

publish haddock-test library
- - - - -
0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00
Copyright holders shown on several lines. Fix haskell/haddock#279

- - - - -
65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00
ocean: Ensure that synopsis fully covers other content

Previously MathJax content was being rendered on top of the synopsis due
to ambiguous z-ordering. Here we explicitly give the synopsis block a
higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531.

- - - - -
68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00
Merge pull request haskell/haddock#534 from bgamari/T531

ocean: Ensure that synopsis fully covers other content
- - - - -
fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00
Merge pull request haskell/haddock#533 from Helkafen/master

Copyright holders shown on several lines. Fix haskell/haddock#279
- - - - -
6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00
do not create empty src directory

Fix haskell/haddock#536.

- - - - -
1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00
Merge pull request haskell/haddock#537 from Helkafen/master

do not create empty src directory
- - - - -
966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00
Add $ as a special character

If this character is not escaped, documentation built with Haddock
2.17.2 will fail.  This was not an issue with 2.16 series, which
causes builds to fail and there is nothing in the docs or error
message giving a clue about why builds that used to succeed now
don't.

- - - - -
324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00
GhcUtils: Changes for multi-pattern signatures

- - - - -
d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00
Add support for unboxed sums

- - - - -
29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00
Disable NFData instances for GHC types when GHC >= 8.2

- - - - -
702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00
Disable NFData instances for GHC types when GHC >= 8.0.2

(cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a)

- - - - -
f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00
ghc.mk: Don't attempt to install html/frames.html

The frames business has been removed.

- - - - -
9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00
Haddock.Types: More precise version guard

This allows haddock to be built with GHC 8.0.2 pre-releases.

- - - - -
f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00
Merge pull request haskell/haddock#538 from massysett/master

Add $ as a special character
- - - - -
16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00
Fix rendering of class methods for Eq and Ord

See haskell/haddock#549 and GHC issue haskell/haddock#12519

- - - - -
7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00
Fix rendering of class methods for Eq and Ord

See haskell/haddock#549 and GHC issue haskell/haddock#12519

(cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b)

- - - - -
33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00
Haddock changes for T10598

See https://ghc.haskell.org/trac/ghc/ticket/10598

- - - - -
1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00
Update for refactoring of NameCache

- - - - -
1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00
Bump upper bound on base

- - - - -
9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00
Match changes in GHC wip/T3384 branch

- - - - -
ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00
haddock-api: Don't use stdcall calling convention on 64-bit Windows

See GHC haskell/haddock#12890.

- - - - -
04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00
Matching changes for GHC wip/T12942

- - - - -
e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00
Bump base upper bound

- - - - -
3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00
HsIParamTy now has a Located name

- - - - -
7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00
Prevent GHC API from doing optimization passes.

- - - - -
d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00
Upstream changes re levity polymorphism

- - - - -
40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00
Changes to match haskell/haddock#13163 in GHC

- - - - -
504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00
Kill remaining static flags

- - - - -
49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00
Adding MDoc to exports of Documentation.Haddock

- - - - -
1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00
Also exposing toInstalledIface

- - - - -
53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00
Bump for GHC 8.3

- - - - -
c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00
Bump for GHC 8.2

- - - - -
4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00
Merge branch 'ghc-head'

- - - - -
e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00
Update Haddock w.r.t. new HsImplicitBndrs

- - - - -
6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00
Update Haddock w.r.t. new HsImplicitBndrs

- - - - -
eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00
Adapt to EnumSet

- - - - -
017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Correctly handle Backpack identity/semantic modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Add a field marking if interface is a signature or not.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Render signature module tree separately from modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Documentation.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
More docs.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00
TODO on moduleExports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Better Backpack support with signature merging.

When we merge signatures, we gain exports that don't
necessarily have a source-level declaration corresponding
to them.  This meant Haddock dropped them.

There are two big limitations:

* If there's no export list, we won't report inherited
  signatures.

* If the type has a subordinate, the current hiDecl
  implementation doesn't reconstitute them.

These are probably worth fixing eventually, but this gets
us to minimum viable functionality.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Fix haddock-test to work with latest version of Cabal.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00
Annotate signature docs with (signature)

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00
Render help documentation link next to (signature) in title.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00
Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD

- - - - -
0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00
haddock-api: Bump bound on GHC

- - - - -
65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00
Merge pull request haskell/haddock#581 from JustusAdam/master

Adding more exports to Documentation.Haddock
- - - - -
37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00
Merge pull request haskell/haddock#568 from awson/ghc-head

Prevent GHC API from doing optimization passes.
- - - - -
1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00
Print any user-supplied kind signatures on type parameters.

This applies to type parameters on data, newtype, type, and class
declarations, and also to forall-bound type vars in type signatures.

- - - - -
1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00
Update test suite to expect kind annotations on type parameters.

- - - - -
a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00
Include travis build indication badge
- - - - -
8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00
haddock-api: Bump bound on GHC

- - - - -
4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Correctly handle Backpack identity/semantic modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737)

- - - - -
a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Add a field marking if interface is a signature or not.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858)

- - - - -
caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Render signature module tree separately from modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0)

- - - - -
49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Documentation.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc)

- - - - -
4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00
More docs.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a)

- - - - -
74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
TODO on moduleExports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e)

- - - - -
a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Better Backpack support with signature merging.

When we merge signatures, we gain exports that don't
necessarily have a source-level declaration corresponding
to them.  This meant Haddock dropped them.

There are two big limitations:

* If there's no export list, we won't report inherited
  signatures.

* If the type has a subordinate, the current hiDecl
  implementation doesn't reconstitute them.

These are probably worth fixing eventually, but this gets
us to minimum viable functionality.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3)

- - - - -
d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Fix haddock-test to work with latest version of Cabal.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267)

- - - - -
ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Annotate signature docs with (signature)

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1)

- - - - -
2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Render help documentation link next to (signature) in title.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe)

- - - - -
37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00
Update MathJax URL

MathJax is shutting down their CDN:
https://www.mathjax.org/cdn-shutting-down/

They recommend migrating to cdnjs.

- - - - -
e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00
Add highlight for :target to ocean.css

- - - - -
4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00
Allow base-4.10 for haddock-test

- - - - -
44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00
cabal.project for haddock-api, haddock-library and haddock-test

- - - - -
935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00
Move dist scripts to scripts/

- - - - -
128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00
Add haddock to cabal.project

- - - - -
cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00
Read files for hyperlinker eagerly

This also exposes Documentation.Haddock.Utf8

- - - - -
152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00
Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create

- - - - -
501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00
Prevent GHC API from doing optimization passes.

- - - - -
c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00
Add @alexbiehl as maintaner

- - - - -
76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00
Disable doctest with ghc-8.3

Currently doctest doesn't support ghc-head
- - - - -
46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00
Render (signature) only if it actually is a signature!

I forgot a conditional, oops!

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00
Travis: Use ghc-8.2.1 on master

- - - - -
966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00
Travis: Verbose cabal output

cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377
- - - - -
36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00
Use travis_retry for cabal invocations
- - - - -
b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00
Use new MathJax URL in html-test

18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL
but didn't update the tests.

- - - - -
ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00
Expand signatures for class declarations

- - - - -
e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00
Hoogle: Correctly print classes with associated data types

- - - - -
3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00
Render (signature) only if it actually is a signature!

I forgot a conditional, oops!

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9)

- - - - -
6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00
`html-test --accept` deltas to reference samples

- - - - -
7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00
Remove anything related to obsolete frames mode

- - - - -
b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00
Cherry-picked remaining commits from haddock-2.17.4-release (#603)

* Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3

* Set version bounds for haddock-library

NB: This allows GHC 8.2.1's base

* Set version bounds for haddock & haddock-api

The version bounds support GHC 8.2

* Merge (temporary) v2.17.3 branch into v2.17

This allows us to delete the v2.17.3 branch

* Fixup changelog

* Pin down haddock-api to a single version

as otherwise `haddock`'s package version has no proper meaning

* fix source-repo spec for haddock-api

- - - - -
4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00
Update changelog to reflect news in HEAD

- - - - -
eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00
Markdownify changelog

- - - - -
5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00
Bump to 2.18.0 (#605)


- - - - -
a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00
Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0

- - - - -
ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00
Improve error message

- - - - -
2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00
Correctly remember collapsed sections (#608)

Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed.
- - - - -
f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00
Lazily decode docMap and argMap (#610)

These are only used in case of a doc reexport so most of the time
decoding these is wasted work.
- - - - -
2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00
Fix Binary instance for InstalledInterface (#611)

(#610) introduced lazy decoding for docs from InstalledInterface but
forgot to remove the original calls to get and put_
- - - - -
6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00
Improve documenation of Haddock markup (#614)

* Improve documentation of Haddock markup.

- document that Haddock supports inferring types top-level functions
  with without type signatures, but also explain why using this
  feature is discouraged. Looks like this feature has been around
  since version 2.0.0.0 in 2008!

- rework the "Module description" section:

  - move the general discussion of field formatting to the section
    intro and add examples illustrating the prose for multiline
    fields.

  - mention that newlines are preserved in some multiline fields, but
    not in others (I also noticed that commas in the `Copyright` field
    are not preserved; I'll look into this bug later).

  - add a subsection for the module description fields documentation,
    and put the field keywords in code formatting (double back ticks)
    instead of double quotes, to be consistent with the typesetting of
    keywords in other parts of the documentation.

  - mention that "Named chunks" are not supported in the long-form
    "Module description" documentation.

- fix formatting of keywords in the "Module attributes"
  section. Perhaps these errors were left over from an automatic
  translation to ReST from some other format as part of the transition
  to using Sphinx for Haddock documentation? Also, add a missing
  reference here; it just said "See ?"!

- update footnote about special treatment for re-exporting partially
  imported modules not being implemented. In my tests it's not
  implemented at all -- I tried re-exporting both `import B
  hiding (f)` and `import B (a, b)` style partial imports, and in both
  cases got the same result as with full imports `import B`: I only
  get a module reference.

* Rework the `Controlling the documentation structure` section.

My main goal was to better explain how to use Haddock without an
export list, since that's my most common use case, but I hope I
improved the section overall:

- remove the incomplete `Omitting the export list` section and fold it
  into the other sections. In particular, summarize the differences
  between using and not using an export list -- i.e. control over what
  and in what order is documented -- in the section lead.

- add "realistic" examples that use the structure markup, both with
  and without an export list. I wanted a realistic example here to
  capture how it can be useful to explain the relationship between a
  group of functions in a section, in addition to documenting their
  individual APIs.

- make it clear that you can associate documentation chunks with
  documentation sections when you aren't using an export list, and
  that doing it in the most obvious way -- i.e. with `-- |`, as you
  can in the export list -- doesn't work without an export list. It
  took me a while to figure this out the first time, since the docs
  didn't explain it at all before.

- add a "no export list" example to the section header section.

- add more cross references.

* Add examples of gotchas for markup in `@...@`.

I'm not sure this will help anyone, since I think most people first
learn about `@...@` by reading other people's Haddocks, but I've
documented the mistakes which I've made and then gotten confused by.

* Use consistent Capitalization of Titles.

Some titles were in usual title caps, and others only had the first
word capitalized. I chose making them all use title caps because that
seems to make the cross references look better.

- - - - -
d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00
Haddock: Fix broken lazy IO in prologue reading (#615)

We previously used withFile in conjunction with hGetContents. The list returned
by the latter wasn't completely forced by the time we left the withFile block,
meaning that we would try to read from a closed handle.
- - - - -
93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00
Haddock: Fix broken lazy IO in prologue reading (#615)

We previously used withFile in conjunction with hGetContents. The list returned
by the latter wasn't completely forced by the time we left the withFile block,
meaning that we would try to read from a closed handle.
- - - - -
5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00
Consequently use inClass and notInClass in haddock-library (#617)

These allow attoparsec to do some clever lookup optimization
- - - - -
77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00
Don't enable compilation for template haskell (#624)

This is no longer necessary after
ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa
- - - - -
5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00
Improve Syb code (#621)

Specialize.hs and Ast.hs are modified to have their Syb code not recurse into
Name or Id in HsSyn types.

Specialize.hs is refactored to have fewer calls to Syb functions.

Syb.hs has some foldl calls replaced with foldl' calls.

There is still a lot of performance on the floor of Ast.hs. The RenamedSource
is traversed many times, and lookupBySpan is very inefficient. everywhereBut and
lookupBySpan dominate the runtime whenever --hyperlinked-source is passed.
- - - - -
3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00
Clear fixme comment (#625)


- - - - -
2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00
Make haddock-library and haddock-api warning free (#626)


- - - - -
bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00
Include `driver-test/*.hs` sdist (#630)

This lead to haskell/haddock#629.
- - - - -
184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00
Disable pattern match warnings (#628)

This disables the pattern match checker which can be very expensive in some
cases.

The disabled warnings include:
* Opt_WarnIncompletePatterns
* Opt_WarnIncompleteUniPatterns
* Opt_WarnIncompletePatternsRecUpd
* Opt_WarnOverlappingPatterns
- - - - -
0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00
Allow user defined signatures for pattern synonyms (#631)


- - - - -
7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00
Use NameSet for isExported check (#632)


- - - - -
d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00
Match new AST as per GHC wip/new-tree-one-param

See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow

- - - - -
da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00
Rename extension index tags

- - - - -
538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00
Haddock support for bundled pattern synonyms (#627)

* Haddock support for bundled pattern synonyms

* Add fixities to bundled pattern synonyms

* Add bundled pattern synonyms to the synopsis

* Store bundled pattern fixities in expItemFixities

* Add test for bundled pattern synonyms

* Stop threading fixities

* Include bundled pattern synonyms for re-exported data types

Sadly, fixity information isn't found for re-exported data types

* Support for pattern synonyms

* Modify tests after haskell/haddock#631

* Test some reexport variations

* Also lookup bundled pattern synonyms from `InstalledInterface`s

* Check isExported for bundled pattern synonyms

* Pattern synonym is exported check

* Always look for pattern synonyms in the current module

Another overlooked cornercase

* Account for types named twice in export lists

Also introduce a fast function for nubbing on a `Name` and use it
throughout the code base.

* correct fixities for reexported pattern synonyms

* Fuse concatMap and map

* Remove obsolete import

* Add pattern synonyms to visible exports

* Fix test

* Remove corner case

- - - - -
a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00
Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636)

There is some performance improvement.

GHC compiler:
| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 56057108648     | 41.0
| after   | 51592019560     | 35.1

base:
| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 25174011784     | 14.6
| after   | 23712637272     | 13.1

Cabal:

| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 18754966920     | 12.6
| after   | 18198208864     | 11.6
- - - - -
5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00
Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639)

* Use new function getNameToInstancesIndex instead of tcRnGetInfo

There is some significant performance improvement in the ghc testsuite.

haddock.base: -23.3%
haddock.Cabal: -16.7%
haddock.compiler: -19.8%

* Remove unused imports

- - - - -
b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00
Lookup fixities for reexports without subordinates (#642)

So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-).

The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities.
- - - - -
d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00
Don't include names with empty subordinates in maps (#644)

These are unecessary anyway and just blow up interface size
- - - - -
69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00
Make per-argument docs for class methods work again (#648)

* Make per-argument docs for class methods work again

* Test case

- - - - -
c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00
Fix haddock: internal error: links: UnhelpfulSpan (#561)

* Fix haddock: internal error: links: UnhelpfulSpan

This fixes haskell/haddock#554 for me. I believe this is another fall out
of `wildcard-refactor`, like haskell/haddock#549.

* Comment to clarify why we take the methods name location

- - - - -
d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00
Document record fields when DuplicateRecordFields is enabled (#649)


- - - - -
9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00
Fix test failures on Windows (#564)

* Ignore .stack-work

* Fix for windows: use nul instead of /dev/null

* Fix for windows: canonicalize line separator

* Also normalize osx line endings

- - - - -
7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00
Avoid errors on non UTF-8 Windows (#566)

* Avoid errors on non UTF-8 Windows

Problem
====

haddock exits with errors like below:

`(1)`

```
haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character)
```

`(2)`

```
haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence)
```

`(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr.
For example, this warning contains it:

```
Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods]
    • No explicit implementation for
        ‘toEnum’
    • In the instance declaration for ‘Enum Highlight’
```

`(2)` is caused when the input file of `readFile` contains some Unicode characters.
In the case above, '⇒' is the cause.

Environment
----

OS: Windows 10
haddock: 2.17.3
GHC: 8.0.1

Solution
====

Add `hSetEncoding handle utf8` to avoid the errors.

Note
====

- I found the detailed causes by these changes for debugging:
    - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b
    - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4
- These errors happen even after executing `chcp 65001` on the console.
  According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding.

* Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows

Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1)

- - - - -
eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00
Remove redudant import warning (#651)


- - - - -
05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00
Avoid missing home module warning (#652)

* Avoid missing home module warning

* Update haddock-library.cabal

- - - - -
e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00
Fix haskell/haddock#249 (#655)


- - - - -
eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00
Fix compilation of lib:haddock-library w/ GHC < 8

- - - - -
9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00
Prepare 2.18.1 release (#657)


- - - - -
46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Tweak haddock-api.cabal for pending release

- - - - -
85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Avoid trivial use of LambdaCase

otherwise we can't test w/ e.g. GHC 7.4.2

- - - - -
3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Refactor .cabal to use sub-lib for vendored lib

A practical benefit is that we can control the build-depends and also
avoid some recompilation between library and test-suite.

- - - - -
e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00
haddock-api: add changelog pointing to haddock's changelog

This addresses
https://github.com/haskell/haddock/issues/638#issuecomment-309283297

- - - - -
2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00
Drop obsolete/misleading `stability: experimental`

This .cabal property has long been considered obsolete

- - - - -
9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00
Beef up haddock description (#658)

* Beef up haddock description

* Handle empty lines

- - - - -
bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00
Import @aisamanra's Haddock cheatsheet

from https://github.com/aisamanra/haddock-cheatsheet

- - - - -
0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00
Add cheatsheet to haddock.cabal

- - - - -
2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00
Mention new-build in README

- - - - -
947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00
Update README

Also improves markup and removes/fixes redundant/obsolete parts

[skip ci]

- - - - -
785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00
Bump haddock to 2.18.2, haddock-library to 1.4.5

- - - - -
e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00
Move `DocMarkup` from haddock-api to haddock-library (#659)

* Move `DocMarkup` from haddock-api to haddock-library

* Move more markup related functions

* Markup module

* CHANGELOG

- - - - -
cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00
Fixup haddock
- - - - -
583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00
Changelog for haddock-library

- - - - -
bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00
Prepare haddock-library-1.4.5 release

- - - - -
58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00
Fix renaming after instance signature specializing (#660)

* rework rename

* Add regression test for Bug 613

* update tests

* update changelog

- - - - -
b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00
Fix: Generate pattern signatures for constructors exported as patterns (#663)

* Fix pretty-printing of pattern signatures

Pattern synonyms can have up to two contexts, both having a
different semantic meaning: The first holds the constraints
required to perform the matching, the second contains the
constraints provided by a successful pattern match. When the
first context is empty but the second is not it is necessary
to render the first, empty context.

* Generate pattern synonym signatures for ctors exported as patterns

This fixes haskell/haddock#653.

* Simplify extractPatternSyn

It is not necessary to generate the simplest type signature since
it will be simplified when pretty-printed.

* Add changelog entries for PR haskell/haddock#663

* Fix extractPatternSyn error message

- - - - -
d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00
Bump haddock-library
- - - - -
99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00
Bump haddock-library in haddock-api
- - - - -
94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00
Provide --show-interface option to dump interfaces (#645)

* WIP: Provide --show-interface option to dump interfaces

Like ghcs own --show-iface this flag dumps a binary interface file to
stdout in a human (and machine) readable fashion. Currently it uses
json as output format.

* Fill all the jsonNull stubs

* Rework Bifunctor instance of DocH, update changelog and documentation

* replace changelog, bring DocMarkupH doc back

* Update CHANGES.md

* Update CHANGES.md

* Move Control.Arrow up

It would result in unused import if the Bifunctor instance is not generated.

- - - - -
c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00
Adapt to haskell/haddock#14060

- - - - -
b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00
Bifoldable and Bitraversable for DocH and MetaDoc

- - - - -
021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00
Refactoring: Make doc renaming monadic

This allows us to later throw warnings if can't find an identifier

- - - - -
39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00
Hyperlinker: Avoid linear lookup in enrichToken (#669)

* Make Span strict in Position

* Hyperlinker: Use a proper map to enrich tokens

- - - - -
e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00
Drop Avails from export list

- - - - -
86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00
Bump ghc version for haddock-api tests

- - - - -
d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00
Revert "Drop Avails from export list"

This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def.

- - - - -
c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00
IntefaceFile version

- - - - -
a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00
haddock: Add Documentation.Haddock.Markup to other-modules

- - - - -
34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00
haddock: Add Documentation.Haddock.Markup to other-modules

- - - - -
577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00
Update for haskell/haddock#14131

- - - - -
da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00
Generate an index for package content search (#662)

Generate an index for package content search
- - - - -
39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00
Content search for haddock html doc

- - - - -
91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00
Fix tests for content search

- - - - -
b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00
Add search button to #page-menu

- - - - -
25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00
Load javascript below the fold

- - - - -
8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00
Accept tests

- - - - -
c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00
Content search css

- - - - -
89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00
Removed `nowrap` for interface method sigs (#674)

with nowrap the interfaces method sigs would expand at libitum
- - - - -
a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00
Include subordinates in content index

- - - - -
4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00
QuickNav: Make docbase configurable

- - - - -
c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00
QuickNav: Also use baseUrl for doc-index.json request

- - - - -
47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00
Fix test fallout (again)

- - - - -
924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00
Write meta.json when generating html output (#676)


- - - - -
717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00
Use relative URL when no docBaseUrl given
- - - - -
e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00
Add missing js files to data-files (#677)


- - - - -
95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00
Rename "Search" tab to "Quick Jump"
- - - - -
da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00
Make trigger link configurable (#678)

QuickNav: Configurable show/hide trigger
- - - - -
de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00
Account for "Remember the AvailInfo for each IE"

As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the
AvailInfo associated with each IE. @alexbiehl has a patch making proper use of
this change, but this is just to keep things building.

- - - - -
b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00
Bump upper bound on base

- - - - -
79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00
Make compatible with Prelude.<> export in GHC 8.4/base-4.11

- - - - -
3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00
Add compile step that bundles and compresses JS files (#684)

* Add compile step that bundles and compresses JS files

Also, manage dependencies on third-party JS libraries using NPM.

* Compile JS from TypeScript

* Enable 'noImplicitAny' in TypeScript

* QuickJump: use JSX syntax

* Generate source maps from TypeScript for easier debugging

* TypeScript: more accurate type

* Separate quick jump css file from ocean theme

- - - - -
df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00
Bump base for haddock-library and haddock-test

- - - - -
62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00
Inhibit output of coverage information for hidden modules. (#687)

* Inhibit output of coverage information for hidden modules.

* Add changelog entry.

- - - - -
8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00
Don't use subMap in attachInstances

- - - - -
ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00
Revert "Don't use subMap in attachInstances"

This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9.

- - - - -
7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00
Precise Haddock: Use Avails for export resolution (#688)

* Use Avails for export resolution

* Support reexported modules

* Factor out availExportItem

* Use avails for fullModuleExports

* Don't use subMap in attachInstances

* lookupDocs without subMap

* Completely remove subMap

* Only calculate unqualified modules when explicit export list is given

* Refactor

* Refine comment

* return

* Fix

* Refactoring

* Split avail if declaration is not exported itself

* Move avail splitting

- - - - -
b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00
Fix merge fallout

- - - - -
c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00
Copy QuickJump files over

- - - - -
1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00
Use <details> element for collapsibles (#690)

* Remove unnecessary call to 'collapseSection'

The call is unnecessary since there is no corresponding toggle for hiding the
section of orphan instances.

* Use <details> for collapsibles

This makes them work even when JS is disabled. Closes haskell/haddock#560.

- - - - -
1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00
Quick Jump: Show error when loading 'doc-index.json' failed (#691)


- - - - -
910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00
Fix tiny typo in docs (#693)


- - - - -
b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00
Overhaul Haddock's rendering of kind signatures (#681)

* Overhaul Haddock's rendering of kind signatures

* Strip off kind signatures when specializing

As an added bonus, this lets us remove an ugly hack specifically for `(->)`.
Yay!

* Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67

* @alexbiehl's suggestions

* Import injectiveVarsOfBinder from GHC

- - - - -
6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00
Fix Haddock rendering of kind-indexed data family instances (#694)


- - - - -
470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00
Add QuickJump version to meta.json (#696)


- - - - -
b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00
Put Quickjump behind --quickjump flag (#697)


- - - - -
3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00
Add build command to package.json

- - - - -
f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00
Decrease threshold for fuzzy matching

- - - - -
80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00
Supported reexported-modules via --reexport flag.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00
Correct missing title in changelog

- - - - -
1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00
Copy quickjump.css for nicer error messages

- - - - -
db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00
Reexported modules: Report warnings if argument cannot be parsed or

... module cannot be found

- - - - -
eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00
More general type for nameCacheFromGhc. (#539)


- - - - -
580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00
Remote tab

- - - - -
0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00
fullModuleContents traverses exports in declaration order

- - - - -
0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00
Remove excessive use of list comprehensions

- - - - -
f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00
Make better use of AvailInfo

- - - - -
f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00
Always return documentation for exported subordinates

... event if they have no documentation (e.g. noDocForDecl)

By using the information in the AvailInfo we don't need additional
export checks.

- - - - -
7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00
Match changes for Trees that Grow in GHC

- - - - -
e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00
Match Trees That Grow

- - - - -
55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00
Match Trees that Grow in GHC for HsExpr

- - - - -
2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00
Actually render infix type operators as infix (#703)

* Actually render infix type operators as infix

* Account for things like `(f :*: g) p`, too

- - - - -
c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00
Clean up use of PlaceHolder, to match TTG

- - - - -
81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00
Declare use of `Paths_haddock` module in other-modules (#705)

This was detected by `-Wmissing-home-modules`
- - - - -
f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00
Drop Paths_haddock from ghc.mk (#707)

With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more.
# Conflicts:
#	ghc.mk
- - - - -
f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00
Add autogen-modules (#706)

> Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail.
# Conflicts:
#	haddock.cabal
- - - - -
bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00
Revert "Clean up use of PlaceHolder, to match TTG"

This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049.

- - - - -
af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00
Revert "Match Trees that Grow in GHC for HsExpr"

This reverts commit 9f054dc365379c66668de6719840918190ae6e44.

- - - - -
5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00
Revert "Match Trees That Grow"

This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c.

- - - - -
99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00
Revert "Match changes for Trees that Grow in GHC"

This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547.

- - - - -
c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00
Bump GHC version

- - - - -
027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00
Bump GHC bound to 8.4.*

- - - - -
58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00
Update changelog
- - - - -
d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00
Track changes to follow Trac haskell/haddock#14529

This tracks the refactoring of HsDecl.ConDecl.

- - - - -
dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00
Pass to GHC visible modules for instance filtering

The GHC-side `getNameToInstancesIndex` filters out incorrectly some
instances because it is not aware of what modules are visible. On the
Haddock side, we need to pass in the modules we are processing.

On the GHC side, we need to check against _those_ modules when checking
if an instance is visible.

- - - - -
8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00
Constructor and pattern synonym argument docs (#709)

* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

- - - - -
ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00
Update the GblRdrEnv when processing modules

Without a complete environment, we will miss some instances that were
encountered during typechecking.

- - - - -
4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00
Fix haskell/haddock#732 (#733)


- - - - -
bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00
extractDecl: Extract associated types correctly (#736)


- - - - -
a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00
extractDecl: Extract associated types correctly (#736)


- - - - -
26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00
haddock-api: bump ghc to ^>= 8.4

- - - - -
f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00
Fix duplicate declarations and TypeFamilies specifics

- - - - -
0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00
Fix duplicate declarations and TypeFamilies specifics

- - - - -
cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00
Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head

- - - - -
0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00
Pass to GHC visible modules for instance filtering

The GHC-side `getNameToInstancesIndex` filters out incorrectly some
instances because it is not aware of what modules are visible. On the
Haddock side, we need to pass in the modules we are processing.

On the GHC side, we need to check against _those_ modules when checking
if an instance is visible.

- - - - -
b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00
Update the GblRdrEnv when processing modules

Without a complete environment, we will miss some instances that were
encountered during typechecking.

- - - - -
0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00
Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702)

- - - - -
8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00
Use the GHC lexer for the Hyperlinker backend (#714)

* Start changing to use GHC lexer

* better cpp

* Change SrcSpan to RealSrcSpan

* Remove error

* Try to stop too many open files

* wip

* wip

* Revert "wip"

This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1.

Conflicts:
	haddock-api/haddock-api.cabal
	haddock-api/src/Haddock/Interface.hs

* Remove pointless 'caching'

* Use dlist rather than lists when finding vars

* Use a map rather than list

* Delete bogus comment

* Rebase followup

Things now run using the GHC lexer. There are still

  - stray debug statements
  - unnecessary changes w.r.t. master

* Cleaned up differences w.r.t. current Haddock HEAD

Things are looking good. quasiquotes in particular look beautiful: the
TH ones (with Haskell source inside) colour/link their contents too!

Haven't yet begun to check for possible performance problems.

* Support CPP and top-level pragmas

The support for these is hackier - but no more hacky than the existing
support.

* Tests pass, CPP is better recognized

The tests were in some cases altered: I consider the new output to be more
correct than the old one....

* Fix shrinking of source without tabs in test

* Replace 'Position'/'Span' with GHC counterparts

Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'.

* Nits

* Forgot entry in .cabal

* Update changelog

- - - - -
95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00
Clickable anchors for headings (#716)

See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the
heading itself.
- - - - -
21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00
Quickjump: Matches on function names weight more than matches in ...

module names.

- - - - -
8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00
Treat escaped \] better in definition lists (#717)

This fixes haskell/haddock#546.
- - - - -
e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00
Remove scanner, takeWhile1_ already takes care of escaping

- - - - -
9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00
Take until line feed

- - - - -
01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00
Add simple framework for running parser fixtures (#668)

* Add simple framework for running parser fixtures

* Compatible with tree-diff-0.0.0.1

* Use parseParas to parse fixtures

This allows to test all syntactic constructs available in haddock
markup.

- - - - -
31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00
Patch flaky parser test (#720)

* Patch flaky parser test

This test was a great idea, but it doesn't port over too well to using
the GHC lexer. GHC rewrites its input a bit - nothing surprising, but
we need to guard against those cases for the test.

* Change instance head

* Change use site

- - - - -
9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00
Include secondary LICENSE file in source dist

- - - - -
51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00
Grid Tables (#718)

* Add table examples

* Add table types and adopt simple parser

Simple parser is done by Giovanni Cappellotto (@potomak)
in https://github.com/haskell/haddock/pull/577
It seems to support single fine full tables, so far from full
RST-grid tables, but it's good start.

Table type support row- and colspans, but obviously parser is lacking.

Still TODO:
- Latex backend. Should we use multirow package
  https://ctan.org/pkg/multirow?lang=en?
- Hoogle backend: ?

* Implement grid-tables

* Refactor table parser

* Add two ill-examples

* Update CHANGES.md

* Basic documentation for tables

* Fix documentation example

- - - - -
670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00
Add grid table example to cheatsheet

(pdf and svg need to be regenerated thought)
- - - - -
4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00
Fix infinite loop when specializing instance heads (#723)

* Fix infinite loop when specializing instance heads

The bug can only be triggered from TH, hence why it went un-noticed for
so long.

* Add test for haskell/haddock#679 and haskell/haddock#710

- - - - -
67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00
Filter RTS arguments from 'ghc-options' arguments (#725)

This fixes haskell/haddock#666.
- - - - -
7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00
Quickjump Scrollable overlay
- - - - -
da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Hyperlinker: Adjust parser to new PFailed constructor

- - - - -
7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00
Specialize: Add missing IdP annotations

- - - - -
78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Convert: Correct pass type

- - - - -
a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Warning free compilation

- - - - -
cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00
hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0

- - - - -
c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Adjust changelogs

- - - - -
1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00
haddock-library: Info about breaking changes

- - - - -
f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00
Properly color pragma contents in hyperlinker

The hyperlinker backend now classifies the content of pragmas as
'TkPragma'. That means that in something like '{-# INLINE foo #-}',
'foo' still gets classified as a pragma token.

- - - - -
c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00
Support the new 'ITcolumn_prag' token

- - - - -
4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00
QuickJump: Mitigate encoding problems on Windows

- - - - -
bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00
Use withBinaryFile

- - - - -
637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00
Try GHC 8.4.1 for Travis CI job

- - - - -
7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00
try harder to build w/ GHC 8.4.1

- - - - -
8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00
Add `SPDX-License-Identifier` as alised for "license" module header tokens

C.f. SPDX 2.1 - Appendix V
 https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b

    The tag should appear on its own line in the source file, generally as part of a comment.

    SPDX-License-Identifier: <SPDX License Expression>

Cherry-picked from haskell/haddock#743

- - - - -
267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00
Make test-suite SMP compatible

- - - - -
95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00
Hyperlink pattern synonyms and 'module' imports (#744)

Links to pattern synonyms are now generated, as well as links from
modules in import lists.

Fixes haskell/haddock#731.
- - - - -
67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00
Don't warn about missing '~' (#746)

This manually filters out '~' from the list of things to warn about. It truly
makes no sense to warn on this since '~' has nothing it could link to - it is
magical.

This fixes haskell/haddock#532.
- - - - -
ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00
Don't barf on 'HsSpliceTy' (#745)

This handles 'HsSpliceTy's by replacing them with what they expand to.
IIUC everything that is happening, 'renameHsSpliceTy' should not be
able to fail for the inputs we feed it from GHC.

This fixes haskell/haddock#574.

- - - - -
92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00
Rename: renameHsSpliceTy ttg

- - - - -
3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00
Expand SigDs

- - - - -
c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00
fullModuleContents: support named docs

- - - - -
de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00
Hyperlinker: Also link pattern synonym arguments

- - - - -
b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00
Expand SigD in a better place

In https://github.com/haskell/haddock/issues/287 we found that
haddock-2.19.0 would miss documentation on class methods with
multiples names.

This patch uses expandSigDecls in a more sensible place.

- - - - -
8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00
Add module tooltips to linked identifiers (#753)

No more clicking to figure out whether your bytestring is strict or lazy!
- - - - -
d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00
Add 'show' option to complement 'hide' (#752)

* Add 'show' option to complement 'hide'

The behaviour is for flags passed in the command line to override
flags in file headers. In the command line, later flags override
earlier ones.

Fixes haskell/haddock#751 and haskell/haddock#266.

* Add a '--show-all' option

- - - - -
6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00
QuickJump: Mitigate encoding problems on Windows

(cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231)

- - - - -
e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00
Use withBinaryFile

- - - - -
724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00
Haddock: support splitted include paths. (#689)


- - - - -
9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00
Teach the HTML backend how to render methods with multiple names

- - - - -
a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00
Hoogle/Latex: Remove use of partial function

- - - - -
66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00
Fix file handle leak (#763) (#764)

Brought back some mistakenly deleted code for handling encoding and eager
reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137.
- - - - -
bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00
Enable running test suite with stock haddock and ghc using

```
$ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc)
```

- - - - -
dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00
Make testsuite work with haddock-1.19.0 release (#766)


- - - - -
f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00
Support unicode operators, proper modules

Unicode operators are a pretty big thing in Haskell, so supporting linking them
seems like it outweighs the cost of the extra machinery to force Attoparsec to
look for unicode.

Fixes haskell/haddock#458.

- - - - -
09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00
Remove bang pattern

- - - - -
d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00
fix test

- - - - -
d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00
haddock-test: Be more explicit which packages to pass

We now pass `-hide-all-packages` to haddock when invoking the
testsuite. This ensures we don't accidentally pick up any dependencies
up through ghc.env files.

- - - - -
0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00
Revert "fix test"

This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197.

- - - - -
52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00
Fix Bug548 for real

- - - - -
89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00
Hyperlinker: Links for TyOps, class methods and associated types

- - - - -
d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00
Updates for haskell/haddock#13324

- - - - -
6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00
Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1

- - - - -
c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00
Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1

- - - - -
500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00
Update to QC 2.11

- - - - -
ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00
Restore backward-compat with base-4.5 through base-4.8

- - - - -
baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00
Bump lower bound for haddock-library

- - - - -
10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00
Haddock: Straighten out base bound

- - - - -
a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00
extractDecl: Extract constructor patterns from data family instances (#776)

* extractDecl: Allow extraction of data family instance constructors

* extractDecl: extract data family instance constructors

- - - - -
ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00
Readme: Update GHC version (#778)


- - - - -
8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for definition lists

- - - - -
425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for links

- - - - -
d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for inline links

- - - - -
f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00
fixtures: Slightly unmangle output

- - - - -
0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00
fixtures: Prevent stdout buffering

- - - - -
1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00
haddock-library.cabal: Clean up GHC options

- - - - -
066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00
Make a proper definition for the <link> parser

- - - - -
573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00
Show where instances are defined (#748)

* Indicate source module of instances

Above instance, we now also display a link to the module where the
instance was defined. This is sometimes helpful in figuring out
what to import.

* Source module for type/data families too

* Remove parens

* Accept tests

- - - - -
99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00
Prepare changelog for next release

- - - - -
482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00
Useful cost centres, timers and allocation counters (#785)

* Add some useful cost-centres for profiling

* Add withTiming for each haddock phase

Invoking haddock with `--optghc=-ddump-timings` now shows the amount
of time spent and the number of allocated bytes for each phase.

- - - - -
773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00
@since includes package name (#749)

* Metadoc stores a package name

This means that '@since' annotations can be package aware.

* Get the package name the right way

This should extract the package name for `@since` annotations the
right way. I had to move `modulePackageInfo` around to do this and,
in the process, I took the liberty to update it.

Since it appears that finding the package name is something that can
fail, I added a warning for this case.

* Silence warnings

* Hide package for local 'since' annotations

As discussed, this is still the usual case (and we should avoid being
noisy for it).

Although this commit is large, it is basically only about threading a
'Maybe Package' from 'Haddock.render' all the way to
'Haddock.Backends.Xhtml.DocMarkup.renderMeta'.

* Bump binary interface version

* Add a '--since-qual' option

This controls when to qualify since annotations with the package they
come from. The default is always, but I've left an 'external' variant
where only those annotations coming from outside of the current
package are qualified.

* Make ParserSpec work

* Make Fixtures work

* Use package name even if package version is not available

The @since stuff needs only the package name passed in, so it
makes sense to not be forced to pass in a version too.

- - - - -
e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00
haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0

- - - - -
8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00
Bump haddock and haddock-api to 2.20.0

- - - - -
5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00
Clear search string on hide for haskell/haddock#781 (#789)


- - - - -
920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00
Travis: Build with ghc-8.4.2 (#793)


- - - - -
a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00
Match changes in GHC for D4199

Removing HasSourceText and SourceTextX classes.

- - - - -
ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00
Match GHC changes for TTG

- - - - -
739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00
Match GHC for TTG implemented on HsBinds, D4581

- - - - -
2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00
Bump upper bound on base to < 4.13

See https://ghc.haskell.org/trac/ghc/ticket/15018.

- - - - -
a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00
Don't treat fixity signatures like declarations

- - - - -
d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00
Add regression test for haskell/haddock#413

Fixes haskell/haddock#413.

- - - - -
c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00
Improve the Hoogle backend's treatment of type families (#808)

Fixes parts 1 and 2 of haskell/haddock#806.
- - - - -
d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00
Replace 'attoparsec' with 'parsec' (#799)

* Remove attoparsec with parsec and start fixing failed parses

* Make tests pass

* Fix encoding issues

The Haddock parser no longer needs to worry about bytestrings. All
the internal parsing work in haddock-library happens over 'Text'.

* Remove attoparsec vendor

* Fix stuff broken in 'attoparsec' -> 'parsec'

* hyperlinks
* codeblocks
* examples

Pretty much all issues are due to attoparsec's backtracking failure
behaviour vs. parsec's non-backtracking failure behaviour.

* Fix small TODOs

* Missing quote + Haddocks

* Better handle spaces before/after paragraphs

* Address review comments

- - - - -
fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00
Match changes in GHC for TTG

- - - - -
06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00
Merge branch 'ghc-head' with 'ghc-8.4'

- - - - -
879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00
Filter out CRLFs in hyperlinker backend (#813)

This prevents spurious lines from appearing in the final output.
- - - - -
3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00
Add docs for some DocH constructors (#814)


- - - - -
0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00
Remove 'TokenGroup' from Hyperlinker (#818)

Since the hyperlinker backend now relies on the GHC tokenizer, something
like 'Bar.Baz.foo' already gets bunched together into one token (as
opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo').
- - - - -
8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00
Renamer: Warn about out of scope identifiers. (#819)


- - - - -
ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00
Remove Hoogle backend hack that butchers infix datatype names

- - - - -
03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00
Wibbles

- - - - -
b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00
Use the response file utilities defined in `base` (#821)

Summary: The response file related modules were recently copied from
`haddock` into `base`. This patch removes them from `haddock`.

GHC Trac Issues: haskell/haddock#13896
- - - - -
9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00
Account for refactoring of LitString

- - - - -
ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00
Merge pull request haskell/haddock#826 from haskell/T825

Remove Hoogle backend hack that butchers infix datatype names
- - - - -
0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00
Use `ClassOpSig` instead of `TypeSig` for class methods (#835)

* Fix minimal pragma handling

Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834.

* Accept html-test output

- - - - -
15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00
Adjust to new HsDocString internals

- - - - -
6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00
Remove ParallelArrays and Data Parallel Haskell

- - - - -
0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00
DerivingVia changes

- - - - -
0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00
Bump a few dependency bounds (#845)


- - - - -
5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00
Improve hyperlinker's 'spanToNewline' (#846)

'spanToNewline' is used to help break apart the source into lines which
can then be partioned into CPP and non-CPP chunks. It is important that
'spanToNewline' not break apart tokens, so it needs to properly handle
things like

  * block comments, possibly nested
  * string literals, possibly multi-line
  * CPP macros, possibly multi-line

String literals in particular were not being properly handled. The fix
is to to fall back in 'Text.Read.lex' to help lex things that are not
comments.

Fixes haskell/haddock#837.
- - - - -
9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00
Extract docs from strict/unpacked constructor args (#839)

This fixes haskell/haddock#836.
- - - - -
70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00
Renamer: Warn about ambiguous identifiers (#831)

* Renamer: Warn about ambiguous identifiers

Example:

    Warning: 'elem' is ambiguous. It is defined
        * in ‘Data.Foldable’
        * at /home/simon/tmp/hdk/src/Lib.hs:7:1
        You may be able to disambiguate the identifier by qualifying it or
        by hiding some imports.
        Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1

Fixes haskell/haddock#830.

* Deduplicate warnings

Fixes haskell/haddock#832.

- - - - -
495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00
Use the response file utilities defined in `base` (#821)

Summary: The response file related modules were recently copied from
`haddock` into `base`. This patch removes them from `haddock`.

GHC Trac Issues: haskell/haddock#13896
- - - - -
81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00
Account for refactoring of LitString

- - - - -
7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00
Adjust to new HsDocString internals

- - - - -
bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00
Remove ParallelArrays and Data Parallel Haskell

- - - - -
5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00
DerivingVia changes

- - - - -
73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00
Extract docs from strict/unpacked constructor args (#839)

This fixes haskell/haddock#836.
- - - - -
4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Remove `ITtildehsh` token

- - - - -
b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00
Filter out CRLFs in hyperlinker backend (#813)

This prevents spurious lines from appearing in the final output.
- - - - -
9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Add docs for some DocH constructors (#814)


- - - - -
8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00
Remove 'TokenGroup' from Hyperlinker (#818)

Since the hyperlinker backend now relies on the GHC tokenizer, something
like 'Bar.Baz.foo' already gets bunched together into one token (as
opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo').
- - - - -
29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Renamer: Warn about out of scope identifiers. (#819)


- - - - -
2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00
Remove Hoogle backend hack that butchers infix datatype names

- - - - -
a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00
Wibbles

- - - - -
a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00
Use `ClassOpSig` instead of `TypeSig` for class methods (#835)

* Fix minimal pragma handling

Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834.

* Accept html-test output

- - - - -
8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00
Bump a few dependency bounds (#845)


- - - - -
4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00
Improve hyperlinker's 'spanToNewline' (#846)

'spanToNewline' is used to help break apart the source into lines which
can then be partioned into CPP and non-CPP chunks. It is important that
'spanToNewline' not break apart tokens, so it needs to properly handle
things like

  * block comments, possibly nested
  * string literals, possibly multi-line
  * CPP macros, possibly multi-line

String literals in particular were not being properly handled. The fix
is to to fall back in 'Text.Read.lex' to help lex things that are not
comments.

Fixes haskell/haddock#837.
- - - - -
311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Renamer: Warn about ambiguous identifiers (#831)

* Renamer: Warn about ambiguous identifiers

Example:

    Warning: 'elem' is ambiguous. It is defined
        * in ‘Data.Foldable’
        * at /home/simon/tmp/hdk/src/Lib.hs:7:1
        You may be able to disambiguate the identifier by qualifying it or
        by hiding some imports.
        Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1

Fixes haskell/haddock#830.

* Deduplicate warnings

Fixes haskell/haddock#832.

- - - - -
d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Complete FixitySig and FamilyDecl pattern matches

- - - - -
055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Fix redundant import warnings

- - - - -
f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00
html-test: Accept output

- - - - -
04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00
Bump bounds on Cabal

- - - - -
0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00
Merge branch 'ghc-head' into ghc-head-update-3

- - - - -
c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00
Bump ghc bound for haddock-api spec test-suite

- - - - -
119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00
Travis: `--allow-newer` for all packages

- - - - -
0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00
Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3

Update ghc-head
- - - - -
5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00
Improved handling of interfaces in 'haddock-test' (#851)

This should now work with an inplace GHC where (for instance)
HTML directories may not be properly recorded in the package DB.
- - - - -
96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00
Handle -XStarIsType

- - - - -
e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00
Revert unintentional reversion of fix of haskell/haddock#548

- - - - -
01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00
Match changes in GHC for haskell/haddock#14259

- - - - -
7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00
Bump GHC version to 8.6

- - - - -
11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00
Remove HsEqTy and XEqTy

- - - - -
b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00
Revert "Bump GHC version to 8.6"

This was applied to the wrong branch; there's now a `ghc-8.6` branch;
ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version.
The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7

This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1.

- - - - -
f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00
Update Travis CI job

- - - - -
ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00
Drop GHC HEAD from CI and update GHC to 8.4.3

It's a waste of resource to even try to build this branch w/ ghc-head;
so let's not do that...

- - - - -
41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00
Bump GHC version to 8.7

- - - - -
8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00
Update CI job to use GHC 8.7.*

- - - - -
b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00
README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

- - - - -
f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00
Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.
- - - - -
a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00
Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

- - - - -
13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00
Match XFieldOcc rename in GHC

Trac haskell/haddock#15386

- - - - -
c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00
haddock-library: Bump bounds for containers

- - - - -
722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00
tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

- - - - -
f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00
Fix HEAD html-test (#860)

* Update tests for 'StarIsType'

* Accept tests

* Revert "Update tests for 'StarIsType'"

This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a.

- - - - -
394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00
haddock-library: Bump bounds for containers

- - - - -
1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00
Add HEAD.hackage overlay (#887)

* Add HEAD.hackage overlay

* Add HCPKG variable

- - - - -
c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00
Refactor handling of parens in types (#874)

* Fix type parenthesization in Hoogle backend

Ported the logic in the HTML and LaTeX backends for adding in parens
into something top-level in 'GhcUtil'. Calling that from the Hoogle
backend fixes haskell/haddock#873.

* Remove parenthesizing logic from LaTeX and XHTML backends

Now, the only times that parenthesis in types are added in any backend
is through the explicit 'HsParTy' constructor. Precedence is also
represented as its own datatype.

* List out cases explicitly vs. catch-all

* Fix printing of parens for QuantifiedConstraints

The priority of printing 'forall' types was just one too high.

Fixes haskell/haddock#877.

* Accept HTML output for quantified contexts test

- - - - -
c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00
Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

- - - - -
24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00
Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.
- - - - -
cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00
README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

(cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c)

- - - - -
133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00
Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.

(cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce)

- - - - -
11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00
Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

(cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0)

- - - - -
de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00
tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

(cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9)

- - - - -
6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00
Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

(cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4)

- - - - -
1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00
Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.

(cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05)

- - - - -
69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00
Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)
- - - - -
6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00
Misc tests (#858)

* More tests

* spliced types
* constructor/pattern argument docs
* strictness marks on fields with argument docs

* latex test cases need seperate directory

* Accept tests

- - - - -
92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00
Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)

(cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370)

- - - - -
981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00
Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

- - - - -
27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00
Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

(cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071)

- - - - -
49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00
Update the ghc-8.6 branch (#889)

* Revert "Bump GHC version to 8.6"

This was applied to the wrong branch; there's now a `ghc-8.6` branch;
ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version.
The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7

This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1.

* README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

(cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c)

* Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.

(cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce)

* Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

(cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0)

* tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

(cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9)

* Fix HEAD html-test (#860)

* Update tests for 'StarIsType'

* Accept tests

* Revert "Update tests for 'StarIsType'"

This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a.

* Refactor handling of parens in types (#874)

* Fix type parenthesization in Hoogle backend

Ported the logic in the HTML and LaTeX backends for adding in parens
into something top-level in 'GhcUtil'. Calling that from the Hoogle
backend fixes haskell/haddock#873.

* Remove parenthesizing logic from LaTeX and XHTML backends

Now, the only times that parenthesis in types are added in any backend
is through the explicit 'HsParTy' constructor. Precedence is also
represented as its own datatype.

* List out cases explicitly vs. catch-all

* Fix printing of parens for QuantifiedConstraints

The priority of printing 'forall' types was just one too high.

Fixes haskell/haddock#877.

* Accept HTML output for quantified contexts test

* Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

(cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4)

* Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.

(cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05)

* Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)

(cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370)

* Misc tests (#858)

* More tests

* spliced types
* constructor/pattern argument docs
* strictness marks on fields with argument docs

* latex test cases need seperate directory

* Accept tests

* Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

(cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071)

- - - - -
5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00
Revert "Revert "Bump GHC version to 8.6""

That commit didn't belong onto the ghc-8.6 branch.

This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967.

- - - - -
2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00
Don't warn about ambiguous identifiers when the candidate names belong to the same type

This also changes the defaulting heuristic for ambiguous identifiers.
We now prefer local names primarily, and type constructors or class
names secondarily.

Partially fixes haskell/haddock#854.

- - - - -
fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00
outOfScope: Recommend qualifying the identifier

- - - - -
acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00
outOfScope: Recommend qualifying the identifier

(cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7)

- - - - -
1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00
Don't warn about ambiguous identifiers when the candidate names belong to the same type

This also changes the defaulting heuristic for ambiguous identifiers.
We now prefer local names primarily, and type constructors or class
names secondarily.

Partially fixes haskell/haddock#854.

(cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f)

- - - - -
48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00
Add # as a special character (#884)

'#' has special meaning used for anchors and can be escaped using backslash.
Therefore it would be nice to be listed as special characters.
- - - - -
5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00
Let `haddock-test` bypass interface version check (#890)

This means `haddock-test` might

  * crash during deserialization
  * deserialize incorrectly

Still - it means things _might_ work where they were previously sure
not to.
- - - - -
27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00
Avoid "invalid argument (invalid character)" on non-unicode Windows (#892)

Steps to reproduce and the error message
====

```
> stack haddock basement
... snip ...
    Warning: 'A' is out of scope.
    Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character)
```

Environment
====

OS: Windows 10 ver. 1709
haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD)
GHC: 8.4.3
stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2

Related pull request
====

https://github.com/haskell/haddock/pull/566
- - - - -
6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00
Accumulate explicitly which modules to load for 'attachInstances'

The old approach to fixing haskell/haddock#469, while correct, consumes a lot of
memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However,
'getNameToInstancesIndex' takes that environment and compresses it down
to a much smaller 'ModuleSet'.

Now, we compute that 'ModuleSet' explicitly as we process modules. That
way we can just tell 'getNameToInstancesIndex' what modules to load
(instead of it trying to compute that information from the interactive
context).

- - - - -
8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00
eqTyCon_RDR now lives in TysWiredIn

After GHC commit
http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071

- - - - -
1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00
Match XFieldOcc rename in GHC

Trac haskell/haddock#15386

(cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6)

- - - - -
8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00
Update against new HsImplicitBndrs

- - - - -
e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00
Latex type families (#734)

* Support for type families in LaTeX

The code is ported over from the XHTML backend.

* Refactor XHTML and LaTeX family handling

This is mostly a consolidation effort: stripping extra exports,
inlining some short definitions, and trying to make the backends
match.

The LaTeX backend now has preliminary support for data families,
although the only the data instance head is printed (not the actual constructors).

Both backends also now use "newtype" for newtype data family
instances.

* Add some tests

- - - - -
0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00
Make --package-version optional for --hoogle generation (#899)

* Make --package-version optional for --hoogle generation

* Import mkVersion

* It's makeVersion not mkVersion

- - - - -
d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00
Remove unnecessary backslashes from docs (#908)

On
https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters
the backslash and backtick special characters showed up with an extra
backslash before them – I think the escaping is not (or no longer)
needed for those characters in rst.
- - - - -
7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900
- - - - -
aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900
- - - - -
ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00
Better test output when Haddock crashes on a test (#902)

In particular: we report the tests that crashed seperately from the tests
that produced incorrect output. In order for tests to pass (and exit 0),
they must not crash and must produce the right output.
- - - - -
4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00
Fix a typo (#878)


- - - - -
4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00
Add ITcomment_line_prag token to Hyperlinker Parser

This token is necessary for parsing #line pragmas inside nested comments.

Reviewers: bgamari

Reviewed By: bgamari

Differential Revision: https://phabricator.haskell.org/D4935

- - - - -
9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00
Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances

Accumulate explicitly which modules to load for 'attachInstances'
- - - - -
d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00
Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head

- - - - -
14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00
Accumulate explicitly which modules to load for 'attachInstances'

The old approach to fixing haskell/haddock#469, while correct, consumes a lot of
memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However,
'getNameToInstancesIndex' takes that environment and compresses it down
to a much smaller 'ModuleSet'.

Now, we compute that 'ModuleSet' explicitly as we process modules. That
way we can just tell 'getNameToInstancesIndex' what modules to load
(instead of it trying to compute that information from the interactive
context).

(cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1)

- - - - -
438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900

(cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d)

- - - - -
a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00
Better rendering of unboxed sums/tuples

* adds space after/before the '#' marks
* properly reify 'HsSumTy' in 'synifyType'

- - - - -
88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00
Handle promoted tuples in 'synifyType'

When we have a fully applied promoted tuple, we can expand it out properly.

- - - - -
fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00
Accept test cases

- - - - -
6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00
Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff

Better rendering of unboxed sums, unboxed tuples, promoted tuples.
- - - - -
181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00
Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6

- - - - -
3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00
Properly synify promoted list types

We reconstruct promoted list literals whenever possible. That means
that 'synifyType' produces

   '[Int, Bool, ()]

instead of

   (Int ': (() ': (Bool ': ([] :: [Type]))))

- - - - -
b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00
Only look at visible types when synifying a 'HsListTy'

The other types are still looked at when considering whether to make
a kind signature or not.

- - - - -
a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00
Merge pull request haskell/haddock#922 from harpocrates/promoted-lists

Properly synify promoted list types
- - - - -
0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00
Update according to GHC Core changes

- - - - -
7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00
update dataFullSig to work with Co Quantification

This should have been in the previous patch, but wasn't.

- - - - -
cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00
Fix/add to various docs

* Add documentation for a bunch of previously undocumented
  options (fixes haskell/haddock#870)
* Extend the documentation of `--hoogle` considerably (see haskell/haddock#807)
* Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912)
* Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780)

- - - - -
ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00
Update Travis

- - - - -
d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00
Accept failing tests

Also silence orphan warnings.

- - - - -
f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00
Bump haddock-api-2.21.0, haddock-library-1.7.0

* Update CHANGELOGS
* Update new versions in Cabal files
* Purge references to ghc-8.4/master branches in README

- - - - -
3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00
Turn haddock-library into a minor release

Fix some version bounds in haddock-library too.

- - - - -
b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00
keep cabal.project file

- - - - -
4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00
Build on 7.4 and 7.8

- - - - -
99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00
Minor tweak to package description

- - - - -
a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00
Merge pull request haskell/haddock#945

haddock-api 2.21.0 and haddock-library 1.6.1 release
- - - - -
2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00
Bump haddock-library to 1.7.0

The 1.6.1 release should've been a major bump, since types in
the `Documentation.Haddock.Parser.Monad` module changed. This version
makes that module internal (as it morally should be).

- - - - -
ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00
Merge branch 'ghc-8.4' into ghc-8.6

- - - - -
2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00
Merge branch 'ghc-8.6' into ghc-head

- - - - -
a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00
Latex type families (#734)

* Support for type families in LaTeX

The code is ported over from the XHTML backend.

* Refactor XHTML and LaTeX family handling

This is mostly a consolidation effort: stripping extra exports,
inlining some short definitions, and trying to make the backends
match.

The LaTeX backend now has preliminary support for data families,
although the only the data instance head is printed (not the actual constructors).

Both backends also now use "newtype" for newtype data family
instances.

* Add some tests

- - - - -
63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00
Update changelog

- - - - -
099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00
Merge pull request haskell/haddock#942 from harpocrates/update-docs

Fix & add to documentation
- - - - -
0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00
Set UTF-8 encoding before writing files (#934)

This should fix haskell/haddock#929, as well as guard against future problems of this
sort in other places. Basically replaces 'writeFile' (which selects the
users default locale) with 'writeUtf8File' (which always uses utf8).
- - - - -
83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00
Output pattern synonyms in Hoogle backend (#947)

* Output pattern synonyms in Hoogle backend

We were previously weren't outputting _any_ pattern synonyms, bundled or
not. Now, we output both.

Fixes haskell/haddock#946.

* Update changelog

- - - - -
81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00
Release `haddock{,-api}-2.22.0`

This version will accompany ghc-8.6.2

- - - - -
9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00
Add NewOcean theme

And make it the default theme.

- - - - -
7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Improve appearance and readability

These changes include:

- use latest Haskell's logo colors
- decrease #content width to improve readability
- use nicer font
- improve sizes and distances

- - - - -
37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00
Include custom font in the html head

- - - - -
1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Update html test reference files

- - - - -
53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00
Make it responsive

- It makes small screens taking more space than larger ones
- fixes a few issues present in small screens currently
- make it look good across different screen sizes.

- - - - -
6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make the style consistent with hackage

Several things are addressed here:

- better responsive behaviour on the header
- better space usage
- consistent colors overall
- other nit PR comments

- - - - -
3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Place the package name before the menu links

This supports the expected responsive menu design, where the
package name appears above the menu links.

- - - - -
cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update html-test reference files

The package name element in the package-header is now a div instead of a
paragraph, and it is now above the menu ul.links instead of below.

- - - - -
2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve synopsis style and code

- Use CSS3 instead of loading pictures to show "+" and "-" symbols
- Drop redundant code

- - - - -
0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Decrease space between code blocks

There was too much space between code blocks as pointed out by
reviewers.

- - - - -
85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Add an initial-scale property to all haddock pages

This solves an issue reported about the content looking
incredibly small on mobile devices.

- - - - -
c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Address several PR comments

- Darken text color like done for hackage
- Move synopsis to left side
- Make table of contents stick to the left on wide screens
- Wrap links to avoid page overflow
- Improve expand/collapse buttons
- Fix issue with content size on mobile devices
- Fix issue with font-size on landscape mode
- Increase width of the content
- Change colors of table of contents and synopsis
- Etc

- - - - -
e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make synopsis scrollable on wide screens

When the synopsis is longer than the screen, you can’t see its end
and you can't scroll down either, making the content unreachable.

- - - - -
1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve information density

- Reduce font size
- Improve space between and within code blocks
- Improve alignments
- Improve spacing within sub-blocks

- - - - -
bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Minor adjustments

Bring in some adjustments made to hackage:
- link colors
- page header show everything when package title is too long

- - - - -
10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Fix responsive triggers overlap issue

The min and max width triggers have the same values,
which caused the style resolution to take an intersection of
both style declarations when the screen resolution had the size
of the limts (say 1280px), causing an odd behaviour and look.

- - - - -
95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Fix issue with menu alignment on firefox

Reported and described here:
https://github.com/haskell/haddock/pull/721#issuecomment-374668869

- - - - -
dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00
Changelog entry for NewOcean

- - - - -
27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00
html-test --accept

- - - - -
83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00
Avoid name shadowing

- - - - -
231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update font to PT Sans

Also migrate some general text related changes from hackage.

- - - - -
313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Use 'flex' to fix header alignment

- - - - -
5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Misc of tweaks

- Update link colors to hackage scheme
- Tune spacing between content elements
- Update footer style
- Fix and improve code blocks identation

- - - - -
b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update font in Xhtml.hs to PT Sans

- - - - -
78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve code blocks styling

- Fix and improve spacing
- Improve colors and borders

- - - - -
81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make package-header caption backward-compatible

The current html generator of this branch wraps the package-header
caption as a div, which does not work (without style adjustments) with
the old themes. Changing it from div to span does the trick, without
needing to adjust the old stylesheets.

- - - - -
dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update test-suite reference html pages

- - - - -
393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00
Accept tests

- - - - -
a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00
Fix CHANGELOG

- - - - -
8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00
Update 'data-files' to include NewOcean stuff

- - - - -
1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00
Fix typo in a warning

- - - - -
009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00
Update JS dependencies

This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with
some more serious vulnerabilities that nobody seems to have noticed.

- - - - -
051994db by Alec Theriault at 2018-10-24T17:31:09-07:00
Resurrect the style-switcher

This fixes haskell/haddock#810. Looks like things were broken during the quickjump
refactor of the JS.

For the (git) record: I do not think the style switcher is a good idea.
I'm fixing it for the same reason @mzero added it; as an answer to

  "rumblings from some that they didn't want their pixels changed on bit"

- - - - -
2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00
Fix copy-pasta error in data-files

- - - - -
ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00
Fix the synopsis button

Here's these changes are supposed to do:

  * put the synopsis back on the right side
  * properly have it on the edge of the screen on wide screens
  * adjust the background of the synopsis to match the button
    (otherwise the grey blends in with what is underneath)
  * get rid of the dotted purple line
  * the synopsis contents are now scrollable even when in wide
    screens (this has been a long-standing bug)

- - - - -
883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00
Avoid more conflicts in generated ids  (#954)

This fixes haskell/haddock#953 by passing more names into the generated ids.


- - - - -
ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00
Don't hide bullets in method docs

I think thst CSS was meant only to deal with fields and the
effect on bullets was accidental.

Fixes haskell/haddock#926.

- - - - -
9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00
Indent more things + slightly smaller font

- - - - -
b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00
Merge branch 'ghc-8.6' into wip/new-ocean

- - - - -
096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00
Accept HTML output

- - - - -
2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00
User manual + stuff for building GHC docs

- - - - -
46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00
Make 'Contents' in NewOcean scrollable

This only happens if the contents block on the left is so big that it
doesn't fit (vertically) on the page. If that happens, we want it to
be scrollable.

- - - - -
3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00
Revert "Make 'Contents' in NewOcean scrollable"

This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922.

I missed the fact this also forces the 'Contents' to always go down
to the bottom of the page.

- - - - -
ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00
Avoid some partiality

AFAICT this wasn't causing any crashes, but that's mostly because
we happen not to be forcing `pkgStr` when it would diverge. We come
dangerously close to doing that in `ppHtmlIndex`.

Fixes haskell/haddock#569.

- - - - -
6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00
Fix documentation in `haddock-api` (#957)

* Fix misplaced Haddocks in Haddock itself

Haddock should be able to generate documentation for 'haddock-api'
again.

* Make CI check that documentation can be built.

* Add back a doc that is OK

- - - - -
5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00
More explicit foralls (GHC Proposal 0007)

- - - - -
8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00
Only run MathJax on entities with "mathjax" class (#960)

Correspondingly, we wrap all inline/diplay math in

    <span class="mathjax"> ... the math .... </span>

This fixes haskell/haddock#959.
- - - - -
bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00
Deduplicate some work in 'AttachInstances'

Perf only change:

  * avoid needlessly union-ing maps
  * avoid synify-ing instances twice

Took this opportunity to add some docs too

- - - - -
cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00
Specialize some SYB functions

Perf only change:

  * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint
  * Manually specialize the needlessly general type of 'specializeTyVarBndrs'

- - - - -
4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00
Improve perf of renaming

Perf only change:

  * don't look up type variable names (they're never in the environment)
  * use a difference list for accumulating missing names
  * more efficient 'Functor'/'Applicative' instances for 'RnM'

- - - - -
4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00
Faster 'Text' driven parser combinators

Perf only change:

  * use 'getParserState'/'setParserState' to make 'Text'-optimized
    parser combinators
  * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}'

- - - - -
fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00
Support hyperlink labels with inline markup

The parser for pictures hasn't been properly adjusted yet.

- - - - -
c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00
Support (and flatten) inline markup in image links

Inline markup is supported in image links but, as per the [commonmark
recommendation][0], it is stripped back to a plain text representation.

  [0]: https://spec.commonmark.org/0.28/#example-547

- - - - -
d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00
Accept test case

- - - - -
8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00
Fix/add to haddock-library test suite

- - - - -
e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00
Bump version bounds

- - - - -
644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00
Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks

Inline markup in markdown-style links and images
- - - - -
e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00
Fix issues around plus/minus

  * swap the minimize unicode to something more intuitive
  * use new unicode expander/collapser for instance lists
  * address some alignment issues in the "index" page

- - - - -
b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00
Allow "Contents" summary to scroll in a fixed div

In the unfortunate event that the "Contents" summary doesn't fit
vertically (like in the "Prelude"), it will be scrollable.

- - - - -
ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00
Accept HTML output changes

- - - - -
82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00
overflow-y 'scroll' -> 'auto'

- - - - -
571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00
Clicking on "Contents" navigates to top of page

- - - - -
8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00
Space out functions more

Also, functions and data decls now have the same space before and after
them.

- - - - -
cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00
Merge branch 'ghc-8.6' into wip/new-ocean

- - - - -
65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00
Update changelog

- - - - -
20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00
Replace oplus/ominus expander/collapser icons with triangles

- - - - -
16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00
Merge pull request haskell/haddock#949 from haskell/wip/new-ocean

Introduce NewOcean theme.
- - - - -
357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00
Merge branch 'ghc-8.6' into ghc-head

- - - - -
de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00
Rename 'NewOcean' theme to 'Linuwial'

- - - - -
954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00
Add blockquote styling

Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server.

Fixes haskell/haddock#967.

- - - - -
d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00
Fix some broken links (#15733)

Summary:
For links in subpackages as well.
https://phabricator.haskell.org/D5257

Test Plan: Manually verify links

Reviewers: mpickering, bgamari, osa1

Reviewed By: osa1

GHC Trac Issues: haskell/haddock#15733

Differential Revision: https://phabricator.haskell.org/D5262

- - - - -
41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00
Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change

It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62.

- - - - -
c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00
Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag

Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change
- - - - -
6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00
[TTG: Handling Source Locations] Foundation and Pat
Trac Issues haskell/haddock#15495

This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A).
- the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced
- some instances of `HasSrcSpan` are introduced
- some constructors `L` are replaced with `cL`
- some patterns `L` are replaced with `dL->L` view pattern
- some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`)

- - - - -
7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00
More uniform handling of `forall`'s in HTML/LaTeX

 * don't forget to print explicit `forall`'s when there are arg docs
 * when printing an explicit `forall`, print all tyvars

Fixes haskell/haddock#973

- - - - -
d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00
Fix warnings, accept output

* remove redundant imports (only brought to light due to recent work for
  improving redundant import detection)
* fix a bug that was casuing exports to appear in reverse order
* fix something in haddock-library that prevented compilation on old GHC's

- - - - -
a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00
Output better debug infromation on internal error in extractDecl

This will make investigation of haskell/haddock#979 easier

- - - - -
2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00
Refactor names + unused functions (#982)

This commit should not introduce any change in functionality!

  * consistently use `getOccString` to convert `Name`s to strings
  * compare names directly when possible (instead of comparing strings)
  * get rid of unused utility functions
- - - - -
e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00
Load plugins when compiling each module (#983)

* WIP: Load (typechecker) plugins from language pragmas

* Revert "Load plugins when starting a GHC session (#905)"

This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193.

* Simplify plugin initialization code

- - - - -
96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00
Properly synify and render promoted type variables  (#985)

* Synify and render properly promoted type variables

Fixes haskell/haddock#923.

* Accept output

- - - - -
23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00
Remove `haddock-test`'s dep. on `syb` (#987)

The functionality is easily inlined into one short function: `gmapEverywhere`.
This doesn't warrant pulling in another package.
- - - - -
d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00
Address deprecation warnings in `haddock-test` (#988)

Fixes haskell/haddock#885.
- - - - -
4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00
Visible kind application haddock update

- - - - -
ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00
Print kinded tyvars in constructors for Hoogle (#993)

Fixes haskell/haddock#992
- - - - -
2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00
Accept new output `GHC.Maybe` -> `Data.Maybe` (#996)

Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe"
is marked as `not-home`. That changes around some test output.
- - - - -
055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00
Lone typofix
- - - - -
01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00
Keep forall on H98 existential data constructors (#1003)

The information about whether or not there is a source-level `forall`
is already available on a `ConDecl` (as `con_forall`), so we should use
it instead of always assuming `False`!

Fixes haskell/haddock#1002.
- - - - -
f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00
Fix haskell/haddock#1004 with a pinch of dropForAlls

- - - - -
5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00
Loosen 'QuickCheck' and 'hspec' bounds

It looks like the new versions don't cause any breakage
and loosening the bounds helps deps fit in one stack resolver.

- - - - -
3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00
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  haskell/haddock#998)
 * restructure temporary folder logic for `.hi`/`.hie` model
- - - - -
2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00
Update/modernise haddock-library.cabal file

- - - - -
62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00
Tentatively declare support for unreleased base-4.13/ghc-8.8

- - - - -
6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00
Normalise LICENSE text w/ cabal's BSD2 template

Also, correct the `.cabal` files to advertise `BSD2` instead
of the incorrect `BSD3` license.

- - - - -
0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00
CI: fetch GHC from validate artifact

Should help make CI be less broken

- - - - -
6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00
Fix some Hyperlinker test suite fallout

* Amend `ParserSpec` to match new Hyperlinker API
    - pass in compiler info
    - strip out null tokens

* Make `hypsrc-test` pass reliably
    - strip out `local-*` ids
    - strip out `line-*` ids from the `ClangCppBug` test
    - re-accept output

- - - - -
ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00
Update README instructions for Stack

No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock.
- - - - -
723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00
Remove `Documentation.Haddock.Utf8`

The circumstances under which this module appeared are completely gone.
The Hyperlinker backend no longer needs this module (it uses the more
efficient `Encoding` module from `ghc`).

Why no deprecation? Because this module really shouldn't exist!

  - It isn't used in `haddock-library`/`haddock-api` anymore
  - It was copy pasted directly from `utf8-string`
  - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding`

- - - - -
51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00
Miscellaneous improvements to `Convert` (#1020)

Now that Haddock is moving towards working entirely over `.hi` and `.hie` files,
all declarations and types are going to be synthesized via the `Convert` module.
In preparation for this change, here are a bunch of fixes to this module:

  * Add kind annotations to type variables in `forall`'s whose kind is not `Type`,
    unless the kind can be inferred from some later use of the variable. See
    `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this.

  * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with
    what GHC's `toIfaceTypeX` does and checking the first argument of
    `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker
    (see `isPredTy`). 

  * Beef up the logic around figuring out when an explicit `forall` is needed. This
    includes: observing if any of the type variables will need kind signatures, if the
    inferred type variable order _without_ a forall will still match the one GHC
    claims, and some other small things.

  * Add some (not yet used) functionality for default levity polymorphic type
    signatures. This functionality similar to `fprint-explicit-runtime-reps`.

Couple other smaller fixes only worth mentioning:

  * Show the family result signature only when it isn't `Type`
  * Fix rendering of implicit parameters in the LaTeX and Hoogle backends
  * Better handling of the return kind of polykinded H98 data declarations
  * Class decls produced by `tyThingToLHsDecl` now contain associated type
    defaults and default method signatures when appropriate
  * Filter out more `forall`'s in pattern synonyms
- - - - -
841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00
Make a fixture of weird parsing of lists (#997)

The second example is interesting.
If there's a list directly after the header, and that list has
deeper structure, the parser is confused: It finds two lists:

 - One with the first nested element,
 - everything after it

I'm not trying to fix this, as I'm not even sure this is a bug,
and not a feature.

- - - - -
7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00
Fix haskell/haddock#1015 with dataConUserTyVars (#1022)

The central trick in this patch is to use `dataConUserTyVars` instead of
`univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in
a way that's more faithful to how the user originally wrote it.

Fixes haskell/haddock#1015.
- - - - -
ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00
Changes from haskell/haddock#14579

We now have a top-level `tyConAppNeedsKindSig` function, which means
that we can delete lots of code in `Convert`.

- - - - -
1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00
Matching changes in GHC for haskell/haddock#16236

- - - - -
ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00
Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise

Normalise LICENSE text w/ cabal's BSD2 template
- - - - -
5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00
Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head

- - - - -
c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00
Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027)

This means that `html-test`, `latex-test`, `hoogle-test`, and
`hypsrc-test` now only depend on GHC boot libs. So we should
now be able to build and run these as part of GHC's testsuite. \o/

The reference output has changed very slightly, in three ways:

  * we don't convert quotes back into `&quot;` as the `xml` lib did
  * we don't add extra `&nbsp;` as the `xml` lib did
  * we now remove the entire footer `div` (instead of just emptying it)
- - - - -
65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00
Remove workaround for now-fixed Clang CPP bug (#1028)

Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where
lines that started with an octothorpe but turned out not
to lex like pragmas would have an extra line added after them.

Since this bug has been fixed upstream and that it doesn't have dire
consequences anyways, the workaround is not really worth it
anymore - we can just tell people to update their clang version (or re-structure
their pragma code).
- - - - -
360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00
Clean up logic for guessing `-B` and `--lib` (#1026)

Haddock built with the `in-ghc-tree` flag tries harder to find the GHC
lib folder and its own resources. This should make it possible to use
`in-ghc-tree`-built Haddock without having to specify the `-B` and
`--lib` options (just how you can use in-tree GHC without always
specifying the `-B` option).

The logic to do this relies on `getExecutablePath`, so we only get
this auto-detection on platforms where this function works.
- - - - -
d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00
Fix tests broken by GHC

Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some
of the hyperlinker output. Accepted the new output (hovering over a
`..` now shows you what that wildcard binds).

Also fixed some stray deprecation warnings.

- - - - -
da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00
Parser changes to match !380

- - - - -
ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00
Bump ghc version to 8.9

- - - - -
44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00
Match GHC changes for T16185

`FunTy` now has an `AnonArgFlag` that indicates whether the arrow is
a `t1 => t2` or `t1 -> t2`.

This commit shouldn't change any functionality in Haddock.

- - - - -
2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00
Update .travis.yml

Points to the new GHC CI artifact.
- - - - -
90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00
Support value/type namespaces on identifier links

Identifier links can be prefixed with a 'v' or 't' to indicate the value or
type namespace of the desired identifier. For example:

-- | Some link to a value: v'Data.Functor.Identity'
--
-- Some link to a type: t'Data.Functor.Identity'

The default is still the type (with a warning about the ambiguity)

- - - - -
d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00
Better identifier parsing

  * '(<|>)' and '`elem`' now get parsed and rendered properly as links
  * 'DbModule'/'DbUnitId' now properly get split apart into two links
  * tuple names now get parsed properly
  * some more small niceties...

The identifier parsing code is more precise and more efficient (although to be
fair: it is also longer and in its own module). On the rendering side, we need
to pipe through information about backticks/parens/neither all the way through
from renaming to the backends.

In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc
lib docs change. The only "regression" is things like '\0'. These should be
changed to @\\0@ (the path by which this previously worked seems accidental).

- - - - -
3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00
Fix standalone deriving docs

Docs on standalone deriving decls for classes with associated types
should be associated with the class instance, not the associated type
instance.

Fixes haskell/haddock#1033

- - - - -
d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00
Fix bogus identifier defaulting

This avoids a situation in which an identifier would get defaulted to
a completely different identifier. Prior to this commit, the 'Bug1035'
test case would hyperlink 'Foo' into 'Bar'!

Fixes haskell/haddock#1035.

- - - - -
88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00
Visible dependent quantification (#16326) changes

- - - - -
0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00
Menu item controlling which instances are expanded/collapsed (#1007)

Adds a menu item (like "Quick Jump") for options related to displaying
instances. This provides functionality for:

  * expanding/collapsing all instances on the currently opened page
  * controlling whether instances are expanded/collapsed by default
  * controlling whether the state of instances should be "remembered"

This new functionality is implemented in Typescript in `details-helper`.
The built-in-themes style switcher also got a revamp so that all three
of QuickJump, the style switcher, and instance preferences now have
the same style and implementation structure.

See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html

Fixes haskell/haddock#698.

Co-authored-by: Lysxia <lysxia at gmail.com>
Co-authored-by: Nathan Collins <conathan at galois.com>


- - - - -
3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00
`--show-interface` should output to stdout. (#1040)

Fixes haskell/haddock#864.
- - - - -
a50f4cda by gbaz at 2019-03-01T07:43:16-08:00
Increase contrast of Linuwal theme (#1037)

This is to address the concern that, on less nice and older screens,
some of the shades of grey blend in too easily with the white
background.

 * darken the font slightly
 * darken slightly the grey behind type signatures and such
 * add a border and round the corners on code blocks
 * knock the font down by one point
- - - - -
ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00
Merge branch 'ghc-8.6' into ghc-8.8

- - - - -
12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00
Remove reference to Opt_SplitObjs flag

Split-objects has been removed.

- - - - -
5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00
Update html-test output to reflect haskell/haddock#16391 changes

- - - - -
fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00
Match changes for "Stop inferring over-polymorphic kinds"

The `hsq_ext` field of `HsQTvs` is now just the implicit variables
(instead of also including information about which of these variables
are dependent).

This commit shouldn't change any functionality in Haddock.

- - - - -
6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00
Add .hi, .dyn_hi, etc files to .gitignore

Fixes haskell/haddock#1030.

- - - - -
b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00
Better support for default methods in classes

  * default methods now get rendered differently
  * default associated types get rendered
  * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend
  * LaTeX backend now renders default method signatures

NB: there is still no way to document default class members and the
NB: LaTeX backend still crashes on associated types

- - - - -
10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00
Avoid multi-line `emph` in LaTeX backend

`markupWarning` often processes inputs which span across paragraphs.
Unfortunately, LaTeX's `emph` is not made to handle this (and will
crash).

Fixes haskell/haddock#936.

- - - - -
d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00
Many LaTeX backend fixes

After this commit, we can run with `--latex` on all boot libraries
without crashing (although the generated LaTeX still fails to compile in
a handful of larger packages like `ghc` and `base`).

 * Add newlines after all block elements in LaTeX. This is important to
   prevent the final output from being more an more indented. See the
   `latext-test/src/Example` test case for a sample of this.

 * Support associated types in class declarations (but not yet defaults)

 * Several small issues for producing compiling LaTeX;
     - avoid empy `\haddockbeginargs` lists (ex: `type family Any`)
     - properly escape identifiers depending on context (ex: `Int#`)
     - add `vbox` around `itemize`/`enumerate` (so they can be in tables)

 * Several spacing fixes:
     - limit the width of `Pretty`-arranged monospaced code
     - cut out extra space characters in export lists
     - only escape spaces if there are _multiple_ spaces
     - allow type signatures to be multiline (even without docs)

 * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files
   from `latex-test` test reference output.

Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile)
Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...)

- - - - -
0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00
Remove workaround for now-fixed Clang CPP bug (#1028)

Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where
lines that started with an octothorpe but turned out not
to lex like pragmas would have an extra line added after them.

Since this bug has been fixed upstream and that it doesn't have dire
consequences anyways, the workaround is not really worth it
anymore - we can just tell people to update their clang version (or re-structure
their pragma code).

- - - - -
ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00
Matching changes in GHC for haskell/haddock#16236

(cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576)

- - - - -
d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00
Bump GHC to 8.8

- - - - -
5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00
Redo ParseModuleHeader

- - - - -
b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00
Comment C, which clarifies why e.g. ReadP is not enough

- - - - -
bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00
Remove outdated `.ghci` files and `scripts`

The `.ghci` files are actively annoying when trying to `cabal v2-repl`.
As for the `scripts`, the distribution workflow is completely different.

- - - - -
5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00
Remove obsolete arcanist files + STYLE

Now that GHC is hosted on Gitlab, the arcanist files don't make sense
anymore. The STYLE file contains nothing more than a dead link too.

- - - - -
d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00
Redo ParseModuleHeader

- - - - -
492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00
Comment C, which clarifies why e.g. ReadP is not enough

- - - - -
af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00
Changes for haskell/haddock#16110/#16356

- - - - -
6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00
Unbreak haskell/haddock#1004 test case

`fail` is no longer part of `Monad`.

- - - - -
6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00
Fix haskell/haddock#1063 with better parenthesization logic for contexts

The only other change in html/hoogle/hyperlinker output for the boot
libraries that this caused is a fix to some Hoogle output for implicit
params.

```
$ diff -r _build/docs/ old_docs
diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt
13296c13296
< assertError :: (?callStack :: CallStack) => Bool -> a -> a
---
> assertError :: ?callStack :: CallStack => Bool -> a -> a
```

- - - - -
b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00
Match changes with haskell/haddock#14332

- - - - -
c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00
Remove Haddock's dependency on `Cabal`

At this point, Haddock depended on Cabal-the-library solely for a
verbosity parser (which misleadingly accepts all sorts of verbosity
options that Haddock never uses). Now, the only dependency on Cabal
is for `haddock-test` (which uses Cabal to locate the Haddock interface
files of a couple boot libraries).

- - - - -
e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00
Regression test: promoted lists in associated types

When possible, associated types with promoted lists should use the
promoted list literal syntax (instead of repeated applications of
': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c.

Closes haskell/haddock#466,

- - - - -
cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00
Merge branch 'ghc-8.6' into ghc-8.8

- - - - -
4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00
Release haddock-2.23, haddock-library-1.8.0

Tentatively adjust bounds and changelogs for the release to be bundled
with GHC 8.8.1.

- - - - -
69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00
Update hyperlinker tests for new types in .hie files

- - - - -
29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00
update for new way to store hiefile headers

- - - - -
aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00
update for new way to store hiefile headers

- - - - -
ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00
Update test output for introduction of Safe-Inferred

- - - - -
3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00
Changes for haskell/haddock#15247

- - - - -
0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00
Fix haddockHypsrcTest

- - - - -
2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00
Fix for GHC module renaming

- - - - -
9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00
Fix Travis CI, loosen .cabal bounds (#1089)

Tentatively for the 2.23 release:

  * updated Travis CI to work again
  * tweaked bounds in the `.cabal` files
  * adjusted `extra-source-files` to properly identify test files
- - - - -
ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00
Small change in to facilitate extended typed-holes (#1090)

This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later.
- - - - -
02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00
Remove spaces around @-patterns (#1093)

This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented.
- - - - -
83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00
Fix the ignore-exports option (#1082)

The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it.
- - - - -
e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00
Fix a few haddock issues

- - - - -
3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00
Fix crash when there are no srcspans in the file due to CPP

- - - - -
339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00
Prefer un-hyperlinked sources to no sources

It is possible to fail to extract an HIE ast. This is however not a
reason to produce _no_ output - we should still make a colorized HTML
page.

- - - - -
d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00
Add a regression test for haskell/haddock#1091

Previously, this input would crash Haddock.

- - - - -
ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00
Add Hyperlinker test cases for TH-related stuff

Hopefully this will guard against regressions around quasiquotes, TH
quotes, and TH splices.

- - - - -
d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00
Refactor for withTiming changes.

- - - - -
4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00
Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor

Refactor for withTiming changes.
- - - - -
d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00
Reify oversaturated data family instances correctly (#1103)

This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see
https://gitlab.haskell.org/ghc/ghc/issues/17296 and
https://gitlab.haskell.org/ghc/ghc/merge_requests/1877).

- - - - -
331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00
Refactor for OutputableBndrId changes

- - - - -
48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00
Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable

Refactor for OutputableBndrId changes
- - - - -
f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00
Define `XRec` for location information and get rid of `HasSrcSpan`

In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a
simpler way to encode location information into the GHC and Haddock AST
while incurring no cost for e.g. TH which doesn't need location
information.

These are just changes that have to happen in lock step.

- - - - -
d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00
Changes from haskell/haddock#14579

We now have a top-level `tyConAppNeedsKindSig` function, which means
that we can delete lots of code in `Convert`.

(cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70)

- - - - -
dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00
Define `XRec` for location information and get rid of `HasSrcSpan`

In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a
simpler way to encode location information into the GHC and Haddock AST
while incurring no cost for e.g. TH which doesn't need location
information.

These are just changes that have to happen in lock step.

- - - - -
0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00
Import isRuntimeRepVar from Type rather than TyCoRep

isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441.

- - - - -
091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00
Bump to GHC 8.10

- - - - -
e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00
Merge pull request haskell/haddock#1110 from haskell/wip/T17441

Import isRuntimeRepVar from Type rather than TyCoRep
- - - - -
4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00
Version bumps for GHC 8.11

- - - - -
0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00
Bump to GHC 8.10

- - - - -
00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00
Bump ghc version to 8.11

- - - - -
dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00
Drop support for base 4.13

- - - - -
f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00
Update Hyperlinker.Parser.classify to use ITdollar

- - - - -
1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00
Remove HasSrcSpan (#17494)

- - - - -
651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00
Document error-prone conditional definition of instances

This can easily trip up people if one isn't aware of it. Usually it's
better to avoid this kind of conditionality especially for typeclasses
for which there's an compat-package as conditional instances like
these tend to fragment the ecosystem into those packages that go the
extra mile to provide backward compat via those compat-packages and
those that fail to do so.

- - - - -
b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00
Fix build-failure regression for base < 4.7

The `$>` operator definition is available only since base-4.7 which
unfortunately wasn't caught before release to Hackage (but has been
fixed up by a metadata-revision)

This commit introduces a `CompatPrelude` module which allows to reduce
the amount of CPP by ousting it to a central location, i.e. the new
`CompatPrelude` module. This pattern also tends to reduce the tricks
needed to silence unused import warnings.

Addresses haskell/haddock#1119

- - - - -
556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00
Fix after Iface modules renaming

- - - - -
bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00
hsyl20-modules-renamer

- - - - -
fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00
Changes for GHC#17608

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372

- - - - -
4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00
Changes for GHC#17566

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469

- - - - -
e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00
Rename PackageConfig into UnitInfo

- - - - -
ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00
Rename lookupPackage

- - - - -
ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00
Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two

Changes for GHC#17566
- - - - -
3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00
Merge branch 'wip-hsyl20-package-refactor' into ghc-head

- - - - -
602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00
Echo GHC's removal of PlaceHolder module

This goes with GHC's !2083.

- - - - -
ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00
Module hierarchy: runtime (cf haskell/haddock#13009)

- - - - -
554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00
Fix build of haddock in stage1

We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter.

- - - - -
5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00
Noramlize `tested-with` fields in cabal files

- - - - -
e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00
No MonadFail/Alternative for P

- - - - -
90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00
Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build

Fix build of haddock in stage1
- - - - -
93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00
Modules: Driver (#13009)

- - - - -
da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00
Use RealSrcSpan in InstMap

- - - - -
479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00
Merge remote-tracking branch 'upstream/ghc-head' into HEAD

- - - - -
55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00
Modules: Core (#13009)

- - - - -
60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00
Ignore the BufLoc/BufSpan added in GHC's !2516

- - - - -
1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00
Modules: Core (#13009)

- - - - -
6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00
Changes in GHC's !1913.

- - - - -
30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00
Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2

Modules: Core (#13009)
- - - - -
cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00
Modules: Types

- - - - -
b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00
Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types

Modules: Types
- - - - -
9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00
Replace the 'caption' class so that the collapsible sections are shown

- - - - -
5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00
Force ghc-8.8.3

- - - - -
c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00
Update test fixtures

- - - - -
5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00
Modules: Types

- - - - -
7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00
Merge branch 'ghc-8.8' into ghc-8.10

- - - - -
b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00
Update parsing to strip whitespace from table cells (#1074)

* Update parsing to strip leading & trailing whitespace from table cells

* Update fixture data to disallow whitespaces at both ends in table cells

* Add test case for whitespaces stripped from both ends of table cells

* Update table reference test data for html tests

- - - - -
b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00
Clean up warnings

  * unused imports
  * imports of `Data.List` without import lists
  * missing `CompatPrelude` file in `.cabal`

- - - - -
0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00
Fix NPM security warnings

This was done by calling `npm audit fix`. Note that the security issues
seem to have been entirely in the build dependencies, since the output
JS has not changed.

- - - - -
6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00
Tentative 2.24 release

Adjusted changelogs and versions in `.cabal` files in preparation for
the upcoming release bundled with GHC 8.10.

- - - - -
1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00
Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD

More changes from the GHC types module refactoring.

- - - - -
be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00
Update `.travis.yml` to work with GHC 8.10.1

  * Regenerated the Travis file with `haskell-ci`

  * Beef up `.cabal` files with more `tested-with` information

- - - - -
b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00
Update README

Removed some out of date links/info, added some more useful links.

  * badge to Hackage
  * update old trac link
  * `ghc-head` => `ghc-8.10`
  * `cabal new-*` is now `cabal v2-*` and it should Just Work
  * `--test-option='--accept'` is the way to accept testsuite output

- - - - -
564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00
Fix crash in `haddock-library` on unicode space

Our quickcheck tests for `haddock-library` stumbled across an edge case
input that was causing Haddock to crash: it was a unicode space
character.

The root cause of the crash is that we were implicitly assuming that
if a space character was not " \t\f\v\r", it would have to be "\n".
We fix this by instead defining horizontal space as: any space character
that is not '\n'.

Fixes haskell/haddock#1142

- - - - -
2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00
Disallow qualified uses of reserved identifiers

This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too,
but it is a relatively easy fix in Haddock. Note that the fix must live
in `haddock-api` instead of `haddock-library` because we can only really
decide if an identifier is a reserved one by asking the GHC lexer.

Fixes haskell/haddock#952

- - - - -
47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00
Remove unused `Haddock.Utils` functions

  * removed functions in `Haddock.Utils` that were not used anywhere
    (or exported from the `haddock-api` package)

  * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils`

- - - - -
c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00
Use TTG empty extensions to remove some `error`'s

None of these error cases should ever have been reachable, so this is
just a matter of leveraging the type system to assert this.

  * Use the `NoExtCon` and `noExtCon` to handle case matches for no
    extension constructors, instead of throwing an `error`.

  * Use the extension field of `HsSpliceTy` to ensure that this variant
    of `HsType` cannot exist in an `HsType DocNameI`.

- - - - -
0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00
Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL`

 * `unL` is already defined by GHC as `unLoc`
 * `reL` is already defined by GHC as `noLoc` (in a safer way too!)
 * Condense `setOutputDir` and add a about exporting from GHC

Fixes haskell/haddock#978

- - - - -
bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00
Cleanup up GHC flags in `.cabal` files

  * enable more useful warning flags in `haddock-api`, handle the new
    warnings generated

  * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in
    `-Wall` for a while now)

- - - - -
c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00
`haddock-library` document header level

Document the fact the header level is going to always be between 1 and 6
inclusive. Along the way, I also optimized the parsing code a bit.

- - - - -
71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00
Disallow links in section headers

This is quite straightforward to implement, since we already had a
function `docToHtmlNoAnchors` (which we used to generate the link in the
sidebar "Contents").

This breaks test `Bug387`, but that test case has aged badly: we now
automatically generate anchors for all headings, so manually adding an
anchor in a section makes no sense. Nested anchors are, as pointed out
in haskell/haddock#1054, disallowed by the HTML standard.

Fixes haskell/haddock#1054

- - - - -
b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00
Modules: type checker

- - - - -
cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00
Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc

Module renaming
- - - - -
5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00
Allow QuickCheck 2.14

Builds fine and all tests pass.
- - - - -
dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00
Module renaming: amend previous patch

- - - - -
eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00
Fix haskell/haddock#1050 by filtering out invisible AppTy arguments

This makes the `synifyType` case for `AppTy` more intelligent by
taking into consideration the visibilities of each `AppTy` argument
and filtering out any invisible arguments, as they aren't intended
to be displayed in the source code. (See haskell/haddock#1050 for an example of what
can happen if you fail to filter these out.)

Along the way, I noticed that a special `synifyType` case for
`AppTy t1 (CoercionTy {})` could be consolidated with the case below
it, so I took the opportunity to tidy this up.

- - - - -
23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00
Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc

Module renaming: amend previous patch
- - - - -
072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00
Make NoExtCon fields strict

These changes are a part of a fix for
[GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992).

- - - - -
d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00
Recode Doc to Json. (#1159)

* Recode Doc to Json.

* More descriptive field labels.
- - - - -
52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00
Module renaming

- - - - -
d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00
Add instance of XCollectPat for DocNameI

- - - - -
323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00
Rename XCollectPat -> CollectPass

- - - - -
2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00
Prune docstrings that are never rendered

When first creating a Haddock interface, trim `ifaceDocMap` and
`ifaceArgMap` to not include docstrings that can never appear in the
final output. Besides checking with GHC which names are exported, we
also need to keep all the docs attached to instance declarations (it is
much tougher to detect when an instance is fully private).

This change means:

  * slightly smaller interface files (7% reduction on boot libs)
  * slightly less work to do processing docstrings that aren't used
  * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070)

I've tested manually that this does not affect any of the boot library
generated docs (the only change in output was some small re-ordering in
a handful of instance lists). This should mean no docstrings have been
incorrectly dropped.

- - - - -
f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00
Don't warn about missing links in miminal sigs

When renaming the Haddock interface, never emit warnings when renaming a
minimal signature. Also added some documention around `renameInterface`.

Minimal signatures intentionally include references to potentially
un-exported methods (see the discussion in haskell/haddock#330), so it is expected
that they will not always have a link destination. On the principle
that warnings should always be resolvable, this shouldn't produce a
warning. See haskell/haddock#1070.

- - - - -
a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00
Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools

Module renaming
- - - - -
f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00
Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat

- - - - -
a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00
Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat

Trees that Grow refactor (GHC !2553)
- - - - -
6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00
Fallback to `hiDecl` when `extractDecl` fails

Sometimes, the declaration being exported is a subdecl (for instance, a
record accessor getting exported at the top-level). For these cases,
Haddock has to find a way to produce some synthetic sensible top-level
declaration. This is done with `extractDecl`.

As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a
syntactic level (for instance when the subdecl is re-exported). In these
cases, the only sensible thing to do is to try to reify a declaration
based on a GHC `TyThing` via `hiDecl`.

- - - - -
eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00
Module structure

- - - - -
50b9259c by Iñaki at 2020-04-25T18:38:11-04:00
Add support for custom section anchors (#1179)

This allows to have stable anchors for groups, even if the set of
groups in the documentation is altered.

The syntax for setting the anchor of a group is

-- * Group name #desiredAnchor#

Which will produce an html anchor of the form '#g:desiredAnchor'

Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc>
- - - - -
4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00
Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils

Module structure
- - - - -
5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00
Renamed UnitInfo fields

- - - - -
c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00
UnitId has been renamed into Unit

- - - - -
3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00
Fix for GHC.Unit.* modules

- - - - -
ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00
Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid

Refactoring of Unit code
- - - - -
b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00
add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075)

- - - - -
9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00
Atomic update of NameCache in readHieFile

- - - - -
86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00
Fix after Config module renaming

- - - - -
a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00
Explicit Specificity Support for Haddock

- - - - -
46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00
Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config

Fix after Config module renaming
- - - - -
f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00
Explicit Specificity Support for Haddock

- - - - -
55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00
Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head

- - - - -
a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00
isBootSummary now produces a result of type IsBootInterface

- - - - -
ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00
update for hiefile-typeclass-info

- - - - -
49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00
Use floor over round to calculate the percentage (#1195)

If we compile documentation where only a small fraction is undocumented,
it is misleading to see 100% coverage - 99% is more intuitive.

Fixes haskell/haddock#1194
- - - - -
c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00
Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig

isBootSummary now produces a result of type IsBootInterface
- - - - -
74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00
haddock: Bounds bumps for GHC 8.12

- - - - -
b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00
testsuite: Update expected output for simplified subsumption

- - - - -
624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00
Changes for GHC#18191

See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337.

- - - - -
fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00
Fix after unit refactoring

- - - - -
743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00
Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii

Fix after unit refactoring
- - - - -
d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00
Use HsForAllTelescope (GHC#18235)

- - - - -
389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00
haddock: Bounds bumps for GHC 8.12

- - - - -
7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00
Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12

haddock: Bounds bumps for GHC 8.12
- - - - -
9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00
Adapt Haddock to LinearTypes

See ghc/ghc!852.

- - - - -
46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30
Use functions exported from HsToCore

- - - - -
8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00
Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore

Use functions exported from GHC.HsToCore.Docs
- - - - -
22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00
Adapt Haddock for QualifiedDo

- - - - -
3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00
Handle LexicalNegation's ITprefixminus

- - - - -
03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00
Rename hsctarget into backend

- - - - -
ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00
Update for UniqFM changes.

- - - - -
9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00
Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm

Update for UniqFM changes.
- - - - -
68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00
Sync with GHC removing {-# CORE #-} pragma

See ghc ticket haskell/haddock#18048

- - - - -
eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00
Rename hscTarget into backend

- - - - -
fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00
Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg

Rename hscTarget into backend
- - - - -
1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00
Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head

- - - - -
d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30
Update for modular ping pong

- - - - -
8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00
Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong

Modular ping pong
- - - - -
a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00
Bump GHC version to 9.0

- - - - -
6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00
Fix after Outputable refactoring

- - - - -
c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00
Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception

Fix after Outputable refactoring
- - - - -
d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00
Fix after HomeUnit

- - - - -
8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00
Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit

Fix after HomeUnit
- - - - -
8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00
Remove Ord FastString instance

- - - - -
8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00
Another round of `npm audit fix` (#1228)

This should shut down the warnings on Github. Note that the security issues
seem to have been entirely in the build dependencies, since the output
JS has not changed.

Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0

Co-authored-by: Alex Biehl <alex.biehl at target.com>
- - - - -
7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00
Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord

Remove Ord FastString instance
- - - - -
ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00
Match GHC for haskell/haddock#18639, remove GENERATED pragma

- - - - -
a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00
Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma,

Match GHC for haskell/haddock#18639, remove GENERATED pragma
- - - - -
1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00
Bump GHC version to 9.1

- - - - -
6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00
Bump base upper bound to 4.16

- - - - -
a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00
Update hypsrc-test for QuickLook

This appears to be a spurious change.

- - - - -
e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00
Updates for the new linear types syntax: a %p -> b

- - - - -
30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00
Update for parser (#1234)


- - - - -
b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00
Updates for the new linear types syntax: a %p -> b

- - - - -
0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00
Adapt to GHC parser changes

- - - - -
b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00
Don't pass the HomeUnitId (#1239)


- - - - -
34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00
Changed tests due to unification of `Nat` and `Natural`

in the follwing merge request:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583

- - - - -
256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00
Add whitespace in: map ($ v)

- - - - -
4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

- - - - -
072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

(cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1)

- - - - -
9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

(cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1)

- - - - -
636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00
GHC.Driver.Types refactoring (#1242)


- - - - -
a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00
Adapt to the removal of Hs{Boxed,Constraint}Tuple

See ghc/ghc!4097 and GHC#18723.

- - - - -
b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00
Adapt to HsConDecl{H98,GADT}Details split

Needed for GHC#18844.

- - - - -
c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00
Adapt to HsOuterTyVarBndrs

These changes accompany ghc/ghc!4107, which aims to be a fix
for haskell/haddock#16762.

- - - - -
a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00
Adapt to splitPiTysInvisible being renamed to splitInvisPiTys

This is a part of !4434, a fix for GHC#18939.

- - - - -
66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00
Fix after Plugins moved into HscEnv

- - - - -
508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00
Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv

Fix after Plugins moved into HscEnv
- - - - -
620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00
Update for changes in GHC's Pretty

- - - - -
01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00
Avoid GHC#18932.

- - - - -
8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00
Add type arguments to PrefixCon

- - - - -
414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00
DynFlags's unit fields moved to HscEnv

- - - - -
e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00
Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate

Unit fields moved from DynFlags to HscEnv
- - - - -
7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00
Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps

Update for changes in GHC's Pretty
- - - - -
fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00
Fix docs links from Darcs to GitHub in intro (#1262)


- - - - -
7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00
Use gender neutral word in docs (#1260)


- - - - -
1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00
Allow scrolling search results (#1235)

Closes https://github.com/haskell/haddock/issues/1231
- - - - -
8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00
Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255)

Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3.
- [Release notes](https://github.com/rvagg/bl/releases)
- [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3)

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00
Allow more characters in anchor following module reference (#1220)


- - - - -
14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00
Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243)

* Fix multiple typos and inconsistencies in doc/markup.rst

Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from
@parsonsmatt after creating these proposed changes - mea culpa for not
looking at the open PRs sooner.

* Fix haskell/haddock#1113 If no Signatures, no section of index.html

* Change the formatting of missing link destinations

The current formatting of the missing link destination does not really
help user to understand the reasons of the missing link.

To address this, I've changed the formatting in two ways:

- the missing link symbol name is now fully qualified. This way you
immediately know which haskell module cannot be linked. It is then easier
to understand why this module does not have documentation (hidden module
or broken documentation).
- one line per missing link, that's more readable now that symbol name
can be longer due to qualification.

For example, before haddock was listing missing symbol such as:

```
could not find link destinations for:
  Word8 Word16 mapMaybe
```

Now it is listed as:

```
could not find link destinations for:
  - Data.Word.Word8
  - Data.Word.Word16
  - Data.Maybe.mapMaybe
```

* Add `--ignore-link-symbol` command line argument

This argument can be used multiples time. A missing link to a symbol
listed by `--ignore-link-symbol` won't trigger "missing link" warning.

* Forbid spaces in anchors (#1148)

* Improve error messages with context information (#1060)

Co-authored-by: Matt Audesse <matt at mattaudesse.com>
Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com>
Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io>
Co-authored-by: Pepe Iborra <pepeiborra at gmail.com>
- - - - -
89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00
Enable two warnings (#1245)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656
- - - - -
c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00
simplify calculating percentages fixing haskell/haddock#1194 (#1236)


- - - - -
685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00
Changes for GHC#17566

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469

- - - - -
be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00
Import intercalate

- - - - -
32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00
Adapt Haddock for QualifiedDo

- - - - -
31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00
Fix haddock-library tests

- - - - -
fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00
Move to GitHub CI (#1266)

* Initial version of ci.yml

This is a straight copy from Dmitrii Kovanikov's blog post
at https://kodimensional.dev/github-actions.

Will adapt to haddock in successive commits.

* Delete .travis.yml

* Modify to only test on ghc-8.10.{1,2}

* Use actions/setup-haskell at v1.1.4

* Relax QuickCheck bound on haddock-api

* Remove stack matrix for now

* Nail down to ghc-8.10 branch for now

* Pin index state to 2020-12-08T20:13:44Z for now

* Disable macOS and Windows tests for now for speed up
- - - - -
5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00
Enable two warnings (#1245) (#1268)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656
- - - - -
bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00
Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269)

Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7.
- [Release notes](https://github.com/isaacs/ini/releases)
- [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7)

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00
Update for boxed rep

- - - - -
a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00
Revert "Enable two warnings (#1245) (#1268)"

As this does not build on GHC `master`.

This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce.

- - - - -
a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00
Revert "Update for boxed rep"

This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d.

- - - - -
53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00
Update output for nullary TyConApp optimisation (ghc/ghc!2952)

- - - - -
4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00
Display linear/multiplicity arrows correctly (#1238)

Previously we were ignoring multiplicity and displayed
a %1 -> b as a -> b.
- - - - -
ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00
Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym

Needed for !4417, the fix for GHC#15706 and GHC#18914.

- - - - -
ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00
Enable two warnings (#1245) (#1268)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656

- - - - -
d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00
Fix after binder collect changes

- - - - -
bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00
Adapt to changes to GlobalRdrElt and AvailInfo

Needed for ghc/ghc!4467

- - - - -
37736c4c by John Ericson at 2020-12-28T12:27:02-05:00
Support a new ghc --make node type for parallel backpack upsweep

- - - - -
717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00
Inline and fix getGADTConTypeG

The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782.

I noticed that getGADTConTypeG was only used in the Hoogle backend.
Interestingly, when handling H98 constructors, Hoogle converts RecCon to
PrefixCon (see Haddock.Backends.Hoogle.ppCtor).

So I changed getGADTConTypeG to handle RecConGADT in the same manner as
PrefixConGADT, and after this simplification moved it into the 'where'
clause of ppCtor, to the only place where it is used.

The practical effect of this change is as follows.
Consider this example:
	data TestH98 = T98 { bar::Int }
	data TestGADT where
	  TG :: { foo :: Int } -> TestGADT

Before this patch,  haddock --hoogle  used to produce:
	T98 :: Int -> TestH98
	[TG] :: {foo :: Int} -> TestGADT

Notice how the record syntax was discarded in T98 but not TG.
With this patch, we always produce signatures without record syntax:
	T98 :: Int -> TestH98
	[TG] :: Int -> TestGADT

I suspect this might also be a bugfix, as currently Hoogle doesn't seem
to render GADT record constructors properly.

- - - - -
cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00
Build instructions: haddock-library and -api first!

- - - - -
b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00
Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j

Changes to support -j with backpack
- - - - -
120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00
Merge pull request haskell/haddock#1282 from andreasabel/master

Build instructions: haddock-library and -api first!
- - - - -
fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00
Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0

- - - - -
b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00
Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0

- - - - -
81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00
Prepare Haddock for being a GHC Plugin

- - - - -
b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00
Make Haddock a GHC Plugin

- - - - -
cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00
Add -j[n] CLI param to Haddock executable

It translates to `--ghcopt=-j[n]`

- - - - -
84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00
Abstract Monad for interface creation

I found that when running as a plugin the lookupName function (which
runs in Ghc monad) does not work correctly from the
typeCheckResultAction hook.

Instead, we abstracted the monad used when creating interfaces, so
that access to GHC session specific parts is explicit and so that the
TcM can provide their (correct) implementation of lookupName.

- - - - -
5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00
Accept tests

- - - - -
8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00
Add missing dependency for mtl

- - - - -
3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00
Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head

- - - - -
33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00
Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows

Fix after binder collect changes
- - - - -
70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00
Make haddock more robust to changes to the `Language` data type

With the introduction of GHC2021, the `Languages` data type in GHC will
grow. In preparation of that (and to avoid changing haddock with each
new language), this change makes the code handle extensions to that data
type gracefully.

(cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5)

- - - - -
7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00
Add `NoGhcTc` instance now that it's not closed

- - - - -
e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00
Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936

Add `NoGhcTc` instance now that it's not closed
- - - - -
989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00
Add import list to Data.List

- - - - -
368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00
Adapt to "Make PatSyn immutable"

- - - - -
abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00
Rename pprLogErrMsg to new name

- - - - -
e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00
Move CI to ghc-9.0

- - - - -
dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00
Update cabal.project and README build instructions

- - - - -
31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00
Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0

Merge the late additions to ghc-8.10 into ghc-9.0
- - - - -
6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00
Cleanup: fix build warnings

- - - - -
f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00
type level characters support for haddock (required for haskell/haddock#11342)

- - - - -
d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00
Add a CONTRIBUTING.md file

- - - - -
6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00
Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette

Add a CONTRIBUTING.md file
- - - - -
955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00
Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head

- - - - -
47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00
Amend the CONTRIBUTING.md file

- - - - -
23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00
Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing

Amend the CONTRIBUTING.md file
- - - - -
69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00
Display linear/multiplicity arrows correctly (#1238)

Previously we were ignoring multiplicity and displayed
a %1 -> b as a -> b.

(cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb)

- - - - -
ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00
Add import list to Data.List

- - - - -
5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00
Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list

Add import list to Data.List
- - - - -
1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00
Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge

- - - - -
13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00
Fix partial record selector warning

- - - - -
5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00
Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge

- - - - -
b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00
Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge

- - - - -
a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00
Merge branch 'wip/ghc-head-merge' into ghc-head

- - - - -
1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00
Fix search div not scrolling

- - - - -
684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00
Add support for labeled module references

Support a markdown-style way of annotating module references. For instance

-- | [label]("Module.Name#anchor")

will create a link that points to the same place as the module
reference "Module.Name#anchor" but the text displayed on the link will
be "label".

- - - - -
bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00
Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat

Backward compat: Add support for labeled module references
- - - - -
6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00
Merge pull request haskell/haddock#1314 from tweag/show-linear-backport

Backport haskell/haddock#1238 (linear types) to ghc-9.0
- - - - -
d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00
Remove dubious parseModLink

Instead construct the ModLink value directly when parsing.

- - - - -
33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00
Merge pull request haskell/haddock#1320 from haskell/alex/fix

Remove dubious parseModLink
- - - - -
54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00
Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0

Fix search div not scrolling
- - - - -
19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00
Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge

Merge ghc-8.10 into ghc-head
- - - - -
6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00
simplify calculating percentages fixing haskell/haddock#1194 (#1236)

- - - - -
c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00
Merge pull request haskell/haddock#1322 from haskell/alex/forward-port

simplify calculating percentages fixing haskell/haddock#1194 (#1236)
- - - - -
2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00
Merge branch 'ghc-head' into ghc-9.0
- - - - -
849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00
Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0

Merge ghc-9.0 into ghc-head
- - - - -
ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00
Update for Logger

- - - - -
4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00
Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2

Logger refactoring
- - - - -
922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00
Fix to build with HEAD

- - - - -
a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00
Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2

Fix to build with HEAD
- - - - -
0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00
Add UnitId to Target record

- - - - -
d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00
Stable sort for (data/newtype) instances

- - - - -
8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00
Also make TyLit deterministic

- - - - -
f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00
Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface

Stable sort for instances
- - - - -
5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00
Add import list to Data.List in Haddock.Interface.Create

- - - - -
fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00
Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports

Add import list to Data.List in Haddock.Interface.Create
- - - - -
f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00
Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target

Add UnitId to Target record
- - - - -
674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00
html-test: Always set language

from ghc-9.2 on, the “default” langauge of GHC is expected to change
more wildly. To prepare for that (and unblock
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the
language for all the test files to `Haskell2010`. This should insolate
this test suite against changes to the default.

Cherry-picked from https://github.com/haskell/haddock/pull/1341

- - - - -
f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00
Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head

html-test: Always set language
- - - - -
caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00
Clean-up of Interface and Interface.Create's imports and pragmata

- - - - -
f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00
Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports

[ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata 
- - - - -
7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00
Explicit imports for Haddock.Interface and Haddock.Interface.Create

- - - - -
6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00
Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface

Explicit imports for Haddock.Interface and Haddock.Interface.Create
- - - - -
9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00
Context becomes a Maybe in the GHC AST

This prevents noLoc's appearing in the ParsedSource.

Match the change in GHC.

- - - - -
0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00
Fix the call-site of guessTarget in Interface.hs

Explicit the imports from GHC.HsToCore.Docs

- - - - -
b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00
Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call

Fix the call-site of guessTarget in Interface.hs
- - - - -
9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00
Fix haddockHypsrcTest output in ghc-head

- - - - -
b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00
Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head

Fix haddockHypsrcTest output in ghc-head
- - - - -
3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00
Add ITproj to parser

- - - - -
d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00
Update for boxed rep

- - - - -
6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00
Update for "FastString: Use FastMutInt instead of IORef Int"

- - - - -
e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00
Implement template-haskell's putDoc

This catches up to GHC using the new extractTHDocs function, which
returns documentation added via the putDoc function (provided it was
compiled with Opt_Haddock). Since it's already a map from names -> docs,
there's no need to do traversal etc.
It also matches the change from the argument map being made an IntMap
rather than a Map Int

- - - - -
89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00
Match changes in GHC AST for in-tree API Annotations

As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418

- - - - -
28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00
Change some type family test results.

It is not clear to me whether the original was printing
incorrectly (since we did not have the TopLevel flag before now), or
if this behaviour is expected.

For the time being I am assuming the former.

- - - - -
7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00
Fix after NameCache changes

- - - - -
addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00
NameCache doesn't store a UniqSupply anymore

- - - - -
15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00
Bump GHC version to 9.2

- - - - -
dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00
Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1

NameCache refactoring
- - - - -
2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00
Specialization of Data.List

- - - - -
32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00
Add UnitId to Target record

This way we always know to which home-unit a given target belongs to.
So far, there only exists a single home-unit at a time, but it
enables having multiple home-units at the same time.

- - - - -
54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00
Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert

Add UnitId to Target record
- - - - -
7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00
EPA : Rename ApiAnn to EpAnn

- - - - -
72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00
pprError changed name in GHC

- - - - -
4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00
EPA : Rename ApiAnn to EpAnn

- - - - -
108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00
Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD

- - - - -
1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00
Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity

Rename pprError to mkParserErr
- - - - -
d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00
Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head

- - - - -
170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00
Bump GHC version to 9.3

- - - - -
a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00
Update for EPA changes in GHC

(cherry picked from commit cafb48118f7c111020663776845897e225607b41)

- - - - -
1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00
Removal of HsVersions.h (#1388)

* Update for EPA changes in GHC

* Account for HsVersions.h removal

Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>
- - - - -
79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00
Revert "Removal of HsVersions.h (#1388)"

This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6.

- - - - -
3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00
Update for EPA changes in GHC

- - - - -
2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00
Account for HsVersions.h removal

- - - - -
00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00
Add Haddock support for the OPAQUE pragma (#1380)


- - - - -
8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00
fixup! Use GHC 9.2 in CI runner

- - - - -
27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00
EPA: match changes from GHC T19834

- - - - -
f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00
Allow hspec 2.8 (#1389)

All tests are passing.
- - - - -
df44453b by Divam Narula at 2021-05-20T15:42:42+02:00
Update ref, the variables got renamed. (#1391)

This is due to ghc/ghc!5555 which caused a change in ModDetails in case of
NoBackend. Now the initModDetails is used to recreate the ModDetails from
interface and in-memory ModDetails is not used.
- - - - -
e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00
Remove Maybe from HsQualTy

Match changes in GHC for haskell/haddock#19845

- - - - -
79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00
FieldOcc: rename extFieldOcc to foExt

- - - - -
6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00
Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head

- - - - -
f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00
New Parser diagnostics interface

- - - - -
392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00
Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages

Align Haddock to use the new Parser diagnostics interface
- - - - -
33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00
Revert "Add Haddock support for the OPAQUE pragma (#1380)"

This reverts commit a1337c599ef7720b0482a25c55f11794112496dc.

The GHC patch associated with this change is not yet ready to be merged.

- - - - -
8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00
CI configuration for ghc-head (#1395)


- - - - -
1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00
Use GHC 9.2 in CI runner (#1378)


- - - - -
e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00
Add page about common errors (#1396)

* Update index.rst

Common errors page

* Create common-errors.rst

* Update common-errors.rst

* Use GHC 9.2 in CI runner (#1378)

* [haddock-api] remove .hspec-failures

Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com>
- - - - -
abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00
Adapt Haddock to Logger and Parser changes (#1399)


- - - - -
91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00
Update haddockHypSrc tests since we now compute slighly more type info (#1397)


- - - - -
ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00
Added myself to contributors

- - - - -
49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00
Document multi component support

- - - - -
9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00
Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support

Document multi component support
- - - - -
585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00
Update CONTRIBUTING.md (#1402)


- - - - -
1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00
Update CONTRIBUTING.md (#1403)


- - - - -
58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00
Update Haddock Bug873 to account for renaming

- - - - -
c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00
HsToken in FunTy, RecConGADT

- - - - -
1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00
Update the CI badges
- - - - -
6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00
Fix mkParserOpts (#1411)


- - - - -
18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00
Rename getErrorMessages Lexer import

This commit renames the Lexer import in `Hyperlinker.Parser` from
`getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity
with the `getErrorMessages` function defined in `GHC.Types.Error`.

- - - - -
23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00
Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920

Rename getErrorMessages Lexer import
- - - - -
b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00
EPA: match changes from GHC T19834

(cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2)

- - - - -
5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00
Merge commit '2a966c8ca37' into HEAD

- - - - -
cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00
coot/multiple packages (ghc-9.2) (#1418)


- - - - -
be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00
coot/multiple package (ghc-head) (#1419)

* FromJSON class

Aeson style FromJSON class with Parsec based json parser.

* doc-index.json file for multiple packages

When creating haddock summary page for multiple packages render
doc-index.json file using contents of all found 'doc-index.json' files.

* Render doc-index.json

When rendering html, render doc-index.json file independently of
maybe_index_url option.  doc-index.json file is useful now even if
maybe_index_url is not `Nothing`.

* base url option

New `Flag_BaseURL` which configures from where static files are loaded
(--base-url).  If given and not equal "." static files are not coppied,
as this indicates that they are not read from the the directory where
we'd copy them.  The default value is ".".
- - - - -
3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00
Update GHC 9.2 to latest pre-release in CI

- - - - -
7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00
Enable Haddock tests in GHC windows CI (#1428)

* testsuite: strip windows line endings for haddock

* hyperlinker: Work around double escaping (#19236)

* deterministic SCC
- - - - -
1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00
haddock-library does not depend on bytestring or transformers (#1426)


- - - - -
a890b9aa by sheaf at 2021-10-15T22:19:42+02:00
update haddockHypsrcTest for GHC MR !6705 (#1430)


- - - - -
42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00
Fix after PkgQual refactoring (#1429)


- - - - -
91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00
Update for changes in GHC for branch

wip/az/no-srcspan-anno-instances

- - - - -
acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00
Do not use forall as an identifier

See GHC ticket haskell/haddock#20609

- - - - -
c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00
Update after NoExtCon -> DataConCantHappen rename

- - - - -
b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00
fix CI for 9.2 (#1436)


- - - - -
25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00
Update html-test for Data.List revert

- - - - -
1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00
Add hint about inline link issue (#1444)


- - - - -
791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00
Bump ghc-head (#1445)

* Update after NoExtCon -> DataConCantHappen rename

* Update html-test for Data.List revert

* Fix for new Plugins datatype

Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>
- - - - -
44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00
Fix for new Plugins datatype

- - - - -
80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00
Remove ghc-head workflow (#1446)

Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore.
- - - - -
49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00
Remove use of ExtendedModSummary

- - - - -
0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00
update URLs
- - - - -
9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00
Fix solver for GHC 9.2

- - - - -
386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00
IDoc link has bitrotted; replaced with web.archive.org cache. (#1454)


- - - - -
d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00
Fix haddock user guide  (#1456)


- - - - -
cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00
Allow text-2.0 in haddock-library (#1459)


- - - - -
7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00
Add multi-line style hint to style section (#1460)


- - - - -
c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00
Fix CollectPass instance to match TTG refactor

Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614)

- - - - -
b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00
Link to (~)

- - - - -
877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00
Add Haddock support for the OPAQUE pragma

- - - - -
0ea22721 by askeblad at 2022-03-16T09:44:27+01:00
typos (#1464)


- - - - -
a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00
Minimum changes needed for compilation with hi-haddock

With hi-haddock, of course there is a much large refactoring of haddock
which could be achieved but that is left for a future patch which can
implemented at any time independently of GHC.

- - - - -
e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00
Update test output

- - - - -
6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00
Merge branch 'wip/opaque_pragma' into 'ghc-head'

Add Haddock support for the OPAQUE pragma

See merge request ghc/haddock!2
- - - - -
42208183 by Steve Hart at 2022-03-25T20:43:50+01:00
Fix CI (#1467)

* CI: Reinstall GHC with docs

CI tests were failing because the GHC preinstalled to the CI
environment does not include documentation, which is required for
running the Haddock tests. This commit causes the CI workflow to
reinstall GHC with docs so that tests can succeed.
- - - - -
9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00
Make links in Synopsis functional again (#1458)

Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to
e.preventDefault() when handling click events that reach a toggle
element. This prevents the browser from following hyperlinks within the
Synopsis section when they are clicked by a user. This commit restores
functioning hyperlinks within the Synopsis section by removing the call
to e.preventDefault(), as it does not appear to be necessary, and
removing it increases the flexibility of the details-helper code.
- - - - -
d1edd637 by sheaf at 2022-04-01T12:02:02+02:00
Keep track of promotion ticks in HsOpTy

Keeping track of promotion ticks in HsOpTy allows us to properly
pretty-print promoted constructors such as lists.

- - - - -
9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00
Add support for \cases

See merge request ghc/ghc!7873
- - - - -
b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00
spelling errors (#1471)


- - - - -
6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00
Rename [] to List

- - - - -
2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00
HsToken ConDeclGADT con_dcolon

- - - - -
90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00
Parse Markdown links at beginning of line within a paragraph (#1470)

* Catch Markdown links at beginning of line within paragraph

Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when
they occurred at the beginning of a line other than the first line of
the paragraph. This occurred because the parser was not interpreting a
left square bracket as a special character that could delimit special
markup. A space character was considered a special character, so, if a
space occurred at the beginning of the new line, then the parser would
interpret the space by itself and then continue parsing, thereby
catching the Markdown link. '\n' was not treated as a special character,
so the parser did not catch a Markdown link that may have followed.

Note that this will allow for Markdown links that are not surrounded by
spaces. For example, the following text includes a Markdown link that
will be parsed:

  Hello, world[label](url)

This is consistent with how the parser handles other types of markup.

* Remove obsolete documentation hint

Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the
need for the workaround suggested in the documentation.
- - - - -
5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00
Force ghc-9.2 in the cabal.project

- - - - -
0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00
Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469)

Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7.
- [Release notes](https://github.com/jbgutierrez/path-parse/releases)
- [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7)

---
updated-dependencies:
- dependency-name: path-parse
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00
Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468)

Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5.
- [Release notes](https://github.com/gulpjs/copy-props/releases)
- [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md)
- [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5)

---
updated-dependencies:
- dependency-name: copy-props
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00
Update for GHC 9.4

- - - - -
9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00
Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head

- - - - -
f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00
Bump ghc version to 9.5

- - - - -
e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00
Revert "Bump ghc-head (#1445)"

This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2.

This should not have been merged.

- - - - -
a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00
Merge commit '2627a86c' into ghc-head

- - - - -
0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4

- - - - -
b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00
Revert "HsToken ConDeclGADT con_dcolon"

This reverts commit 24208496649a02d5f87373052c430ea4a97842c5.

- - - - -
15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00
Bump base upper bound

- - - - -
165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00
Update test output

- - - - -
e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00
Add hlint action .hlint.yaml with ignores & CPP. (#1475)


- - - - -
ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00
fix grammar in docs: "can the" → "can be" (#1477)


- - - - -
cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00
Allow base-4.17

- - - - -
e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00
Remove unused imports that GHC warned about. (#1480)


- - - - -
222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00
Follow hlint suggestion to remove redundant bang. (#1479)


- - - - -
058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00
Follow hlint, remove language pragmas in libs. (#1478)


- - - - -
0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00
Keep track of ordered list indexes and render them (#1407)

* Keep track of ordered list indexes and render them

* Rename some identifiers to clarify
- - - - -
f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00
update for changes in GHC API

- - - - -
3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00
Add link to the readthedocs in cabal description to show on hackage.

(cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b)

- - - - -
5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00
remove Bug873

- - - - -
968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00
Ignore "Use second" HLint suggestion. It increases laziness.

- - - - -
02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00
Fix hyperlinks to external items and modules (#1482)

Fixes haskell/haddock#1481.

There were two bugs in this:
* We were assuming that we were always getting a relative path to the
  module in question, while Nix gives us file:// URLs sometimes. This
  change checks for those and stops prepending `..` to them.
* We were not linking to the file under the module. This seems
  to have been a regression introduced by haskell/haddock#977. That is, the URLs were
  going to something like
  file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src
  which does not have the appropriate HTML file or fragment for the item
  in question at the end.

There is a remaining instance of the latter bug, but not in the
hyperlinker: the source links to items reexported from other modules are
also not including the correct file name. e.g. the reexport of Entity in
esqueleto, from persistent.

NOTE: This needs to get tested with relative-path located modules. It seems
correct for Nix based on my testing.

Testing strategy:

```
nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson
mkdir /tmp/aesonbuild && cd /tmp/aesonbuild
export out=/tmp/aesonbuild/out
genericBuild

ln -sf $HOME/co/haddock/haddock-api/resources .
./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source
```
- - - - -
b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00
fix parsing trailing quotes in backticked identifiers (#1408) (#1483)


- - - - -
80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00
Fix "Defined by not used" error

(cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a)

- - - - -
4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00
Fix the changelog and bump the version of haddock-library on ghc-9.2

- - - - -
fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00
Fix the changelog and bump the version of haddock-library on ghc-9.2

- - - - -
b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00
Hide synopsis from search when hidden (#1486)

Fix haskell/haddock#1451
- - - - -
f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00
Allow to hide interfaces when rendering multiple components (#1487)

This is useful when one wishes to `--gen-contents` when rendering
multiple components, but one does not want to render all modules.  This
is in particular useful when adding base package.
- - - - -
f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00
Check if doc-index.json exists before reading it (#1488)


- - - - -
31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00
Version bump 2.26.1 (#1489)

* Version bump 2.26.1

We extended format accepted by `--read-interface` option, which requires
updating the minor version.

* Update documentation of --read-interface option
- - - - -
7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00
Updated HaddockHypsrcTest output for record update changes (MR !7981)

- - - - -
cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00
Use visibility to decide which interfaces are included in quickjump (#1490)

This is also consistent with how html index is build.  See
haskell/cabal#7669 for rationale behind this decision.
- - - - -
00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00
Add code of conduct and hspec failure files in .gitignore

- - - - -
2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00
Add code of conduct and hspec failure files in .gitignore

- - - - -
63a5650c by romes at 2022-05-31T12:43:22+01:00
TTG: Match new GHC AST

- - - - -
dd7d1617 by romes at 2022-06-02T16:11:00+01:00
Update for IE changes in !8228

- - - - -
c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00
Fix and improve CI (#1495)

* Pin GHC version before creating the freeze file

* Use newest action versions

* Improve caching

* Avoid unnecessarily reinstalling GHC

* Use GHC 9.2.2 for CI

Co-authored-by: Cyd Wise <cwise at tripshot.com>
- - - - -
c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00
Add Mergify configuration (#1496)


- - - - -
2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00
Bump haddock's version in cabal file to 2.26.1 (#1497)


- - - - -
d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00
Render module tree per package in the content page (#1492)

* Render module tree per package in the content page

When rendering content page for multiple packages it is useful to split
the module tree per package.  Package names in this patch are inferred
from haddock's interface file names.

* Write PackageInfo into interface file

To keep interface file format backward compatible, instead of using
`Binary` instance for `InterfaceFile` we introduce functions to
serialise and deserialise, which depends on the interface file version.
- - - - -
77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00
Fix haskell/haddock#783 Don't show button if --quickjump not present

- - - - -
b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00
Merge pull request haskell/haddock#1108 from mpilgrem/fix783

Fix haskell/haddock#783 Don't show button if --quickjump not present
- - - - -
6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00
Update the contribution guide

- - - - -
e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00
Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500)

Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3.
- [Release notes](https://github.com/substack/node-shell-quote/releases)
- [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md)
- [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3)

---
updated-dependencies:
- dependency-name: shell-quote
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
29d0ef70 by romes at 2022-07-06T11:29:39+02:00
TTG: AST Updates for !8308

- - - - -
1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00
Match GHC changes for T21805

This brings in a newtype for FieldLabelString

- - - - -
6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00
Bump hlint version to 3.4.1, the version with counts. (#1503)

Redo the counts available with the --default option.
- - - - -
48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00
Follow hlint suggestion: unused LANGUAGE pragma. (#1504)

* Follow hlint suggestion: unused LANGUAGE pragma.

* Ignore within modules to pass linting and pass tests.
- - - - -
c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00
Follow hlint suggestion: redundant $. (#1505)

* Follow hlint suggestion: redundant $.

* Remove $ and surplus blank lines in Operators.
- - - - -
74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00
Fix hyperlinks to external items and modules (#1482)

Fixes haskell/haddock#1481.

There were two bugs in this:
* We were assuming that we were always getting a relative path to the
  module in question, while Nix gives us file:// URLs sometimes. This
  change checks for those and stops prepending `..` to them.
* We were not linking to the file under the module. This seems
  to have been a regression introduced by haskell/haddock#977. That is, the URLs were
  going to something like
  file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src
  which does not have the appropriate HTML file or fragment for the item
  in question at the end.

There is a remaining instance of the latter bug, but not in the
hyperlinker: the source links to items reexported from other modules are
also not including the correct file name. e.g. the reexport of Entity in
esqueleto, from persistent.

NOTE: This needs to get tested with relative-path located modules. It seems
correct for Nix based on my testing.

Testing strategy:

```
nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson
mkdir /tmp/aesonbuild && cd /tmp/aesonbuild
export out=/tmp/aesonbuild/out
genericBuild

ln -sf $HOME/co/haddock/haddock-api/resources .
./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source
```

(cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a)

- - - - -
faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00
Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks

Backport 9-4: Fix hyperlinks to external items and modules (#1482)
- - - - -
5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00
Merge remote-tracking branch 'origin/ghc-9.4'

- - - - -
63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00
Clean up build and testsuite for GHC 9.4

- - - - -
d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00
Bump the versions

- - - - -
505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00
Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge

Merge GHC 9.4 into `main`
- - - - -
5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00
html-test: Testsuite changes for GHC 9.4.1

- - - - -
5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00
doc: Fix a few minor ReST issues

Sphinx was complaining about too-short title underlines.

- - - - -
220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00
Merge branch 'main' into ghc-head

- - - - -
fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00
Updates for GHC 9.5

- - - - -
eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00
HsToken ConDeclGADT con_dcolon

- - - - -
c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00
Updates for GHC 9.5

- - - - -
3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00
HsToken ConDeclGADT con_dcolon

- - - - -
a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00
Merge branch 'wip/ghc-head-bump' into ghc-head

- - - - -
af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00
Disuse `mapLoc`.

- - - - -
a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00
Scrub partiality about `NewOrData`.

- - - - -
2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00
Test output changed because of change to `base`

Spooky, but I guess that is intended?

- - - - -
a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00
update tests for the move of tuples to GHC.Tuple.Prim

- - - - -
461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00
match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion)

- - - - -
f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00
Update Haddock for GHC MR !8563 (configuration of diagnostics)

- - - - -
3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00
Class layout info

- - - - -
cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00
Adapt to Constraint-vs-Type

See haskell/haddock#21623 and !8750

- - - - -
7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00
Remove outdated footnote about module re-exports

The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine.
- - - - -
206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00
Merge pull request haskell/haddock#1534 from tomsmeding/patch-1


- - - - -
a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00
Support mtl-2.3

- - - - -
e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00
Track small API change in TyCon.hs

- - - - -
eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00
Update for GhC 9.6

- - - - -
063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00
Merge remote-tracking branch 'upstream/ghc-head' into HEAD

- - - - -
4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00
Bump bounds to accomodate base-4.18

- - - - -
340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00
HsToken in HsAppKindTy

- - - - -
946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00
Bump GHC version to 9.7

- - - - -
2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00
Rename () to Unit, Rename (,,...,,) to Tuple<n>

- - - - -
eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00
Bump versions for ghc-9.6 release

- - - - -
4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00
Adapt to warning categories changes

- - - - -
642d8d60 by sheaf at 2023-03-29T13:35:56+02:00
Adapt to record field refactor

This commit adapts to the changes in GHC MR !8686, which overhauls
the treatment of record fields in the renamer, adding separate record
field namespaces and entirely removing the GreName datatype.

- - - - -
ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00
Update UniqMap API

- - - - -
7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00
update classify with new tokens

- - - - -
ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00
Remove index-state

- - - - -
05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00
`renameInterface` space leak fixes

- Change logic for accumulation of names for which link warnings
  will be generated
- Change handling of `--ignore-link-symbol` to allow qualified and
  unqualified names. Added to CHANGES.md
- Some formatting changes and comments here and there

- - - - -
e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00
Messy things

- ghc-debug dependency and instrumentation
- cabal.project custom with-compiler
- hie.yaml files
- traces and such

- - - - -
0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00
Stop retaining GRE closures

GRE closures should never be necessary to Haddock, so we never want to
keep them on the heap. Despite that, they are retained by a lot of the
data structures that Haddock makes use of.

- Attempt to fix that situation by adding strictness to various
  computations and pruning the `ifaceInstances` field of `Interface` to
  a much thinner data type.

- Removes the `ifaceFamInstances` field, as it was never used.

- Move some of the attach instances types (e.g. `SimpleType`) to the
  types module

- - - - -
8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00
Memory usage fixes

- Refactor `ifaceDeclMap` to drastically reduce memory footprint. We
  no longer store all declarations associated with a given name, since
  we only cared to determine if the only declaration associated with a
  name was a value declaration. Change the `DeclMap` type to better
  reflect this.
- Drop pre-renaming export items after the renaming step. Since the
  Hoogle backend used the pre-renamed export items, this isn't trivial.
  We now generate Hoogle output for exported declarations during the
  renaming step (if Hoogle output /should/ be generated), and store that
  with the renamed export item.
- Slightly refactor Hoogle backend to handle the above change and allow
  for early generation of Hoogle output.
- Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the
  `Interface` type, as they were never used.
- Remove some unnecessary strictness
- Remove a lot of dead code from `Syb` module

- - - - -
1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00
Unify ErrMsgM and IfM

- Delete ErrMsgM, stop accumulating warnings in a writer
- Make IfM a state monad, print warnings directly to stdout, move IfM
  type into types module
- Drop ErrMsg = String synonym
- Unset IORefs from plugin after they are read, preventing unnecessary
  retention of interfaces

- - - - -
42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00
Thunk leak fixes

The strictness introduced in this commit was motivated by observing
thunk leaks in the eventlog2html output.

- Refactor attach instances list comprehension to avoid large
  intermediate thunks
- Refactor some HTML backend list comprehensions to avoid large
  intermediate thunks
- Avoid thunks accumulating in documentation types or documentation
  parser
- A lot of orphan NFData instances to allow us to force documentation
  values

- - - - -
68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00
Remove GHC debug dep

- - - - -
10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00
Force HIE file path

Removes a potential retainer of `ModSummary`s

- - - - -
1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00
Re-add index-state, with-compiler, delete hie.yamls

- - - - -
a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00
Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes

Reduce memory usage
- - - - -
e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00
Merge branch ghc-9.6 into ghc-head

- - - - -
22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00
Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head

- - - - -
41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00
changes to the WarningTxt cases

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00
Port the remains of Hi-Haddock

- - - - -
9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00
Stdout for tests

- - - - -
36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00
Formatting, organize imports

- - - - -
a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix empty context confusion in Convert module

- - - - -
379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix associated type families in Hoogle output

- - - - -
fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix test refs

Accept several changes in Hoogle tests:

Pretty printing logic no longer prints the `(Proxy (Proxy (...))`
chain in Bug806 with parentheses. Since this test was only meant
to verify that line breaks do not occur, accept the change.

`tyThingToLHsDecl` is called for class and data declarations, which ends
up "synifying" the type variables and giving unlifted types kind
signatures. As a result, type variables of kind `Type -> Type`
are now printed with kind signatures in Hoogle output. This could
be changed by manually drop kind signatures from class variables
in the Hoogle backend if the behavior is deemed unacceptable.

Sometimes subordinate declarations are exported separate from their
parent declarations (e.g. record selectors). In this case, a type
signature is cobbled together for the export item in `extractDecl`.
Since this type signature is very manually constructed, it may lack
kind signatures of decls constructed from `tyThingToLHsDecl`. An
example of this is the `type-sigs` Hoogle test.

Change `*` to `Type` in Hoogle test refs. I don't think this will
break Hoogle behavior, since it appears to not consider type
signatures in search. I have not fully verified this.

- - - - -
e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Fix LaTeX backend test refs

Changes to GHC pretty printing code have resulted in some
differences to Haddock's LaTeX output.

- Type variables are printed explicitly quantified in the
  LinearTypes test
- Wildcard types in type family equations are now printed numbered,
  e.g. _1 _2, in the TypeFamilies3 test
- Combined signatures in DefaultSignatures test are now documented
  as separate signatures

- - - - -
41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Formatting and test source updates

- Stop using kind `*` in html test sources
- Add TypeOperators where necessary to avoid warnings and future errors
- Rename some test modules to match their module names

- - - - -
c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Fix missing deprecation warnings on record fields

`lookupOccEnv` was used to resolve `OccNames` with warnings attached, but
it doesn't look in the record field namespace. Thus, if a record field
had a warning attached, it would not resolve and the warning map would
not include it. This commit fixes by using `lookupOccEnv_WithFields`
instead.

- - - - -
fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Formatting and some comments

- - - - -
751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00
Accept HTML test diffs

All diffs now boil down to the expected differences resulting from
declarations being reified from TyThings in hi-haddock. Surface
syntax now has much less control over the syntax used in the
documentation.

- - - - -
d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00
Adapt to new load' type

- - - - -
dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00
Update mkWarningMap and moduleWarning

- - - - -
8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00
Revert load' changes

- - - - -
aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00
Accept change to Instances test in html-test

Link to Data.Tuple instead of GHC.Tuple.Prim

- - - - -
8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00
Reset ghc dep to ^>= 9.6

- - - - -
2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00
Update CHANGES.md, user guide, recomp avoidance

* Add --trace-args flag for tracing arguments received to standard output
* Avoid recompiling due to changes in optimization flags
* Update users guide and changes.md

- - - - -
f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00
Add "Avoiding Recompilation" section to docs

This section is a bit of a WIP due to the unstable nature of hi-haddock
and the lack of tooling supporting it, but its a good start.

- - - - -
bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00
Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345

Neither of these MRs are ready to land yet which causes issues with
other MRs which are ready to land and need haddock changes.

- - - - -
421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
atSign has no unicode variant

Prior to this change, atSign was defined as follows:

	atSign unicode = text (if unicode then "@" else "@")

Yes, this is the same symbol '\64' and not your font playing
tricks on you. Now we define:

	atSign = char '@'

Both the LaTeX and the Xhtml backend are updated accordingly.

- - - - -
3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
LaTeX: fix printing of type variable bindings

Consider this type signature:

	kindOf :: forall {k} (a :: k). Proxy a -> Proxy k

Prior to this fix, the LaTeX backend rendered it like this:

	kindOf :: forall k a. Proxy a -> Proxy k

Now we preserve explicit specificity and kind annotations.

- - - - -
0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
Add support for invisible binders in type declarations

- - - - -
13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00
Add "Avoiding Recompilation" section to docs

This section is a bit of a WIP due to the unstable nature of hi-haddock
and the lack of tooling supporting it, but its a good start.

- - - - -
3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00
Add note about stubdir to recompilation docs

- - - - -
db7e84dc by Finley at 2023-06-08T08:11:03-06:00
Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6

hi-haddock for ghc 9.6
- - - - -
4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00
Replace SYB traversals

- - - - -
7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00
Test ref accepts, remove unused HaddockClsInst

- - - - -
df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00
Use batchMsg for progress reporting during load

With hi-haddock as is, there is an awkward silence during the load operation.
This commit makes haddock use the default `batchMsg` Messager for progress
reporting, and makes the default GHC verbosity level 1, so the user can see
what GHC is doing.

- - - - -
f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00
Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim


- - - - -
a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00
hi-haddock squashed

- - - - -
c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00
Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed

- - - - -
40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00
Changes related to MR !10283

MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase.

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00
Bump GHC version to 9.8

- - - - -
74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00
Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head

- - - - -
418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00
Remove NFData SourceText, IfaceWarnings updates

The NFData SourceText instance is now available in GHC

Handle mod_iface mi_warns now being IfaceWarnings

- - - - -
62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00
Accept Instances.hs test output

Due to ghc!10469.

- - - - -
a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00
Test fixes for "Fix associated data family doc structure items"

Associated data families were being given their own export DocStructureItems,
which resulted in them being documented separately from their classes in
haddocks. This commit fixes it.

- - - - -
cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00
Changes related to MR !10283

MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase.

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00
Bump GHC version to 9.8

- - - - -
fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00
Bump GHC version to 9.9

- - - - -
0c2a756e by sheaf at 2023-07-07T13:45:12+02:00
Avoid incomplete record update in Haddock Hoogle

This commit avoids running into an incomplete record update warning
in the Hoogle backend of Haddock.

This was only noticed now, because incomplete record updates were broken
in GHC 9.6. Now that they are fixed, we have to avoid running into them!

- - - - -
f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00
Bump base bound to <4.20

For GHC 9.8.

- - - - -
1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Check for puns (see ghc#23368)

- - - - -
457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Remove fake exports for (~), List, and Tuple<n>

The old reasoning no longer applies, nowadays those names can be
mentioned in export lists.

- - - - -
bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Fix pretty-printing of Solo and MkSolo

- - - - -
495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00
Fix issue with duplicate reexported definitions (T23616)

When a class method was reexported, it's default methods were also
showing up in the generated html page.

The simplest and most non-invasive fix is to not look for the default
method if we are just exporting the class method.. because the backends
are just showing default methods when the whole class is exported.

In general it would be worthwhile to rewrite this bit of code I think as
the logic and what gets included is split over `lookupDocs` and
`availExportDecl` it would be clearer to combine the two. The result of
lookupDocs is always just passed to availExportDecl so it seems simpler
and more obvious to just write the function directly.

- - - - -
6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00
Remove fake export of `FUN` from Prelude

This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes
\#23920 on GHC.

- - - - -
9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00
Match changes in wip/az/T23885-unicode-funtycon

- - - - -
4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00
EPA: match changes in GHC

- EPA: Comments in AnchorOperation
- EPA: Remove EpaEofComment

- - - - -
e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00
EPA: match changes in GHC, l2l cleanup

- - - - -
4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00
EPA: Replace Anchor with EpaLocation

Match GHC

- - - - -
94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00
Match GHC, No comments in EpaDelta for comments

- - - - -
32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00
EPA: Match changes to LHsToken removal

- - - - -
eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00
Changes for haskell/haddock#18324

- - - - -
a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00
Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value

A test *сс018* is attached (not sure about the naming convention though).
Note that without the fix, the test fails with the *dodgy-foreign-imports*
warning passed to stderr. The warning disappears after the fix.

GHC shouldn't warn on imports of natural function pointers from C by value
(which is feasible with CApiFFI), such as

```haskell
foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ())
```

where

```c
void (*f)(int);
```

See a related real-world use-case
[here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17).
There, GHC warns on import of C function pointer `pcre_free`.

- - - - -
ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00
Rename test cc018 -> T24034

- - - - -
88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00
rts/TraverseHeap.c: Ensure that PosixSource.h is included first
- - - - -
ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00
Make decomposeRuleLhs a bit more clever

This fixes #24370 by making decomposeRuleLhs undertand
dictionary /functions/ as well as plain /dictionaries/

- - - - -
94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00
doc: Add -Dn flag to user guide

Resolves #24394
- - - - -
31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00
cmm: Introduce MO_RelaxedRead

In hand-written Cmm it can sometimes be necessary to atomically load
from memory deep within an expression (e.g. see the `CHECK_GC` macro).
This MachOp provides a convenient way to do so without breaking the
expression into multiple statements.

- - - - -
0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00
codeGen: Use relaxed accesses in ticky bumping

- - - - -
be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00
base: use atomic write when updating timer manager

- - - - -
8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00
Use relaxed atomics to manipulate TSO status fields

- - - - -
d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Add necessary barriers when manipulating TSO owner

- - - - -
39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Use `switch` to branch on why_blocked

This is a semantics-preserving refactoring.

- - - - -
515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix synchronization on thread blocking state

We now use a release barrier whenever we update a thread's blocking
state. This required widening StgTSO.why_blocked as AArch64 does not
support atomic writes on 16-bit values.

- - - - -
eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in threadPaused

This only affects an assertion in the debug RTS and only needs relaxed
ordering.

- - - - -
26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in threadStatus#

- - - - -
6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in Interpreter's preemption check

- - - - -
9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00
rts/Messages: Fix data race

- - - - -
60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00
rts/Prof: Fix data race

- - - - -
ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Use relaxed ordering on dirty/clean info tables updates

When changing the dirty/clean state of a mutable object we needn't have
any particular ordering.

- - - - -
76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00
codeGen: Use relaxed-read in closureInfoPtr

- - - - -
a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00
STM: Use acquire loads when possible

Full sequential consistency is not needed here.

- - - - -
6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Use fence rather than redundant load

Previously we would use an atomic load to ensure acquire ordering.
However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this
more directly.

- - - - -
55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Fix data races in profiling timer

- - - - -
856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00
Add Note [C11 memory model]

- - - - -
6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: move generic cmm optimization logic in NCG to a standalone module

This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module,
GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be
run in the wasm backend NCG code, which is defined in other modules
that's imported by GHC.CmmToAsm, causing a cyclic dependency issue.

- - - - -
87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: explicitly disable PIC in wasm32 NCG

This commit explicitly disables the ncgPIC flag for the wasm32 target.
The wasm backend doesn't support PIC for the time being.

- - - - -
c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: enable generic cmm optimizations in wasm backend NCG

This commit enables the generic cmm optimizations in other NCGs to be
run in the wasm backend as well, followed by a late cmm control-flow
optimization pass. The added optimizations do catch some corner cases
not handled by the pre-NCG cmm pipeline and are useful in generating
smaller CFGs.

- - - - -
151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00
Namespacing for WARNING/DEPRECATED pragmas (#24396)

New syntax for WARNING and DEPRECATED pragmas was added,
namely namespace specifierss:

  namespace_spec ::= 'type' | 'data' | {- empty -}

  warning ::= warning_category namespace_spec namelist strings

  deprecation ::= namespace_spec namelist strings

A new data type was introduced to represent these namespace specifiers:

  data NamespaceSpecifier =
    NoSpecifier |
    TypeNamespaceSpecifier (EpToken "type") |
    DataNamespaceSpecifier (EpToken "data")

Extension field XWarning now contains this NamespaceSpecifier.

lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier
and checks that the namespace of the found names matches the passed flag.
With this change {-# WARNING data D "..." #-} pragma will only affect value
namespace and {-# WARNING type D "..." #-} will only affect type
namespace. The same logic is applicable to DEPRECATED pragmas.

Finding duplicated warnings inside rnSrcWarnDecls now takes into
consideration NamespaceSpecifier flag to allow warnings with the
same names that refer to different namespaces.

- - - - -
38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00
CI: Disable the test-cabal-reinstall job

Fixes #24363

- - - - -
27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00
Bump bytestring submodule to something closer to 0.12.1

...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c
(which reworks unaligned writes in Builder) and the stuff in
https://github.com/haskell/bytestring/pull/631 can see wider testing.

The less-terrible code for unaligned writes used in Builder on
hosts not known to be ulaigned-friendly also takes less effort
for GHC to compile, resulting in a metric decrease for T21839c
on some platforms.

The metric increase on T21839r is caused by the unrelated commit
750dac33465e7b59100698a330b44de7049a345c.  It perhaps warrants
further analysis and discussion (see #23822) but is not critical.

Metric Decrease:
T21839c
Metric Increase:
T21839r

- - - - -
cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00
Work around autotools setting C11 standard in CC/CXX

In autoconf >=2.70, C11 is set by default for $CC and $CXX via the
-std=...11 flag. In this patch, we split the "-std" flag out of the $CC
and $CXX variables, which we traditionally assume to be just the
executable name/path, and move it to $CFLAGS/$CXXFLAGS instead.

Fixes #24324

- - - - -
5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00
Expand `do` blocks right before typechecking using the `HsExpansion` philosophy.

- Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206

- The change is detailed in
  - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do`
  - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr`
         expains the rational of doing expansions in type checker as opposed to in the renamer

- Adds new datatypes:
  - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier
    1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`)
    2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack

  - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated
    This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam`

  - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc`

- Ensures warnings such as
  1. Pattern match checks
  2. Failable patterns
  3. non-() return in body statements are preserved

- Kill `HsMatchCtxt` in favor of `TcMatchAltChecker`

- Testcases:
  * T18324 T20020 T23147 T22788 T15598 T22086
  * T23147b (error message check),
  * DoubleMatch (match inside a match for pmc check)
  * pattern-fails (check pattern match with non-refutable pattern, eg. newtype)
  * Simple-rec (rec statements inside do statment)
  * T22788 (code snippet from #22788)
  * DoExpanion1 (Error messages for body statments)
  * DoExpansion2 (Error messages for bind statements)
  * DoExpansion3 (Error messages for let statements)

Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass

Metric Increase 'compile_time/bytes allocated':
    T9020

The testcase is a pathalogical example of a `do`-block with many statements that do nothing.
Given that we are expanding the statements into function binds, we will have to bear
a (small) 2% cost upfront in the compiler to unroll the statements.

- - - - -
0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00
Reduce parser allocations in allocateCommentsP

In the most common case, the comment queue is empty, so we can skip the
work of processing it. This reduces allocations by about 10% in the
parsing001 test.

Metric Decrease:
    MultiLayerModulesRecomp
    parsing001

- - - - -
ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00
ghc-internals fallout

- - - - -
cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00
Stop dropping a case whose binder is demanded

This MR fixes #24251.

See Note [Case-to-let for strictly-used binders]
in GHC.Core.Opt.Simplify.Iteration, plus #24251, for
lots of discussion.

Final Nofib changes over 0.1%:
+-----------------------------------------
|        imaginary/digits-of-e2    -2.16%
|                imaginary/rfib    -0.15%
|                    real/fluid    -0.10%
|                   real/gamteb    -1.47%
|                       real/gg    -0.20%
|                 real/maillist    +0.19%
|                      real/pic    -0.23%
|                      real/scs    -0.43%
|               shootout/n-body    -0.41%
|        shootout/spectral-norm    -0.12%
+========================================
|                     geom mean    -0.05%

Pleasingly, overall executable size is down by just over 1%.

Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the
geometric mean is -0.1% which seems good.

- - - - -
e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00
Add Note [Bangs in Integer functions]

...to document the bangs in the functions in GHC.Num.Integer

- - - - -
ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00
Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396)

- - - - -
e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00
Refactoring in preparation for lazy skolemisation

* Make HsMatchContext and HsStmtContext be parameterised over the
  function name itself, rather than over the pass.
  See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr
    - Replace types
        HsMatchContext GhcPs --> HsMatchContextPs
        HsMatchContext GhcRn --> HsMatchContextRn
        HsMatchContext GhcTc --> HsMatchContextRn  (sic! not Tc)
        HsStmtContext  GhcRn --> HsStmtContextRn
    - Kill off convertHsMatchCtxt

* Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing
  a complete user-supplied signature) is its own data type.
    - Split TcIdSigInfo(CompleteSig, PartialSig) into
        TcCompleteSig(CSig)
        TcPartialSig(PSig)
    - Use TcCompleteSig in tcPolyCheck, CheckGen
    - Rename types and data constructors:
        TcIdSigInfo         --> TcIdSig
        TcPatSynInfo(TPSI)  --> TcPatSynSig(PatSig)
    - Shuffle around helper functions:
        tcSigInfoName           (moved to GHC.Tc.Types.BasicTypes)
        completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes)
        tcIdSigName             (inlined and removed)
        tcIdSigLoc              (introduced)
    - Rearrange the pattern match in chooseInferredQuantifiers

* Rename functions and types:
    tcMatchesCase         --> tcCaseMatches
    tcMatchesFun          --> tcFunBindMatches
    tcMatchLambda         --> tcLambdaMatches
    tcPats                --> tcMatchPats
    matchActualFunTysRho  --> matchActualFunTys
    matchActualFunTySigma --> matchActualFunTy

* Add HasDebugCallStack constraints to:
    mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy,
    mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe

* Use `penv` from the outer context in the inner loop of
  GHC.Tc.Gen.Pat.tcMultiple

* Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file,
  factor out and export tcMkScaledFunTy.

* Move isPatSigCtxt down the file.

* Formatting and comments

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00
Lazy skolemisation for @a-binders (#17594)

This patch is a preparation for @a-binders implementation.  The main changes are:

* Skolemisation is now prepared to deal with @binders.
  See Note [Skolemisation overview] in GHC.Tc.Utils.Unify.
  Most of the action is in
    - Utils.Unify.matchExpectedFunTys
    - Gen.Pat.tcMatchPats
    - Gen.Expr.tcPolyExprCheck
    - Gen.Binds.tcPolyCheck

Some accompanying refactoring:

* I found that funTyConAppTy_maybe was doing a lot of allocation, and
  rejigged userTypeError_maybe to avoid calling it.

- - - - -
532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00
driver: Really don't lose track of nodes when we fail to resolve cycles

This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose
track of acyclic components at the start of an unresolved cycle. We now ensure we
never loose track of any of these components.

As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC:

When viewed without boot files, we have a single SCC

```
[REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
     main:T24275A [main:T24275A {-# SOURCE #-}]]
```

But with boot files this turns into

```
[NONREC main:T24275B {-# SOURCE #-} [],
 REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
    main:T24275A {-# SOURCE #-} [main:T24275B],
 NONREC main:T24275A [main:T24275A {-# SOURCE #-}]]
```

Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot.
However, we treat this entire group as a single "SCC" because it seems so when we
analyse the graph without taking boot files into account.

Indeed, we must return a single ResolvedCycle element in the BuildPlan for this
as described in Note [Upsweep].

However, since after resolving this is not a true SCC anymore, `findCycle` fails
to find a cycle and we have a sub-optimal error message as a result.

To handle this, I extended `findCycle` to not assume its input is an SCC, and to
try harder to find cycles in its input.

Fixes #24275

- - - - -
b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00
GHCi: Lookup breakpoint CCs in the correct module

We need to look up breakpoint CCs in the module that the breakpoint
points to, and not the current module.

Fixes #24327

- - - - -
b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00
testsuite: Add test for #24327

- - - - -
569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add compile_artifact, ignore_extension flag

In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the
capability to collect generic metrics. But this assumed that the test
was not linking and producing artifacts and we only wanted to track
object files, interface files, or build artifacts from the compiler
build. However, some backends, such as the JS backend, produce artifacts when
compiling, such as the jsexe directory which we want to track.

This patch:

- tweaks the testsuite to collect generic metrics on any build artifact
in the test directory.

- expands the exe_extension function to consider windows and adds the
ignore_extension flag.

- Modifies certain tests to add the ignore_extension flag. Tests such as
heaprof002 expect a .ps file, but on windows without ignore_extensions
the testsuite will look for foo.exe.ps. Hence the flag.

- adds the size_hello_artifact test

- - - - -
75a31379 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add wasm_arch, heapprof002 wasm extension

- - - - -
c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00
Synchronize bindist configure for #24324

In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a
workaround for #24324 in the in-tree configure script, but forgot to
update the bindist configure script accordingly. This updates it.

- - - - -
d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00
distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable

Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we
were missing passing `--target` when invoking the linker.

Fixes #24414

- - - - -
77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00
llvmGen: Adapt to allow use of new pass manager.

We now must use `-passes` in place of `-O<n>` due to #21936.

Closes #21936.

- - - - -
3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00
testsuite: Mark length001 as fragile on javascript

Modifying the timeout multiplier is not a robust way to get this test to
reliably fail. Therefore we mark it as fragile until/if javascript ever
supports the stack limit.

- - - - -
20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00
Javascript: Don't filter out rtsDeps list

This logic appears to be incorrect as it would drop any dependency which
was not in a direct dependency of the package being linked.

In the ghc-internals split this started to cause errors because
`ghc-internal` is not a direct dependency of most packages, and hence
important symbols to keep which are hard coded into the js runtime were
getting dropped.

- - - - -
2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00
base: Cleanup whitespace in cbits

- - - - -
44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00
Move `base` to `ghc-internal`

Here we move a good deal of the implementation of `base` into a new
package, `ghc-internal` such that it can be evolved independently
from the user-visible interfaces of `base`.

While we want to isolate implementation from interfaces, naturally, we
would like to avoid turning `base` into a mere set of module re-exports.
However, this is a non-trivial undertaking for a variety of reasons:

 * `base` contains numerous known-key and wired-in things, requiring
   corresponding changes in the compiler

 * `base` contains a significant amount of C code and corresponding
   autoconf logic, which is very fragile and difficult to break apart

 * `base` has numerous import cycles, which are currently dealt with via
   carefully balanced `hs-boot` files

 * We must not break existing users

To accomplish this migration, I tried the following approaches:

* [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental
  migration of modules into ghc-internal: this knot is simply too
  intertwined to be easily pulled apart, especially given the rather
  tricky import cycles that it contains)

* [Move-Core]: Moving the "core" connected component of base (roughly
  150 modules) into ghc-internal. While the Haskell side of this seems
  tractable, the C dependencies are very subtle to break apart.

* [Move-Incrementally]:

  1. Move all of base into ghc-internal
  2. Examine the module structure and begin moving obvious modules (e.g.
     leaves of the import graph) back into base
  3. Examine the modules remaining in ghc-internal, refactor as necessary
     to facilitate further moves
  4. Go to (2) iterate until the cost/benefit of further moves is
     insufficient to justify continuing
  5. Rename the modules moved into ghc-internal to ensure that they don't
     overlap with those in base
  6. For each module moved into ghc-internal, add a shim module to base
     with the declarations which should be exposed and any requisite
     Haddocks (thus guaranteeing that base will be insulated from changes
     in the export lists of modules in ghc-internal

Here I am using the [Move-Incrementally] approach, which is empirically
the least painful of the unpleasant options above

Bumps haddock submodule.

Metric Decrease:
    haddock.Cabal
    haddock.base
Metric Increase:
    MultiComponentModulesRecomp
    T16875
    size_hello_artifact

- - - - -
e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00
Haddock comments on infix constructors (#24221)

Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for
infix constructors.

This change fixes a Haddock regression (introduced in 19e80b9af252)
that affected leading comments on infix data constructor declarations:

	-- | Docs for infix constructor
	| Int :* Bool

The comment should be associated with the data constructor (:*), not
with its left-hand side Int.

- - - - -
9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00
Add os-string as a boot package

Introduces `os-string` submodule. This will be necessary for
`filepath-1.5`.

- - - - -
9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00
gitignore: Ignore .hadrian_ghci_multi/

- - - - -
d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00
hadrian: Set -this-package-name

When constructing the GHC flags for a package Hadrian must take care to
set `-this-package-name` in addition to `-this-unit-id`. This hasn't
broken until now as we have not had any uses of qualified package
imports. However, this will change with `filepath-1.5` and the
corresponding `unix` bump, breaking `hadrian/multi-ghci`.

- - - - -
f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00
Bump filepath to 1.5.0.0

Required bumps of the following submodules:

 * `directory`
 * `filepath`
 * `haskeline`
 * `process`
 * `unix`
 * `hsc2hs`
 * `Win32`
 * `semaphore-compat`

and the addition of `os-string` as a boot package.

- - - - -
ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Use specific clang assembler when compiling with -fllvm

There are situations where LLVM will produce assembly which older gcc
toolchains can't handle. For example on Deb10, it seems that LLVM >= 13
produces assembly which the default gcc doesn't support.

A more robust solution in the long term is to require a specific LLVM
compatible assembler when using -fllvm.

Fixes #16354

- - - - -
c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0

- - - - -
5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update bootstrap plans for 9.4.8 and 9.6.4

- - - - -
707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Add alpine 3_18 release job

This is mainly experimental and future proofing to enable a smooth
transition to newer alpine releases once 3_12 is too old.

- - - - -
c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00
Generate LLVM min/max bound policy via Hadrian

Per #23966, I want the top-level configure to only generate
configuration data for Hadrian, not do any "real" tasks on its own.
This is part of that effort --- one less file generated by it.

(It is still done with a `.in` file, so in a future world non-Hadrian
also can easily create this file.)

Split modules:

- GHC.CmmToLlvm.Config
- GHC.CmmToLlvm.Version
- GHC.CmmToLlvm.Version.Bounds
- GHC.CmmToLlvm.Version.Type

This also means we can get rid of the silly `unused.h` introduced in
!6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge.

Part of #23966

- - - - -
9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00
Enable mdo statements to use HsExpansions
Fixes: #24411
Added test T24411 for regression

- - - - -
f8429266 by Jade at 2024-02-08T14:56:50+01:00
Adjust test for ghc MR !10993

- - - - -
762b2120 by Jade at 2024-02-08T15:17:15+00:00
Improve Monad, Functor & Applicative docs

This patch aims to improve the documentation of Functor, Applicative,
Monad and related symbols. The main goal is to make it more consistent
and make accessible. See also: !10979 (closed) and !10985 (closed)

Ticket #17929

Updates haddock submodule

- - - - -
151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00
JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309)

- - - - -
2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00
ci: Allow release-hackage-lint to fail

Otherwise it blocks the ghcup metadata pipeline from running.

- - - - -
b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00
rts: eras profiling mode

The eras profiling mode is useful for tracking the life-time of
closures. When a closure is written, the current era is recorded in the
profiling header. This records the era in which the closure was created.

* Enable with -he
* User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era
* Automatically: --automatic-era-increment, increases the user era on major
  collections
* The first era is era 1
* -he<era> can be used with other profiling modes to select a specific
  era

If you just want to record the era but not to perform heap profiling you
can use `-he --no-automatic-heap-samples`.

https://well-typed.com/blog/2024/01/ghc-eras-profiling/

Fixes #24332

- - - - -
be674a2c by Jade at 2024-02-10T14:30:04-05:00
Adjust error message for trailing whitespace in as-pattern.

Fixes #22524

- - - - -
53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00
gitlab: js: add codeowners

Fixes:
- #24409

Follow on from:
- #21078 and MR !9133
- When we added the JS backend this was forgotten. This patch adds the
rightful codeowners.

- - - - -
8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00
Bump CI images so that alpine3_18 image includes clang15

The only changes here are that clang15 is now installed on the
alpine-3_18 image.

- - - - -
df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: handle stored null StablePtr

Some Haskell codes unsafely cast StablePtr into ptr to compare against
NULL. E.g. in direct-sqlite:

  if castStablePtrToPtr aggStPtr /= nullPtr then

where `aggStPtr` is read (`peek`) from zeroed memory initially.

We fix this by giving these StablePtr the same representation as other
null pointers. It's safe because StablePtr at offset 0 is unused (for
this exact reason).

- - - - -
55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: disable MergeObjsMode test

This isn't implemented for JS backend objects.

- - - - -
aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: add support for linking C sources

Support linking C sources with JS output of the JavaScript backend.
See the added documentation in the users guide.

The implementation simply extends the JS linker to use the objects (.o)
that were already produced by the emcc compiler and which were filtered
out previously. I've also added some options to control the link with C
functions (see the documentation about pragmas).

With this change I've successfully compiled the direct-sqlite package
which embeds the sqlite.c database code. Some wrappers are still
required (see the documentation about wrappers) but everything generic
enough to be reused for other libraries have been integrated into
rts/js/mem.js.

- - - - -
b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: avoid EMCC logging spurious failure

emcc would sometime output messages like:

  cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds)
  cache:INFO:  - ok

Cf https://github.com/emscripten-core/emscripten/issues/18607

This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0

- - - - -
ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00
Remove a dead comment

Just remove an out of date block of commented-out code, and tidy up
the relevant Notes.  See #8317.

- - - - -
bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00
nonmoving: Add support for heap profiling

Add support for heap profiling while using the nonmoving collector.

We greatly simply the implementation by disabling concurrent collection for
GCs when heap profiling is enabled. This entails that the marked objects on
the nonmoving heap are exactly the live objects.

Note that we match the behaviour for live bytes accounting by taking the size
of objects on the nonmoving heap to be that of the segment's block
rather than the object itself.

Resolves #22221

- - - - -
d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00
doc: Add requires prof annotation to options that require it

Resolves #24421

- - - - -
6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00
EPA: Match changes to HsParTy and HsFunTy

- - - - -
57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00
deriveConstants: add needed constants for wasm backend

This commit adds needed constants to deriveConstants. They are used by
RTS code in the wasm backend to support the JSFFI logic.

- - - - -
615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms

The pure Haskell implementation causes i386 regression in unrelated
work that can be fixed by using C-based atomic increment, see added
comment for details.

- - - - -
a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: allow JSFFI for wasm32

This commit allows the javascript calling convention to be used when
the target platform is wasm32.

- - - - -
8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: allow boxed JSVal as a foreign type

This commit allows the boxed JSVal type to be used as a foreign
argument/result type.

- - - - -
053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: ensure ctors have the right priority on wasm32

This commit fixes the priorities of ctors generated by GHC codegen on
wasm32, see the referred note for details.

- - - - -
b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: add JSFFI desugar logic for wasm32

This commit adds JSFFI desugar logic for the wasm backend.

- - - - -
2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: add JavaScriptFFI to supported extension list on wasm32

This commit adds JavaScriptFFI as a supported extension when the
target platform is wasm32.

- - - - -
9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00
rts/ghc-internal: add JSFFI support logic for wasm32

This commit adds rts/ghc-internal logic to support the wasm backend's
JSFFI functionality.

- - - - -
e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00
ghc-internal: fix threadDelay for wasm in browsers

This commit fixes broken threadDelay for wasm when it runs in
browsers, see added note for detailed explanation.

- - - - -
f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00
utils: add JSFFI utility code

This commit adds JavaScript util code to utils to support the wasm
backend's JSFFI functionality:

- jsffi/post-link.mjs, a post-linker to process the linked wasm module
  and emit a small complement JavaScript ESM module to be used with it
  at runtime
- jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side
  of runtime logic
- jsffi/test-runner.mjs, run the jsffi test cases

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00
hadrian: distribute jsbits needed for wasm backend's JSFFI support

The post-linker.mjs/prelude.js files are now distributed in the
bindist libdir, so when using the wasm backend's JSFFI feature, the
user wouldn't need to fetch them from a ghc checkout manually.

- - - - -
c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: add opts.target_wrapper

This commit adds opts.target_wrapper which allows overriding the
target wrapper on a per test case basis when testing a cross target.
This is used when testing the wasm backend's JSFFI functionality; the
rest of the cases are tested using wasmtime, though the jsffi cases
are tested using the node.js based test runner.

- - - - -
8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: T22774 should work for wasm JSFFI

T22774 works since the wasm backend now supports the JSFFI feature.

- - - - -
1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: add JSFFI test cases for wasm backend

This commit adds a few test cases for the wasm backend's JSFFI
functionality, as well as a simple README to instruct future
contributors to add new test cases.

- - - - -
b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00
docs: add documentation for wasm backend JSFFI

This commit adds changelog and user facing documentation for the wasm
backend's JSFFI feature.

- - - - -
ffeb000d by David Binder at 2024-02-13T14:08:30-05:00
Add tests from libraries/process/tests and libraries/Win32/tests to GHC

These tests were previously part of the libraries, which themselves are
submodules of the GHC repository. This commit moves the tests directly
to the GHC repository.

- - - - -
5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00
Do not execute win32 tests on non-windows runners

- - - - -
500d8cb8 by Jade at 2024-02-13T14:09:07-05:00
prevent GHCi (and runghc) from suggesting other symbols when not finding main

Fixes: #23996

- - - - -
b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: update xxHash to v0.8.2

- - - - -
4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: use XXH3_64bits hash on all 64-bit platforms

This commit enables XXH3_64bits hash to be used on all 64-bit
platforms. Previously it was only enabled on x86_64, so platforms like
aarch64 silently falls back to using XXH32 which degrades the hashing
function quality.

- - - - -
ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: define XXH_INLINE_ALL

This commit cleans up how we include the xxhash.h header and only
define XXH_INLINE_ALL, which is sufficient to inline the xxHash
functions without symbol collision.

- - - - -
0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00
EPA: Move EpAnn out of extension points

Leaving a few that are too tricky, maybe some other time.

Also
 - remove some unneeded helpers from Parser.y
 - reduce allocations with strictness annotations

Updates haddock submodule

Metric Decrease:
    parsing001

- - - - -
de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00
Fix ffi callbacks with >6 args and non-64bit args.

Check for ptr/int arguments rather than 64-bit width arguments when counting
integer register arguments.
The old approach broke when we stopped using exclusively W64-sized types to represent
sub-word sized integers.

Fixes #24314

- - - - -
9c588f19 by Fendor at 2024-02-14T11:05:36+01:00
Adapt to GHC giving better Name's for linking

- - - - -
325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00
rts/EventLog: Place eliminate duplicate strlens

Previously many of the `post*` implementations would first compute the
length of the event's strings in order to determine the event length.
Later we would then end up computing the length yet again in
`postString`. Now we instead pass the string length to `postStringLen`,
avoiding the repeated work.

- - - - -
8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00
rts/eventlog: Place upper bound on IPE string field lengths

The strings in IPE events may be of unbounded length. Limit the lengths
of these fields to 64k characters to ensure that we don't exceed the
maximum event length.

- - - - -
0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00
rts: drop unused postString function

- - - - -
d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00
compiler/rts: fix wasm unreg regression

This commit fixes two wasm unreg regressions caught by a nightly
pipeline:

- Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm
- Invalid _hs_constructor(101) function name when handling ctor

- - - - -
264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00
feat: Add sortOn to Data.List.NonEmpty

Adds `sortOn` to `Data.List.NonEmpty`, and adds
comments describing when to use it, compared to
`sortWith` or `sortBy . comparing`.

The aim is to smooth out the API between
`Data.List`, and `Data.List.NonEmpty`.

This change has been discussed in the
[clc issue](https://github.com/haskell/core-libraries-committee/issues/227).

- - - - -
b57200de by Fendor at 2024-02-15T09:41:47-05:00
Prefer RdrName over OccName for looking up locations in doc renaming step

Looking up by OccName only does not take into account when functions are
only imported in a qualified way.

Fixes issue #24294

Bump haddock submodule to include regression test

- - - - -
8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00
JS: add simple optimizer

The simple optimizer reduces the size of the code generated by the
JavaScript backend without the complexity and performance penalty
of the optimizer in GHCJS.

Also see #22736

Metric Decrease:
    libdir
    size_hello_artifact

- - - - -
20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00
base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API

This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and
modifies the base API to reflect the new RTS flag.

CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243

Fixes #24337

- - - - -
778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00
Namespace specifiers for fixity signatures

- - - - -
08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00
base: export System.Mem.performBlockingMajorGC

The corresponding C function was introduced in
ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264.

Resolves #24228

The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230

Co-authored-by: Ben Gamari <bgamari.foss at gmail.com>

- - - - -
1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00
Fix C output for modern C initiative

GCC 14 on aarch64 rejects the C code written by GHC with this kind of
error:

   error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion]
         68 | *(ffi_arg*)resp = cret;
            |                 ^

Add the correct cast.

For more information on this see:
https://fedoraproject.org/wiki/Changes/PortingToModernC

Tested-by: Richard W.M. Jones <rjones at redhat.com>

- - - - -
5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00
Bump bytestring submodule to 0.12.1.0

- - - - -
902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00
Add missing BCO handling in scavenge_one.

- - - - -
97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00
Make cast between words and floats real primops (#24331)

First step towards fixing #24331. Replace foreign prim imports with real
primops.

- - - - -
a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00
Perf: add constant folding for bitcast between float and word (#24331)

- - - - -
5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00
Perf: replace stack checks with assertions in casting primops

There are RESERVED_STACK_WORDS free words (currently 21) on the stack,
so omit the checks.

Suggested by Cheng Shao.

- - - - -
401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00
Reexport primops from GHC.Float + add deprecation

- - - - -
4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00
rts/Hash: Don't iterate over chunks if we don't need to free data

When freeing a `HashTable` there is no reason to walk over the hash list
before freeing it if the user has not given us a `dataFreeFun`.

Noticed while looking at #24410.

- - - - -
bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00
compiler: add SEQ_CST fence support

In addition to existing Acquire/Release fences, this commit adds
SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a
fence that enforces total memory ordering. The following logic is
added:

- The MO_SeqCstFence callish MachOp
- The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h
- MO_SeqCstFence lowering logic in every single GHC codegen backend

- - - - -
2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00
testsuite: fix hs_try_putmvar002 for targets without pthread.h

hs_try_putmvar002 includes pthread.h and doesn't work on targets
without this header (e.g. wasm32). It doesn't need to include this
header at all. This was previously unnoticed by wasm CI, though recent
toolchain upgrade brought in upstream changes that completely removes
pthread.h in the single-threaded wasm32-wasi sysroot, therefore we
need to handle that change.

- - - - -
1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00
ci: bump ci-images to use updated wasm image

This commit bumps our ci-images revision to use updated wasm image.

- - - - -
56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00
Bump submodule text to 2.1.1

T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a.

Metric Decrease:
    T17123

- - - - -
a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00
rts: remove redundant rCCCS initialization

This commit removes the redundant logic of initializing each
Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before
initProfiling() is called during RTS startup, each Capability's rCCCS
has already been assigned CCS_SYSTEM when they're first initialized.

- - - - -
7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00
Drop dependence on `touch`

This drops GHC's dependence on the `touch` program, instead implementing
it within GHC. This eliminates an external dependency and means that we
have one fewer program to keep track of in the `configure` script

- - - - -
0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00
Parser, renamer, type checker for @a-binders (#17594)

GHC Proposal 448 introduces binders for invisible type arguments
(@a-binders) in various contexts. This patch implements @-binders
in lambda patterns and function equations:

  {-# LANGUAGE TypeAbstractions #-}

  id1 :: a -> a
  id1 @t x = x :: t      -- @t-binder on the LHS of a function equation

  higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16)
  higherRank f = (f 42, f 42)

  ex :: (Int8, Int16)
  ex = higherRank (\ @a x -> maxBound @a - x )
                         -- @a-binder in a lambda pattern in an argument
                         -- to a higher-order function

Syntax
------

To represent those @-binders in the AST, the list of patterns in Match
now uses ArgPat instead of Pat:

  data Match p body
     = Match {
         ...
-        m_pats  :: [LPat p],
+        m_pats  :: [LArgPat p],
         ...
   }

+ data ArgPat pass
+   = VisPat (XVisPat pass) (LPat pass)
+   | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass))
+   | XArgPat !(XXArgPat pass)

The VisPat constructor represents patterns for visible arguments,
which include ordinary value-level arguments and required type arguments
(neither is prefixed with a @), while InvisPat represents invisible type
arguments (prefixed with a @).

Parser
------

In the grammar (Parser.y), the lambda and lambda-cases productions of
aexp non-terminal were updated to accept argpats instead of apats:

  aexp : ...
-        | '\\' apats '->' exp
+        | '\\' argpats '->' exp
         ...
-        | '\\' 'lcases' altslist(apats)
+        | '\\' 'lcases' altslist(argpats)
         ...

+ argpat : apat
+        | PREFIX_AT atype

Function left-hand sides did not require any changes to the grammar, as
they were already parsed with productions capable of parsing @-binders.
Those binders were being rejected in post-processing (isFunLhs), and now
we accept them.

In Parser.PostProcess, patterns are constructed with the help of
PatBuilder, which is used as an intermediate data structure when
disambiguating between FunBind and PatBind. In this patch we define
ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived
data structure produced in isFunLhs and consumed in checkFunBind.

Renamer
-------

Renaming of @-binders builds upon prior work on type patterns,
implemented in 2afbddb0f24, which guarantees proper scoping and
shadowing behavior of bound type variables.

This patch merely defines rnLArgPatsAndThen to process a mix of visible
and invisible patterns:

+ rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn]
+ rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where
+   rnArgPatAndThen (VisPat x p)    = ... rnLPatAndThen ...
+   rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ...

Common logic between rnArgPats and rnPats is factored out into the
rn_pats_general helper.

Type checker
------------

Type-checking of @-binders builds upon prior work on lazy skolemisation,
implemented in f5d3e03c56f.

This patch extends tcMatchPats to handle @-binders. Now it takes and
returns a list of LArgPat rather than LPat:

  tcMatchPats ::
              ...
-             -> [LPat GhcRn]
+             -> [LArgPat GhcRn]
              ...
-             -> TcM ([LPat GhcTc], a)
+             -> TcM ([LArgPat GhcTc], a)

Invisible binders in the Match are matched up with invisible (Specified)
foralls in the type. This is done with a new clause in the `loop` worker
of tcMatchPats:

  loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a)
  loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys)
    ...
    -- NEW CLAUSE:
    | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis
    = ...

In addition to that, tcMatchPats no longer discards type patterns. This
is done by filterOutErasedPats in the desugarer instead.

x86_64-linux-deb10-validate+debug_info
Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -
486979b0 by Jade at 2024-02-19T07:12:13-05:00
Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First

Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246
Fixes: #24346

- - - - -
17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00
Fix reST in users guide

It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax.

- - - - -
35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00
Fix searching for errors in sphinx build

- - - - -
4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00
hadrian: fix wasm backend post linker script permissions

The post-link.mjs script was incorrectly copied and installed as a
regular data file without executable permission, this commit fixes it.

- - - - -
a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00
testsuite: mark T23540 as fragile on i386

See #24449 for details.

- - - - -
249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00
Add @since annotation to Data.Data.mkConstrTag

- - - - -
cdd939e7 by Jade at 2024-02-19T20:36:46-05:00
Enhance documentation of Data.Complex

- - - - -
d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

- - - - -
efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00
hadrian: Generate HSC2HS_EXTRAS variable in bindist installation

We must generate the hsc2hs wrapper at bindist installation time since
it must contain `--lflag` and `--cflag` arguments which depend upon the
installation path.

The solution here is to substitute these variables in the configure
script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in
the install rules.

Fixes #24050.

- - - - -
c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00
ci: Show --info for installed compiler

- - - - -
ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00
configure: Correctly set --target flag for linker opts

Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4
arguments, when it only takes 3 arguments. Instead we need to use the
`FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags.

Actually fixes #24414

- - - - -
9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00
configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS

- - - - -
77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00
Namespacing for fixity signatures (#14032)

Namespace specifiers were added to syntax of fixity signatures:
  - sigdecl ::= infix prec ops | ...
  + sigdecl ::= infix prec namespace_spec ops | ...

To preserve namespace during renaming MiniFixityEnv type
now has separate FastStringEnv fields for names that should be
on the term level and for name that should be on the type level.

makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way:
 - signatures without namespace specifiers fill both fields
 - signatures with 'data' specifier fill data field only
 - signatures with 'type' specifier fill type field only

Was added helper function lookupMiniFixityEnv that takes care about
looking for a name in an appropriate namespace.

Updates haddock submodule.

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00
rts: only collect live words in nonmoving census when non-concurrent

This avoids segfaults when the mutator modifies closures as we examine
them.

Resolves #24393

- - - - -
9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00
mutex wrap in refreshProfilingCCSs

- - - - -
1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00
rts: remove unused HAVE_C11_ATOMICS macro

This commit removes the unused HAVE_C11_ATOMICS macro. We used to have
a few places that have fallback paths when HAVE_C11_ATOMICS is not
defined, but that is completely redundant, since the
FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler
doesn't support C11 style atomics. There are also many places (e.g. in
unreg backend, SMP.h, library cbits, etc) where we unconditionally use
C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the
oldest distro we test in our CI, so there's no value in keeping
HAVE_C11_ATOMICS.

- - - - -
0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00
RTS: -Ds - make sure incall is non-zero before dereferencing it.

Fixes #24445

- - - - -
e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00
rts/AdjustorPool: Use ExecPage abstraction

This is just a minor cleanup I found while reviewing the implementation.

- - - - -
826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00
rename GHC.Tuple.Prim to GHC.Tuple

- - - - -
09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00
Define GHC2024 language edition (#24320)

See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also
fixes #24343 and improves the documentation of language editions.

Co-authored-by: Joachim Breitner <mail at joachim-breitner.de>

- - - - -
2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00
Bump bounds

- - - - -
f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00
Allow `@since` annotations in export lists

Here we extend Haddock to admit `@since` annotations in export lists.
These can be attached to most export list items (although not
subordinate lists). These annotations supercede the declaration's
`@since` annotation in produced Haddocks.

- - - - -
b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00
Allow package-qualified @since declarations

- - - - -
8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00
Documentation changes from ghc-internal restructuring

Previously many declarations (e.g. `Int`) were declared to have a "home"
in `Prelude`. However, now Haddock instead chooses to put these in
more specific homes (e.g. `Data.Int`). Given that the "home" decision is
driven by heuristics and in general these changes seem
quite reasonable I am accepting them:

 * `Int` moved from `Prelude` to `Data.Int`
 * `(~)` moved from `Prelude` to `Data.Type.Equality`
 * `Type` moved from `GHC.Types` to `Data.Kind`
 * `Maybe` moved from `Prelude` to `Data.Maybe`
 * `Bool` moved from `Prelude` to `Data.Bool`
 * `Ordering` moved from `Prelude` to `Data.Ord`

As well, more identifiers are now hyperlinked; it's not immediately
clear *why*, but it is an improvement nevertheless.

- - - - -
ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00
Allow docstrings after exports

Here we extend the parser and AST to preserve docstrings following
export items. We then extend Haddock to parse `@since` annotations in
such docstrings, allowing changes in export structure to be properly
documented.

Bumps haddock submodule.

- - - - -
30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00
rename GHC.Tuple.Prim to GHC.Tuple

- - - - -
0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00
Improve the synopsis and description of base

- - - - -
2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00
Error Messages: Properly align cyclic module error

Fixes: #24476

- - - - -
bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00
Allow docstrings after exports

Here we extend the parser and AST to preserve docstrings following
export items. We then extend Haddock to parse `@since` annotations in
such docstrings, allowing changes in export structure to be properly
documented.

- - - - -
d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00
ghc-internal: Move modules into GHC.Internal.* namespace

Bumps haddock submodule due to testsuite output changes.

- - - - -
a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00
ghc-internal: Rewrite `@since ` to `@since base-`

These will be incrementally moved to the export sites in `base` where
possible.

- - - - -
ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Migrate Haddock `not-home` pragmas from `ghc-internal`

This ensures that we do not use `base` stub modules as declarations'
homes when not appropriate.

- - - - -
c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Partially freeze exports of GHC.Base

Sadly there are still a few module reexports. However, at least we have
decoupled from the exports of `GHC.Internal.Base`.

- - - - -
272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00
Move Haddock named chunks

- - - - -
2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00
Drop GHC.Internal.Data.Int

- - - - -
55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler: Fix mention to `GHC....` modules in wasm desugaring

Really, these references should be via known-key names anyways. I have
fixed the proximate issue here but have opened #24472 to track the
additional needed refactoring.

- - - - -
64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00
Accept performance shifts from ghc-internal restructure

As expected, Haddock now does more work. Less expected is that some
other testcases actually get faster, presumably due to less interface
file loading. As well, the size_hello_artifact test regressed a bit when
debug information is enabled due to debug information for the new stub
symbols.

Metric Decrease:
    T12227
    T13056
Metric Increase:
    haddock.Cabal
    haddock.base
    MultiLayerModulesTH_OneShot
    size_hello_artifact

- - - - -
317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00
Expose GHC.Wasm.Prim from ghc-experimental

Previously this was only exposed from `ghc-internal` which violates our
agreement that users shall not rely on things exposed from that package.

Fixes #24479.

- - - - -
3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler/tc: Small optimisation of evCallStack

Don't lookupIds unless we actually need them.

- - - - -
3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler/tc: Use toException instead of SomeException

- - - - -
125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Factor out errorBelch

This was useful when debugging

- - - - -
3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Clean up imports of GHC.Stack.CloneStack

- - - - -
6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Move PrimMVar to GHC.Internal.MVar

- - - - -
28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Move prettyCallStack to GHC.Internal.Stack

- - - - -
4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Explicit dependency to workaround #24436

Currently `ghc -M` fails to account for `.hs-boot` files correctly,
leading to issues with cross-package one-shot builds failing. This
currently manifests in `GHC.Exception` due to the boot file for
`GHC.Internal.Stack`. Work around this by adding an explicit `import`,
ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`.

See #24436.

- - - - -
294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Use displayException in top-level exception handler

Happily this also allows us to eliminate a special case for Deadlock
exceptions.

Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198).

- - - - -
732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00
rts: Fix symbol references in Wasm RTS

- - - - -
4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00
GHCi: Improve response to unloading, loading and reloading modules

Fixes #13869

- - - - -
f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00
rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job

- - - - -
c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00
hadrian/hie-bios: pass -j to hadrian

This commit passes -j to hadrian in the hadrian/hie-bios scripts. When
the user starts HLS in a fresh clone that has just been configured, it
takes quite a while for hie-bios to pick up the ghc flags and start
actual indexing, due to the fact that the hadrian build step defaulted
to -j1, so -j speeds things up and improve HLS user experience in GHC.
Also add -j flag to .ghcid to speed up ghcid, and sets the Windows
build root to .hie-bios which also works and unifies with other
platforms, the previous build root _hie-bios was missing from
.gitignore anyway.

- - - - -
50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00
ci: enable parallelism in hadrian/ghci scripts

This commit enables parallelism when the hadrian/ghci scripts are
called in CI. The time bottleneck is in the hadrian build step, but
previously the build step wasn't parallelized.

- - - - -
61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00
m4: Correctly detect GCC version

When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here.

```
$ cc --version
cc (GCC) 13.2.1 20230801
...
```

This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler`

This patch makes it check for upper-cased "GCC" too so that it works correctly:

```
checking version of gcc... 13.2.1
```
- - - - -
001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00
Fix formatting in whereFrom docstring

Previously it used markdown syntax rather than Haddock syntax for code quotes

- - - - -
e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00
Move ClosureType type to ghc-internal

- Use ClosureType for InfoProv.ipDesc.
- Use ClosureType for CloneStack.closureType.
- Now ghc-heap re-exports this type from ghc-internal.

See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210

Resolves #22600

- - - - -
3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00
StgToJS: Simplify ExprInline constructor of ExprResult

Its payload was used only for a small optimization in genAlts,
avoiding a few assignments for programs of this form:

  case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; }

But when compiling with optimizations, this sort of code is
generally eliminated by case-of-known-constructor in Core-to-Core.
So it doesn't seem worth tracking and cleaning up again in StgToJS.

- - - - -
61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00
cg: Remove GHC.Cmm.DataFlow.Collections

In pursuit of #15560 and #17957 and generally removing redundancy.

- - - - -
d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00
utils: remove unused lndir from tree

Ever since the removal of the make build system, the in tree lndir
hasn't been actually built, so this patch removes it.

- - - - -
86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00
rts: avoid checking bdescr of value outside of Haskell heap

In nonmovingTidyWeaks we want to check if the key of a weak pointer
lives in the non-moving heap. We do this by checking the flags of the
block the key lives in. But we need to be careful with values that live
outside the Haskell heap, since they will lack a block descriptor and
looking for one may lead to a segfault. In this case we should just
accept that it isn't on the non-moving heap.

Resolves #24492

- - - - -
b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00
In mkDataConRep, ensure the in-scope set is right

A small change that fixes #24489

- - - - -
3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00
testsuite: fix T23540 fragility on 32-bit platforms

T23540 is fragile on 32-bit platforms. The root cause is usage of
`getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord`
instance, which is indeterministic. The solution is adding a
deterministic `Ord` instance for `EvidenceInfo` and sorting the
evidence trees before pretty printing. Fixes #24449.

- - - - -
960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00
Reduce AtomicModifyIORef increment count

This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490

- - - - -
2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00
hadrian: Improve parallelism in binary-dist-dir rule

I noticed that the "docs" target was needed after the libraries and
executables were built. We can improve the parallelism by needing
everything at once so that documentation can be built immediately after
a library is built for example.

- - - - -
cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: Bump windows and freebsd boot compilers to 9.6.4

We have previously bumped the docker images to use 9.6.4, but neglected
to bump the windows images until now.

- - - - -
30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: darwin: Update to 9.6.2 for boot compiler

9.6.4 is currently broken due to #24050

Also update to use LLVM-15 rather than LLVM-11, which is out of date.

- - - - -
d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00
Bump minimum bootstrap version to 9.6

- - - - -
67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: Enable more documentation building

Here we enable documentation building on

1. Darwin: The sphinx toolchain was already installed so we enable html
   and manpages.
2. Rocky8: Full documentation (toolchain already installed)
3. Alpine: Full documetnation (toolchain already installed)
4. Windows: HTML and manpages (toolchain already installed)

Fixes #24465

- - - - -
39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00
ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15

- - - - -
d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00
Introduce ListTuplePuns extension

This implements Proposal 0475, introducing the `ListTuplePuns` extension
which is enabled by default.

Disabling this extension makes it invalid to refer to list, tuple and
sum type constructors by using built-in syntax like `[Int]`,
`(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`.
Instead, this syntax exclusively denotes data constructors for use with
`DataKinds`.
The conventional way of referring to these data constructors by
prefixing them with a single quote (`'(Int, Int)`) is now a parser
error.

Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo`
data constructor has been renamed to `MkSolo` (in a previous commit).
Unboxed tuples and sums now have real source declarations in `GHC.Types`.
Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo`
and `Solo#`.
Constraint tuples now have the unambiguous type constructors `CTuple<n>`
as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before.

A new parser construct has been added for the unboxed sum data
constructor declarations.

The type families `Tuple`, `Sum#` etc. that were intended to provide
nicer syntax have been omitted from this change set due to inference
problems, to be implemented at a later time.
See the MR discussion for more info.

Updates the submodule utils/haddock.
Updates the cabal submodule due to new language extension.

    Metric Increase:
        haddock.base

    Metric Decrease:
        MultiLayerModulesTH_OneShot
        size_hello_artifact

Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst

Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820

Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294

- - - - -
bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00
JS linker: filter unboxed tuples

- - - - -
dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00
Improve error messages coming from non-linear patterns

This enriched the `CtOrigin` for non-linear patterns to include data
of the pattern that created the constraint (which can be quite useful
if it occurs nested in a pattern) as well as an explanation why the
pattern is non-restricted in (at least in some cases).

- - - - -
6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00
Adjust documentation of linear lets according to committee decision

- - - - -
1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00
compiler: start deprecating cmmToRawCmmHook

cmmToRawCmmHook was added 4 years ago in
d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the
Asterius project, which has been archived and deprecated in favor of
the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by
placing a DEPRECATED pragma, and actual removal shall happen in a
future GHC major release if no issue to oppose the deprecation has
been raised in the meantime.

- - - - -
9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00
Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258

- - - - -
61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00
add -fprof-late-overloaded and -fprof-late-overloaded-calls

* Refactor late cost centre insertion for extensibility
* Add two more late cost centre insertion methods that add SCCs to overloaded
  top level bindings and call sites with dictionary arguments.
* Some tests for the basic functionality of the new insertion methods

Resolves: #24500

- - - - -
82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00
x86-ncg: Fix fma codegen when arguments are globals

Fix a bug in the x86 ncg where results would be wrong when the desired output
register and one of the input registers were the same global.

Also adds a tiny optimization to make use of the memory addressing
support when convenient.

Fixes #24496

- - - - -
18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00
rel_eng: Update hackage docs upload scripts

This adds the upload of ghc-internal and ghc-experimental to our scripts
which upload packages to hackage.

- - - - -
bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00
docs: Remove stray module comment from GHC.Profiling.Eras

- - - - -
37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00
Fix ghc-internal cabal file

The file mentioned some artifacts relating to the base library. I have
renamed these to the new ghc-internal variants.

- - - - -
23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

- - - - -
2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00
filepath: Bump submodule to 1.5.2.0

- - - - -
31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00
os-string: Bump submodule to 2.0.2

- - - - -
4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00
base: Reflect new era profiling RTS flags in GHC.RTS.Flags

* -he profiling mode
* -he profiling selector
* --automatic-era-increment

CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254

- - - - -
a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00
JS: faster implementation for some numeric primitives (#23597)

Use faster implementations for the following primitives in the JS
backend by not using JavaScript's BigInt:
- plusInt64
- minusInt64
- minusWord64
- timesWord64
- timesInt64

Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com>

- - - - -
21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00
rts: add -xr option to control two step allocator reserved space size

This patch adds a -xr RTS option to control the size of virtual memory
address space reserved by the two step allocator on a 64-bit platform,
see added documentation for explanation. Closes #24498.

- - - - -
dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00
rts: expose HeapAlloc.h as public header

This commit exposes HeapAlloc.h as a public header. The intention is
to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in
assertions in other public headers, and they may also be useful for
user code.

- - - - -
d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00
rts: assert pointer is indeed heap allocated in Bdescr()

This commit adds an assertion to Bdescr() to assert the pointer is
indeed heap allocated. This is useful to rule out RTS bugs that
attempt to access non-existent block descriptor of a static closure, #24492
being one such example.

- - - - -
9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00
ghc-experimental: Add dummy dependencies to work around #23942

This is a temporary measure to improve CI reliability until a proper
solution is developed.

Works around #23942.

- - - - -
1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00
Three compile perf improvements with deep nesting

These were changes are all triggered by #24471.

1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are
   many free variables.  See Note [Large free-variable sets].

2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument.
   This benefits the common case where the ArityType turns out to
   be nullary. See Note [Care with nested expressions]

3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested
   expressions.  See Note [Eta expansion of arguments in CorePrep]
   wrinkle (EA2).

Compile times go down by up to 4.5%, and much more in artificial
cases. (Geo mean of compiler/perf changes is -0.4%.)

Metric Decrease:
    CoOpt_Read
    T10421
    T12425

- - - - -
c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00
Use "module" instead of "library" when applicable in base haddocks

- - - - -
9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00
Rephrase error message to say "visible arguments" (#24318)

* Main change: make the error message generated by mkFunTysMsg more
  accurate by changing "value arguments" to "visible arguments".

* Refactor: define a new type synonym VisArity and use it instead of
  Arity in a few places.

It might be the case that there other places in the compiler that should
talk about visible arguments rather than value arguments, but I haven't
tried to find them all, focusing only on the error message reported in
the ticket.

- - - - -
4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00
fix haskell/haddock#24493, with module name introduced in hieAst

The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153
Two things have been done:
1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst,
2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated.

- - - - -
d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00
Bump array submodule

- - - - -
7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00
Bump stm submodule

- - - - -
32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00
Introduce exception context

Here we introduce the `ExceptionContext` type and `ExceptionAnnotation`
class, allowing dynamically-typed user-defined annotations to be
attached to exceptions.

CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199
GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330

- - - - -
39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00
testsuite/interface-stability: Update documentation

- - - - -
fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00
ghc-internal: comment formatting

- - - - -
4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00
compiler: Default and warn ExceptionContext constraints

- - - - -
3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00
base: Introduce exception backtraces

Here we introduce the `Backtraces` type and associated machinery for
attaching these via `ExceptionContext`. These has a few compile-time
regressions (`T15703` and `T9872d`) due to the additional dependencies
in the exception machinery.

As well, there is a surprisingly large regression in the
`size_hello_artifact` test. This appears to be due to various `Integer` and
`Read` bits now being reachable at link-time. I believe it should be
possible to avoid this but I have accepted the change for now to get the
feature merged.

CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199
GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330

Metric Increase:
    T15703
    T9872d
    size_hello_artifact

- - - - -
18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00
users guide: Release notes for exception backtrace work

- - - - -
f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00
compiler: Don't show ExceptionContext of GhcExceptions

Most GhcExceptions are user-facing errors and therefore the
ExceptionContext has little value. Ideally we would enable
it in the DEBUG compiler but I am leaving this for future work.

- - - - -
dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00
Disable T9930fail for the JS target (cf #19174)

- - - - -
bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00
Update showAstData to honour blanking of AnnParen

Also tweak rendering of SrcSpan to remove extra blank line.

- - - - -
50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00
ghc-internal: Eliminate GHC.Internal.Data.Kind

This was simply reexporting things from `ghc-prim`. Instead reexport
these directly from `Data.Kind`. Also add build ordering dependency to
work around #23942.

- - - - -
38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00
rts: Fix SET_HDR initialization of retainer set

This fixes a regression in retainer set profiling introduced by
b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit
the heap traversal word would be initialized by `SET_HDR` using
`LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling`
check in `LDV_RECORD_CREATE`, meaning that this initialization no longer
happened.

Given that this initialization was awkwardly indirectly anyways, I have
fixed this by explicitly initializating the heap traversal word to
`NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior,
but much more direct.

Fixes #24513.

- - - - -
635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00
Bump ghc version to 9.10

- - - - -
2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00
base: Use strerror_r instead of strerror

As noted by #24344, `strerror` is not necessarily thread-safe.
Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is
safe to use.

Fixes #24344.

CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249

- - - - -
5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00
Bump base upper bound

- - - - -
b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00
Testsuite output update

- - - - -
edb9bf77 by Jade at 2024-03-09T03:39:38-05:00
Error messages: Improve Error messages for Data constructors in type signatures.

This patch improves the error messages from invalid type signatures by
trying to guess what the user did and suggesting an appropriate fix.

Partially fixes: #17879

- - - - -
cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00
HieAst: add module name #24493

The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst.
It should fix #24493.

The following have been done:
1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))`
   To store the located module name information.
2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information.
3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests.
4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53

- - - - -
2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00
GHC.Utils.Binary: fix a couple of typos

- - - - -
5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00
rts: Drop .wasm suffix from .prof file names

This replicates the behavior on Windows, where `Hi.exe` will produce
profiling output named `Hi.prof` instead of `Hi.exe.prof`.

While in the area I also fixed the extension-stripping logic, which
incorrectly rewrote `Hi.exefoo` to `Hi.foo`.

Closes #24515.

- - - - -
259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00
testsuite: drop exe extension from .hp & .prof filenames

See #24515 for details.

- - - - -
c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00
rts/linker: Enable GOT support on all platforms

There is nothing platform-dependent about our GOT implementation and
GOT support is needed by `T24171` on i386.

- - - - -
2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00
Drop outdated comment on TcRnIllformedTypePattern

This should have been done in 0f0c53a501b but I missed it.

- - - - -
c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Bounds check array write

- - - - -
15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Don't expose helper functions in header

- - - - -
e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00
base: Move internals of GHC.InfoProv into GHC.InfoProv.Types

Such that we can add new helpers into GHC.InfoProv.Types without
breakage.

- - - - -
6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00
rts: Lazily decode IPE tables

Previously we would eagerly allocate `InfoTableEnt`s for each
info table registered in the info table provenance map. However, this
costs considerable memory and initialization time. Instead we now
lazily decode these tables. This allows us to use one-third the memory
*and* opens the door to taking advantage of sharing opportunities within
a module.

This required considerable reworking since lookupIPE now must be passed
its result buffer.

- - - - -
9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Don't expose helper in header

- - - - -
308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Share module_name within a Node

This allows us to shave a 64-bit word off of the packed IPE entry size.

- - - - -
bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00
IPE: Expose unit ID in InfoTableProv

Here we add the unit ID to the info table provenance structure.

- - - - -
6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00
rts: Refactor GHC.Stack.CloneStack.decode

Don't allocate a Ptr constructor per frame.

- - - - -
ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00
base: Do not expose whereFrom# from GHC.Exts

- - - - -
2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00
docs: Update info on TypeAbstractions

* Mention TypeAbstractions in 9.10.1-notes.rst
* Set the status to "Experimental".
* Add a "Since: GHC 9.x" comment to each section.

- - - - -
f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00
ci-images: Bump Alpine image to bootstrap with 9.8.2

- - - - -
705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark T24171 as fragile due to #24512

I will fix this but not in time for 9.10.1-alpha1

- - - - -
c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark linker_unload_native as fragile

In particular this fails on platforms without `dlinfo`. I plan to
address this but not before 9.10.1-alpha1.

- - - - -
f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00
configure: Bump version to 9.10

- - - - -
88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00
Bump transformers submodule to 0.6.1.1

- - - - -
8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Increase ulimit for T18623

1 MByte was just too tight and failed intermittently on some platforms
(e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient
headroom.

Fixes #23139.

- - - - -
c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00
base: Bump version to 4.20.0.0

- - - - -
b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-internal: Set initial version at 9.1001.0

This provides PVP compliance while maintaining a clear correspondence
between GHC releases and `ghc-internal` versions.

- - - - -
4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-prim: Bump version to 0.11.0

- - - - -
50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00
template-haskell: Bump version to 2.22.0.0

- - - - -
8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00
base-exports: Accommodate spurious whitespace changes in 32-bit output

It appears that this was

- - - - -
9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00
users-guide: Move exception backtrace relnotes to 9.10

This was previously mistakenly added to the GHC 9.8 release notes.

- - - - -
145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix name of Rocky8 artifact

- - - - -
39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix path of generate_jobs_metadata

- - - - -
aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/upload: Rework recompression

The old `combine` approach was quite fragile due to use of filename
globbing. Moreover, it didn't parallelize well. This refactoring
makes the goal more obvious, parallelizes better, and is more robust.

- - - - -
9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00
Merge branch 'ghc-9.10' into ghc-head

- - - - -
cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00
Bump GHC version to 9.11

- - - - -
4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00
configure: Bump GHC version to 9.11

Bumps haddock submodule.

- - - - -
8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload code when profiling is enabled

The heap census may contain references (e.g. `Counter.identity`) to
static data which must be available when the census is reported at the
end of execution.

Fixes #24512.

- - - - -
7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00
rel_eng/upload: Purge both $rel_name/ and $ver/

This is necessary for prereleases, where GHCup accesses the release via
`$ver/`

- - - - -
b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Remove duplicate code normalising slashes

- - - - -
c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Simplify regexes with raw strings

- - - - -
1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00
Don't normalize backslashes in characters

- - - - -
7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00
Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470)

- - - - -
39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00
Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms"

This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was
originally intended to fix #24449, but it was merely sweeping the bug
under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly
fixed the fragile test, and we no longer need the C version of genSym.
Furthermore, the C implementation causes trouble when compiling with
clang that targets i386 due to alignment warning and libatomic linking
issue, so it makes sense to revert it.

- - - - -
e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00
compiler: fix out-of-bound memory access of genSym on 32-bit

This commit fixes an unnoticed out-of-bound memory access of genSym on
32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms,
but we mistakenly treat it as a Word64 pointer in genSym, and
therefore will accidentally load 2 garbage higher bytes, or with a
small but non-zero chance, overwrite something else in the data
section depends on how the linker places the data segments. This
regression was introduced in !11802 and fixed here.

- - - - -
77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00
Note mutability of array and address access primops

Without an understanding of immutable vs. mutable memory, the index
primop family have a potentially non-intuitive type signature:

    indexOffAddr :: Addr# -> Int# -> a
    readOffAddr  :: Addr# -> Int# -> State# d -> (# State# d, a #)

indexOffAddr# might seem like a free generality improvement, which it
certainly is not!

This change adds a brief note on mutability expectations for most
index/read/write access primops.

- - - - -
7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00
EPA: Fix regression discarding comments in contexts

Closes #24533

- - - - -
73be65ab by Fendor at 2024-03-19T01:42:53-04:00
Fix sharing of 'IfaceTyConInfo' during core to iface type translation

During heap analysis, we noticed that during generation of
'mi_extra_decls' we have lots of duplicates for the instances:

* `IfaceTyConInfo NotPromoted IfaceNormalTyCon`
* `IfaceTyConInfo IsPromoted IfaceNormalTyCon`

which should be shared instead of duplicated. This duplication increased
the number of live bytes by around 200MB while loading the agda codebase
into GHCi.

These instances are created during `CoreToIface` translation, in
particular `toIfaceTyCon`.

The generated core looks like:

    toIfaceTyCon
      = \ tc_sjJw ->
          case $wtoIfaceTyCon tc_sjJw of
          { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) ->
          IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM)
          }

whichs removes causes the sharing to work propery.

Adding explicit sharing, with NOINLINE annotations, changes the core to:

    toIfaceTyCon
      = \ tc_sjJq ->
          case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) ->
          IfaceTyCon ww_sjNB ww1_sjNC
          }

which looks much more like sharing is happening.
We confirmed via ghc-debug that all duplications were eliminated and the
number of live bytes are noticeably reduced.

- - - - -
bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00
EPA: Address more 9.10.1-alpha1 regressions from recent changes

Closes #24533
Hopefully for good this time

- - - - -
31bf85ee by Fendor at 2024-03-19T14:48:08-04:00
Escape multiple arguments in the settings file

Uses responseFile syntax.

The issue arises when GHC is installed on windows into a location that
has a space, for example the user name is 'Fake User'.
The $topdir will also contain a space, consequentially.
When we resolve the top dir in the string `-I$topdir/mingw/include`,
then `words` will turn this single argument into `-I/C/Users/Fake` and
`User/.../mingw/include` which trips up the flag argument parser of
various tools such as gcc or clang.
We avoid this by escaping the $topdir before replacing it in
`initSettngs`.
Additionally, we allow to escape spaces and quotation marks for
arguments in `settings` file.

Add regression test case to count the number of options after variable
expansion and argument escaping took place.
Additionally, we check that escaped spaces and double quotation marks are
correctly parsed.

- - - - -
f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00
Read global package database from settings file

Before this patch, the global package database was always assumed to be
in libdir </> package.conf.d.

This causes issues in GHC's build system because there are sometimes
situations where the package database you need to use is not located in
the same place as the settings file.

* The stage1 compiler needs to use stage1 libraries, so we should set
  "Global Package DB" for the stage1 compiler to the stage1 package
  database.
* Stage 2 cross compilers need to use stage2 libraries, so likewise, we
  should set the package database path to `_build/stage2/lib/`

* The normal situation is where the stage2 compiler uses stage1
  libraries. Then everything lines up.

* When installing we have rearranged everything so that the settings
  file and package database line up properly, so then everything should
  continue to work as before. In this case we set the relative package
  db path to `package.conf.d`, so it resolves the same as before.

* ghc-pkg needs to be modified as well to look in the settings file fo
  the package database rather than assuming the global package database
  location relative to the lib folder.

* Cabal/cabal-install will work correctly because they query the global
  package database using `--print-global-package-db`.

A reasonable question is why not generate the "right" settings files in
the right places in GHC's build system. In order to do this you would
need to engineer wrappers for all executables to point to a specific
libdir. There are also situations where the same package db is used by
two different compilers with two different settings files (think stage2
cross compiler and stage3 compiler).

In short, this 10 line patch allows for some reasonable simplifications
in Hadrian at very little cost to anything else.

Fixes #24502

- - - - -
4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00
hadrian: Remove stage1 testsuite wrappers logic

Now instead of producing wrappers which pass the global package database
argument to ghc and ghc-pkg, we write the location of the correct
package database into the settings file so you can just use the intree
compiler directly.

- - - - -
da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00
Remove unused ghc-internal module "GHC.Internal.Constants"

- - - - -
b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00
CorePrep: Rework lowering of BigNat# literals

Don't use bigNatFromWord#, because that's terrible:
 * We shouldn't have to traverse a linked list at run-time
   to build a BigNat# literal. That's just silly!
 * The static List object we have to create is much larger
   than the actual BigNat#'s contents, bloating code size.
 * We have to read the corresponding interface file,
   which causes un-tracked implicit dependencies. (#23942)

Instead, encode them into the appropriate platform-dependent
sequence of bytes, and generate code that copies these bytes
at run-time from an Addr# literal into a new ByteArray#.
A ByteArray# literal would be the correct thing to generate,
but these are not yet supported; see also #17747.

Somewhat surprisingly, this change results in a slight
reduction in compiler allocations, averaging around 0.5%
on ghc's compiler performance tests, including when compiling
programs that contain no bignum literals to begin with.
The specific cause of this has not been investigated.

Since this lowering no longer reads the interface file for
GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer]
is obsoleted.  But the story of un-tracked built-in dependencies
remains complex, and Note [Tracking dependencies on primitives]
now exists to explain this complexity.

Additionally, many empty imports have been modified to refer to
this new note and comply with its guidance.  Several empty imports
necessary for other reasons have also been given brief explanations.

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
349ea330 by Fendor at 2024-03-19T14:50:00-04:00
Eliminate thunk in 'IfaceTyCon'

Heap analysis showed that `IfaceTyCon` retains a thunk to
`IfaceTyConInfo`, defeating the sharing of the most common instances of
`IfaceTyConInfo`.
We make sure the indirection is removed by adding bang patterns to
`IfaceTyCon`.

Experimental results on the agda code base, where the `mi_extra_decls`
were read from disk:

Before this change, we observe around 8654045 instances of:

`IfaceTyCon[Name,THUNK_1_0]`

But these thunks almost exclusively point to a shared value!

Forcing the thunk a little bit more, leads to `ghc-debug` reporting:

`IfaceTyCon[Name:Name,IfaceTyConInfo]`

and a noticeable reduction of live bytes (on agda ~10%).

- - - - -
594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00
Minor misc cleanups

- GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs;
  boxed tuples don't take RuntimeRep args
- GHC.HsToCore.Foreign.Call: avoid partial pattern matching
- GHC.Stg.Unarise: strengthen the assertion; we can assert that
  non-rubbish literals are unary rather than just non-void
- GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires
- users_guide/using-warnings.rst: remove -Wforall-identifier,
  now deprecated and does nothing
- users_guide/using.rst: fix formatting
- andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed

The rest are simple cleanups.

- - - - -
cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00
mk/relpath: Fix quoting

Previously there were two instances in this script which lacked proper
quoting. This resulted in `relpath` invocations in the binary
distribution Makefile producing incorrect results on Windows, leading to
confusing failures from `sed` and the production of empty package
registrations.

Fixes #24538.

- - - - -
5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00
testsuite: Disable T21336a on wasm

- - - - -
60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00
hadrian/bindist: Eliminate extraneous `dirname` invocation

Previously we would call `dirname` twice per installed library file.
We now instead reuse this result. This helps appreciably on Windows, where
processes are quite expensive.

- - - - -
616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00
hadrian: Package mingw toolchain in expected location

This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89.
Specifically, GHC expects to find the mingw32 toolchain in the binary distribution
root. However, after this patch it was packaged in the `lib/` directory.

- - - - -
de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00
gitlab/rel_eng: More upload.sh tweaks

- - - - -
1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00
rel_eng: Drop dead prepare_docs codepath

- - - - -
dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00
rel_env/recompress_all: unxz before recompressing

Previously we would rather compress the xz *again*, before in addition
compressing it with the desired scheme.

Fixes #24545.

- - - - -
9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00
mk-ghcup-metadata: Fix directory of testsuite tarball

As reported in #24546, the `dlTest` artifact should be extracted into
the `testsuite` directory.

- - - - -
6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00
ghcup-metadata: Don't populate dlOutput unless necessary

ghcup can apparently infer the output name of an artifact from its URL.
Consequently, we should only include the `dlOutput` field when it would
differ from the filename of `dlUri`.

Fixes #24547.

- - - - -
576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00
Revert "Apply shellcheck suggestion to SUBST_TOOLDIR"

This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392.

The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a
no-op. `set` sets positional arguments for bash, but we want to set the variable
given as the first autoconf argument.

Fixes #24542

Metric decreases because the paths in the settings file are now shorter,
so we allocate less when we read the settings file.

-------------------------
Metric Decrease:
    T12425
    T13035
    T9198
-------------------------

- - - - -
cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00
Compact serialisation of IfaceAppArgs

In #24563, we identified that IfaceAppArgs serialisation tags each
cons cell element with a discriminator byte. These bytes add up
quickly, blowing up interface files considerably when
'-fwrite-if-simplified-core' is enabled.

We compact the serialisation by writing out the length of
'IfaceAppArgs', followed by serialising the elements directly without
any discriminator byte.

This improvement can decrease the size of some interface files by up
to 35%.

- - - - -
97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00
Expand untyped splices in tcPolyExprCheck

Fixes #24559

- - - - -
5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00
EPA: Clean up Exactprint helper functions a bit

- Introduce a helper lens to compose on `EpAnn a` vs `a` versions
- Rename some prime versions of functions back to non-prime
  They were renamed during the rework

- - - - -
da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00
Type operators in promoteOccName (#24570)

Type operators differ from term operators in that they are lexically
classified as (type) constructors, not as (type) variables.

Prior to this change, promoteOccName did not account for this
difference, causing a scoping issue that affected RequiredTypeArguments.

  type (!@#) = Bool
  f = idee (!@#)      -- Not in scope: ‘!@#’  (BUG)

Now we have a special case in promoteOccName to account for this.

- - - - -
247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00
docs: Remove mention of non-existent Ord instance for Complex

The documentation for Data.Complex says that the Ord instance for Complex Float
is deficient, but there is no Ord instance for Complex a. The Eq instance for
Complex Float is similarly deficient, so we use that as an example instead.

- - - - -
6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00
Fix TH handling in `pat_to_type_pat` function (#24571)

There was missing case for `SplicePat` in `pat_to_type_at` function,
hence patterns with splicing that checked against `forall->` doesn't work
properly because they fall into the "illegal pattern" case.

Code example that is now accepted:

  g :: forall a -> ()
  g $([p| a |]) = ()

- - - - -
52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00
Type-check default declarations before deriving clauses (#24566)

See added Note and #24566. Default declarations must be type-checked
before deriving clauses.

- - - - -
7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00
Lexer: small perf changes

- Use unsafeChr because we know our values to be valid
- Remove some unnecessary use of `ord` (return Word8 values directly)

- - - - -
864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00
JS: fix some comments

- - - - -
3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00
Simplifier: Re-do dependency analysis in abstractFloats (#24551)

In #24551, we abstracted a string literal binding over a type variable,
triggering a CoreLint error when that binding floated to top-level.

The solution implemented in this patch fixes this by re-doing dependency
analysis on a simplified recursive let binding that is about to be type
abstracted, in order to find the minimal set of type variables to abstract over.
See wrinkle (AB5) of Note [Floating and type abstraction] for more details.

Fixes #24551

- - - - -
8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00
Improve toInteger @Word32 on 64-bit platforms

On 64-bit platforms, every Word32 fits in an Int, so we can
convert to Int# without having to perform the overflow check
integerFromWord# uses internally.

- - - - -
0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00
Fix for #24552 (see testcase T24552)

Fixes for a bug in desugaring pattern synonyms matches, introduced
while working on  on expanding `do`-blocks in #18324

The `matchWrapper` unecessarily (and incorrectly) filtered out the
default wild patterns in a match. Now the wild pattern alternative is
simply ignored by the pm check as its origin is `Generated`.
The current code now matches the expected semantics according to the language spec.

- - - - -
b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00
Print more info about kinds in error messages

This fixes #24553, where GHC unhelpfully said

  error: [GHC-83865]
    • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’

See Note [Showing invisible bits of types in error messages]

- - - - -
8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00
docs: remove the don't use float hint

This hint is outdated, ``Complex Float`` are now specialised,
and the heap space suggestion needs more nuance so it should
be explained in the unboxed/storable array documentation.

- - - - -
5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00
NCG: Fix a bug in jump shortcutting.

When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.

We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.

Fixes #24507

- - - - -
8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00
docs: Drop old release notes, add for 9.12.1

- - - - -
7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00
rts: fix clang compilation on aarch64

This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h
which causes "error: address argument to atomic operation must be a
pointer to _Atomic type" when compiling with clang on aarch64.

- - - - -
237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00
Lexer: fix imports for Alex 3.5.1 (#24583)

- - - - -
810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00
libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6

This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which
includes numerous upstream libffi fixes, especially
https://github.com/libffi/libffi/issues/760.

- - - - -
d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00
EPA: do not duplicate comments in signature RHS

- - - - -
32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00
configure: Use LDFLAGS when trying linkers

A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we
will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to
check for a working linker. If either of these fail, we try the next in
line.

However, we were not considering the `$LDFLAGS` when checking if these
linkers worked. So we would pick a linker that does not support the
current $LDFLAGS and fail further down the line when we used that linker
with those flags.

Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not
supported by `ld.gold` but that was being picked still.

- - - - -
bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00
bindist: Clean xattrs of bin and lib at configure time

For issue #21506, we started cleaning the extended attributes of
binaries and libraries from the bindist *after* they were installed to
workaround notarisation (#17418), as part of `make install`.

However, the `ghc-toolchain` binary that is now shipped with the bindist
must be run at `./configure` time. Since we only cleaned the xattributes
of the binaries and libs after they were installed, in some situations
users would be unable to run `ghc-toolchain` from the bindist, failing
at configure time (#24554).

In this commit we move the xattr cleaning logic to the configure script.

Fixes #24554

- - - - -
cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00
Revert "NCG: Fix a bug in jump shortcutting."

This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66.

Fixes #24586

- - - - -
13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00
JS: `h$rts_isProfiled` is removed from `profiling` and left its version at
`rts/js/config.js`

- - - - -
0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00
EPA: Do not extend declaration range for trailine zero len semi

The lexer inserts virtual semicolons having zero width.
Do not use them to extend the list span of items in a list.

- - - - -
cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00
EPA: Fix FamDecl range

The span was incorrect if opt_datafam_kind_sig was empty

- - - - -
f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00
Fix type of _get_osfhandle foreign import

Fixes #24601.

- - - - -
00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00
EPA: Extend StringLiteral range to include trailing commas

This goes slightly against the exact printing philosophy where
trailing decorations should be in an annotation, but the
practicalities of adding it to the WarningTxt environment, and the
problems caused by deviating do not make a more principles approach
worthwhile.

- - - - -
efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00
clarify Note [Preproccesing invocations]

- - - - -
c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00
rts: Fix TSAN_ENABLED CPP guard

This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`,
lest we suffer warnings.

- - - - -
e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00
rts: fix errors when compiling with TSAN

This commit fixes rts compilation errors when compiling with TSAN:

- xxx_FENCE macros are redefined and trigger CPP warnings.
- Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which
  Cmm.h doesn't include by default.

- - - - -
a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00
rts: fix clang-specific errors when compiling with TSAN

This commit fixes clang-specific rts compilation errors when compiling
with TSAN:

- clang doesn't have -Wtsan flag
- Fix prototype of ghc_tsan_* helper functions
- __tsan_atomic_* functions aren't clang built-ins and
  sanitizer/tsan_interface_atomic.h needs to be included
- On macOS, TSAN runtime library is
  libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread
  as a link-time flag will take care of linking the TSAN runtime
  library anyway so remove tsan as an rts extra library

- - - - -
865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00
compiler: fix github link to __tsan_memory_order in a comment

- - - - -
07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00
ci: improve TSAN CI jobs

- Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm
  instrumentation as well.
- Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc
  that @bgamari confirms he's using in #GHC:matrix.org. Ideally we
  should be using latest clang release for latest improvements in
  sanitizers, though that's left as future work.
- Mark TSAN jobs as manual+allow_failure in validate pipelines. The
  purpose is to demonstrate that we have indeed at least fixed
  building of TSAN mode in CI without blocking the patch to land, and
  once merged other people can begin playing with TSAN using their own
  dev setups and feature branches.

- - - - -
a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00
Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639)

This patch implements refactoring which is a prerequisite to
updating kind checking of type patterns. This is a huge simplification
of the main worker that checks kind of HsType.

It also fixes the issues caused by previous code duplication, e.g.
that we didn't add module finalizers from splices in inference mode.

- - - - -
817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00
th: Hide the Language.Haskell.TH.Lib.Internal module from haddock

Fixes #24562

- - - - -
b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00
JS: reenable h$appendToHsString optimization (#24495)

The optimization introducing h$appendToHsString wasn't kicking in
anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30).
This patch reenables the optimization by matching on case-expression, as
done in Cmm for unpackCString# standard thunks.

The test is also T24495 added in the next commits (two commits for ease
of backporting to 9.8).

- - - - -
527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00
JS: fix h$appendToHsString implementation (#24495)

h$appendToHsString needs to wrap its argument in an updatable thunk
to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is
passed, it is stored as-is in a CONS cell, making the resulting list
impossible to deepseq (forcing the thunk doesn't update the contents of
the CONS cell)!

The added test checks that the optimization kicks in and that
h$appendToHsString works as intended.

Fix #24495

- - - - -
faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00
Deal with duplicate tyvars in type declarations

GHC was outright crashing before this fix: #24604

- - - - -
e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00
Try using MCoercion in exprIsConApp_maybe

This is just a simple refactor that makes exprIsConApp_maybe
a little bit more direct, simple, and efficient.

Metrics: compile_time/bytes allocated
    geo. mean                                          -0.1%
    minimum                                            -2.0%
    maximum                                            -0.0%

Not a big gain, but worthwhile given that the code is, if anything,
easier to grok.

- - - - -
15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Initial ./configure support for selecting I/O managers

In this patch we just define new CPP vars, but don't yet use them
or replace the existing approach. That will follow.

The intention here is that every I/O manager can be enabled/disabled at
GHC build time (subject to some constraints). More than one I/O manager
can be enabled to be built. At least one I/O manager supporting the
non-threaded RTS must be enabled as well as at least one supporting the
non-threaded RTS. The I/O managers enabled here will become the choices
available at runtime at RTS startup (in later patches). The choice can
be made with RTS flags. There are separate sets of choices for the
threaded and non-threaded RTS ways, because most I/O managers are
specific to these ways. Furthermore we must establish a default I/O
manager for the threaded and non-threaded RTS.

Most I/O managers are platform-specific so there are checks to ensure
each one can be enabled on the platform. Such checks are also where (in
future) any system dependencies (e.g. libraries) can be checked.

The output is a set of CPP flags (in the mk/config.h file), with one
flag per named I/O manager:
* IOMGR_BUILD_<name>                : which ones should be built (some)
* IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one)
* IOMGR_DEFAULT_THREADED_<name>     : which one is default (exactly one)

and a set of derived flags in IOManager.h

* IOMGR_ENABLED_<name>              : enabled for the current RTS way

Note that IOMGR_BUILD_<name> just says that an I/O manager will be
built for _some_ RTS way (i.e. threaded or non-threaded). The derived
flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is
enabled in the "current" RTS way. These are the ones that can be used
for conditional compilation of the I/O manager code.

Co-authored-by: Pi Delport <pi at well-typed.com>

- - - - -
85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00
Change the handling of the RTS flag --io-manager=

Now instead of it being just used on Windows to select between the WinIO
vs the MIO or Win32-legacy I/O managers, it is now used on all platforms
for selecting the I/O manager to use.

Right now it remains the case that there is only an actual choice on
Windows, but that will change later.

Document the --io-manager flag in the user guide.

This change is also reflected in the RTS flags types in the base
library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a
message to import it from GHC.IO.Subsystem.

The way the 'IoSubSystem' is detected also changes. Instead of looking
at the RTS flag, there is now a C bool global var in the RTS which gets
set on startup when the I/O manager is selected. This bool var says
whether the selected I/O manager classifies as "native" on Windows,
which in practice means the WinIO I/O manager has been selected.

Similarly, the is_io_mng_native_p RTS helper function is re-implemented
in terms of the selected I/O manager, rather than based on the RTS
flags.

We do however remove the ./configure --native-io-manager flag because
we're bringing the WinIO/MIO/Win32-legacy choice under the new general
scheme for selecting I/O managers, and that new scheme involves no
./configure time user choices, just runtime RTS flag choices.

- - - - -
1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00
Convert {init,stop,exit}IOManager to switch style

Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS,
we use a style where we switch on the I/O manager impl, with cases for
each I/O manager impl.

- - - - -
a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Split up the CapIOManager content by I/O manager

Using the new IOMGR_ENABLED_<name> CPP defines.

- - - - -
1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Convert initIOManagerAfterFork and wakeupIOManager to switch style

- - - - -
c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move most of waitRead#/Write# from cmm to C

Moves it into the IOManager.c where we can follow the new pattern of
switching on the selected I/O manager.

- - - - -
457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move most of the delay# impl from cmm to C

Moves it into the IOManager.c where we can follow the new pattern of
switching on the selected I/O manager.

Uses a new IOManager API: syncDelay, following the naming convention of
sync* for thread-synchronous I/O & timer/delay operations.

As part of porting from cmm to C, we maintain the rule that the
why_blocked gets accessed using load acquire and store release atomic
memory operations. There was one exception to this rule: in the delay#
primop cmm code on posix (not win32), the why_blocked was being updated
using a store relaxed, not a store release. I've no idea why. In this
convesion I'm playing it safe here and using store release consistently.

- - - - -
e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00
insertIntoSleepingQueue is no longer public

No longer defined in IOManager.h, just a private function in
IOManager.c. Since it is no longer called from cmm code, just from
syncDelay. It ought to get moved further into the select() I/O manager
impl, rather than living in IOManager.c.

On the other hand appendToIOBlockedQueue is still called from cmm code
in the win32-legacy I/O manager primops async{Read,Write}#, and it is
also used by the select() I/O manager. Update the CPP and comments to
reflect this.

- - - - -
60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move anyPendingTimeoutsOrIO impl from .h to .c

The implementation is eventually going to need to use more private
things, which will drag in unwanted includes into IOManager.h, so it's
better to move the impl out of the header file and into the .c file, at
the slight cost of it no longer being inline.

At the same time, change to the "switch (iomgr_type)" style.

- - - - -
f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Take a simpler approach to gcc warnings in IOManager.c

We have lots of functions with conditional implementations for
different I/O managers. Some functions, for some I/O managers,
naturally have implementations that do nothing or barf. When only one
such I/O manager is enabled then the whole function implementation will
have an implementation that does nothing or barfs. This then results in
warnings from gcc that parameters are unused, or that the function
should be marked with attribute noreturn (since barf does not return).
The USED_IF_THREADS trick for fine-grained warning supression is fine
for just two cases, but an equivalent here would need
USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial
blowup. So we take a coarse grained approach and simply disable these
two warnings for the whole file.

So we use a GCC pragma, with its handy push/pop support:

 #pragma GCC diagnostic push
 #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn"
 #pragma GCC diagnostic ignored "-Wunused-parameter"

...

 #pragma GCC diagnostic pop

- - - - -
b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add a new trace class for the iomanager

It makes sense now for it to be separate from the scheduler class of
tracers.

Enabled with +RTS -Do. Document the -Do debug flag in the user guide.

- - - - -
f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Have the throwTo impl go via (new) IOManager APIs

rather than directly operating on the IO manager's data structures.

Specifically, when thowing an async exception to a thread that is
blocked waiting for I/O or waiting for a timer, then we want to cancel
that I/O waiting or cancel the timer. Currently this is done directly in
removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs
both for modularity but also to let us support multiple I/O managers.

So add sync{IO,Delay}Cancel, which is the cancellation for the
corresponding sync{IO,Delay}. The implementations of these use the usual
"switch (iomgr_type)" style.

- - - - -
4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move awaitEvent into a proper IOManager API

and have the scheduler use it.

Previously the scheduler calls awaitEvent directly, and awaitEvent is
implemented directly in the RTS I/O managers (select, win32). This
relies on the old scheme where there's a single active I/O manager for
each platform and RTS way.

We want to move that to go via an API in IOManager.{h,c} which can then
call out to the active I/O manager.

Also take the opportunity to split awaitEvent into two. The existing
awaitEvent has a bool wait parameter, to say if the call should be
blocking or non-blocking. We split this into two separate functions:
pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them
for a few reasons: they have different post-conditions (specifically the
await version is supposed to guarantee that there are threads runnable
when it completes). Secondly, it is also anticipated that in future I/O
managers the implementations of the two cases will be simpler if they
are separated.

- - - - -
5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00
Rename awaitEvent in select and win32 I/O managers

These are now just called from IOManager.c and are the per-I/O manager
backend impls (whereas previously awaitEvent was the entry point).

Follow the new naming convention in the IOManager.{h,c} of
awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix:
so awaitCompletedTimeoutsOrIO{Select,Win32}.

- - - - -
d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Tidy up a couple things in Select.{h,c}

Use the standard #include {Begin,End}Private.h style rather than
RTS_PRIVATE on individual decls.

And conditionally build the code for the select I/O manager based on
the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS.

- - - - -
4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add an IOManager API for scavenging TSO blocked_info

When the GC scavenges a TSO it needs to scavenge the tso->blocked_info
but the blocked_info is a big union and what lives there depends on the
two->why_blocked, which for I/O-related reasons is something that in
principle is the responsibility of the I/O manager and not the GC. So
the right thing to do is for the GC to ask the I/O manager to sscavenge
the blocked_info if it encounters any I/O-related why_blocked reasons.

So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style.

Now as it happens, right now, there is no special scavenging to do, so
the implementation of scavengeTSOIOManager is a fancy no-op. That's
because the select I/O manager uses only the fd and target members,
which are not GC pointers, and the win32-legacy I/O manager _ought_ to
be using GC-managed heap objects for the StgAsyncIOResult but it is
actually usingthe C heap, so again no GC pointers. If the win32-legacy
were doing this more sensibly, then scavengeTSOIOManager would be the
right place to do the GC magic.

Future I/O managers will need GC heap objects in the tso->blocked_info
and will make use of this functionality.

- - - - -
94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add I/O manager API notifyIOManagerCapabilitiesChanged

Used in setNumCapabilities.

It only does anything for MIO on Posix.

Previously it always invoked Haskell code, but that code only did
anything on non-Windows (and non-JS), and only threaded. That currently
effectively means the MIO I/O manager on Posix.

So now it only invokes it for the MIO Posix case.

- - - - -
3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Select an I/O manager early in RTS startup

We need to select the I/O manager to use during startup before the
per-cap I/O manager initialisation.

- - - - -
aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Make struct CapIOManager be fully opaque

Provide an opaque (forward) definition in Capability.h (since the cap
contains a *CapIOManager) and then only provide a full definition in
a new file IOManagerInternals.h. This new file is only supposed to be
included by the IOManager implementation, not by its users. So that
means IOManager.c and individual I/O manager implementations.

The posix/Signals.c still needs direct access, but that should be
eliminated. Anything that needs direct access either needs to be clearly
part of an I/O manager (e.g. the sleect() one) or go via a proper API.

- - - - -
877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00
The select() I/O manager does have some global initialisation

It's just to make sure an exception CAF is a GC root.

- - - - -
9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add tracing for the main I/O manager actions

Using the new tracer class.

Note: The unconditional definition of showIOManager should be
compatible with the debugTrace change in 7c7d1f6.

Co-authored-by: Pi Delport <pi at well-typed.com>

- - - - -
c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Include the default I/O manager in the +RTS --info output

Document the extra +RTS --info output in the user guide

- - - - -
8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00
waitRead# / waitWrite# do not work for win32-legacy I/O manager

Previously it was unclear that they did not work because the code path
was shared with other I/O managers (in particular select()).

Following the code carefully shows that what actually happens is that
the calling thread would block forever: the thread will be put into the
blocked queue, but no other action is scheduled that will ever result in
it getting unblocked.

It's better to just fail loudly in case anyone accidentally calls it,
also it's less confusing code.

- - - - -
83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Conditionally ignore some GCC warnings

Some GCC versions don't know about some warnings, and they complain
that we're ignoring unknown warnings. So we try to ignore the warning
based on the GCC version.

- - - - -
1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Accept changes to base-exports

All the changes are in fact not changes at all.

Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and
exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data
type is defined in GHC.IO.SubSystem and still exported from both
modules.

Therefore, the same exports and same instances are still available from
both modules. But the base-exports records only the defining module, and
so it looks like a change when it is fully compatible.

Related: we do add a deprecation to the export of the type via
GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem.

Also the sort order for some unrelated Show instances changed. No idea
why.

The same changes apply in the other versions, with a few more changes
due to sort order weirdness.

- - - - -
8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Accept metric decrease in T12227

I can't think of any good reason that anything in this MR should have
changed the number of allocations, up or down.

(Yes this is an empty commit.)

Metric Decrease:
    T12227

- - - - -
e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Several improvements to the handling of coercions

* Make `mkSymCo` and `mkInstCo` smarter
  Fixes #23642

* Fix return role of `SelCo` in the coercion optimiser.
  Fixes #23617

* Make the coercion optimiser `opt_trans_rule` work better for newtypes
  Fixes #23619

- - - - -
1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
FloatOut: improve floating for join point

See the new Note [Floating join point bindings].

* Completely get rid of the complicated join_ceiling nonsense, which
  I have never understood.

* Do not float join points at all, except perhaps to top level.

* Some refactoring around wantToFloat, to treat Rec and NonRec more
  uniformly

- - - - -
9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Improve eta-expansion through call stacks

See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity

This is a one-line change, that fixes an inconsistency
-               || isCallStackPredTy ty
+               || isCallStackPredTy ty || isCallStackTy ty

- - - - -
95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Spelling, layout, pretty-printing only

- - - - -
bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Improve exprIsConApp_maybe a little

Eliminate a redundant case at birth.  This sometimes reduces
Simplifier iterations.

See Note [Case elim in exprIsConApp_maybe].

- - - - -
609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo

When exploring compile-time regressions after meddling with the Simplifier, I
discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately
balanced.  It's a small, heavily used, overloaded function and it's important
that it inlines. By a fluke it was before, but at various times in my journey it
stopped doing so.  So I just added an INLINE pragma to it; no sense in depending
on a delicately-balanced fluke.

- - - - -
ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Slight improvement in WorkWrap

Ensure that WorkWrap preserves lambda binders, in case of join points.  Sadly I
have forgotten why I made this change (it was while I was doing a lot of
meddling in the Simplifier, but
  * it does no harm,
  * it is slightly more efficient, and
  * presumably it made something better!

Anyway I have kept it in a separate commit.

- - - - -
e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Use named record fields for the CastIt { ... } data constructor

This is a pure refactor

- - - - -
b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Remove a long-commented-out line

Pure refactoring

- - - - -
e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Simplifier improvements

This MR started as: allow the simplifer to do more in one pass,
arising from places I could see the simplifier taking two iterations
where one would do.  But it turned into a larger project, because
these changes unexpectedly made inlining blow up, especially join
points in deeply-nested cases.

The main changes are below.  There are also many new or rewritten Notes.

Avoiding simplifying repeatedly
~~~~~~~~~~~~~~~
See Note [Avoiding simplifying repeatedly]

* The SimplEnv now has a seInlineDepth field, which says how deep
  in unfoldings we are.  See Note [Inline depth] in Simplify.Env.
  Currently used only for the next point: avoiding repeatedly
  simplifying coercions.

* Avoid repeatedly simplifying coercions.
  see Note [Avoid re-simplifying coercions] in Simplify.Iteration
  As you'll see from the Note, this makes use of the seInlineDepth.

* Allow Simplify.Iteration.simplAuxBind to inline used-once things.
  This is another part of Note [Post-inline for single-use things], and
  is really good for reducing simplifier iterations in situations like
      case K e of { K x -> blah }
  wher x is used once in blah.

* Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case
  elimination.  Note [Case elim in exprIsConApp_maybe]

* Improve the case-merge transformation:
  - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts`
    and friends.  See Note [Merge Nested Cases] in GHC.Core.Utils.
  - Add a new case for `tagToEnum#`; see wrinkle (MC3).
  - Add a new case to look through join points: see wrinkle (MC4)

postInlineUnconditionally
~~~~~~~~~~~~~~~~~~~~~~~~~
* Allow Simplify.Utils.postInlineUnconditionally to inline variables
  that are used exactly once. See Note [Post-inline for single-use things].

* Do not postInlineUnconditionally join point, ever.
  Doing so does not reduce allocation, which is the main point,
  and with join points that are used a lot it can bloat code.
  See point (1) of Note [Duplicating join points] in
  GHC.Core.Opt.Simplify.Iteration.

* Do not postInlineUnconditionally a strict (demanded) binding.
  It will not allocate a thunk (it'll turn into a case instead)
  so again the main point of inlining it doesn't hold.  Better
  to check per-call-site.

* Improve occurrence analyis for bottoming function calls, to help
  postInlineUnconditionally.  See Note [Bottoming function calls]
  in GHC.Core.Opt.OccurAnal

Inlining generally
~~~~~~~~~~~~~~~~~~
* In GHC.Core.Opt.Simplify.Utils.interestingCallContext,
  use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case.
  See Note [Seq is boring]  Also, wrinkle (SB1), inline in that
  `seq` context only for INLINE functions (UnfWhen guidance).

* In GHC.Core.Opt.Simplify.Utils.interestingArg,
  - return ValueArg for OtherCon [c1,c2, ...], but
  - return NonTrivArg for OtherCon []
  This makes a function a little less likely to inline if all we
  know is that the argument is evaluated, but nothing else.

* isConLikeUnfolding is no longer true for OtherCon {}.
  This propagates to exprIsConLike.  Con-like-ness has /positive/
  information.

Join points
~~~~~~~~~~~
* Be very careful about inlining join points.
  See these two long Notes
    Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration
    Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline

* When making join points, don't do so if the join point is so small
  it will immediately be inlined; check uncondInlineJoin.

* In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining
  heuristics for join points. In general we /do not/ want to inline
  join points /even if they are small/.  See Note [Duplicating join points]
  GHC.Core.Opt.Simplify.Iteration.

  But sometimes we do: see Note [Inlining join points] in
  GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function.

* Do not add an unfolding to a join point at birth.  This is a tricky one
  and has a long Note [Do not add unfoldings to join points at birth]
  It shows up in two places
  - In `mkDupableAlt` do not add an inlining
  - (trickier) In `simplLetUnfolding` don't add an unfolding for a
    fresh join point
  I am not fully satisifed with this, but it works and is well documented.

* In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise
  having a non-inlined join point.

Performance changes
~~~~~~~~~~~~~~~~~~~
* Binary sizes fall by around 2.6%, according to nofib.

* Compile times improve slightly. Here are the figures over 1%.

  I investiate the biggest differnce in T18304. It's a very small module, just
  a few hundred nodes. The large percentage difffence is due to a single
  function that didn't quite inline before, and does now, making code size a
  bit bigger.  I decided gains outweighed the losses.

    Metrics: compile_time/bytes allocated (changes over +/- 1%)
    ------------------------------------------------
           CoOpt_Singletons(normal)   -9.2% GOOD
                LargeRecord(normal)  -23.5% GOOD
MultiComponentModulesRecomp(normal)   +1.2%
MultiLayerModulesTH_OneShot(normal)   +4.1%  BAD
                  PmSeriesS(normal)   -3.8%
                  PmSeriesV(normal)   -1.5%
                     T11195(normal)   -1.3%
                     T12227(normal)  -20.4% GOOD
                     T12545(normal)   -3.2%
                     T12707(normal)   -2.1% GOOD
                     T13253(normal)   -1.2%
                 T13253-spj(normal)   +8.1%  BAD
                     T13386(normal)   -3.1% GOOD
                     T14766(normal)   -2.6% GOOD
                     T15164(normal)   -1.4%
                     T15304(normal)   +1.2%
                     T15630(normal)   -8.2%
                    T15630a(normal)          NEW
                     T15703(normal)  -14.7% GOOD
                     T16577(normal)   -2.3% GOOD
                     T17516(normal)  -39.7% GOOD
                     T18140(normal)   +1.2%
                     T18223(normal)  -17.1% GOOD
                     T18282(normal)   -5.0% GOOD
                     T18304(normal)  +10.8%  BAD
                     T18923(normal)   -2.9% GOOD
                      T1969(normal)   +1.0%
                     T19695(normal)   -1.5%
                     T20049(normal)  -12.7% GOOD
                    T21839c(normal)   -4.1% GOOD
                      T3064(normal)   -1.5%
                      T3294(normal)   +1.2%  BAD
                      T4801(normal)   +1.2%
                      T5030(normal)  -15.2% GOOD
                   T5321Fun(normal)   -2.2% GOOD
                      T6048(optasm)  -16.8% GOOD
                       T783(normal)   -1.2%
                      T8095(normal)   -6.0% GOOD
                      T9630(normal)   -4.7% GOOD
                      T9961(normal)   +1.9%  BAD
                      WWRec(normal)   -1.4%
        info_table_map_perf(normal)   -1.3%
                 parsing001(normal)   +1.5%

                          geo. mean   -2.0%
                          minimum    -39.7%
                          maximum    +10.8%

* Runtimes generally improve. In the testsuite perf/should_run gives:
   Metrics: runtime/bytes allocated
   ------------------------------------------
             Conversions(normal)   -0.3%
                 T13536a(optasm)  -41.7% GOOD
                   T4830(normal)   -0.1%
           haddock.Cabal(normal)   -0.1%
            haddock.base(normal)   -0.1%
        haddock.compiler(normal)   -0.1%

                       geo. mean   -0.8%
                       minimum    -41.7%
                       maximum     +0.0%

* For runtime, nofib is a better test.  The news is mostly good.
  Here are the number more than +/- 0.1%:

    # bytes allocated
    ==========================++==========
       imaginary/digits-of-e1 ||  -14.40%
       imaginary/digits-of-e2 ||   -4.41%
          imaginary/paraffins ||   -0.17%
               imaginary/rfib ||   -0.15%
       imaginary/wheel-sieve2 ||   -0.10%
                real/compress ||   -0.47%
                   real/fluid ||   -0.10%
                  real/fulsom ||   +0.14%
                  real/gamteb ||   -1.47%
                      real/gg ||   -0.20%
                   real/infer ||   +0.24%
                     real/pic ||   -0.23%
                  real/prolog ||   -0.36%
                     real/scs ||   -0.46%
                 real/smallpt ||   +4.03%
        shootout/k-nucleotide ||  -20.23%
              shootout/n-body ||   -0.42%
       shootout/spectral-norm ||   -0.13%
              spectral/boyer2 ||   -3.80%
         spectral/constraints ||   -0.27%
          spectral/hartel/ida ||   -0.82%
                spectral/mate ||  -20.34%
                spectral/para ||   +0.46%
             spectral/rewrite ||   +1.30%
              spectral/sphere ||   -0.14%
    ==========================++==========
                    geom mean ||   -0.59%

    real/smallpt has a huge nest of local definitions, and I
    could not pin down a reason for a regression.  But there are
    three big wins!

Metric Decrease:
    CoOpt_Singletons
    LargeRecord
    T12227
    T12707
    T13386
    T13536a
    T14766
    T15703
    T16577
    T17516
    T18223
    T18282
    T18923
    T21839c
    T20049
    T5321Fun
    T5030
    T6048
    T8095
    T9630
    T783
Metric Increase:
    MultiLayerModulesTH_OneShot
    T13253-spj
    T18304
    T18698a
    T9961
    T3294

- - - - -
27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Testsuite message changes from simplifier improvements

- - - - -
271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Account for bottoming functions in OccurAnal

This fixes #24582, a small but long-standing bug

- - - - -
0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00
testsuite: Introduce template-haskell-exports test

- - - - -
0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00
Update correct counter in bumpTickyAllocd

- - - - -
5f085d3a by Fendor at 2024-04-04T14:47:33-04:00
Replace `SizedSeq` with `FlatBag` for flattened structure

LinkedLists are notoriously memory ineffiecient when all we do is
traversing a structure.
As 'UnlinkedBCO' has been identified as a data structure that impacts
the overall memory usage of GHCi sessions, we avoid linked lists and
prefer flattened structure for storing.

We introduce a new memory efficient representation of sequential
elements that has special support for the cases:

* Empty
* Singleton
* Tuple Elements

This improves sharing in the 'Empty' case and avoids the overhead of
'Array' until its constant overhead is justified.

- - - - -
82cfe10c by Fendor at 2024-04-04T14:47:33-04:00
Compact FlatBag array representation

`Array` contains three additional `Word`'s we do not need in `FlatBag`. Move
`FlatBag` to `SmallArray`.

Expand the API of SmallArray by `sizeofSmallArray` and add common
traversal functions, such as `mapSmallArray` and `foldMapSmallArray`.
Additionally, allow users to force the elements of a `SmallArray`
via `rnfSmallArray`.

- - - - -
36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00
Change how invisible patterns represented in  haskell syntax and TH AST (#24557)

Before this patch:
  data ArgPat p
    = InvisPat (LHsType p)
    | VisPat (LPat p)

With this patch:
  data Pat p
    = ...
    | InvisPat (LHsType p)
    ...

And the same transformation in the TH land. The rest of the
changes is just updating code to handle new AST and writing tests
to check if it is possible to create invalid states using TH.

Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -
28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00
Fix off by one error in seekBinNoExpand and seekBin

- - - - -
9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00
compiler: Allow more types in GHCForeignImportPrim

For many, many years `GHCForeignImportPrim` has suffered from the rather
restrictive limitation of not allowing any non-trivial types in arguments
or results. This limitation was justified by the code generator allegely
barfing in the presence of such types.

However, this restriction appears to originate well before the NCG
rewrite and the new NCG does not appear to have any trouble with such
types (see the added `T24598` test). Lift this restriction.

Fixes #24598.

- - - - -
1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00
EPA: Use EpaLocation not SrcSpan in ForeignDecls

This allows us to update them for makeDeltaAst in ghc-exactprint

- - - - -
19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00
EPA: Use EpaLocation for RecFieldsDotDot

So we can update it to a delta position in makeDeltaAst if needed.

- - - - -
e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00
Remove accidentally committed test.hs

- - - - -
88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00
Avoid UArray when indexing is not required

`UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO`
references two `UArray`'s but never indexes them. They are only needed
to encode the elements into a `ByteArray#`. The three words for
the lower bound, upper bound and number of elements are essentially
unused, thus we replace `UArray` with a wrapper around `ByteArray#`.
This saves us up to three words for each `UnlinkedBCO`.

Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat
the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances.

For example, agda's repl session has around 360_000 UnlinkedBCO's,
so avoiding these three words is already saving us around 8MB residency.

- - - - -
f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00
Never UNPACK `FastMutInt` for counting z-encoded `FastString`s

In `FastStringTable`, we count the number of z-encoded FastStrings
that exist in a GHC session.
We used to UNPACK the counters to not waste memory, but live retainer
analysis showed that we allocate a lot of `FastMutInt`s, retained by
`mkFastZString`.

We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is
forced.
The function `mkFastStringWith` calls `mkZFastString` and boxes the
`FastMutInt`, leading to the following core:

    mkFastStringWith
      = \ mk_fs _  ->
             = case stringTable of
                { FastStringTable _ n_zencs segments# _ ->
                    ...
                         case ((mk_fs (I# ...) (FastMutInt n_zencs))
                            `cast` <Co:2> :: ...)
                            ...

Marking this field as `NOUNPACK` avoids this reboxing, eliminating the
allocation of a fresh `FastMutInt` on every `FastString` allocation.

- - - - -
c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00
Force in_multi to avoid retaining entire hsc_env

- - - - -
fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00
Eliminate name thunk in declaration fingerprinting

Thunk analysis showed that we have about 100_000 thunks (in agda and
`-fwrite-simplified-core`) pointing to the name of the name decl.
Forcing this thunk fixes this issue.

The thunk created here is retained by the thunk created by forkM, it is
better to eagerly force this because the result (a `Name`) is already
retained indirectly via the `IfaceDecl`.

- - - - -
3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00
EPA: Use EpaLocation in WarningTxt

This allows us to use an EpDelta if needed when using makeDeltaAst.

- - - - -
12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00
EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc

This allows us to use a NoCommentsLocation for the possibly trailing
comma location in a StringLiteral.
This in turn allows us to correctly roundtrip via makeDeltaAst.

- - - - -
868c8a78 by Fendor at 2024-04-09T08:51:50-04:00
Prefer packed representation for CompiledByteCode

As there are many 'CompiledByteCode' objects alive during a GHCi
session, representing its element in a more packed manner improves space
behaviour at a minimal cost.

When running GHCi on the agda codebase, we find around 380 live
'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode'
can save quite some pointers.

- - - - -
be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00
EPA: Capture all comments in a ClassDecl

Hopefully the final fix needed for #24533

- - - - -
3d0806fc by Jade at 2024-04-10T05:39:53-04:00
Validate -main-is flag using parseIdentifier

Fixes #24368

- - - - -
dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

- - - - -
e008a19a by Alexis King at 2024-04-10T05:40:29-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)

- - - - -
dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
rts: Make addDLL a wrapper around loadNativeObj

Rewrite the implementation of `addDLL` as a wrapper around the more
principled `loadNativeObj` rts linker function. The latter should be
preferred while the former is preserved for backwards compatibility.

`loadNativeObj` was previously only available on ELF platforms, so this
commit further refactors the rts linker to transform loadNativeObj_ELF
into loadNativeObj_POSIX, which is available in ELF and MachO platforms.

The refactor made it possible to remove the `dl_mutex` mutex in favour
of always using `linker_mutex` (rather than a combination of both).

Lastly, we implement `loadNativeObj` for Windows too.

- - - - -
12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
Use symbol cache in internal interpreter too

This commit makes the symbol cache that was used by the external
interpreter available for the internal interpreter too.

This follows from the analysis in #23415 that suggests the internal
interpreter could benefit from this cache too, and that there is no good
reason not to have the cache for it too. It also makes it a bit more
uniform to have the symbol cache range over both the internal and
external interpreter.

This commit also refactors the cache into a function which is used by
both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the
caching logic to `lookupSymbolInDLL` too.

- - - - -
dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00
testsuite: Add test for lookupSymbolInNativeObj

- - - - -
1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00
EPA: Remove unnecessary XRec in CompleteMatchSig

The XRec for [LIdP pass] is not needed for exact printing, remove it.

- - - - -
6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00
users-guide: Clarify language extension documentation

Over the years the users guide's language extension documentation has
gone through quite a few refactorings. In the process some of the
descriptions have been rendered non-sensical. For instance, the
description of `NoImplicitPrelude` actually describes the semantics of
`ImplicitPrelude`.

To fix this we:

 * ensure that all extensions are named in their "positive" sense (e.g.
   `ImplicitPrelude` rather than `NoImplicitPrelude`).
 * rework the documentation to avoid flag-oriented wording
   like "enable" and "disable"
 * ensure that the polarity of the documentation is consistent with
   reality.

Fixes #23895.

- - - - -
a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00
driver: Make `checkHomeUnitsClosed` faster

The implementation of `checkHomeUnitsClosed` was traversing every single path
in the unit dependency graph - this grows exponentially and quickly grows to be
infeasible on larger unit dependency graphs.

Instead we replace this with a faster implementation which follows from the
specificiation of the closure property - there is a closure error if there are
units which are both are both (transitively) depended upon by home units and
(transitively) depend on home units, but are not themselves home units.

To compute the set of units required for closure, we first compute the closure
of the unit dependency graph, then the transpose of this closure, and find all
units that are reachable from the home units in the transpose of the closure.

- - - - -
23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00
RTS: Emit warning when -M < -H

Fixes #24487

- - - - -
d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00
testsuite: Add broken test for CApiFFI with -fprefer-bytecode

See #24634.

- - - - -
a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00
base: Deprecate GHC.Pack

As proposed in #21461.

Closes #21540.

- - - - -
55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00
ghc-internal: Fix mentions of ghc-internal in deprecation warnings

Closes #24609.

- - - - -
b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00
rts: Implement set_initial_registers for AArch64

Fixes #23680.

- - - - -
14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00
ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17

Closes #24646.

- - - - -
35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00
Bump unix submodule to 2.8.5.1

Closes #24640.

- - - - -
a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00
Correct default -funfolding-use-threshold in docs

- - - - -
0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00
FastString is a __Modified__ UTF-8

- - - - -
c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00
rts: Improve tracing message when nursery is resized

It is sometimes more useful to know how much bigger or smaller the
nursery got when it is resized.

In particular I am trying to investigate situations where we end up with
fragmentation due to the nursery (#24577)

- - - - -
5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00
Don't generate wrappers for `type data` constructors with StrictData

Previously, the logic for checking if a data constructor needs a wrapper or not
would take into account whether the constructor's fields have explicit
strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into
account whether `StrictData` was enabled. This meant that something like `type
data T = MkT Int` would incorrectly generate a wrapper for `MkT` if
`StrictData` was enabled, leading to the horrible errors seen in #24620. To fix
this, we disable generating wrappers for `type data` constructors altogether.

Fixes #24620.

Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com>

- - - - -
dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00
Implements MO_S_Mul2 and MO_U_Mul2 using the  UMULH, UMULL and SMULH instructions for AArch64

Also adds a test for MO_S_Mul2

- - - - -
42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00
Make template-haskell a stage1 package

Promoting template-haskell from a stage0 to a stage1 package means that
we can much more easily refactor template-haskell.

We implement this by duplicating the in-tree `template-haskell`.
A new `template-haskell-next` library is autogenerated to mirror `template-haskell`
`stage1:ghc` to depend on the new interface of the library including the
`Binary` instances without adding an explicit dependency on `template-haskell`.

This is controlled by the `bootstrap-th` cabal flag

When building `template-haskell` modules as part of this vendoring we do
not have access to quote syntax, so we cannot use variable quote
notation (`'Just`). So we either replace these with hand-written `Name`s
or hide the code behind CPP.

We can remove the `th_hack` from hadrian, which was required when
building stage0 packages using the in-tree `template-haskell` library.

For more details see Note [Bootstrapping Template Haskell].

Resolves #23536

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>
Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00
Bump parsec submodule to 3.1.17.0

- - - - -
9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00
Clone CoVars in CorePrep

This MR addresses #24463.  It's all explained in the new

   Note [Cloning CoVars and TyVars]

- - - - -
0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00
NCG: Fix a bug where we errounously removed a required jump instruction.

Add a new method to the Instruction class to check if we can eliminate a
jump in favour of fallthrough control flow.

Fixes #24507

- - - - -
9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00
Fix documentation preview from doc-tarball job

- Include all the .html files and assets in the job artefacts
- Include all the .pdf files in the job artefacts
- Mark the artefact as an "exposed" artefact meaning it turns up in the
  UI.

Resolves #24651

- - - - -
3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00
rts: Ignore EINTR while polling in timerfd itimer implementation

While the RTS does attempt to mask signals, it may be that a foreign
library unmasks them. This previously caused benign warnings which we
now ignore.

See #24610.

- - - - -
9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00
EPA: Add additional comments field to AnnsModule

This is used in exact printing to store comments coming after the
`where` keyword but before any comments allocated to imports or decls.

It is used in ghc-exactprint, see
https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7

- - - - -
e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00
Remove unrunnable FreeBSD CI jobs

FreeBSD runner supply is inelastic. Currently there is only one, and
it's unavailable because of a hardware issue.

- - - - -
914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00
rel-eng: Fix mktemp usage in recompress-all

We need a temporary directory, not a file.

- - - - -
f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00
Fix ghc API link in docs/index.html

This was missing part of the unit ID meaning it would 404.

Resolves #24674

- - - - -
d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00
template-haskell: Declare TH.Lib.Internal as not-home

Rather than `hide`.

Closes #24659.

- - - - -
5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00
testsuite: Rename isCross() predicate to needsTargetWrapper()

isCross() was a misnamed because it assumed that all cross targets would
provide a target wrapper, but the two most common cross targets
(javascript, wasm) don't need a target wrapper.

Therefore we rename this predicate to `needsTargetWrapper()` so
situations in the testsuite where we can check whether running
executables requires a target wrapper or not.

- - - - -
55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00
Do not float HNFs out of lambdas

This MR adjusts SetLevels so that it is less eager to float a
HNF (lambda or constructor application) out of a lambda, unless
it gets to top level.

Data suggests that this change is a small net win:
 * nofib bytes-allocated falls by -0.09% (but a couple go up)
 * perf/should_compile bytes-allocated falls by -0.5%
 * perf/should_run bytes-allocated falls by -0.1%
See !12410 for more detail.

When fiddling elsewhere, I also found that this patch had a huge
positive effect on the (very delicate) test
  perf/should_run/T21839r
But that improvement doesn't show up in this MR by itself.

Metric Decrease:
    MultiLayerModulesRecomp
    T15703
    parsing001

- - - - -
f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00
EPA: Fix comments in mkListSyntaxTy0

Also extend the test to confirm.

Addresses #24669, 1 of 4

- - - - -
b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00
JS: set image `x86_64-linux-deb11-emsdk-closure` for build

- - - - -
c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00
EPA: Provide correct span for PatBind

And remove unused parameter in checkPatBind

Contributes to #24669

- - - - -
bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00
Update quantification order following GHC haskell/haddock#23764

- - - - -
2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00
hypsrc-test: Fix output of PositionPragmas.html

- - - - -
26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00
EPA: Fix span for PatBuilderAppType

Include the location of the prefix @ in the span for InVisPat.

Also removes unnecessary annotations from HsTP.

Contributes to #24669

- - - - -
dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00
testsuite: Give the pre_cmd for mhu-perf more time

- - - - -
d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00
Fix quantification order for a `op` b and a %m -> b

Fixes #23764

Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst

Updates haddock submodule.

- - - - -
385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00
Make `seq#` a magic Id and inline it in CorePrep (#24124)

We can save much code and explanation in Tag Inference and StgToCmm by making
`seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in
CorePrep. See the updated `Note [seq# magic]`.
I also implemented a new `Note [Flatten case-bind]` to get better code for
otherwise nested case scrutinees.

I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to
resolve the clash between `type CpeApp = CoreExpr` and the data constructor of
`ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`.

Fixes #24252 and #24124.

- - - - -
275e41a9 by Jade at 2024-04-20T11:10:40-04:00
Put the newline after errors instead of before them

This mainly has consequences for GHCi but also slightly alters how the
output of GHC on the commandline looks.

Fixes: #22499

- - - - -
dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00
Remove unecessary stage0 packages

Historically quite a few packages had to be stage0 as they depended on
`template-haskell` and that was stage0. In #23536 we made it so that was
no longer the case. This allows us to remove a bunch of packages from
this list.

A few still remain. A new version of `Win32` is required by
`semaphore-compat`. Including `Win32` in the stage0 set requires also
including `filepath` because otherwise Hadrian's dependency logic gets
confused. Once our boot compiler has a newer version of `Win32` all of
these will be able to be dropped.

Resolves #24652

- - - - -
2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00
EPA: Avoid duplicated comments in splice decls

Contributes to #24669

- - - - -
c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: fix typos and namings (fixes #24602)

You may noted that I've also changed term of

```
, global "h$vt_double" ||= toJExpr IntV
```

See "IntV"

and

```
  WaitReadOp  -> \[] [fd] -> pure $ PRPrimCall $ returnS (app
"h$waidRead" [fd])
```

See "h$waidRead"

- - - - -
3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: trivial checks for variable presence (fixes #24602)

- - - - -
777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped
in a closure to prevent conflict with emscripten (fixes #24602)

Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues.
At first glance we should try UMD (See https://github.com/umdjs/umd)

- - - - -
a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal
code copied from GHCJS (fixes #24602)

I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607).
Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};`

- - - - -
ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: heap and stack overflows reporting defined as js hard failure (fixes #24602)

These errors were treated as a hard failure for browser application. The fix is trivial: just throw error.

- - - - -
5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00
JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602)

These errors were fixed just by introducing stubbed functions with throw for further implementation.

- - - - -
a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Add externs to linker (fixes #24602)

After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following:

1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8).
2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle.
3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`.
4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?`

- - - - -
e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: added both tests: for size and for correctness (fixes #24602)

By some reason MacOS builds add to stderr messages like:

    Ignoring unexpected archive entry:
    __.SYMDEF
    ...

However I left stderr to `/dev/null` for compatibility with linux CI builds.

- - - - -
909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments

- - - - -
83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602)

Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators.
But now there are following compiler options: `-C` and `-CC`.
You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC).
It seems that `-CC` works better for javascript jsdoc than `-traditional`.
At least it leaves `/* ... */` comments w/o changes.

- - - - -
e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00
fix link in CODEOWNERS

It seems that our local Gitlab no longer has documentation for the
`CODEOWNERS` file, but the master documentation still does. Use
that instead.

- - - - -
a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00
Adapt to UserData split

- - - - -
1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00
Adapt to BinHandle split

- - - - -
593f4e04 by Fendor at 2024-04-23T10:19:14-04:00
Add performance regression test for '-fwrite-simplified-core'

- - - - -
1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00
Typecheck corebindings lazily during bytecode generation

This delays typechecking the corebindings until the bytecode generation
happens.

We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`.
In general, we shouldn't retain values of the hydrated `Type`, as not evaluating
the bytecode object keeps it alive.

It is better if we retain the unhydrated `IfaceType`.

See Note [Hydrating Modules]

- - - - -
e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00
EPA: Keep comments in a CaseAlt match

The comments now live in the surrounding location, not inside the
Match. Make sure we keep them.

Closes #24707

- - - - -
d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00
driver: force merge objects when building dynamic objects

This patch forces the driver to always merge objects when building
dynamic objects even when ar -L is supported. It is an oversight of
!8887: original rationale of that patch is favoring the relatively
cheap ar -L operation over object merging when ar -L is supported,
which makes sense but only if we are building static objects! Omitting
check for whether we are building dynamic objects will result in
broken .so files with undefined reference errors at executable link
time when building GHC with llvm-ar. Fixes #22210.

- - - - -
209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00
Allow non-absolute values for bootstrap GHC variable

Fixes #24682

- - - - -
3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00
Don't depend on registerPackage function in Cabal

More recent versions of Cabal modify the behaviour of libAbiHash which
breaks our usage of registerPackage.

It is simpler to inline the part of registerPackage that we need and
avoid any additional dependency and complication using the higher-level
function introduces.

- - - - -
c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00
ghc-bignum: remove obsolete ln script

This commit removes an obsolete ln script in ghc-bignum/gmp. See
060251c24ad160264ae8553efecbb8bed2f06360 for its original intention,
but it's been obsolete for a long time, especially since the removal
of the make build system. Hence the house cleaning.

- - - - -
6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00
ghc-bignum: update gmp to 6.3.0

This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0.
The tarball format is now xz, and gmpsrc.patch has been patched into
the tarball so hadrian no longer needs to deal with patching logic
when building in-tree GMP.

- - - - -
65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00
hadrian: remove obsolete Patch logic

This commit removes obsolete Patch logic from hadrian, given we no
longer need to patch the gmp tarball when building in-tree GMP.

- - - - -
71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00
autoconf: remove obsolete patch detection

This commit removes obsolete deletection logic of the patch command
from autoconf scripts, given we no longer need to patch anything in
the GHC build process.

- - - - -
daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00
JS: correctly handle RUBBISH literals (#24664)

- - - - -
8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00
Linearise ghc-internal and base build

This is achieved by requesting the final package database for
ghc-internal, which mandates it is fully built as a dependency of
configuring the `base` package. This is at the expense of cross-package
parrallelism between ghc-internal and the base package.

Fixes #24436

- - - - -
94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00
Fix tuple puns renaming (24702)

Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module.

I also fixed some hidden bugs that raised after the change was done.

- - - - -
fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00
Refactor the Binary serialisation interface

The goal is simplifiy adding deduplication tables to `ModIface`
interface serialisation.

We identify two main points of interest that make this difficult:

1. UserData hardcodes what `Binary` instances can have deduplication
   tables. Moreover, it heavily uses partial functions.
2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and
   'FastString', making it difficult to add more deduplication.

Instead of having a single `UserData` record with fields for all the
types that can have deduplication tables, we allow to provide custom
serialisers for any `Typeable`.
These are wrapped in existentials and stored in a `Map` indexed by their
respective `TypeRep`.
The `Binary` instance of the type to deduplicate still needs to
explicitly look up the decoder via `findUserDataReader` and
`findUserDataWriter`, which is no worse than the status-quo.

`Map` was chosen as microbenchmarks indicate it is the fastest for a
small number of keys (< 10).

To generalise the deduplication table serialisation mechanism, we
introduce the types `ReaderTable` and `WriterTable` which provide a
simple interface that is sufficient to implement a general purpose
deduplication mechanism for `writeBinIface` and `readBinIface`.

This allows us to provide a list of deduplication tables for
serialisation that can be extended more easily, for example for
`IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540
for more motivation.

In addition to this refactoring, we split `UserData` into `ReaderUserData`
and `WriterUserData`, to avoid partial functions and reduce overall
memory usage, as we need fewer mutable variables.

Bump haddock submodule to accomodate for `UserData` split.

-------------------------
Metric Increase:
    MultiLayerModulesTH_Make
    MultiLayerModulesRecomp
    T21839c
-------------------------

- - - - -
bac57298 by Fendor at 2024-04-26T18:03:13-04:00
Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle`

A `BinHandle` contains too much information for reading data.
For example, it needs to keep a `FastMutInt` and a `IORef BinData`,
when the non-mutable variants would suffice.

Additionally, this change has the benefit that anyone can immediately
tell whether the `BinHandle` is used for reading or writing.

Bump haddock submodule BinHandle split.

- - - - -
4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00
Fix missing escaping-kind check in tcPatSynSig

Note [Escaping kind in type signatures] explains how we deal
with escaping kinds in type signatures, e.g.
    f :: forall r (a :: TYPE r). a
where the kind of the body is (TYPE r), but `r` is not in
scope outside the forall-type.

I had missed this subtlety in tcPatSynSig, leading to #24686.
This MR fixes it; and a similar bug in tc_top_lhs_type. (The
latter is tested by T24686a.)

- - - - -
981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00
EPA: check-exact: check that the roundtrip reproduces the source

Closes #24670

- - - - -
a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00
Document that setEnv is not thread-safe

- - - - -
1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00
CI: Work around frequent Signal 9 errors

- - - - -
a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00
ghc-internal: add MonadFix instance for (,)

Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC
proposal https://github.com/haskell/core-libraries-committee/issues/238.

Adds a MonadFix instance for tuples, permitting value recursion in the
"native" writer monad and bringing consistency with the existing
instance for transformers's WriterT (and, to a lesser extent, for Solo).

- - - - -
64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00
bindist: Fix xattr cleaning

The original fix (725343aa) was incorrect because it used the shell
bracket syntax which is the quoting syntax in autoconf, making the test
for existence be incorrect and therefore `xattr` was never run.

Fixes #24554

- - - - -
e2094df3 by damhiya at 2024-04-28T23:52:00+09:00
Make read accepts binary integer formats

CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177

- - - - -
c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00
Fix tests for T22229

- - - - -
1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00
EPA: Preserve comments in Match Pats

Closes #24708
Closes #24715
Closes #24734

- - - - -
4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00
LLVM: better unreachable default destination in Switch (#24717)

See added note.

Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com>

- - - - -
a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00
ci: enable wasm jobs for MRs with wasm label

This patch enables wasm jobs for MRs with wasm label. Previously the
wasm label didn't actually have any effect on the CI pipeline, and
full-ci needed to be applied to run wasm jobs which was a waste of
runners when working on the wasm backend, hence the fix here.

- - - - -
702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00
Make interface files and object files depend on inplace .conf file

A potential fix for #24737

- - - - -
728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00
utils: remove obsolete vagrant scripts

Vagrantfile has long been removed in !5288. This commit further
removes the obsolete vagrant scripts in the tree.

- - - - -
36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00
Update autoconf scripts

Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02

- - - - -
ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00
ghcup-metadata: Drop output_name field

This is entirely redundant to the filename of the URL. There is no
compelling reason to name the downloaded file differently from its
source.

- - - - -
c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00
testsuite: Handle exceptions in framework_fail when testdir is not initialised

When `framework_fail` is called before initialising testdir, it would fail with
an exception reporting the testdir not being initialised instead of the actual failure.

Ensure we report the actual reason for the failure instead of failing in this way.

One way this can manifest is when trying to run a test that doesn't exist using `--only`

- - - - -
d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00
EPA: Fix range for GADT decl with sig only

Closes #24714

- - - - -
4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00
Fix TH dependencies (#22229)

Add a dependency between Syntax and Internal (via module reexport).

- - - - -
37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00
Bump haddock submodule

- - - - -
ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00
JS: cleanup to prepare for #24743

- - - - -
40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00
EPA: Preserve comments for PrefixCon

Preserve comments in

    fun (Con {- c1 -} a b)
        = undefined

Closes #24736

- - - - -
92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00
Correct `@since` metadata in HpcFlags

It was introduced in base-4.20, not 4.22.
Fix #24721

- - - - -
a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00
testsuite: fix req_target_smp predicate

- - - - -
ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00
STM: Remove (unused)coarse grained locking.

The STM code had a coarse grained locking mode guarded by #defines that was unused.
This commit removes the code.

- - - - -
917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00
STM: Be more optimistic when validating in-flight transactions.

* Don't lock tvars when performing non-committal validation.
* If we encounter a locked tvar don't consider it a failure.

This means in-flight validation will only fail if committing at the
moment of validation is *guaranteed* to fail.

This prevents in-flight validation from failing spuriously if it happens in
parallel on multiple threads or parallel to thread comitting.

- - - - -
167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00
EPA: fix span for empty \case(s)

In
    instance SDecide Nat where
      SZero %~ (SSucc _) = Disproved (\case)

Ensure the span for the HsLam covers the full construct.

Closes #24748

- - - - -
9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00
testsuite: expand size testing infrastructure

- closes #24191
- adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so
- path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite
- adds on_windows and req_dynamic_ghc predicate to testsuite

The design is to not make the testsuite too smart and simply offload to
ghc-pkg for locations of object files and directories.

- - - - -
b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00
GHCi: support inlining breakpoints (#24712)

When a breakpoint is inlined, its context may change (e.g. tyvars in
scope). We must take this into account and not used the breakpoint tick
index as its sole identifier. Each instance of a breakpoint (even with
the same tick index) now gets a different "info" index.

We also need to distinguish modules:
- tick module: module with the break array (tick counters, status, etc.)
- info module: module having the CgBreakInfo (info at occurrence site)

- - - - -
649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00
Expose constructors of SNat, SChar and SSymbol in ghc-internal

- - - - -
d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00
Add DCoVarSet to PluginProv (!12037)

- - - - -
ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00
JS: Enable more efficient packing of string data (fixes #24706)

- - - - -
be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Track in-scope variables in ruleCheckProgram

This small patch fixes #24726, by tracking in-scope variables
properly in -drule-check.  Not hard to do!

- - - - -
58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Add a couple more HasCallStack constraints in SimpleOpt

Just for debugging, no effect on normal code

- - - - -
70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Add comments to Prep.hs

This documentation patch fixes a TODO left over from !12364

- - - - -
e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Use HasDebugCallStack, rather than HasCallStack

- - - - -
631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00
driver: always merge objects when possible

This patch makes the driver always merge objects with `ld -r` when
possible, and only fall back to calling `ar -L` when merge objects
command is unavailable. This completely reverts !8887 and !12313,
given more fixes in Cabal seems to be needed to avoid breaking certain
configurations and the maintainence cost is exceeding the behefits in
this case :/

- - - - -
1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00
Bump time submodule to 1.14

As requested in #24528.

-------------------------
Metric Decrease:
    ghc_bignum_so
    rts_so
Metric Increase:
    cabal_syntax_dir
    rts_so
    time_dir
    time_so
-------------------------

- - - - -
4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00
Bump terminfo submodule to current master

- - - - -
43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00
wasm: use scheduler.postTask() for context switch when available

This patch makes use of scheduler.postTask() for JSFFI context switch
when it's available. It's a more principled approach than our
MessageChannel based setImmediate() implementation, and it's available
in latest version of Chromium based browsers.

- - - - -
08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00
testsuite: give pre_cmd for mhu-perf 5x time

- - - - -
bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00
EPA: Preserve comments for pattern synonym sig

Closes #24749

- - - - -
c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00
tests: Widen acceptance window for dir and so size tests

These are testing things which are sometimes out the control of a GHC
developer. Therefore we shouldn't fail CI if something about these
dependencies change because we can't do anything about it.

It is still useful to have these statistics for visualisation in grafana
though.

Ticket #24759

- - - - -
9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00
Disable rts_so test

It has already manifested large fluctuations and destabilising CI

Fixes #24762

- - - - -
fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00
unboxedSum{Type,Data}Name: Use GHC.Types as the module

Unboxed sum constructors are now defined in the `GHC.Types` module, so if you
manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like:

```hs
GHC.Types.Sum2#
```

The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly
believes that unboxed sum constructors are defined in `GHC.Prim`, so
`unboxedSumTypeName 2` would return an entirely different `Name`:

```hs
GHC.Prim.(#|#)
```

This is a problem for Template Haskell users, as it means that they can't be
sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.)

This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use
`GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the
`unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums
(`Sum<N>#`) as the `OccName`.

Fixes #24750.

- - - - -
7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00
EPA: Widen stmtslist to include last semicolon

Closes #24754

- - - - -
06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00
doc: Fix type error in hs_try_putmvar example
- - - - -
af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00
Fix parsing of module names in CLI arguments
  closes issue #24732

- - - - -
da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00
ghc-platform: Add Setup.hs

The Hadrian bootstrapping script relies upon `Setup.hs` to drive its
build.

Addresses #24761.

- - - - -
35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00
EPA: preserve comments in class and data decls

Fix checkTyClHdr which was discarding comments.

Closes #24755

- - - - -
03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00
Fix a float-out error

Ticket #24768 showed that the Simplifier was accidentally destroying
a join point.  It turned out to be that we were sending a bottoming
join point to the top, accidentally abstracting over /other/ join
points.

Easily fixed.

- - - - -
adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00
Substitute bindist files with Hadrian not configure

The `ghc-toolchain` overhaul will eventually replace all this stuff with
something much more cleaned up, but I think it is still worth making
this sort of cleanup in the meantime so other untanglings and dead code
cleaning can procede.

I was able to delete a fair amount of dead code doing this too.

`LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it
wasn't actually turned into a valid CPP identifier. (Original to
1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.)

Progress on #23966

Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com>

- - - - -
18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00
EPA: fix mkHsOpTyPV duplicating comments

Closes #24753

- - - - -
a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00
Add test cases for #24664

...since none are present in the original MR !12463 fixing this issue.

- - - - -
46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00
EPA: preserve comments in data decls

Closes #24771

- - - - -
3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00
Rename Solo# data constructor to MkSolo# (#24673)

- data Solo# a = (# a #)
+ data Solo# a = MkSolo# a

And `(# foo #)` syntax now becomes just a syntactic
sugar for `MkSolo# a`.

- - - - -
4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00
Add the cmm_cpp_is_gcc predicate to the testsuite

A future C-- test called T24474-cmm-override-g0 relies on the
GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it
emitting #defines past the preprocessing stage.  Clang, at least, does
not do this, so the test would fail if ran on Clang.

As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of
the workaround we apply as a fix for bug #24474, and the workaround was
for GCC-specific behaviour, the test needs to be marked as fragile on
other compilers.

- - - - -
25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00
Split out the C-- preprocessor, and make it pass -g0

Previously, C-- was processed with the C preprocessor program.  This
means that it inherited flags passed via -optc.  A flag that is somewhat
often passed through -optc is -g.  At certain -g levels (>=2), GCC
starts emitting defines *after* preprocessing, for the purposes of
debug info generation.  This is not useful for the C-- compiler, and, in
fact, causes lexer errors.  We can suppress this effect (safely, if
supported) via -g0.

As a workaround, in older versions of GCC (<=10), GCC only emitted
defines if a certain set of -g*3 flags was passed.  Newer versions check
the debug level.  For the former, we filter out those -g*3 flags and,
for the latter, we specify -g0 on top of that.

As a compatible and effective solution, this change adds a C--
preprocessor distinct from the C compiler and preprocessor, but that
keeps its flags.  The command line produced for C-- preprocessing now
looks like:

  $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP

Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474

- - - - -
9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00
-fprof-late: Only insert cost centres on functions/non-workfree cafs.

They are usually useless and doing so for data values comes with
a large compile time/code size overhead.

Fixes #24103

- - - - -
259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00
Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770)

See the adjusted `Note [DataAlt occ info]`.
This change also has a positive repercussion on
`Note [Combine case alts: awkward corner]`.

Fixes #24770.

We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all
fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675.

Metric Decrease:
    T9675

- - - - -
31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00
Kill seqRule, discard dead seq# in Prep (#24334)

Discarding seq#s in Core land via `seqRule` was problematic; see #24334.
So instead we discard certain dead, discardable seq#s in Prep now.
See the updated `Note [seq# magic]`.

This fixes the symptoms of #24334.

- - - - -
b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00
Document NcgImpl methods

Fixes #19914

- - - - -
4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00
Make renamer to be more flexible with parens in the LHS of the rules

We used to reject LHS like `(f a) b` in RULES and requires it to be written as
`f a b`. It will be handy to allow both as the expression may be more
readable with extra parens in some cases when infix operator is involved.
Espceially when TemplateHaskell is used, extra parens may be added out of
user's control and result in "valid" rules being rejected and there
are not always ways to workaround it.

Fixes #24621

- - - - -
ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00
IPE: Eliminate dependency on Read

Instead of encoding the closure type as decimal string we now simply
represent it as an integer, eliminating the need for `Read` in
`GHC.Internal.InfoProv.Types.peekInfoProv`.

Closes #24504.

-------------------------
Metric Decrease:
    T24602_perf_size
    size_hello_artifact
-------------------------

- - - - -
a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00
testsuite: fix testwsdeque with recent clang

This patch fixes compilation of testwsdeque.c with recent versions of
clang, which will fail with the error below:

```
testwsdeque.c:95:33: error:
     warning: format specifies type 'long' but the argument has type 'void *' [-Wformat]
       95 |         barf("FAIL: %ld %d %d", p, n, val);
          |                     ~~~         ^

testwsdeque.c:95:39: error:
     warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat]
       95 |         barf("FAIL: %ld %d %d", p, n, val);
          |                            ~~         ^~~
          |                            %lu

testwsdeque.c:133:42: error:
     error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types]
      133 |         createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n);
          |                                          ^~~~~

/workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error:
     note: passing argument to parameter 'startProc' here
      193 |                                     OSThreadProc *startProc, void *param);
          |                                                   ^

2 warnings and 1 error generated.
```

- - - - -
c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00
Rename pre-processor invocation args

Small clean up. Uses proper names for the various groups of arguments
that make up the pre-processor invocation.

- - - - -
2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00
ghc-heap: fix typo in ghc-heap cbits

- - - - -
fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00
Improve performance of Data.List.sort(By)

This patch improves the algorithm to sort lists in base.
It does so using two strategies:

1) Use a four-way-merge instead of the 'default' two-way-merge.
This is able to save comparisons and allocations.

2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization.
This mainly benefits types with a fast (>).

Note that this *may* break instances with a *malformed* Ord instance
where `a > b` is *not* equal to `compare a b == GT`.

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236

Fixes #24280

-------------------------
Metric Decrease:
    MultiLayerModulesTH_Make
    T10421
    T13719
    T15164
    T18698a
    T18698b
    T1969
    T9872a
    T9961
    T18730
    WWRec
    T12425
    T15703
-------------------------

- - - - -
1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00
Revert "ghcup-metadata: Drop output_name field"

This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f.

This breaks the ghcup metadata generation on the nightly jobs.

- - - - -
daff1e30 by Jannis at 2024-05-12T13:38:35-04:00
Division by constants optimization

- - - - -
413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00
Tidy: Add flag to expose unfoldings if they take dictionary arguments.

Add the flag `-fexpose-overloaded-unfoldings` to be able to control this
behaviour.

For ghc's boot libraries file size grew by less than 1% when it was
enabled. However I refrained from enabling it by default for now.

I've also added a section on specialization more broadly to the users
guide.

-------------------------
Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    T12425
    T13386
    hard_hole_fits
-------------------------

- - - - -
c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00
Don't store a GlobalRdrEnv in `mi_globals` for GHCi.

GHCi only needs the `mi_globals` field for modules imported with
:module +*SomeModule.

It uses this field to make the top level environment in `SomeModule` available
to the repl.

By default, only the first target in the command line parameters is
"star" loaded into GHCi. Other modules have to be manually "star" loaded
into the repl.

Storing the top level GlobalRdrEnv for each module is very wasteful, especially
given that we will most likely never need most of these environments.

Instead we store only the information needed to reconstruct the top level environment
in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements
as well as all top level symbols defined in the module (not taking export lists into account)

When a particular module is "star-loaded" into GHCi (as the first commandline target, or via
an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using
the `IfaceTopEnv`.

- - - - -
d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00
Add perf regression test for `-fwrite-if-simplified-core`

- - - - -
2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00
Improve pattern to type pattern transformation (23739)

`pat_to_type_pat` function now can handle more patterns:
  - TuplePat
  - ListPat
  - LitPat
  - NPat
  - ConPat

Allowing these new constructors in type patterns significantly
increases possible shapes of type patterns without `type` keyword.

This patch also changes how lookups in `lookupOccRnConstr` are
performed, because we need to fall back into
types when we didn't find a constructor on data level to perform
`ConPat` to type transformation properly.

- - - - -
be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00
hadrian: fix hadrian building with ghc-9.10.1

- - - - -
ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00
linters: fix lint-whitespace compilation with ghc-9.10.1

- - - - -
a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00
Expand the `inline` rule to look through casts/ticks.

Fixes #24808

- - - - -
b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00
testsuite: bump PartialDownSweep timeout to 5x on wasm32

- - - - -
b2227487 by Fendor at 2024-05-15T17:14:06-04:00
Add Eq and Ord instance to `IfaceType`

We add an `Ord` instance so that we can store `IfaceType` in a
`Data.Map` container.
This is required to deduplicate `IfaceType` while writing `.hi` files to
disk. Deduplication has many beneficial consequences to both file size
and memory usage, as the deduplication enables implicit sharing of
values.
See issue #24540 for more motivation.

The `Ord` instance would be unnecessary if we used a `TrieMap` instead
of `Data.Map` for the deduplication process. While in theory this is
clerarly the better option, experiments on the agda code base showed
that a `TrieMap` implementation has worse run-time performance
characteristics.

To the change itself, we mostly derive `Eq` and `Ord`. This requires us
to change occurrences of `FastString` with `LexicalFastString`, since
`FastString` has no `Ord` instance.
We change the definition of `IfLclName` to a newtype of
`LexicalFastString`, to make such changes in the future easier.

Bump haddock submodule for IfLclName changes

- - - - -
d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00
Move out LiteralMap to avoid cyclic module dependencies

- - - - -
2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00
Add deduplication table for `IfaceType`

The type `IfaceType` is a highly redundant, tree-like data structure.
While benchmarking, we realised that the high redundancy of `IfaceType`
causes high memory consumption in GHCi sessions when byte code is
embedded into the `.hi` file via `-fwrite-if-simplified-core` or
`-fbyte-code-and-object-code`.
Loading such `.hi` files from disk introduces many duplicates of
memory expensive values in `IfaceType`, such as `IfaceTyCon`,
`IfaceTyConApp`, `IA_Arg` and many more.

We improve the memory behaviour of GHCi by adding an additional
deduplication table for `IfaceType` to the serialisation of `ModIface`,
similar to how we deduplicate `Name`s and `FastString`s.
When reading the interface file back, the table allows us to automatically
share identical values of `IfaceType`.

To provide some numbers, we evaluated this patch on the agda code base.
We loaded the full library from the `.hi` files, which contained the
embedded core expressions (`-fwrite-if-simplified-core`).

Before this patch:

* Load time: 11.7 s, 2.5 GB maximum residency.

After this patch:

* Load time:  7.3 s, 1.7 GB maximum residency.

This deduplication has the beneficial side effect to additionally reduce
the size of the on-disk interface files tremendously.

For example, on agda, we reduce the size of `.hi` files (with
`-fwrite-if-simplified-core`):

* Before: 101 MB on disk
* Now:     24 MB on disk

This has even a beneficial side effect on the cabal store. We reduce the
size of the store on disk:

* Before: 341 MB on disk
* Now:    310 MB on disk

Note, none of the dependencies have been compiled with
`-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple
locations in a `ModIface`.

We also add IfaceType deduplication table to .hie serialisation and
refactor .hie file serialisation to use the same infrastrucutre as
`putWithTables`.

Bump haddock submodule to accomodate for changes to the deduplication
table layout and binary interface.

- - - - -
36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00
Add run-time configurability of `.hi` file compression

Introduce the flag `-fwrite-if-compression=<n>` which allows to
configure the compression level of writing .hi files.

The motivation is that some deduplication operations are too expensive
for the average use case. Hence, we introduce multiple compression
levels with variable impact on performance, but still reduce the
memory residency and `.hi` file size on disk considerably.

We introduce three compression levels:

* `1`: `Normal` mode. This is the least amount of compression.
    It deduplicates only `Name` and `FastString`s, and is naturally the
    fastest compression mode.
* `2`: `Safe` mode. It has a noticeable impact on .hi file size and is
  marginally slower than `Normal` mode. In general, it should be safe to
  always use `Safe` mode.
* `3`: `Full` deduplication mode. Deduplicate as much as we can,
  resulting in minimal .hi files, but at the cost of additional
  compilation time.

Reading .hi files doesn't need to know the initial compression level,
and can always deserialise a `ModIface`, as we write out a byte that
indicates the next value has been deduplicated.
This allows users to experiment with different compression levels for
packages, without recompilation of dependencies.

Note, the deduplication also has an additional side effect of reduced
memory consumption to implicit sharing of deduplicated elements.
See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where
that matters.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhciWithCore
    T16875
    T21839c
    T24471
    hard_hole_fits
    libdir
-------------------------

- - - - -
1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00
Introduce regression tests for `.hi` file sizes

Add regression tests to track how `-fwrite-if-compression` levels affect
the size of `.hi` files.

- - - - -
639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00
TTG: ApplicativeStatement exist only in Rn and Tc

Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com>

- - - - -
aa7b336b by Jade at 2024-05-15T23:06:17-04:00
Documentation: Improve documentation for symbols exported from System.IO

- - - - -
c561de8f by Jade at 2024-05-15T23:06:54-04:00
Improve suggestions for language extensions

- When suggesting Language extensions, also suggest Extensions which imply them
- Suggest ExplicitForAll and GADTSyntax instead of more specific
  extensions
- Rephrase suggestion to include the term 'Extension'
- Also moves some flag specific definitions out of Session.hs into
Flags.hs (#24478)

Fixes: #24477
Fixes: #24448
Fixes: #10893

- - - - -
4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00
Testsuite: Check if llvm assembler is available for have_llvm

- - - - -
bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00
refactor quadratic search in warnMissingHomeModules

- - - - -
7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00
add test that runs MakeDepend on thousands of modules

- - - - -
b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00
Representation-polymorphic HasField (fixes #22156)

This generalises the HasField class to support representation polymorphism,
so that instead of

    type HasField :: forall {k} . k -> Type -> Type -> Constraint

we have

    type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint

- - - - -
05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00
Bump os-string submodule to 2.0.2.2

Closes #24786

- - - - -
886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00
rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED

This commit fixes a small an oversight in !12148: the prefetch logic
in non-moving GC may trap in debug RTS because it calls Bdescr() for
mark_closure which may be a static one. It's fine in non-debug RTS
because even invalid bdescr addresses are prefetched, they will not
cause segfaults, so this commit implements the most straightforward
fix: don't prefetch mark_closure bdescr when assertions are enabled.

- - - - -
b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00
rts: Allocate non-moving segments with megablocks

Non-moving segments are 8 blocks long and need to be aligned.
Previously we serviced allocations by grabbing 15 blocks, finding
an aligned 8 block group in it and returning the rest.
This proved to lead to high levels of fragmentation as a de-allocating a segment
caused an 8 block gap to form, and this could not be reused for allocation.

This patch introduces a segment allocator based around using entire
megablocks to service segment allocations in bulk.

When there are no free segments, we grab an entire megablock and fill it
with aligned segments. As the megablock is free, we can easily guarantee
alignment. Any unused segments are placed on a free list.

It only makes sense to free segments in bulk when all of the segments in
a megablock are freeable. After sweeping, we grab the free list, sort it,
and find all groups of segments where they cover the megablock and free
them.
This introduces a period of time when free segments are not available to
the mutator, but the risk that this would lead to excessive allocation
is low. Right after sweep, we should have an abundance of partially full
segments, and this pruning step is relatively quick.

In implementing this we drop the logic that kept NONMOVING_MAX_FREE
segments on the free list.

We also introduce an eventlog event to log the amount of pruned/retained
free segments.

See Note [Segment allocation strategy]

Resolves #24150

-------------------------
Metric Decrease:
    T13253
    T19695
-------------------------

- - - - -
710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00
rts: fix I/O manager compilation errors for win32 target

This patch fixes I/O manager compilation errors for win32 target
discovered when cross-compiling to win32 using recent clang:

```
rts/win32/ThrIOManager.c:117:7: error:
     error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      117 |   if (is_io_mng_native_p ()) {
          |       ^
    |
117 |   if (is_io_mng_native_p ()) {
    |       ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/fs.c:143:28: error:
     error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes]
      143 | int setErrNoFromWin32Error () {
          |                            ^
          |                             void
    |
143 | int setErrNoFromWin32Error () {
    |                            ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/win32/ConsoleHandler.c:227:9: error:
     error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      227 |         interruptIOManagerEvent ();
          |         ^
    |
227 |         interruptIOManagerEvent ();
    |         ^

rts/win32/ConsoleHandler.c:227:9: error:
     note: did you mean 'getIOManagerEvent'?
    |
227 |         interruptIOManagerEvent ();
    |         ^

rts/include/rts/IOInterface.h:27:10: error:
     note: 'getIOManagerEvent' declared here
       27 | void *   getIOManagerEvent  (void);
          |          ^
   |
27 | void *   getIOManagerEvent  (void);
   |          ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/win32/ConsoleHandler.c:196:9: error:
     error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      196 |         setThreadLabel(cap, t, "signal handler thread");
          |         ^
    |
196 |         setThreadLabel(cap, t, "signal handler thread");
    |         ^

rts/win32/ConsoleHandler.c:196:9: error:
     note: did you mean 'postThreadLabel'?
    |
196 |         setThreadLabel(cap, t, "signal handler thread");
    |         ^

rts/eventlog/EventLog.h:118:6: error:
     note: 'postThreadLabel' declared here
      118 | void postThreadLabel(Capability    *cap,
          |      ^
    |
118 | void postThreadLabel(Capability    *cap,
    |      ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)
```

- - - - -
28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00
configure: Check C99-compat for Cmm preprocessor

Fixes #24815

- - - - -
8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00
Ensure `tcHasFixedRuntimeRep (# #)` returns True.

- - - - -
04179044 by doyougnu at 2024-05-17T09:00:32-04:00
testsuite: make find_so regex less general

Closes #24759

Background. In MR !12372 we began tracking shared object files and
directories sizes for dependencies. However, this broke  release builds
because release builds alter the filenames swapping "in-place" for a
hash. This was not considered in the MR and thus broke release
pipelines. Furthermore, the rts_so test was found to be wildly varying
and was therefore disabled in !12561.

This commit fixes both of these issues:

- fix the rts_so test by making the regex less general, now the rts_so
test and all other foo.so tests must match
"libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the
rts_so test from accidentally matching different rts variants such as
rts_threaded, which was the cause of the wild swings after !12372.

- add logic to match either a hash or the string in-place. This should
make the find_so function build agnostic.

- - - - -
0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00
TagAnalysis: Treat all bottom ids as tagged during analysis.

Ticket #24806 showed that we also need to treat dead end thunks as
tagged during the analysis.

- - - - -
7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00
Remove haddock submodule

In preparation for merge into the GHC, as proposed in #23178.

- - - - -
47b14dcc by Fendor at 2024-05-17T11:28:17-04:00
Adapt to `IfLclName` newtype changes

(cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1)

- - - - -
6cc6681d by Fendor at 2024-05-17T11:28:17-04:00
Add IfaceType deduplication table to interface file serialisation

Although we do not really need it in the interface file serialisation,
as the deserialisation uses `getWithUserData`, we need to mirror the
structure `getWithUserData` expects. Thus, we write essentially an empty
`IfaceType` table at the end of the file, as the interface file doesn't
reference `IfaceType`.

(cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61)

- - - - -
b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00
ghc-tags.yaml: Initial commit

- - - - -
074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00
fourmolu: Add configuration

- - - - -
151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00
Makefile: Rework for use by haddock developers

Previously the Makefile was present only for GHC's old make-based build
system. Now since the make-based build system is gone we can use it for
more useful ends.

- - - - -
a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00
Reformat with fourmolu

Using previously-added configuration and `fourmolu -i .`
Note that we exclude the test-cases
(`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to
formatting.

- - - - -
0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00
Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660'

git-subtree-dir: utils/haddock
git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3
git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660

- - - - -
aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00
Add exceptions to the dangling notes list

- - - - -
527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00
Add haddock to the whitespace lint ignore list

- - - - -
43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00
git-blame-ignore-revs: Ignore haddock reformatting

- - - - -
0e679e37 by Fendor at 2024-05-18T00:27:24-04:00
Pass cpp options to the CC builder in hadrian

- - - - -
bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00
JS: fix allocation constant (fix #24746)

- - - - -
646d30ab by Jade at 2024-05-18T19:23:31+02:00
Add highlighting for inline-code snippets in haddock

- - - - -
64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00
haddock: Add a .readthedocs.yml file for online documentation

- - - - -
7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00
Unicode: General Category size test (related #24789)

Added trivial size performance test which involves unicode general category usage via `read`.
The `read` itself uses general category to detect spaces.

The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789.

- - - - -
8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00
EPA: Remove redundant code

Remove unused
  epAnnAnns function
  various cases for showAstData that no longer exist

- - - - -
071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00
Improve docs on closed type families in hs-boots

Fixes #24776

- - - - -
d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00
Use default deviation for large-project test

This new performance test has the purpose of detecting regressions in
complexity in relation to the number of modules in a project, so 1%
deviation is way too small to avoid false positives.

- - - - -
20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00
ghcup-metadata: Various fixes from 9.10.1

Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists
where possible.

- - - - -
6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00
Reverse arguments to stgCallocBytes (fix #24828)

- - - - -
f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00
Add log messages for Iface serialisation compression level

Fix the label of the number of 'IfaceType' entries in the log message.
Add log message for the compression level that is used to serialise a an
interface file.

Adds `Outputable` instance for 'CompressionIFace'.

- - - - -
3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00
base: Update doctests outputs

ghc-internal: Update doctests outputs

- - - - -
9317c6fb by David Binder at 2024-05-22T00:34:21-04:00
haddock: Fix the testsuites of the haddock-library

- Apply all the metadata revisions from Hackage
  to the cabal file.
- Fix the `ParserSpec.hs` file in the `spec`
  testsuite of haddock-library.
- Make `CHANGES.md` an extra-doc-file instead of
  an extra-source-file.

- - - - -
54073b02 by David Binder at 2024-05-22T00:34:21-04:00
haddock: Fix parser of @since pragma

The testsuite contained tests for annotations of
the form `@since foo-bar-0.5.0`, but the parser was
written incorrectly.

- - - - -
ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00
Fix nightly pages job

It seems likely broken by 9f99126a which moved `index.html` from the
root folder into `docs/` folder.

Fixes #24840

- - - - -
b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00
autoconf: remove unused context diff check

This patch removes redundant autoconf check for the context diff
program given it isn't actually been used anywhere, especially since
make removal.

- - - - -
ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00
haddock: Rework the contributing guide

- - - - -
0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00
haddock: Add module relationships diagrams of haddock-api and haddock-library

- - - - -
d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00
Add instructions

- - - - -
b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00
Add SVG outputs

- - - - -
6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00
rts: Fix size of StgOrigThunkInfo frames

Previously the entry code of the `stg_orig_thunk` frame failed to
account for the size of the profiling header as it hard-coded the frame
size. Fix this.

Fixes #24809.

- - - - -
c645fe40 by Fendor at 2024-05-22T13:40:05-04:00
Add regression test T24809 for stg_orig_thunk_info_frame size

- - - - -
4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00
bindists: Check for existence of share folder before trying to copy it.

This folder isn't distributed in windows bindists

A lack of doing so resulted us copying loads of files twice.

- - - - -
d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00
Remove ad-hoc installation of mingw toolchain in relocatable bindists

This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951

The choice about whether to install mingw is taken in the installation
makefile.

This is also broken on non-windows systems.

The actual issue was the EnableDistroToolchain variable wasn't declared
in mk/config.mk and therefore the check to install mingw was failing.

- - - - -
7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00
testsuite: fix T17920 for wasm backend

T17920 was marked as fragile on wasm before; it can be trivially fixed
by avoiding calling variadic printf() in cmm.

- - - - -
c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00
testsuite: bump T22744 timeout to 5x

- - - - -
c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00
testsuite: don't attempt to detect host cpu features when testing cross ghc

The testsuite driver CPU feature detection logic only detects host CPU
and only makes sense when we are not testing a cross GHC.

- - - - -
3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00
Better skolemisation

As #24810 showed, it is (a little) better to skolemise en-bloc,
so that Note [Let-bound skolems] fires more often.

See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate.

- - - - -
a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00
Add missing parenthesizePat in cvtp

We need to ensure that the output of `cvtp` is parenthesized (at precedence
`sigPrec`) so that any pattern signatures with a surrounding pattern signature
can parse correctly.

Fixes #24837.

- - - - -
4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00
[base] Document the memory overhead of ByteArray

Add a diagram that shows the constituent parts of a ByteArray and their
memory overhead.

- - - - -
8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00
Haddock: Add MR template for Haddock

- - - - -
ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00
PPC: Support ELF v2 on powerpc64 big-endian

Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF`
preprocessor macro.

Fixes #21191

- - - - -
9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00
gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock

- - - - -
28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00
haddock: Add cabal-fmt to tools for `make style`

- - - - -
00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00
haddock: fix verbosity option parsing

- - - - -
a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00
base: specify tie-breaking behavior of min, max, and related list/Foldable functions

- - - - -
bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00
cmm: add word <-> double/float bitcast

- closes: #25331

This is the last step in the project plan described in #25331. This
commit:

- adds bitcast operands for x86_64, LLVM, aarch64
- For PPC and i386 we resort to using the cmm implementations
- renames conversion MachOps from Conv to Round|Truncate

- - - - -
f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00
StgToByteCode: minor refactor

Some functions in StgToByteCode were filtering out void arguments.
However, StgToByteCode is called after unarisation: the void arguments
should have been removed earlier.
Instead of filtering out, we assert that the args are non-void.

- - - - -
03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00
StgToByteCode: minor refactor

`layoutNativeCall` was always called with a `primRepCmmType platform`
callback. Hence we can put it inside of `layoutNativeCall` rather than
repeat it.

- - - - -
27c430f3 by David Binder at 2024-05-24T07:52:38-04:00
haddock: Remove compatibility shims for GHC < 8.4 from haddock-library

- - - - -
8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00
compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs

This patch makes the STG->Cmm backend avoid saving foreign call target
to local when there are no caller-save GlobalRegs.

Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a
foreign call, we unconditionally save the foreign call target to a
temporary local first, then rely on cmmSink to clean it up later,
which only happens with -fcmm-sink (implied by -O) and not in
unoptimized code.

And this is troublesome for the wasm backend NCG, which needs to infer
a foreign call target symbol's type signature from the Cmm call site.
Previously, the NCG has been emitting incorrect type signatures for
unoptimized code, which happens to work with `wasm-ld` most of the
time, but this is never future-proof against upstream toolchain
updates, and it causes horrible breakages when LTO objects are
included in linker input. Hence this patch.

- - - - -
986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00
testsuite: add callee-no-local regression test

- - - - -
52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00
Fix HasCallStack leftovers from !12514 / #24726

- - - - -
c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00
user_guide: Fix typo in MultiWayIf chapter

Close #24829

- - - - -
bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00
base: Ensure that CHANGELOG is included in extra-source-files

This was missed in the `ghc-internal` split.

Closes #24831.

- - - - -
1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00
base: Fix changelog reference to setBacktraceMechanismState

(cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d)

- - - - -
43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00
Float/double unboxed literal support for HexFloatLiterals (fix #22155)

- - - - -
4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00
Improve test labels for binary interface file size tests

Test labels for binary interface file sizes are hard to read and overly
verbose at the same time. Extend the name for the metric title, but
shorten it in the actual comparison table.

- - - - -
14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00
Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present"

This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa.

- - - - -
f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00
Fix default hyperlinked sources pattern

Previously this didn't include the `%M` token which manifested as broken
links to the hyperlinked sources of reexports of declarations defined
in other packages.

Fixes haddock#1628.

(cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36)

- - - - -
42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00
Make DocPaths a proper data type

(cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c)

- - - - -
53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00
haddock: Bump version to 2.30

(cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602)

- - - - -
e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00
haddock-api: allow base 4.20 and ghc 9.11

- - - - -
e294f7a2 by PHO at 2024-05-24T12:17:55-04:00
Add a flag "threaded" for building haddock with the threaded RTS

GHC isn't guaranteed to have a threaded RTS. There should be a way to build
it with the vanilla one.

(cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d)

- - - - -
51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00
Update ticky counter event docs.

Add the info about the info table address and json fields.

Fixes #23200

- - - - -
98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00
Export extractPromotedList (#24866)

This can be useful in plugins.

- - - - -
228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00
template-haskell: Move wired-ins to ghc-internal

Thus we make `template-haskell` reinstallable and keep it as the public
API for Template Haskell.
All of the wired-in identifiers are moved to `ghc-internal`.
This necessitates also moving much of `ghc-boot-th` into `ghc-internal`.
These modules are then re-exported from `ghc-boot-th` and
`template-haskell`.
To avoid a dependency on `template-haskell` from `lib:ghc`, we instead
depend on the TH ASTs via `ghc-boot-th`.

As `template-haskell` no longer has special status, we can drop the
logic adding an implicit dependency on `template-haskell` when using TH.
We can also drop the `template-haskell-next` package, which was
previously used when bootstrapping.

When bootstrapping, we need to vendor the TH AST modules from
`ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap`
cabal flag as before. See Note [Bootstrapping Template Haskell].

We split out a GHC.Internal.TH.Lift module resolving #24752.
This module is only built when not bootstrapping.

Resolves #24703

-------------------------
Metric Increase:
    ghc_boot_th_dir
    ghc_boot_th_so
-------------------------

- - - - -
62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00
testsuite: mark tests broken by #24886

Now that `template-haskell` is no longer wired-in.
These tests are triggering #24886, and so need to be marked broken.

- - - - -
3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00
rts: fix missing function prototypes in ClosureMacros.h

- - - - -
e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00
UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument.

This allows representing functions like:

    int foo(void);

to be imported like this:

    foreign import ccall "a_number_c"
      c_number :: (# #) -> Int64#

Which can be useful when the imported function isn't implicitly
stateful.

- - - - -
d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00
ci: Update ci-images commit for fedora38 image

The fedora38 nightly job has been failing for quite a while because
`diff` was no longer installed. The ci-images bump explicitly installs
`diffutils` into these images so hopefully they now pass again.

- - - - -
3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00
Update exactprint docs

- - - - -
77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00
Incorporate review feedback

- - - - -
87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00
Remove no longer relevant reference to comments

- - - - -
05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00
Replace outdated code example

- - - - -
45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00
Reword error resulting from missing -XBangPatterns.

It can be the result of either a bang pattern or strict binding,
so now we say so instead of claiming it must be a bang pattern.

Fixes #21032

- - - - -
e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00
testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x

- - - - -
7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: ensure gc_thread/gen_workspace is allocated with proper alignment

gc_thread/gen_workspace are required to be aligned by 64 bytes.
However, this property has not been properly enforced before, and
numerous alignment violations at runtime has been caught by
UndefinedBehaviorSanitizer that look like:

```
rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment
0x0000027a3390: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8

rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment
0x0000027a3450: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13
```

This patch fixes the gc_thread/gen_workspace misalignment issue by
explicitly allocating them with alignment constraint.

- - - - -
c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: fix an unaligned load in nonmoving gc

This patch fixes an unaligned load in nonmoving gc by ensuring the
closure address is properly untagged first before attempting to
prefetch its header. The unaligned load is reported by
UndefinedBehaviorSanitizer:

```
rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment
0x0042005f3a71: note: pointer points here
 00 00 00  98 43 13 8e 12 7f 00 00  50 3c 5f 00 42 00 00 00  58 17 b7 92 12 7f 00 00  89 cb 5e 00 42
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9
```

This issue had previously gone unnoticed since it didn't really harm
runtime correctness, the invalid header address directly loaded from a
tagged pointer is only used as prefetch address and will not cause
segfaults. However, it still should be corrected because the prefetch
would be rendered useless by this issue, and untagging only involves a
single bitwise operation without memory access so it's cheap enough to
add.

- - - - -
05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: use __builtin_offsetof to implement STG_FIELD_OFFSET

This patch fixes the STG_FIELD_OFFSET macro definition by using
__builtin_offsetof, which is what gcc/clang uses to implement offsetof
in standard C. The previous definition that uses NULL pointer involves
subtle undefined behavior in C and thus reported by
UndefinedBehaviorSanitizer as well:

```
rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_')
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58
```

- - - - -
5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00
JS: remove useless h$CLOCK_REALTIME (#23202)

- - - - -
95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00
ghcup-metadata: Fix metadata generation

There were some syntax errors in the generation script which were
preventing it from running.

I have tested this with:

```
nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525
```

which completed successfully.

- - - - -
1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00
Add diagrams to Arrows documentation

This adds diagrams to the documentation of Arrows, similar to the ones found on
https://www.haskell.org/arrows/.

It does not add diagrams for ArrowChoice for the time being, mainly because it's
not clear to me how to visually distinguish them from the ones for Arrow. Ideally,
you might want to do something like highlight the arrows belonging to the same
tuple or same Either in common colors, but that's not really possible with unicode.

- - - - -
d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00
Make UnsafeSNat et al. into pattern synonyms

...so that they do not cause coerce to bypass the nominal
role on the corresponding singleton types when they are imported.
See Note [Preventing unsafe coercions for singleton types] and
the discussion at #23478.

This also introduces unsafeWithSNatCo (and analogues for Char
and Symbol) so that users can still access the dangerous coercions
that importing the real constructors would allow, but only in a
very localized way.

- - - - -
0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00
hadrian: build C/C++ with split sections when enabled

When split sections is enabled, ensure -fsplit-sections is passed to
GHC as well when invoking GHC to compile C/C++; and pass
-ffunction-sections -fdata-sections to gcc/clang when compiling C/C++
with the hadrian Cc builder. Fixes #23381.

- - - - -
02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00
driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled

When -fsplit-sections is passed to GHC, pass -ffunction-sections
-fdata-sections to gcc/clang when building C/C++. Previously,
-fsplit-sections was only respected by the NCG/LLVM backends, but not
the unregisterised backend; the GHC driver did not pass
-fdata-sections and -ffunction-sections to the C compiler, which
resulted in excessive executable sizes.

Fixes #23381.

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00
testsuite: mark process005 as fragile on JS

- - - - -
34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00
Add -Wderiving-typeable to -Wall

Deriving `Typeable` does nothing, and it hasn't done for a long while.

There has also been a warning for a long while which warns you about
uselessly deriving it but it wasn't enabled in -Wall.

Fixes #24784

- - - - -
75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00
docs: Fix formatting of changelog entries

- - - - -
303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00
docs: Fix link to injective type families paper

Closes #24863

- - - - -
df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00
ghc-internal: Fix package description

The previous description was inherited from `base` and was inappropriate
for `ghc-internal`. Also fix the maintainer and bug reporting fields.

Closes #24906.

- - - - -
bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00
compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans

This patch removes special consideration for ArchWasm32 in
cmmDoCmmSwitchPlans, which means the compiler will now disable
cmmImplementSwitchPlans for wasm unreg backend, just like unreg
backend of other targets. We enabled it in the past to workaround some
compile-time panic in older versions of LLVM, but those panics are no
longer present, hence no need to keep this workaround.

- - - - -
7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00
utils: add hie.yaml config file for ghc-config

Add hie.yaml to ghc-config project directory so it can be edited using
HLS.

- - - - -
1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00
hadrian: handle findExecutable "" gracefully

hadrian may invoke findExecutable "" at run-time due to a certain
program is not found by configure script. Which is fine and
findExecutable is supposed to return Nothing in this case. However, on
Windows there's a directory bug that throws an exception (see
https://github.com/haskell/directory/issues/180), so we might as well
use a wrapper for findExecutable and handle exceptions gracefully.

- - - - -
4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00
configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails

When configure fails to find LLC/OPT/LLVMAS within supported version
range, it used to set "llc"/"opt"/"clang" as fallback values. This
behavior is particularly troublesome when the user has llc/opt/clang
with other versions in their PATH and run the testsuite, since hadrian
will incorrectly assume have_llvm=True and pass that to the testsuite
driver, resulting in annoying optllvm test failures (#23186). If
configure determines llc/opt/clang wouldn't work, then we shouldn't
pretend it'll work at all, and the bindist configure will invoke
FIND_LLVM_PROG check again at install time anyway.

- - - - -
5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00
Introduce UniqueSet and use it to replace 'UniqSet Unique'

'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique',
which is wasting space (associated key/value are always the same).

Fix #23572 and #23605

- - - - -
e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00
Improve template-haskell haddocks

Closes #15822

- - - - -
ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00
Bump max LLVM version to 19 (not inclusive)

- - - - -
92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00
ci: Update CI images to test LLVM 18

The debian12 image in this commit has llvm 18 installed.

- - - - -
adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00
Unicode: make ucd2haskell build-able again

ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten.

Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures:
1. Ghc module path environment got a suffix with `src`.
2. Generated code got
2.1 `GHC.Internal` prefix for `Data.*`.
2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure.

- - - - -
ad56fd84 by Jade at 2024-06-01T09:36:29-04:00
Replace 'NB' with 'Note' in error messages

- - - - -
6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00
compiler: fix -ddump-cmm-raw when compiling .cmm

This patch fixes missing -ddump-cmm-raw output when compiling .cmm,
which is useful for debugging cmm related codegen issues.

- - - - -
1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00
Print namespace specifiers in FixitySig's Outputable instance

For whatever reason, the `Outputable` instance for `FixitySig` simply did not
print out namespace specifiers, leading to the confusing `-ddump-splices`
output seen in #24911. This patch corrects this oversight.

Fixes #24911.

- - - - -
cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00
Configure: display C++ compiler path

- - - - -
f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable PIC for in-tree GMP on wasm32

This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC
unconditionally adds undesired code size and runtime overhead for
wasm32.

- - - - -
1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable in-tree gmp fft code path for wasm32

This patch disables in-tree GMP FFT code paths for wasm32 target in
order to give up some performance of multiplying very large operands
in exchange for reduced code size.

- - - - -
06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: build in-tree GMP with malloc-notreentrant on wasm32

This patch makes hadrian build in-tree GMP with the
--enable-alloca=malloc-notreentrant configure option. We will only
need malloc-reentrant when we have threaded RTS and SMP support on
wasm32, which will take some time to happen, before which we should
use malloc-notreentrant to avoid undesired runtime overhead.

- - - - -
9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00
Set package include paths when assembling .S files

Fixes #24839.

Co-authored-by: Sylvain Henry <hsyl20 at gmail.com>

- - - - -
4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00
Improve performance of genericWordQuotRem2Op (#22966)

Implements the algorithm from compiler-rt's udiv128by64to64default. This
rewrite results in a roughly 24x improvement in runtime on AArch64 (and
likely any other arch that uses it).

- - - - -
ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00
testsuite: mark T7773 as fragile on wasm

- - - - -
c8ece0df by Fendor at 2024-06-03T19:43:22-04:00
Migrate `Finder` component to `OsPath`, fixed #24616

For each module in a GHCi session, we keep alive one `ModLocation`.
A `ModLocation` is fairly inefficiently packed, as `String`s are
expensive in memory usage.

While benchmarking the agda codebase, we concluded that we keep alive
around 11MB of `FilePath`'s, solely retained by `ModLocation`.

We provide a more densely packed encoding of `ModLocation`, by moving
from `FilePath` to `OsPath`. Further, we migrate the full `Finder`
component to `OsPath` to avoid unnecessary transformations.
As the `Finder` component is well-encapsulated, this requires only a
minimal amount of changes in other modules.

We introduce pattern synonym for 'ModLocation' which maintains backwards
compatibility and avoids breaking consumers of 'ModLocation'.

- - - - -
0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00
compiler: emit NaturallyAligned when element type & index type are the same width

This commit fixes a subtle mistake in alignmentFromTypes that used to
generate Unaligned when element type & index type are the same width.
Fixes #24930.

- - - - -
18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00
Parser: Remove unused `apats` rule

- - - - -
38757c30 by David Knothe at 2024-06-04T05:05:27-04:00
Implement Or Patterns (#22596)

This commit introduces a new language extension, `-XOrPatterns`, as described in
GHC Proposal 522.

An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ...,
`patk` succeed, in this order.

See also the summary `Note [Implmentation of OrPatterns]`.

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>

- - - - -
395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00
compiler/ghci/rts: remove stdcall support completely

We have formally dropped i386 windows support (#18487) a long time
ago. The stdcall foreign call convention is only used by i386 windows,
and the legacy logic around it is a significant maintenance burden for
future work that adds arm64 windows support (#24603). Therefore, this
patch removes stdcall support completely from the compiler as well as
the RTS (#24883):

- stdcall is still recognized as a FFI calling convention in Haskell
  syntax. GHC will now unconditionally emit a warning
  (-Wunsupported-calling-conventions) and treat it as ccall.
- Apart from minimum logic to support the parsing and warning logic,
  all other code paths related to stdcall has been completely stripped
  from the compiler.
- ghci only supports FFI_DEFAULT_ABI and ccall convention from now on.
- FFI foreign export adjustor code on all platforms no longer handles
  the stdcall case and only handles ccall from now on.
- The Win32 specific parts of RTS no longer has special code paths for
  stdcall.

This commit is the final nail on the coffin for i386 windows support.
Further commits will perform more housecleaning to strip the legacy
code paths and pave way for future arm64 windows support.

- - - - -
d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00
rts: remove legacy i386 windows code paths

This commit removes some legacy i386 windows related code paths in the
RTS, given this target is no longer supported.

- - - - -
a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00
autoconf: remove i386 windows related logic

This commit removes legacy i386 windows logic in autoconf scripts.

- - - - -
91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00
llvm-targets: remove i386 windows support

This commit removes i386 windows from llvm-targets and the script to
generate it.

- - - - -
65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00
libraries/utils: remove stdcall related legacy logic

This commit removes stdcall related legacy logic in libraries and
utils. ccall should be used uniformly for all supported windows hosts
from now on.

- - - - -
d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00
testsuite: adapt the testsuite for stdcall removal

This patch adjusts test cases to handle the stdcall removal:

- Some stdcall usages are replaced with ccall since stdcall doesn't
  make sense anymore.
- We also preserve some stdcall usages, and check in the expected
  warning messages to ensure GHC always warn about stdcall usages
  (-Wunsupported-calling-conventions) as expected.
- Error code testsuite coverage is slightly improved,
  -Wunsupported-calling-conventions is now tested.
- Obsolete code paths related to i386 windows are also removed.

- - - - -
cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: minor adjustments for stdcall removal

This commit include minor adjustments of documentation related to
stdcall removal.

- - - - -
54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: mention i386 Windows removal in 9.12 changelog

This commit mentions removal of i386 Windows support and stdcall
related change in the 9.12 changelog.

- - - - -
2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00
hadrian: improve user settings documentation

This patch adds minor improvements to hadrian user settings documentation:

- Add missing `ghc.cpp.opts` case
- Remove non-existent `cxx` case
- Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't
- Add example of passing configure argument to autoconf packages

- - - - -
71010381 by Alex Mason at 2024-06-04T12:09:07-04:00
Add AArch64 CLZ, CTZ, RBIT primop implementations.

Adds support for emitting the clz and rbit instructions, which are
used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#.

- - - - -
44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00
hadrian: add +text_simdutf flavour transformer to allow building text with simdutf

This patch adds a +text_simdutf flavour transformer to hadrian to
allow downstream packagers and users that build from source to opt-in
simdutf support for text, in order to benefit from SIMD speedup at
run-time. It's still disabled by default for the time being.

- - - - -
077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00
ci: enable +text_simdutf flavour transformer for wasm jobs

This commit enables +text_simdutf flavour transformer for wasm jobs,
so text is now built with simdutf support for wasm.

- - - - -
b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Use TemplateHaskellQuotes in instance Lift ByteArray

Resolves #24852

- - - - -
3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Mark addrToByteArray as NOINLINE

This function should never be inlined in order to keep code size small.

- - - - -
98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00
compiler: remove unused CompilerInfo/LinkerInfo types

This patch removes CompilerInfo/LinkerInfo types from the compiler
since they aren't actually used anywhere.

- - - - -
11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00
rts: remove unused PowerPC/IA64 native adjustor code

This commit removes unused PowerPC/IA64 native adjustor code which is
never actually enabled by autoconf/hadrian. Fixes #24920.

- - - - -
5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00
RTS: fix warnings with doing*Profiling (#24918)

- - - - -
accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00
hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows

- - - - -
6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00
autoconf: normalize paths of some build-time dependencies on Windows

This commit applies path normalization via cygpath -m to some
build-time dependencies on Windows. Without this logic, the
/clang64/bin prefixed msys2-style paths cause the build to fail with
--enable-distro-toolchain.

- - - - -
075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00
hadrian: remove OSDarwin mention from speedHack

This commit removes mentioning of OSDarwin from speedHack, since
speedHack is purely for i386 and we no longer support i386 darwin
(#24921).

- - - - -
83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00
compiler: remove 32-bit darwin logic

This commit removes all 32-bit darwin logic from the compiler, given
we no longer support 32-bit apple systems (#24921). Also contains a
bit more cleanup of obsolete i386 windows logic.

- - - - -
1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00
rts: remove 32-bit darwin/ios logic

This commit removes 32-bit darwin/ios related logic from the rts,
given we no longer support them (#24921).

- - - - -
24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00
llvm-targets: remove 32-bit darwin/ios targets

This commit removes 32-bit darwin/ios targets from llvm-targets given
we no longer support them (#24921).

- - - - -
ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00
testsuite: remove 32-bit darwin logic

This commit removes 32-bit darwin logic from the testsuite given it's
no longer supported (#24921). Also contains more cleanup of obsolete
i386 windows logic.

- - - - -
11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00
docs: mention 32-bit darwin/ios removal in 9.12 changelog

This commit mentions removal of 32-bit darwin/ios support (#24921) in
the 9.12 changelog.

- - - - -
7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00
Add firstA and secondA to Data.Bitraversable

Please see https://github.com/haskell/core-libraries-committee/issues/172
for related discussion

- - - - -
3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00
base: Fix name of changelog

Fixes #24899. Also place it under `extra-doc-files` to better reflect
its nature and avoid triggering unnecessary recompilation if it
changes.

- - - - -
1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00
Announce Or-patterns in the release notes for GHC 9.12 (#22596)

Leftover from !9229.

- - - - -
8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00
Improve haddocks of Language.Haskell.Syntax.Pat.Pat

- - - - -
2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00
testsuite: bump T7653 timeout for wasm

- - - - -
990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00
StgToCmm: refactor opTranslate and friends

- Change arguments order to avoid `\args -> ...` lambdas
- Fix documentation
- Rename StgToCmm options ("big" doesn't mean anything)

- - - - -
1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00
NCG x86: remove dead code (#5444)

Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead.

- - - - -
595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00
testsuite: skip objc-hi/objcxx-hi when cross compiling

objc-hi/objcxx-hi should be skipped when cross compiling. The existing
opsys('darwin') predicate only asserts the host system is darwin but
tells us nothing about the target, hence the oversight.

- - - - -
edfe6140 by qqwy at 2024-06-08T11:23:54-04:00
Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw

- - - - -
35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00
rts: cleanup inlining logic

This patch removes pre-C11 legacy code paths related to
INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE
is treated as static inline in most cases (fixes #24945), and also
corrects the comments accordingly.

- - - - -
9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00
CODEOWNERS: add @core-libraries to track base interface changes

A low-tech tactical solution for #24919

- - - - -
580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update CHANGELOG to reflect current version

- - - - -
391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update prologue.txt to reflect package description

- - - - -
3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00
compiler: Clarify comment regarding need for MOVABS

The comment wasn't clear in stating that it was only applicable to
immediate source and memory target operands.

- - - - -
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
e66c9e80 by Ben Gamari at 2024-10-14T13:28:04-04:00
rts: Tighten up invariants of PACK

- - - - -
c7a8be83 by Ben Gamari at 2024-10-14T13:29:11-04:00
StgToByteCode: Don't assume that data con workers are nullary

Previously StgToByteCode assumed that all data-con workers were of a
nullary representation. This is not a valid assumption, as seen
in #23210, where an unsaturated application of a unary data
constructor's worker resulted in invalid bytecode. Sadly, I have not yet
been able to reduce a minimal testcase for this.

Fixes #23210.

- - - - -
815bf47e by Ben Gamari at 2024-10-14T13:30:10-04:00
StgToByteCode: Fix handling of Addr# literals

Previously we assumed that all unlifted types were Addr#.

- - - - -
fd0e0617 by Ben Gamari at 2024-10-14T14:33:09-04:00
testsuite: Add another test for #23146

- - - - -
83c0940c by Ben Gamari at 2024-10-14T14:53:24-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -


10 changed files:

- .ghcid
- + .git-blame-ignore-revs
- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7da4a5f6bcb8991e0398ff121881c75e2de46d8e...83c0940c754a30b1654d1087e7fed0f0cdb1f0ac

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7da4a5f6bcb8991e0398ff121881c75e2de46d8e...83c0940c754a30b1654d1087e7fed0f0cdb1f0ac
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 18:54:29 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Mon, 14 Oct 2024 14:54:29 -0400
Subject: [Git][ghc/ghc][wip/T25374] rts/Disassembler: Fix encoding of BRK_FUN
 instruction
Message-ID: <670d68e5810cb_79c317926063453@gitlab.mail>



Ben Gamari pushed to branch wip/T25374 at Glasgow Haskell Compiler / GHC


Commits:
a69c8d66 by Ben Gamari at 2024-10-14T14:54:14-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -


2 changed files:

- libraries/process
- rts/Disassembler.c


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e
+Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b


=====================================
rts/Disassembler.c
=====================================
@@ -67,7 +67,7 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 19:11:50 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 14 Oct 2024 15:11:50 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/buildplan
Message-ID: <670d6cf6ea30e_79c361ecc065874@gitlab.mail>



Cheng Shao deleted branch wip/buildplan at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 19:18:44 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 14 Oct 2024 15:18:44 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-3] 37 commits: Handle
 exceptions from IO manager backend
Message-ID: <670d6e944aa72_79c36f7958662b2@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-3 at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
cefa7d38 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsDocTy

- - - - -
b2ec4881 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsBangTy

- - - - -
d5048d5d by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsExplicitListTy

- - - - -
cceb869b by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsExplicitTupleTy

- - - - -
0c057f2b by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsTypedBracket

- - - - -
5e65084b by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from HsUntypedBracket

- - - - -
f70fb012 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
Remove [AddEpAnn] from PatBuilderOpApp

- - - - -
c70d0087 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: break out 'EpToken "|"' from ClassDecl anns

- - - - -
e2188f08 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from ClassDecl

- - - - -
7b21a654 by Alan Zimmerman at 2024-10-14T19:32:18+01:00
EPA: Remove [AddEpAnn] from SynDecl

- - - - -


30 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b8244ff93f30c9eaafed22cc4e6f6e706547d42e...7b21a6540cd330d3e5fce899c167da90872d973d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b8244ff93f30c9eaafed22cc4e6f6e706547d42e...7b21a6540cd330d3e5fce899c167da90872d973d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 20:53:27 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 16:53:27 -0400
Subject: [Git][ghc/ghc][wip/T23479] test
Message-ID: <670d84c741619_1d5aec159e108543@gitlab.mail>



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


Commits:
c2e27327 by Serge S. Gulin at 2024-10-14T23:53:16+03:00
test

- - - - -


3 changed files:

- compiler/GHC/StgToJS/Apply.hs
- testsuite/tests/javascript/Makefile
- testsuite/tests/javascript/T24495.stdout


Changes:

=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -126,6 +126,26 @@ genApp ctx i args
     , [top] <- concatMap typex_expr (ctxTarget ctx)
     = return . (,ExprInline) $ top |= toJExpr d
 
+    -- Test case T24495 with single occurrence at -02 and third occurrence at -01
+    -- Moved back from removal at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12308
+    -- See commit hash b36ee57bfbecc628b7f0919e1e59b7066495034f
+    --
+    -- Case: unpackCStringAppend# "some string"# str
+    --
+    -- Generates h$appendToHsStringA(str, "some string"), which has a faster
+    -- decoding loop.
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendIdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
+
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i
     = do


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -5,7 +5,12 @@ include $(TOP)/mk/test.mk
 T24495:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T24495
-	# check that the optimization occurred
+	# check that the optimization occurred for -01 3 times (2 for cases + 1 for unfloated lits)
+	grep -c appendToHsStringA T24495.dump-js
+
+	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T24495
+	# check that the optimization occurred for -02 1 time (1 for unfloated lits)
 	grep -c appendToHsStringA T24495.dump-js
 
 T23479_1:


=====================================
testsuite/tests/javascript/T24495.stdout
=====================================
@@ -1,2 +1,4 @@
 2 ab bd
-2
+3
+2 ab bd
+1



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 20:56:18 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 16:56:18 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes 23479 (muted temporary))
Message-ID: <670d8572aab89_1d5aecf9fec85844@gitlab.mail>



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


Commits:
e8caf05d by Serge S. Gulin at 2024-10-14T23:55:35+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


23 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- testsuite/tests/javascript/T24495.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,51 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
+
+    -- Test case T24495 with single occurrence at -02 and third occurrence at -01
+    -- Moved back from removal at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12308
+    -- See commit hash b36ee57bfbecc628b7f0919e1e59b7066495034f
+    --
+    -- Case: unpackCStringAppend# "some string"# str
+    --
+    -- Generates h$appendToHsStringA(str, "some string"), which has a faster
+    -- decoding loop.
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendIdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -5,5 +5,28 @@ include $(TOP)/mk/test.mk
 T24495:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T24495
-	# check that the optimization occurred
+	# check that the optimization occurred for -01 3 times (2 for cases + 1 for unfloated lits)
+	grep -c appendToHsStringA T24495.dump-js
+
+	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T24495
+	# check that the optimization occurred for -02 1 time (1 for unfloated lits)
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js || true
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local_once" T23479_2.dump-js
+	# check that the optimization occurred
+	grep -c "h\$$r1 = h\$$decodeUtf8z" T23479_2.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+test_val_80_global :: String
+test_val_80_global = "test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val"
+
+main :: IO ()
+main = do
+  -- Direct usage
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## "test_val_1"#))
+  -- Requires string sinker hit for strings shorter 80 symbols
+  js_log1 (toJSString test_val_2)
+  -- Requires rewrite hit "toJSString/literal"
+  js_log1 (toJSString test_val_3)
+  -- Locally defined strings become unfloatted at any length
+  js_log1 (toJSString test_val_80_local)
+  -- Globally defined strings with length >= 80 should not be unfloatted
+  js_log1 (toJSString test_val_80_global)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,10 @@
+test_val_1
+test_val_2
+test_val_3
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val
+1
+1
+1
+1
+0


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  -- When long string (>= 80) used once it is unfloatted
+  js_log1 (toJSString test_val_80_local_once)
+
+  -- When long string (>= 80) used more than once no unfloatting happened
+  js_log1 (toJSString test_val_80_local)
+  js_log1 (toJSString (testFn80 "testFn80:"))
+
+  -- Even if short string used more than once it is unfloatted anyway
+  js_log1 (toJSString test_val_1)
+  js_log1 (toJSString (testFn "testFn:"))
+  where
+    test_val_80_local_once :: String
+    test_val_80_local_once = "test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"
+
+    testFn80 s = s ++ test_val_80_local
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn80 #-}
+
+    test_val_1 :: String
+    test_val_1 = "test_val_1"
+
+    testFn s = s ++ test_val_1
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn #-}


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,8 @@
+test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+testFn80:test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_1
+testFn:test_val_1
+1
+1
+1


=====================================
testsuite/tests/javascript/T24495.stdout
=====================================
@@ -1,2 +1,4 @@
 2 ab bd
-2
+3
+2 ab bd
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,7 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])
+test('T23479_3', normal, makefile_test, ['T23479_3'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 20:58:24 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Mon, 14 Oct 2024 16:58:24 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes 23479 (muted temporary))
Message-ID: <670d85f0b5137_1d5aecbc638862dd@gitlab.mail>



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


Commits:
ed85dc26 by Serge S. Gulin at 2024-10-14T23:57:57+03:00
JS: Re-add optimization for literal strings in genApp (fixes 23479 (muted temporary))

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


23 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- testsuite/tests/javascript/T24495.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,51 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
+
+    -- Test case T24495 with single occurrence at -02 and third occurrence at -01
+    -- Moved back from removal at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12308
+    -- See commit hash b36ee57bfbecc628b7f0919e1e59b7066495034f
+    --
+    -- Case: unpackCStringAppend# "some string"# str
+    --
+    -- Generates h$appendToHsStringA(str, "some string"), which has a faster
+    -- decoding loop.
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendIdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -5,5 +5,28 @@ include $(TOP)/mk/test.mk
 T24495:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T24495
-	# check that the optimization occurred
+	# check that the optimization occurred for -01 3 times (2 for cases + 1 for unfloated lits)
+	grep -c appendToHsStringA T24495.dump-js
+
+	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T24495
+	# check that the optimization occurred for -02 1 time (1 for unfloated lits)
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js || true
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local_once" T23479_2.dump-js
+	# check that the optimization occurred
+	grep -c "h\$$r1 = h\$$decodeUtf8z" T23479_2.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+test_val_80_global :: String
+test_val_80_global = "test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val"
+
+main :: IO ()
+main = do
+  -- Direct usage
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## "test_val_1"#))
+  -- Requires string sinker hit for strings shorter 80 symbols
+  js_log1 (toJSString test_val_2)
+  -- Requires rewrite hit "toJSString/literal"
+  js_log1 (toJSString test_val_3)
+  -- Locally defined strings become unfloatted at any length
+  js_log1 (toJSString test_val_80_local)
+  -- Globally defined strings with length >= 80 should not be unfloatted
+  js_log1 (toJSString test_val_80_global)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,10 @@
+test_val_1
+test_val_2
+test_val_3
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val
+1
+1
+1
+1
+0


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  -- When long string (>= 80) used once it is unfloatted
+  js_log1 (toJSString test_val_80_local_once)
+
+  -- When long string (>= 80) used more than once no unfloatting happened
+  js_log1 (toJSString test_val_80_local)
+  js_log1 (toJSString (testFn80 "testFn80:"))
+
+  -- Even if short string used more than once it is unfloatted anyway
+  js_log1 (toJSString test_val_1)
+  js_log1 (toJSString (testFn "testFn:"))
+  where
+    test_val_80_local_once :: String
+    test_val_80_local_once = "test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"
+
+    testFn80 s = s ++ test_val_80_local
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn80 #-}
+
+    test_val_1 :: String
+    test_val_1 = "test_val_1"
+
+    testFn s = s ++ test_val_1
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn #-}


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,8 @@
+test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+testFn80:test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_1
+testFn:test_val_1
+1
+1
+1


=====================================
testsuite/tests/javascript/T24495.stdout
=====================================
@@ -1,2 +1,4 @@
 2 ab bd
-2
+3
+2 ab bd
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,6 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 21:34:46 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 17:34:46 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 8 commits: testsuite: normalise
 some versions in callstacks
Message-ID: <670d8e767fc5f_1d5aec58223093015@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
fe72b700 by Zubin Duggal at 2024-10-15T03:04:07+05:30
testsuite: normalise some versions in callstacks

- - - - -
a60f69aa by Zubin Duggal at 2024-10-15T03:04:08+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
1a53e7bf by Zubin Duggal at 2024-10-15T03:04:08+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
eb6f0d0f by Zubin Duggal at 2024-10-15T03:04:08+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
b334a242 by Zubin Duggal at 2024-10-15T03:04:08+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -
d28ee421 by Zubin Duggal at 2024-10-15T03:04:08+05:30
Prepare 9.12.1 alpha

- - - - -
cf4e7882 by Matthew Pickering at 2024-10-15T03:04:08+05:30
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

(cherry picked from commit cca59600f31f2b3e59bd5f8eeca99901a879d007)

- - - - -
34028785 by Zubin Duggal at 2024-10-15T03:04:32+05:30
testsuite: normalise windows file seperators

- - - - -


30 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/ghc.cabal.in
- configure.ac
- libraries/Cabal
- libraries/array
- libraries/base/base.cabal.in
- libraries/deepseq
- libraries/directory
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/unix
- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c14795caad9363cb42e53dbf73b25e796d0beec4...3402878536e6f00a714db559d9f953c222eb814b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c14795caad9363cb42e53dbf73b25e796d0beec4...3402878536e6f00a714db559d9f953c222eb814b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 21:37:44 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 17:37:44 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 2 commits: testsuite: normalise
 windows file seperators
Message-ID: <670d8f28ab42b_1d5aec6a38bc9675c@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
418adce4 by Zubin Duggal at 2024-10-15T03:07:37+05:30
testsuite: normalise windows file seperators

- - - - -
193d7c0e by Zubin Duggal at 2024-10-15T03:07:37+05:30
Prepare 9.12.1 alpha

- - - - -


3 changed files:

- configure.ac
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/profiling/should_run/all.T


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -3,46 +3,46 @@ ghc: Exception:
 default output name would overwrite the input file; must specify -o explicitly
 Usage: For basic information, try the `--help' option.
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling default output name would overwrite the input file; must specify -o explicitly
   | Usage: For basic information, try the `--help' option.
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   | Usage: For basic information, try the `--help' option.
   |   |
-  |   | Package: ghc-9.11-inplace
+  |   | Package: ghc-9.12-8fe2
   |   | Module: GHC.Utils.Panic
   |   | Type: GhcException
   |   |
   |   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   |   | Usage: For basic information, try the `--help' option.
   |   |   |
-  |   |   | Package: ghc-9.11-inplace
+  |   |   | Package: ghc-9.12-8fe2
   |   |   | Module: GHC.Utils.Panic
   |   |   | Type: GhcException
   |   |   |
   |   |   | HasCallStack backtrace:
-  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.11-inplace:GHC.Utils.Panic
+  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.12-8fe2:GHC.Utils.Panic
   |   |
   |   | HasCallStack backtrace:
-  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-inplace:System.Semaphore
+  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-c856:System.Semaphore
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   onException, called at compiler/GHC/Driver/Make.hs:2986:23 in ghc-9.11-inplace:GHC.Driver.Make
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   onException, called at compiler/GHC/Driver/Make.hs:2988:23 in ghc-9.12-8fe2:GHC.Driver.Make
 
 HasCallStack backtrace:
-  bracket, called at compiler/GHC/Driver/Make.hs:2953:3 in ghc-9.11-inplace:GHC.Driver.Make
+  bracket, called at compiler/GHC/Driver/Make.hs:2955:3 in ghc-9.12-8fe2:GHC.Driver.Make
 


=====================================
testsuite/tests/profiling/should_run/all.T
=====================================
@@ -145,11 +145,13 @@ test('T7275', test_opts_dot_prof, makefile_test, [])
 test('callstack001',
      # unoptimised results are different w.r.t. CAF attribution
      [test_opts_dot_prof # produces a different stack
+     ,normalise_fun(lambda s: re.sub(r"(?

From gitlab at gitlab.haskell.org  Mon Oct 14 22:00:23 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 14 Oct 2024 18:00:23 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-3] EPA: Remove [AddEpAnn]
 commit 3
Message-ID: <670d9477f943_1d5aec8b77201020ce@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-3 at Glasgow Haskell Compiler / GHC


Commits:
efd83138 by Alan Zimmerman at 2024-10-14T22:58:44+01:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -


24 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,6 +31,8 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnClassDecl(..),
+  AnnSynDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -337,7 +339,7 @@ instance Outputable SpliceDecoration where
 
 type instance XFamDecl      (GhcPass _) = NoExtField
 
-type instance XSynDecl      GhcPs = [AddEpAnn]
+type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
@@ -352,7 +354,7 @@ data DataDeclRn = DataDeclRn
   deriving Data
 
 type instance XClassDecl    GhcPs =
-  ( [AddEpAnn]
+  ( AnnClassDecl
   , EpLayout              -- See Note [Class EpLayout]
   , AnnSortKey DeclTag )  -- TODO:AZ:tidy up AnnSortKey
 
@@ -364,6 +366,32 @@ type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnClassDecl
+  = AnnClassDecl {
+      acd_class  :: EpToken "class",
+      acd_openp  :: [EpToken "("],
+      acd_closep :: [EpToken ")"],
+      acd_vbar   :: EpToken "|",
+      acd_where  :: EpToken "where",
+      acd_openc  :: EpToken "{",
+      acd_closec :: EpToken "}",
+      acd_semis  :: [EpToken ";"]
+  } deriving Data
+
+instance NoAnn AnnClassDecl where
+  noAnn = AnnClassDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
+data AnnSynDecl
+  = AnnSynDecl {
+    asd_opens  :: [EpToken "("],
+    asd_closes :: [EpToken ")"],
+    asd_type   :: EpToken "type",
+    asd_equal  :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnSynDecl where
+  noAnn = AnnSynDecl noAnn noAnn noAnn noAnn
+
 ------------- Pretty printing FamilyDecls -----------
 
 pprFlavour :: FamilyInfo pass -> SDoc


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -67,10 +67,14 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annotationAnnList
               `extQ` annotationEpAnnImportDecl
               `extQ` annotationNoEpAnns
+              `extQ` annotationExprBracket
+              `extQ` annotationTypedBracket
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
               `extQ` annParen
+              `extQ` annClassDecl
+              `extQ` annSynDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -203,6 +207,23 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               parens $ text "AnnParen"
                         $$ vcat [ppr a, epaLocation o, epaLocation c]
 
+            annClassDecl :: AnnClassDecl -> SDoc
+            annClassDecl (AnnClassDecl c ops cps v w oc cc s) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnClassDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClassDecl"
+                        $$ vcat [showAstData' c, showAstData' ops, showAstData' cps,
+                                 showAstData' v, showAstData' w, showAstData' oc,
+                                 showAstData' cc, showAstData' s]
+
+            annSynDecl :: AnnSynDecl -> SDoc
+            annSynDecl (AnnSynDecl ops cps t e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnSynDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnSynDecl"
+                        $$ vcat [showAstData' ops, showAstData' cps,
+                                 showAstData' t, showAstData' e]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -210,6 +231,22 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "AddEpAnn" <+> ppr a <+> epaLocation s
 
+            annotationExprBracket :: BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|") -> SDoc
+            annotationExprBracket = annotationBracket
+
+            annotationTypedBracket :: BracketAnn (EpToken "[||") (EpToken "[e||") -> SDoc
+            annotationTypedBracket = annotationBracket
+
+            annotationBracket ::forall n h .(Data n, Data h, Typeable n, Typeable h)
+              => BracketAnn n h -> SDoc
+            annotationBracket a = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "BracketAnn"
+             NoBlankEpAnnotations ->
+              parens $ case a of
+                BracketNoE  t -> text "BracketNoE"  <+> showAstData' t
+                BracketHasE t -> text "BracketHasE" <+> showAstData' t
+
             epTokenOC :: EpToken "{" -> SDoc
             epTokenOC  = epToken'
 


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -186,15 +186,23 @@ data HsBracketTc = HsBracketTc
                                         -- pasted back in by the desugarer
   }
 
-type instance XTypedBracket GhcPs = [AddEpAnn]
+type instance XTypedBracket GhcPs = (BracketAnn (EpToken "[||") (EpToken "[e||"), EpToken "||]")
 type instance XTypedBracket GhcRn = NoExtField
 type instance XTypedBracket GhcTc = HsBracketTc
-type instance XUntypedBracket GhcPs = [AddEpAnn]
+type instance XUntypedBracket GhcPs = NoExtField
 type instance XUntypedBracket GhcRn = [PendingRnSplice] -- See Note [Pending Splices]
                                                         -- Output of the renamer is the *original* renamed expression,
                                                         -- plus _renamed_ splices to be type checked
 type instance XUntypedBracket GhcTc = HsBracketTc
 
+data BracketAnn noE hasE
+  = BracketNoE noE
+  | BracketHasE hasE
+  deriving Data
+
+instance (NoAnn n, NoAnn h) => NoAnn (BracketAnn n h) where
+  noAnn = BracketNoE noAnn
+
 -- ---------------------------------------------------------------------
 
 -- API Annotations types
@@ -2141,12 +2149,12 @@ ppr_splice herald mn e
     <> ppr e
 
 
-type instance XExpBr  GhcPs       = NoExtField
-type instance XPatBr  GhcPs       = NoExtField
-type instance XDecBrL GhcPs       = NoExtField
+type instance XExpBr  GhcPs       = (BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|"), EpUniToken "|]" "⟧")
+type instance XPatBr  GhcPs       = (EpToken "[p|", EpUniToken "|]" "⟧")
+type instance XDecBrL GhcPs       = (EpToken "[d|", EpUniToken "|]" "⟧", (EpToken "{", EpToken "}"))
 type instance XDecBrG GhcPs       = NoExtField
-type instance XTypBr  GhcPs       = NoExtField
-type instance XVarBr  GhcPs       = NoExtField
+type instance XTypBr  GhcPs       = (EpToken "[t|", EpUniToken "|]" "⟧")
+type instance XVarBr  GhcPs       = EpaLocation
 type instance XXQuote GhcPs       = DataConCantHappen
 
 type instance XExpBr  GhcRn       = NoExtField


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -471,18 +471,18 @@ type instance XSpliceTy        GhcPs = NoExtField
 type instance XSpliceTy        GhcRn = HsUntypedSpliceResult (LHsType GhcRn)
 type instance XSpliceTy        GhcTc = Kind
 
-type instance XDocTy           (GhcPass _) = [AddEpAnn]
-type instance XBangTy          (GhcPass _) = ([AddEpAnn], SourceText)
+type instance XDocTy           (GhcPass _) = NoExtField
+type instance XBangTy          (GhcPass _) = ((EpaLocation, EpaLocation, EpaLocation), SourceText)
 
 type instance XRecTy           GhcPs = AnnList
 type instance XRecTy           GhcRn = NoExtField
 type instance XRecTy           GhcTc = NoExtField
 
-type instance XExplicitListTy  GhcPs = [AddEpAnn]
+type instance XExplicitListTy  GhcPs = (EpToken "'", EpToken "[", EpToken "]")
 type instance XExplicitListTy  GhcRn = NoExtField
 type instance XExplicitListTy  GhcTc = Kind
 
-type instance XExplicitTupleTy GhcPs = [AddEpAnn]
+type instance XExplicitTupleTy GhcPs = (EpToken "'", EpToken "(", EpToken ")")
 type instance XExplicitTupleTy GhcRn = NoExtField
 type instance XExplicitTupleTy GhcTc = [Kind]
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1292,8 +1292,9 @@ topdecl :: { LHsDecl GhcPs }
 --
 cl_decl :: { LTyClDecl GhcPs }
         : 'class' tycl_hdr fds where_cls
-                {% (mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4))
-                        (mj AnnClass $1:(fst $ unLoc $3)++(fstOf3 $ unLoc $4)) }
+                {% do { let {(wtok, (oc,semis,cc)) = fstOf3 $ unLoc $4}
+                      ; mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4)
+                        (AnnClassDecl (epTok $1) [] [] (fst $ unLoc $3) wtok oc cc semis) }}
 
 -- Default declarations (toplevel)
 --
@@ -1314,7 +1315,7 @@ ty_decl :: { LTyClDecl GhcPs }
                 --
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkTySynonym (comb2 $1 $4) $2 $4 [mj AnnType $1,mj AnnEqual $3] }
+                {% mkTySynonym (comb2 $1 $4) $2 $4 (epTok $1) (epTok $3) }
 
            -- type family declarations
         | 'type' 'family' type opt_tyfam_kind_sig opt_injective_info
@@ -1749,9 +1750,9 @@ decl_cls  : at_decl_cls                 { $1 }
                                       quotes (ppr $2)
                           ; amsA' (sLL $1 $> $ SigD noExtField $ ClassOpSig (AnnSig (epUniTok $3) Nothing (Just (epTok $1))) True [v] $4) }}
 
-decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
+decls_cls :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }  -- Reversed
           : decls_cls ';' decl_cls      {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unitOL $3))
                                             else case (snd $ unLoc $1) of
                                               SnocOL hs t -> do
@@ -1759,7 +1760,7 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
                                                  return (sLL $1 $> (fst $ unLoc $1
                                                                 , snocOL hs t' `appOL` unitOL $3)) }
           | decls_cls ';'               {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1770,24 +1771,24 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
           | {- empty -}                 { noLoc ([],nilOL) }
 
 decllist_cls
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", [EpToken ";"], EpToken "}")
                      , OrdList (LHsDecl GhcPs)
                      , EpLayout) }      -- Reversed
-        : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
+        : '{'         decls_cls '}'     { sLL $1 $> ((epTok $1, fst $ unLoc $2, epTok $3)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
         |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
-                                           in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
+                                           in L l ((NoEpTok, anns, NoEpTok), decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
 --
-where_cls :: { Located ([AddEpAnn]
+where_cls :: { Located ((EpToken "where", (EpToken "{", [EpToken ";"], EpToken "}"))
                        ,(OrdList (LHsDecl GhcPs))    -- Reversed
                        ,EpLayout) }
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_cls          { sLL $1 $> (mj AnnWhere $1:(fstOf3 $ unLoc $2)
+        : 'where' decllist_cls          { sLL $1 $> ((epTok $1,fstOf3 $ unLoc $2)
                                              ,sndOf3 $ unLoc $2,thdOf3 $ unLoc $2) }
-        | {- empty -}                   { noLoc ([],nilOL,EpNoLayout) }
+        | {- empty -}                   { noLoc ((noAnn, noAnn),nilOL,EpNoLayout) }
 
 -- Declarations in instance bodies
 --
@@ -2177,8 +2178,8 @@ sigtypes1 :: { OrdList (LHsSigType GhcPs) }
 -- Types
 
 unpackedness :: { Located UnpackednessPragma }
-        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getUNPACK_PRAGs $1) SrcUnpack) }
-        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
+        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getUNPACK_PRAGs $1) SrcUnpack) }
+        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
 
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
@@ -2304,8 +2305,8 @@ atype :: { LHsType GhcPs }
                                                ; return $ sL1a $1 (HsStarTy noExtField (isUnicode $1)) } }
 
         -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer
-        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnTilde $1] SrcLazy $2)) }
-        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnBang $1] SrcStrict $2)) }
+        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcLazy $2)) }
+        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcStrict $2)) }
 
         | '{' fielddecls '}'             {% do { decls <- amsA' (sLL $1 $> $ HsRecTy (AnnList (listAsAnchorM $2) (Just $ moc $1) (Just $ mcc $3) [] []) $2)
                                                ; checkRecordSyntax decls }}
@@ -2325,17 +2326,17 @@ atype :: { LHsType GhcPs }
         | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $3] []) }}
+                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
         | SIMPLEQUOTE gen_qcon {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
         | SIMPLEQUOTE sysdcon_nolist {% do { requireLTPuns PEP_QuoteDisambiguation $1 (reLoc $>)
                                            ; amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted (L (getLoc $2) $ nameRdrName (dataConName (unLoc $2)))) }}
         | SIMPLEQUOTE  '(' ktype ',' comma_types1 ')'
                              {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                    ; h <- addTrailingCommaA $3 (gl $4)
-                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $6] (h : $5)) }}
+                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $6) (h : $5)) }}
         | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (glR $1) (glR $2)) }
         | SIMPLEQUOTE  '[' comma_types0 ']'     {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy [mj AnnSimpleQuote $1,mos $2,mcs $4] IsPromoted $3) }}
+                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy (epTok $1, epTok $2, epTok $4) IsPromoted $3) }}
         | SIMPLEQUOTE var                       {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
 
         | quasiquote                  { mapLocA (HsSpliceTy noExtField) $1 }
@@ -2346,7 +2347,7 @@ atype :: { LHsType GhcPs }
         -- (One means a list type, zero means the list type constructor,
         -- so you have to quote those.)
         | '[' ktype ',' comma_types1 ']'  {% do { h <- addTrailingCommaA $2 (gl $3)
-                                                ; amsA' (sLL $1 $> $ HsExplicitListTy [mos $1,mcs $5] NotPromoted (h:$4)) }}
+                                                ; amsA' (sLL $1 $> $ HsExplicitListTy (NoEpTok,epTok $1,epTok $5) NotPromoted (h:$4)) }}
         | INTEGER              { sLLa $1 $> $ HsTyLit noExtField $ HsNumTy (getINTEGERs $1)
                                                            (il_value (getINTEGER $1)) }
         | CHAR                 { sLLa $1 $> $ HsTyLit noExtField $ HsCharTy (getCHARs $1)
@@ -2420,10 +2421,9 @@ tyvar_wc :: { Located (HsBndrVar GhcPs) }
         : tyvar                         { sL1 $1 (HsBndrVar noExtField $1) }
         | '_'                           { sL1 $1 (HsBndrWildCard noExtField) }
 
-fds :: { Located ([AddEpAnn],[LHsFunDep GhcPs]) }
-        : {- empty -}                   { noLoc ([],[]) }
-        | '|' fds1                      { (sLL $1 $> ([mj AnnVbar $1]
-                                                 ,reverse (unLoc $2))) }
+fds :: { Located (EpToken "|",[LHsFunDep GhcPs]) }
+        : {- empty -}                   { noLoc (NoEpTok,[]) }
+        | '|' fds1                      { (sLL $1 $> (epTok $1 ,reverse (unLoc $2))) }
 
 fds1 :: { Located [LHsFunDep GhcPs] }
         : fds1 ',' fd   {%
@@ -3138,26 +3138,26 @@ aexp2   :: { ECP }
         | splice_untyped { ECP $ mkHsSplicePV $1 }
         | splice_typed   { ecpFromExp $ fmap (uncurry HsTypedSplice) (reLoc $1) }
 
-        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
-        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
+        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
+        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
         -- See Note [%shift: aexp2 -> TH_TY_QUOTE]
         | TH_TY_QUOTE %shift    {% reportEmptyDoubleQuotes (getLoc $1) }
         | '[|' exp '|]'       {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3]
-                                                                                         else [mu AnnOpenEQ $1,mu AnnCloseQ $3]) (ExpBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (ExpBr (if (hasE $1) then (BracketHasE (epTok $1),   epUniTok $3)
+                                                                                                     else (BracketNoE (epUniTok $1), epUniTok $3)) $2)) }
         | '[||' exp '||]'     {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) $2) }
+                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then (BracketHasE (epTok $1),epTok $3) else (BracketNoE (epTok $1),epTok $3)) $2) }
         | '[t|' ktype '|]'    {% fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (TypBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (TypBr (epTok $1,epUniTok $3) $2)) }
         | '[p|' infixexp '|]' {% (checkPattern <=< runPV) (unECP $2) >>= \p ->
                                       fmap ecpFromExp $
-                                      amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (PatBr noExtField p)) }
+                                      amsA' (sLL $1 $> $ HsUntypedBracket noExtField (PatBr (epTok $1,epUniTok $3) p)) }
         | '[d|' cvtopbody '|]' {% fmap ecpFromExp $
-                                  amsA' (sLL $1 $> $ HsUntypedBracket (mo $1:mu AnnCloseQ $3:fst $2) (DecBrL noExtField (snd $2))) }
+                                  amsA' (sLL $1 $> $ HsUntypedBracket noExtField (DecBrL (epTok $1,epUniTok $3, fst $2) (snd $2))) }
         | quasiquote          { ECP $ mkHsSplicePV $1 }
 
         -- arrow notation extension
@@ -3197,10 +3197,9 @@ acmd    :: { LHsCmdTop GhcPs }
                                    runPV (checkCmdBlockArguments cmd) >>= \ _ ->
                                    return (sL1a cmd $ HsCmdTop noExtField cmd) }
 
-cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
-        :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
-                                                  ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+cvtopbody :: { ((EpToken "{", EpToken "}"),[LHsDecl GhcPs]) }
+        :  '{'            cvtopdecls0 '}'      { ((epTok $1 ,epTok $3),$2) }
+        |      vocurly    cvtopdecls0 close    { ((NoEpTok, NoEpTok),$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -4641,6 +4640,10 @@ epUniTok t@(L !l _) = EpUniTok (EpaSpan l) u
   where
     u = if isUnicode t then UnicodeSyntax else NormalSyntax
 
+-- |Construct an EpToken from the location of the token, provided the span is not zero width
+mzEpTok :: Located Token -> EpToken tok
+mzEpTok !l = if isZeroWidthSpan (gl l) then NoEpTok else (epTok l)
+
 epExplicitBraces :: Located Token -> Located Token -> EpLayout
 epExplicitBraces !t1 !t2 = EpExplicitBraces (epTok t1) (epTok t2)
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -10,7 +10,7 @@ module GHC.Parser.Annotation (
   -- * Core Exact Print Annotation types
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
-  getEpTokenSrcSpan, getEpTokenLocs,
+  getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
   TokDcolon,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
@@ -406,6 +406,10 @@ getEpTokenLocs ls = concatMap go ls
     go NoEpTok   = []
     go (EpTok l) = [l]
 
+getEpTokenLoc :: EpToken tok -> EpaLocation
+getEpTokenLoc NoEpTok   = noAnn
+getEpTokenLoc (EpTok l) = l
+
 type TokDcolon = EpUniToken "::" "∷"
 
 -- | Layout information for declarations.


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -71,7 +71,7 @@ module GHC.Parser.Lexer (
    xtest, xunset, xset,
    disableHaddock,
    lexTokenStream,
-   mkParensEpAnn,
+   mkParensEpToks,
    mkParensLocs,
    getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
    getEofPos,
@@ -3628,13 +3628,14 @@ warn_unknown_prag prags span buf len buf2 = do
 %************************************************************************
 -}
 
+-- TODO:AZ: we should have only mkParensEpToks. Delee mkParensEpAnn, mkParensLocs
 
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'AddEpAnn' values for the opening and closing bordering on the start
 -- and end of the span
-mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
-mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
-                    AddEpAnn AnnCloseP (EpaSpan (RealSrcSpan lc Strict.Nothing)))
+mkParensEpToks :: RealSrcSpan -> (EpToken "(", EpToken ")")
+mkParensEpToks ss = (EpTok (EpaSpan (RealSrcSpan lo Strict.Nothing)),
+                    EpTok (EpaSpan (RealSrcSpan lc Strict.Nothing)))
   where
     f = srcSpanFile ss
     sl = srcSpanStartLine ss
@@ -3644,6 +3645,7 @@ mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
     lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
     lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
 
+
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'EpaLocation' values for the opening and closing bordering on the start
 -- and end of the span


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -161,7 +161,7 @@ import GHC.Utils.Error
 import GHC.Utils.Misc
 import GHC.Utils.Monad (unlessM)
 import Data.Either
-import Data.List        ( findIndex, partition )
+import Data.List        ( findIndex )
 import Data.Foldable
 import qualified Data.Semigroup as Semi
 import GHC.Unit.Module.Warnings
@@ -204,14 +204,14 @@ mkClassDecl :: SrcSpan
             -> Located (a,[LHsFunDep GhcPs])
             -> OrdList (LHsDecl GhcPs)
             -> EpLayout
-            -> [AddEpAnn]
+            -> AnnClassDecl
             -> P (LTyClDecl GhcPs)
 
 mkClassDecl loc' (L _ (mcxt, tycl_hdr)) fds where_cls layout annsIn
   = do { (binds, sigs, ats, at_defs, _, docs) <- cvBindsAndSigs where_cls
-       ; (cls, tparams, fixity, ann, cs) <- checkTyClHdr True tycl_hdr
+       ; (cls, tparams, fixity, ops, cps, cs) <- checkTyClHdr True tycl_hdr
        ; tyvars <- checkTyVars (text "class") whereDots cls tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn { acd_openp = ops, acd_closep = cps}
        ; let loc = EpAnn (spanAsAnchor loc') noAnn cs
        ; return (L loc (ClassDecl { tcdCExt = (anns', layout, NoAnnSortKey)
                                   , tcdCtxt = mcxt
@@ -235,9 +235,10 @@ mkTyData :: SrcSpan
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; !cs' <- getCommentsFor loc'
@@ -247,6 +248,15 @@ mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
+-- TODO:AZ:temporary
+openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
+openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
+openParen2AddEpAnn NoEpTok = []
+
+closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
+closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
+closeParen2AddEpAnn NoEpTok = []
+
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
@@ -265,14 +275,15 @@ mkDataDefn cType mcxt ksig data_cons maybe_deriv
 mkTySynonym :: SrcSpan
             -> LHsType GhcPs  -- LHS
             -> LHsType GhcPs  -- RHS
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "="
             -> P (LTyClDecl GhcPs)
-mkTySynonym loc lhs rhs annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+mkTySynonym loc lhs rhs antype aneq
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (text "type") equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns = AnnSynDecl ops cps antype aneq
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; return (L loc' (SynDecl { tcdSExt = anns'
+       ; return (L loc' (SynDecl { tcdSExt = anns
                                  , tcdLName = tc, tcdTyVars = tyvars
                                  , tcdFixity = fixity
                                  , tcdRhs = rhs })) }
@@ -308,10 +319,12 @@ mkTyFamInstEqn :: SrcSpan
                -> [AddEpAnn]
                -> P (LTyFamInstEqn GhcPs)
 mkTyFamInstEqn loc bndrs lhs rhs anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns `mappend` ann
+                        { feqn_ext    = anns'
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -330,32 +343,20 @@ mkDataFamInst :: SrcSpan
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = ann Semi.<> anns
+                  (FamEqn { feqn_ext    = anns'
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
                           , feqn_fixity = fixity
                           , feqn_rhs    = defn })))) }
 
--- mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
---               ksig data_cons (L _ maybe_deriv) anns
---   = do { (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr
---        ; cs <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan
---        ; let anns' = addAnns (EpAnn (spanAsAnchor loc) ann cs) anns emptyComments
---        ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv
---        ; return (L (noAnnSrcSpan loc) (DataFamInstD anns' (DataFamInstDecl
---                   (FamEqn { feqn_ext    = anns'
---                           , feqn_tycon  = tc
---                           , feqn_bndrs  = bndrs
---                           , feqn_pats   = tparams
---                           , feqn_fixity = fixity
---                           , feqn_rhs    = defn })))) }
-
 
 
 mkTyFamInst :: SrcSpan
@@ -375,11 +376,13 @@ mkFamDecl :: SrcSpan
           -> [AddEpAnn]
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (FamDecl noExtField (FamilyDecl
-                                           { fdExt       = annsIn Semi.<> ann
+                                           { fdExt       = anns'
                                            , fdTopLevel  = topLevel
                                            , fdInfo      = info, fdLName = tc
                                            , fdTyVars    = tyvars
@@ -738,8 +741,7 @@ mkPatSynMatchGroup (L loc patsyn_name) (L ld decls) =
         do { unless (name == patsyn_name) $
                wrongNameBindingErr (locA loc) decl
            -- conAnn should only be AnnOpenP, AnnCloseP, so the rest should be empty
-           ; let (ann_fun, rest) = mk_ann_funrhs []
-           ; unless (null rest) $ return $ panic "mkPatSynMatchGroup: unexpected anns"
+           ; let ann_fun = mk_ann_funrhs [] []
            ; match <- case details of
                PrefixCon _ pats -> return $ Match { m_ext = noExtField
                                                   , m_ctxt = ctxt, m_pats = L l pats
@@ -1063,8 +1065,8 @@ checkTyClHdr :: Bool               -- True  <=> class header
              -> P (LocatedN RdrName,     -- the head symbol (type or class name)
                    [LHsTypeArg GhcPs],   -- parameters of head symbol
                    LexicalFixity,        -- the declaration is in infix format
-                   [AddEpAnn],           -- API Annotation for HsParTy
-                                         -- when stripping parens
+                   [EpToken "("],        -- API Annotation for HsParTy
+                   [EpToken ")"],        -- when stripping parens
                    EpAnnComments)        -- Accumulated comments from re-arranging
 -- Well-formedness check and decomposition of type and class heads.
 -- Decomposes   T ty1 .. tyn   into    (T, [ty1, ..., tyn])
@@ -1081,22 +1083,22 @@ checkTyClHdr is_cls ty
            ; let name = mkOccNameFS tcClsName (starSym isUni)
            ; let a' = newAnns ll l an
            ; return (L a' (Unqual name), acc, fix
-                    , (reverse ops') ++ cps', cs) }
+                    , (reverse ops'), cps', cs) }
 
     go cs l (HsTyVar _ _ ltc@(L _ tc)) acc ops cps fix
-      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops), cps, cs Semi.<> comments l)
     go cs l (HsOpTy _ _ t1 ltc@(L _ tc) t2) acc ops cps _fix
-      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
     go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
       where
-        (o,c) = mkParensEpAnn (realSrcSpan (locA l))
+        (o,c) = mkParensEpToks (realSrcSpan (locA l))
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
       = return (L (l2l l) (nameRdrName tup_name)
-               , map (HsValArg noExtField) ts, fix, (reverse ops)++cps, cs Semi.<> comments l)
+               , map (HsValArg noExtField) ts, fix, (reverse ops), cps, cs Semi.<> comments l)
       where
         arity = length ts
         tup_name | is_cls    = cTupleTyConName arity
@@ -1170,15 +1172,16 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
   -- With NoListTuplePuns, contexts are parsed as data constructors, which causes failure
   -- downstream.
   -- This converts them just like when they are parsed as types in the punned case.
-  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy anns ts))
+  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy (q,o,c) ts))
     = punsAllowed >>= \case
       True -> unprocessed
       False -> do
         let
-          (op, cp) = case anns of
-            [o, c] -> ([o], [c])
-            [q, _, c] -> ([q], [c])
-            _ -> ([], [])
+          ol = AddEpAnn AnnOpenP (getEpTokenLoc o)
+          cl = AddEpAnn AnnCloseP (getEpTokenLoc c)
+          (op, cp) = case q of
+            EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
+            _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
   check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
                                   -- to be sure HsParTy doesn't get into the way
@@ -1331,12 +1334,12 @@ checkAPat loc e0 = do
      addError $ mkPlainErrorMsgEnvelope (getLocA op) PsErrAtInPatPos
      return (WildPat noExtField)
 
-   PatBuilderOpApp l (L cl c) r anns
+   PatBuilderOpApp l (L cl c) r (_os,_cs)
      | isRdrDataCon c || isRdrTc c -> do
          l <- checkLPat l
          r <- checkLPat r
          return $ ConPat
-           { pat_con_ext = mk_ann_conpat anns
+           { pat_con_ext = noAnn
            , pat_con = L cl c
            , pat_args = InfixCon l r
            }
@@ -1389,9 +1392,8 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
   = do  { mb_fun <- isFunLhs lhs
         ; case mb_fun of
-            Just (fun, is_infix, pats, ann) -> do
-              let (ann_fun, ann_rest) = mk_ann_funrhs ann
-              unless (null ann_rest) $ panic "checkValDef: unexpected anns"
+            Just (fun, is_infix, pats, ops, cps) -> do
+              let ann_fun = mk_ann_funrhs ops cps
               let l = listLocation pats
               checkFunBind loc ann_fun
                            fun is_infix (L l pats) grhss
@@ -1404,29 +1406,8 @@ checkValDef loc lhs (mult_ann, Nothing) ghrss
   = do lhs' <- checkPattern lhs
        checkPatBind loc lhs' ghrss mult_ann
 
-mk_ann_funrhs :: [AddEpAnn] -> (AnnFunRhs, [AddEpAnn])
-mk_ann_funrhs ann = (AnnFunRhs strict (map to_tok opens) (map to_tok closes), rest)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenP) ann
-    (closes, ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseP) ra0
-    (bangs, rest) = partition (\(AddEpAnn kw _) -> kw == AnnBang) ra1
-    strict = case bangs of
-               (AddEpAnn _ s:_) -> EpTok s
-               _ -> NoEpTok
-    to_tok (AddEpAnn _ s) = EpTok s
-
-mk_ann_conpat :: [AddEpAnn] -> (Maybe (EpToken "{"), Maybe (EpToken "}"))
-mk_ann_conpat ann = (open, close)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenC) ann
-    (closes, _ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseC) ra0
-    open = case opens of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    close = case closes of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    to_tok (AddEpAnn _ s) = EpTok s
+mk_ann_funrhs :: [EpToken "("] -> [EpToken ")"] -> AnnFunRhs
+mk_ann_funrhs ops cps = AnnFunRhs NoEpTok ops cps
 
 checkFunBind :: SrcSpan
              -> AnnFunRhs
@@ -1468,10 +1449,10 @@ checkPatBind :: SrcSpan
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat an (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m ans v)]))
+                [L (noAnnSrcSpan loc) (m an v)]))
   where
     m a v = Match { m_ext = noExtField
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1517,7 +1498,7 @@ checkDoAndIfThenElse err guardExpr semiThen thenExpr semiElse elseExpr
 
 isFunLhs :: LocatedA (PatBuilder GhcPs)
       -> P (Maybe (LocatedN RdrName, LexicalFixity,
-                   [LocatedA (ArgPatBuilder GhcPs)],[AddEpAnn]))
+                   [LocatedA (ArgPatBuilder GhcPs)],[EpToken "("],[EpToken ")"]))
 -- A variable binding is parsed as a FunBind.
 -- Just (fun, is_infix, arg_pats) if e is a function LHS
 isFunLhs e = go e [] [] []
@@ -1527,7 +1508,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderVar (L loc f))) es ops cps
        | not (isRdrDataCon f)        = do
            let (_l, loc') = transferCommentsOnlyA l loc
-           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+           return (Just (L loc' f, Prefix, es, (reverse ops), cps))
    go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
      let (_l, lf') = transferCommentsOnlyA l lf
      go (L lf' f) (mk e:es) ops cps
@@ -1537,21 +1518,21 @@ isFunLhs e = go e [] [] []
       -- of funlhs.
      where
        (_l, le') = transferCommentsOnlyA l le
-       (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
+       (o,c) = mkParensEpToks (realSrcSpan $ locA l)
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r (os,cs))) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
-           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (os ++ reverse ops), (cs ++ cps))) }
       | otherwise                     -- Infix data con; keep going
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
            ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
-          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
-            = Just (op', Infix, j : op_app : es', anns')
+          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', ops', cps')
+            = Just (op', Infix, j : op_app : es', ops', cps')
             where
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
-                                    (L loc' op) r (reverse ops ++ cps))
+                                    (L loc' op) r (reverse ops, cps))
           reassociate _other = Nothing
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
@@ -1570,13 +1551,13 @@ instance Outputable (ArgPatBuilder GhcPs) where
   ppr (ArgPatBuilderVisPat p) = ppr p
   ppr (ArgPatBuilderArgPat p) = ppr p
 
-mkBangTy :: [AddEpAnn] -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
-mkBangTy anns strictness =
-  HsBangTy (anns, NoSourceText) (HsBang NoSrcUnpack strictness)
+mkBangTy :: EpaLocation -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
+mkBangTy tok_loc strictness =
+  HsBangTy ((noAnn, noAnn, tok_loc), NoSourceText) (HsBang NoSrcUnpack strictness)
 
 -- | Result of parsing @{-\# UNPACK \#-}@ or @{-\# NOUNPACK \#-}@.
 data UnpackednessPragma =
-  UnpackednessPragma [AddEpAnn] SourceText SrcUnpackedness
+  UnpackednessPragma (EpaLocation, EpaLocation) SourceText SrcUnpackedness
 
 -- | Annotate a type with either an @{-\# UNPACK \#-}@ or a @{-\# NOUNPACK \#-}@ pragma.
 addUnpackednessP :: MonadP m => Located UnpackednessPragma -> LHsType GhcPs -> m (LHsType GhcPs)
@@ -1589,11 +1570,11 @@ addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do
     -- such as ~T or !T, then add the pragma to the existing HsBangTy.
     --
     -- Otherwise, wrap the type in a new HsBangTy constructor.
-    addUnpackedness an (L _ (HsBangTy (anns, NoSourceText) bang t))
+    addUnpackedness (o,c) (L _ (HsBangTy ((_,_,tl), NoSourceText) bang t))
       | HsBang NoSrcUnpack strictness <- bang
-      = HsBangTy (an Semi.<> anns, prag) (HsBang unpk strictness) t
-    addUnpackedness an t
-      = HsBangTy (an, prag) (HsBang unpk NoSrcStrict) t
+      = HsBangTy ((o,c,tl), prag) (HsBang unpk strictness) t
+    addUnpackedness (o,c) t
+      = HsBangTy ((o,c,noAnn), prag) (HsBang unpk NoSrcStrict) t
 
 ---------------------------------------------------------------------------
 -- | Check for monad comprehensions
@@ -2051,7 +2032,7 @@ instance DisambECP (PatBuilder GhcPs) where
   superInfixOp m = m
   mkHsOpAppPV l p1 op p2 = do
     !cs <- getCommentsFor l
-    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 []
+    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 ([],[])
 
   mkHsLamPV l lam_variant _ _     = addFatalError $ mkPlainErrorMsgEnvelope l (PsErrLambdaInPat lam_variant)
 
@@ -3658,7 +3639,7 @@ mkTupleSyntaxTy parOpen args parClose =
       HsExplicitTupleTy annsKeyword args
 
     annParen = AnnParen AnnParens parOpen parClose
-    annsKeyword = [AddEpAnn AnnOpenP parOpen, AddEpAnn AnnCloseP parClose]
+    annsKeyword = (NoEpTok, EpTok parOpen, EpTok parClose)
 
 -- | Decide whether to parse tuple con syntax @(,)@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
@@ -3690,7 +3671,7 @@ mkListSyntaxTy0 brkOpen brkClose span =
       HsExplicitListTy annsKeyword NotPromoted []
 
     rdrNameAnn = NameAnnOnly NameSquare brkOpen brkClose []
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     fullLoc = EpaSpan span
 
 -- | Decide whether to parse list type syntax @[Int]@ in a type as a
@@ -3709,5 +3690,5 @@ mkListSyntaxTy1 brkOpen t brkClose =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted [t]
 
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     annParen = AnnParen AnnParensSquare brkOpen brkClose


=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1460,7 +1460,7 @@ instance Monoid ColumnBound where
 
 mkLHsDocTy :: LHsType GhcPs -> Maybe (Located HsDocString) -> LHsType GhcPs
 mkLHsDocTy t Nothing = t
-mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noAnn t $ lexLHsDocString doc)
+mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noExtField t $ lexLHsDocString doc)
 
 getForAllTeleLoc :: HsForAllTelescope GhcPs -> SrcSpan
 getForAllTeleLoc tele =


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -57,7 +57,7 @@ data PatBuilder p
   | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p))
   | PatBuilderAppType (LocatedA (PatBuilder p)) (EpToken "@") (HsTyPat GhcPs)
   | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName)
-                    (LocatedA (PatBuilder p)) [AddEpAnn]
+                    (LocatedA (PatBuilder p)) ([EpToken "("], [EpToken ")"])
   | PatBuilderVar (LocatedN RdrName)
   | PatBuilderOverLit (HsOverLit GhcPs)
 


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -181,7 +181,7 @@ rnUntypedBracket e br_body
        }
 
 rn_utbracket :: ThStage -> HsQuote GhcPs -> RnM (HsQuote GhcRn, FreeVars)
-rn_utbracket outer_stage br@(VarBr x flg rdr_name)
+rn_utbracket outer_stage br@(VarBr _ flg rdr_name)
   = do { name <- lookupOccRn (unLoc rdr_name)
        ; check_namespace flg name
        ; this_mod <- getModule
@@ -204,18 +204,18 @@ rn_utbracket outer_stage br@(VarBr x flg rdr_name)
                                       TcRnTHError $ THNameError $ QuotedNameWrongStage br }
                         }
                     }
-       ; return (VarBr x flg (noLocA name), unitFV name) }
+       ; return (VarBr noExtField flg (noLocA name), unitFV name) }
 
-rn_utbracket _ (ExpBr x e) = do { (e', fvs) <- rnLExpr e
-                                ; return (ExpBr x e', fvs) }
+rn_utbracket _ (ExpBr _ e) = do { (e', fvs) <- rnLExpr e
+                                ; return (ExpBr noExtField e', fvs) }
 
-rn_utbracket _ (PatBr x p)
-  = rnPat ThPatQuote p $ \ p' -> return (PatBr x p', emptyFVs)
+rn_utbracket _ (PatBr _ p)
+  = rnPat ThPatQuote p $ \ p' -> return (PatBr noExtField p', emptyFVs)
 
-rn_utbracket _ (TypBr x t) = do { (t', fvs) <- rnLHsType TypBrCtx t
-                                ; return (TypBr x t', fvs) }
+rn_utbracket _ (TypBr _ t) = do { (t', fvs) <- rnLHsType TypBrCtx t
+                                ; return (TypBr noExtField t', fvs) }
 
-rn_utbracket _ (DecBrL x decls)
+rn_utbracket _ (DecBrL _ decls)
   = do { group <- groupDecls decls
        ; gbl_env  <- getGblEnv
        ; let new_gbl_env = gbl_env { tcg_dus = emptyDUs }
@@ -227,7 +227,7 @@ rn_utbracket _ (DecBrL x decls)
               -- Discard the tcg_env; it contains only extra info about fixity
         ; traceRn "rn_utbracket dec" (ppr (tcg_dus tcg_env) $$
                    ppr (duUses (tcg_dus tcg_env)))
-        ; return (DecBrG x group', duUses (tcg_dus tcg_env)) }
+        ; return (DecBrG noExtField group', duUses (tcg_dus tcg_env)) }
   where
     groupDecls :: [LHsDecl GhcPs] -> RnM (HsGroup GhcPs)
     groupDecls decls


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1655,7 +1655,7 @@ gen_Lift_binds loc (DerivInstTys{ dit_rep_tc = tycon
     liftTyped_bind = mkFunBindEC 1 loc liftTyped_RDR (nlHsApp unsafeCodeCoerce_Expr . nlHsApp pure_Expr)
                                  (map (pats_etc mk_typed_bracket mk_tsplice liftTypedName) data_cons)
 
-    mk_untyped_bracket = HsUntypedBracket noAnn . ExpBr noExtField
+    mk_untyped_bracket = HsUntypedBracket noExtField . ExpBr noAnn
     mk_typed_bracket = HsTypedBracket noAnn
 
     mk_tsplice = HsTypedSplice noAnn


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -319,7 +319,7 @@ cvtDec (ClassD ctxt cl tvs fds decs)
                     , tcdFDs = fds', tcdSigs = Hs.mkClassOpSigs sigs'
                     , tcdMeths = binds'
                     , tcdATs = fams', tcdATDefs = at_defs', tcdDocs = [] }
-                              -- no docs in TH ^^
+                                                     -- no docs in TH ^^
         }
 
 cvtDec (InstanceD o ctxt ty decs)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -48,8 +48,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:5:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:5:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:5:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:5:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -170,7 +179,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T17544.hs:6:14-16 })
@@ -217,8 +226,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:9:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:9:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -384,8 +402,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:13:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:13:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:13:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:13:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -554,8 +581,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:17:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:17:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:17:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:17:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -788,10 +824,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:22:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:22:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:22:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:22:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:22:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:22:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:22:18 }))
+        (EpTok (EpaSpan { T17544.hs:22:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:22:18 }))
         (EpTok (EpaSpan { T17544.hs:22:30 })))
@@ -1129,10 +1172,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:28:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:28:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:28:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:28:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:28:18 }))
+        (EpTok (EpaSpan { T17544.hs:28:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:28:18 }))
         (EpTok (EpaSpan { T17544.hs:28:30 })))
@@ -1470,10 +1520,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:34:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:34:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:34:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:34:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:34:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:34:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:34:18 }))
+        (EpTok (EpaSpan { T17544.hs:34:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:34:18 }))
         (EpTok (EpaSpan { T17544.hs:34:30 })))
@@ -1811,10 +1868,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:40:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:40:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:40:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:40:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:40:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:40:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:40:18 }))
+        (EpTok (EpaSpan { T17544.hs:40:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:40:18 }))
         (EpTok (EpaSpan { T17544.hs:40:30 })))
@@ -2152,10 +2216,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:46:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:46:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:46:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:46:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:46:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:46:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:46:18 }))
+        (EpTok (EpaSpan { T17544.hs:46:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:46:18 }))
         (EpTok (EpaSpan { T17544.hs:46:30 })))
@@ -2493,10 +2564,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:52:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:52:13-17 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:52:19 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:52:32 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:52:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:52:13-17 }))
+        (EpTok (EpaSpan { T17544.hs:52:19 }))
+        (EpTok (EpaSpan { T17544.hs:52:32 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:52:19 }))
         (EpTok (EpaSpan { T17544.hs:52:32 })))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -281,8 +281,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544_kw.hs:21:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:23:3-7 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544_kw.hs:21:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:23:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (5))
        (NoAnnSortKey))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -458,7 +458,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:15:3-5 })
@@ -503,7 +503,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:17:3-6 })
@@ -616,7 +616,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:21:3-5 })
@@ -661,7 +661,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:25:3-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -501,9 +501,13 @@
                 (EpaComments
                  []))
                (HsExplicitListTy
-                [(AddEpAnn AnnSimpleQuote (EpaSpan { DumpParsedAst.hs:12:10 }))
-                ,(AddEpAnn AnnOpenS (EpaSpan { DumpParsedAst.hs:12:11 }))
-                ,(AddEpAnn AnnCloseS (EpaSpan { DumpParsedAst.hs:12:12 }))]
+                ((,,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:11 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:12 })))
                 (IsPromoted)
                 [])))]
             (Prefix)


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -1302,8 +1302,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { DumpSemis.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpSemis.hs:28:40-44 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:40-44 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -240,8 +240,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:15:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:15:6-8 })
@@ -452,8 +457,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:16:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:16:13 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:13 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:16:6-9 })
@@ -664,8 +674,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:19:10 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:10 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:19:6-8 })
@@ -1069,8 +1084,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:26:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:26:11 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:11 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:26:6-9 })
@@ -1092,9 +1112,13 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:26:13 }))
-        ,(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:26:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:26:29 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:13 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:29 })))
         (IsPromoted)
         [(L
           (EpAnn
@@ -1155,8 +1179,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:27:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:27:6-10 })
@@ -1178,8 +1207,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:27:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:27:45 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:45 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -1290,8 +1323,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:28:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:28:14 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:14 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:28:6-10 })
@@ -1340,9 +1378,13 @@
         (EpaComments
          []))
        (HsExplicitTupleTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:28:16 }))
-        ,(AddEpAnn AnnOpenP (EpaSpan { KindSigs.hs:28:17 }))
-        ,(AddEpAnn AnnCloseP (EpaSpan { KindSigs.hs:28:44 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:16 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:17 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:44 })))
         [(L
           (EpAnn
            (EpaSpan { KindSigs.hs:28:19-39 })
@@ -1363,8 +1405,12 @@
              (EpaComments
               []))
             (HsExplicitListTy
-             [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:28:19 }))
-             ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:28:29 }))]
+             ((,,)
+              (NoEpTok)
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:19 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:29 })))
              (NotPromoted)
              [(L
                (EpAnn
@@ -1465,8 +1511,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:31:19 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:19 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:31:6-17 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -262,10 +262,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:8:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:8:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:8:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:8:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:8:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:8:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:8:84 }))
+        (EpTok (EpaSpan { T20452.hs:8:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:8:84 }))
         (EpTok (EpaSpan { T20452.hs:8:85 })))
@@ -492,10 +499,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:9:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:9:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:9:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:9:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:9:84 }))
+        (EpTok (EpaSpan { T20452.hs:9:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:9:84 }))
         (EpTok (EpaSpan { T20452.hs:9:85 })))


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
=====================================
@@ -72,8 +72,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:5:6 })
@@ -101,8 +106,12 @@
              "-- comment inside A")
             { AnnotationNoListTuplePuns.hs:7:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -128,8 +137,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:12:6 })
@@ -157,8 +171,12 @@
              "-- comment inside B")
             { AnnotationNoListTuplePuns.hs:14:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -243,8 +261,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:6 })
@@ -266,8 +289,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -280,8 +307,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:6 })
@@ -303,8 +335,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 })))
         (NotPromoted)
         [(L
           (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -308,7 +308,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.hs:11:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.hs:11:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)
@@ -933,7 +942,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.ppr.hs:4:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.ppr.hs:4:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -837,21 +837,6 @@ markEpAnnLMS'' a l kw (Just str) = do
 
 -- -------------------------------------
 
-markEpAnnMS' :: (Monad m, Monoid w)
-  => [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m [AddEpAnn]
-markEpAnnMS' anns kw Nothing = mark anns kw
-markEpAnnMS' anns kw (Just str) = do
-  mapM go anns
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
--- -------------------------------------
-
 markEpAnnLMS' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
 markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
@@ -3286,51 +3271,53 @@ instance ExactPrint (HsExpr GhcPs) where
     return (ArithSeq (AnnArithSeq o' mc' dd' c') s seqInfo')
 
 
-  exact (HsTypedBracket an e) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[||")
-    an1 <- markEpAnnLMS'' an0 lidl AnnOpenE (Just "[e||")
+  exact (HsTypedBracket (o,c) e) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnLMS'' an1 lidl AnnClose (Just "||]")
-    return (HsTypedBracket an2 e')
+    c' <- markEpToken c
+    return (HsTypedBracket (o',c') e')
 
-  exact (HsUntypedBracket an (ExpBr a e)) = do
-    an0 <- markEpAnnL an  lidl AnnOpenEQ -- "[|"
-    an1 <- markEpAnnL an0 lidl AnnOpenE  -- "[e|" -- optional
+  exact (HsUntypedBracket a (ExpBr (o,c) e)) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpUniToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an2 (ExpBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (ExpBr (o',c') e'))
 
-  exact (HsUntypedBracket an (PatBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[p|")
+  exact (HsUntypedBracket a (PatBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (PatBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (PatBr (o',c') e'))
 
-  exact (HsUntypedBracket an (DecBrL a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[d|")
-    an1 <- markEpAnnL an0 lidl AnnOpenC
+  exact (HsUntypedBracket a (DecBrL (o,c, (oc,cc)) e)) = do
+    o' <- markEpToken o
+    oc' <- markEpToken oc
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseC
-    an3 <- markEpAnnL an2 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an3 (DecBrL a e'))
+    cc' <- markEpToken cc
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (DecBrL (o',c',(oc',cc')) e'))
 
-  exact (HsUntypedBracket an (TypBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[t|")
+  exact (HsUntypedBracket a (TypBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (TypBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (TypBr (o',c') e'))
 
-  exact (HsUntypedBracket an (VarBr a b e)) = do
+  exact (HsUntypedBracket a (VarBr an b e)) = do
     (an0, e') <- if b
       then do
-        an' <- markEpAnnL an lidl AnnSimpleQuote
+        an' <- printStringAtAA an "'"
         e' <- markAnnotated e
         return (an', e')
       else do
-        an' <- markEpAnnL an lidl AnnThTyQuote
+        an' <- printStringAtAA an "''"
         e' <- markAnnotated e
         return (an', e')
-    return (HsUntypedBracket an0 (VarBr a b e'))
+    return (HsUntypedBracket a (VarBr an0 b e'))
 
   exact (HsTypedSplice an s)   = do
     an0 <- markEpToken an
@@ -3768,24 +3755,24 @@ instance ExactPrint (TyClDecl GhcPs) where
     decl' <- markAnnotated decl
     return (FamDecl a decl')
 
-  exact (SynDecl { tcdSExt = an
+  exact (SynDecl { tcdSExt = AnnSynDecl ops cps t eq
                  , tcdLName = ltycon, tcdTyVars = tyvars, tcdFixity = fixity
                  , tcdRhs = rhs }) = do
     -- There may be arbitrary parens around parts of the constructor
     -- that are infix.  Turn these into comments so that they feed
     -- into the right place automatically
     -- TODO: no longer sorting on insert. What now?
-    an0 <- annotationsToComments an lidl [AnnOpenP,AnnCloseP]
-    an1 <- markEpAnnL an0 lidl AnnType
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
+    t' <- markEpToken t
 
     (_anx, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    an2 <- markEpAnnL an1 lidl AnnEqual
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (SynDecl { tcdSExt = an2
+    return (SynDecl { tcdSExt = AnnSynDecl [] [] t' eq'
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  -- TODO: add a workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/20452
   exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
     (_, an', ltycon', tyvars', _, defn') <-
@@ -3795,7 +3782,7 @@ instance ExactPrint (TyClDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ClassDecl {tcdCExt = (an, lo, sortKey),
+  exact (ClassDecl {tcdCExt = (AnnClassDecl c ops cps vb w oc cc semis, lo, sortKey),
                     tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars,
                     tcdFixity = fixity,
                     tcdFDs  = fds,
@@ -3805,10 +3792,10 @@ instance ExactPrint (TyClDecl GhcPs) where
       -- TODO: add a test that demonstrates tcdDocs
       | null sigs && null methods && null ats && null at_defs -- No "where" part
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnL an1 lidl AnnCloseC
-          return (ClassDecl {tcdCExt = (an2, lo, sortKey),
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          cc' <- markEpToken cc
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis, lo, sortKey),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3818,9 +3805,9 @@ instance ExactPrint (TyClDecl GhcPs) where
 
       | otherwise       -- Laid out
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL    an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lidl AnnSemi
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsSigTag, prepareListAnnotationA sigs),
                                 (ClsMethodTag, prepareListAnnotationA methods),
@@ -3828,13 +3815,13 @@ instance ExactPrint (TyClDecl GhcPs) where
                                 (ClsAtdTag, prepareListAnnotationA at_defs)
                              -- ++ prepareListAnnotation docs
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC
+          cc' <- markEpToken cc
           let
             sigs'    = undynamic ds
             methods' = undynamic ds
             ats'     = undynamic ds
             at_defs' = undynamic ds
-          return (ClassDecl {tcdCExt = (an3, lo, sortKey'),
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis', lo, sortKey'),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3843,17 +3830,18 @@ instance ExactPrint (TyClDecl GhcPs) where
                              tcdDocs = _docs})
       where
         top_matter = do
-          an' <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
-          an0 <- markEpAnnL an' lidl AnnClass
+          epTokensToComments AnnOpenP ops
+          epTokensToComments AnnCloseP cps
+          c' <- markEpToken c
           (_, lclas', tyvars',_,context') <-  exactVanillaDeclHead lclas tyvars fixity context
-          (an1, fds') <- if (null fds)
-            then return (an0, fds)
+          (vb', fds') <- if (null fds)
+            then return (vb, fds)
             else do
-              an1 <- markEpAnnL an0 lidl AnnVbar
+              vb' <- markEpToken vb
               fds' <- markAnnotated fds
-              return (an1, fds')
-          an2 <- markEpAnnL an1 lidl AnnWhere
-          return (an2, fds', lclas', tyvars',context')
+              return (vb', fds')
+          w' <- markEpToken w
+          return (c', w', vb', fds', lclas', tyvars',context')
 
 
 -- ---------------------------------------------------------------------
@@ -4202,37 +4190,36 @@ instance ExactPrint (HsType GhcPs) where
   exact (HsDocTy an ty doc) = do
     ty' <- markAnnotated ty
     return (HsDocTy an ty' doc)
-  exact (HsBangTy (an, mt) (HsBang up str) ty) = do
-    an0 <-
+  exact (HsBangTy ((o,c,tk), mt) (HsBang up str) ty) = do
+    (o',c') <-
       case mt of
-        NoSourceText -> return an
+        NoSourceText -> return (o,c)
         SourceText src -> do
           debugM $ "HsBangTy: src=" ++ showAst src
-          an0 <- markEpAnnMS' an AnnOpen  (Just $ unpackFS src)
-          an1 <- markEpAnnMS' an0 AnnClose (Just "#-}")
-          debugM $ "HsBangTy: done unpackedness"
-          return an1
-    an1 <-
+          o' <- printStringAtAA o (unpackFS src)
+          c' <- printStringAtAA c "#-}"
+          return (o',c')
+    tk' <-
       case str of
-        SrcLazy     -> mark an0 AnnTilde
-        SrcStrict   -> mark an0 AnnBang
-        NoSrcStrict -> return an0
+        SrcLazy     -> printStringAtAA tk "~"
+        SrcStrict   -> printStringAtAA tk "!"
+        NoSrcStrict -> return tk
     ty' <- markAnnotated ty
-    return (HsBangTy (an1, mt) (HsBang up str) ty')
-  exact (HsExplicitListTy an prom tys) = do
-    an0 <- if (isPromoted prom)
-             then mark an AnnSimpleQuote
-             else return an
-    an1 <- mark an0 AnnOpenS
+    return (HsBangTy ((o',c',tk'), mt) (HsBang up str) ty')
+  exact (HsExplicitListTy (sq,o,c) prom tys) = do
+    sq' <- if (isPromoted prom)
+             then markEpToken sq
+             else return sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseS
-    return (HsExplicitListTy an2 prom tys')
-  exact (HsExplicitTupleTy an tys) = do
-    an0 <- mark an AnnSimpleQuote
-    an1 <- mark an0 AnnOpenP
+    c' <- markEpToken c
+    return (HsExplicitListTy (sq',o',c') prom tys')
+  exact (HsExplicitTupleTy (sq, o, c) tys) = do
+    sq' <- markEpToken sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseP
-    return (HsExplicitTupleTy an2 tys')
+    c' <- markEpToken c
+    return (HsExplicitTupleTy (sq', o', c') tys')
   exact (HsTyLit a lit) = do
     case lit of
       (HsNumTy src v) -> printSourceText src (show v)


=====================================
utils/check-exact/Main.hs
=====================================
@@ -166,7 +166,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/T18052a.hs" Nothing
  -- "../../testsuite/tests/printer/T18247a.hs" Nothing
  -- "../../testsuite/tests/printer/Test10268.hs" Nothing
- "../../testsuite/tests/printer/Test10269.hs" Nothing
+ -- "../../testsuite/tests/printer/Test10269.hs" Nothing
  -- "../../testsuite/tests/printer/Test10276.hs" Nothing
  -- "../../testsuite/tests/printer/Test10278.hs" Nothing
  -- "../../testsuite/tests/printer/Test10312.hs" Nothing
@@ -209,6 +209,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
+ "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
  -- "../../testsuite/tests/printer/Test23465.hs" Nothing



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 22:28:58 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 14 Oct 2024 18:28:58 -0400
Subject: [Git][ghc/ghc][wip/T25266] Fix build
Message-ID: <670d9b2a22325_1d5aecb2e00811011b@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
6045cee9 by Simon Peyton Jones at 2024-10-14T23:28:43+01:00
Fix build

- - - - -


2 changed files:

- compiler/GHC/Tc/Solver.hs
- testsuite/tests/typecheck/should_compile/T13785.hs


Changes:

=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1469,55 +1469,19 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
                                          ++ tau_tys ++ post_mr_quant)
              co_var_tvs = closeOverKinds co_vars
 
-             -- outer_tvs are belong to some outer level,
+             -- outer_tvs belong to some outer level,
              -- so we definitely can't quantify over them
              outer_tvs = outerLevelTyVars tc_lvl $
                          tyCoVarsOfTypes can_quant `unionVarSet` tyCoVarsOfTypes no_quant
 
-             mono_tvs_ignoring_mr
+             mono_tvs_without_mr
                | isTopTcLevel tc_lvl = outer_tvs
                | otherwise           = outer_tvs
                                        `unionVarSet` tyCoVarsOfTypes no_quant
                                        `unionVarSet` co_var_tvs
 
-             mono_tvs_accounting_for_mr
-               = mono_tvs_ignoring_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
-
-{-
-             -- mono_tvs0 are all the type variables we can't quantify over
-             mono_tvs0
-               | isTopTcLevel tc_lvl
-                 -- At top level: we want to promote only tyvars that are
-                 --  (a) free in envt (outer_tvs)
-                 --  (b) will be defaulted (mr_no_quant)
-                 --  (c) determined by (a) or (b)
-                 -- mono_tvs0 deals with (a) or (b); closeWrtFunDeps deals with (c)
-               = outer_tvs
-                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
-
-               | otherwise
-               = outer_tvs
-                 `unionVarSet` tyCoVarsOfTypes mr_no_quant
-                 `unionVarSet` tyCoVarsOfTypes no_quant
-                 `unionVarSet` co_var_tvs
-                     -- If we don't quantify over a constraint in no_quant, we
-                     -- can either not-quantify its free vars (hoping that call
-                     -- sites will fix them) or just ignore it for the purposes
-                     -- of mono_tvs0 (leaving behind a perhaps insoluble residual
-                     -- constraint)
--}
-
-             add_determined tvs = closeWrtFunDeps post_mr_quant tvs
-                                  `delVarSetList` psig_qtvs
-             -- Finally, delete psig_qtvs
-             -- If the user has explicitly asked for quantification, then that
-             -- request "wins" over the MR.
-             --
-             -- What if a psig variable is also free in the environment
-             -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
-             -- in Step 2 of Note [Deciding quantification].
-
-
+             mono_tvs_with_mr
+               = mono_tvs_without_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
 
              -- Next, use closeWrtFunDeps to find any other variables that are
              -- determined by mono_tvs0, by functional dependencies or equalities.
@@ -1531,8 +1495,17 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- are in the equality constraint with alpha. Actual test case:
              -- typecheck/should_compile/tc213
              -- see Note [growThetaTyVars vs closeWrtFunDeps]
-             mono_tvs_with_mr    = add_determined mono_tvs_accounting_for_mr
-             mono_tvs_without_mr = add_determined mono_tvs_ignoring_mr
+             add_determined tvs = closeWrtFunDeps post_mr_quant tvs
+                                  `delVarSetList` psig_qtvs
+                 -- Why delVarSetList psig_qtvs?
+                 -- If the user has explicitly asked for quantification, then that
+                 -- request "wins" over the MR.
+                 --
+                 -- What if a psig variable is also free in the environment
+                 -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
+                 -- in Step 2 of Note [Deciding quantification].
+             mono_tvs_with_mr_det    = add_determined mono_tvs_with_mr
+             mono_tvs_without_mr_det = add_determined mono_tvs_without_mr
 
              -- Do not quantify over any constraint mentioning a "newly-mono" tyvar
              -- The "newly-mono" tyvars are the ones not free in the envt, nor
@@ -1543,21 +1516,21 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
              -- but we do not want to generate f :: (C Int beta[0]) => beta[0] -> Int
              -- Rather, we generate f :: beta[0] -> Int, but leave [W] C Int beta[0]
              -- in the residual constraints, which will probably cause a type errors
-             newly_mono = mono_tvs `minusVarSet` mono_tvs0
+             newly_mono_tvs = mono_tvs_with_mr_det `minusVarSet` mono_tvs_with_mr
              final_quant
-               | isTopTcLevel tc_lvl = filterOut (predMentions newly_mono) post_mr_quant
+               | isTopTcLevel tc_lvl = filterOut (predMentions newly_mono_tvs) post_mr_quant
                | otherwise           = post_mr_quant
 
        -- Check if the Monomorphism Restriction has bitten
        ; warn_mr <- woptM Opt_WarnMonomorphism
        ; when (warn_mr && case infer_mode of { ApplyMR -> True; _ -> False}) $
-         diagnosticTc (not (mono_tvs `subVarSet` mono_tvs_wo_mr)) $
+         diagnosticTc (not (mono_tvs_with_mr_det `subVarSet` mono_tvs_without_mr_det)) $
               TcRnMonomorphicBindings (map fst name_taus)
              -- If there is a variable in mono_tvs, but not in mono_tvs_wo_mr
              -- then the MR has "bitten" and reduced polymorphism.
 
        -- Promote the mono_tvs: see Note [Promote monomorphic tyvars]
-       ; _ <- promoteTyVarSet mono_tvs
+       ; _ <- promoteTyVarSet mono_tvs_with_mr_det
 
        ; traceTc "decideAndPromoteTyVars" $ vcat
            [ text "tc_lvl =" <+> ppr tc_lvl
@@ -1565,13 +1538,17 @@ decideAndPromoteTyVars infer_mode name_taus psigs wanted
            , text "infer_mode =" <+> ppr infer_mode
            , text "psigs =" <+> ppr psigs
            , text "psig_qtvs =" <+> ppr psig_qtvs
-           , text "mono_tvs0 =" <+> ppr mono_tvs0
+           , text "outer_tvs =" <+> ppr outer_tvs
+           , text "mono_tvs_with_mr =" <+> ppr mono_tvs_with_mr
+           , text "mono_tvs_without_mr =" <+> ppr mono_tvs_without_mr
+           , text "mono_tvs_with_mr_det =" <+> ppr mono_tvs_with_mr_det
+           , text "mono_tvs_without_mr_det =" <+> ppr mono_tvs_without_mr_det
+           , text "newly_mono_tvs =" <+> ppr newly_mono_tvs
            , text "can_quant =" <+> ppr can_quant
            , text "post_mr_quant =" <+> ppr post_mr_quant
            , text "no_quant =" <+> ppr no_quant
            , text "mr_no_quant =" <+> ppr mr_no_quant
            , text "final_quant =" <+> ppr final_quant
-           , text "mono_tvs =" <+> ppr mono_tvs
            , text "co_vars =" <+> ppr co_vars ]
 
        ; return (final_quant, co_vars) }


=====================================
testsuite/tests/typecheck/should_compile/T13785.hs
=====================================
@@ -10,10 +10,10 @@ foo = bar >> baz >> bar1 >> bar2
   where
     -- Should not get MR warning
     bar, baz :: m Char
-    (bar, baz) = (c :: m Char, m Char)
+    (bar, baz) = c
 
     -- Should not get MR warning
-    (bar1, baz1) = (c :: (m Char, m Char))
+    (bar1, baz1) = c :: (m Char, m Char)
 
     -- Should get MR warning
     -- Natural type for the "whole binding": forall x. C x => (x Char, x Char)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6045cee9c5bc0b146503a6dde1ad480bb2a50c49

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 23:00:01 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 19:00:01 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/9.12-alpha-test
Message-ID: <670da27180c3e_1d5aecec9424114569@gitlab.mail>



Zubin pushed new branch wip/9.12-alpha-test at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12-alpha-test
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 14 23:11:42 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 19:11:42 -0400
Subject: [Git][ghc/ghc][wip/9.12-alpha-test] 2 commits: testsuite: normalise
 windows file seperators
Message-ID: <670da52edffc4_1d5aec109c9041147ae@gitlab.mail>



Zubin pushed to branch wip/9.12-alpha-test at Glasgow Haskell Compiler / GHC


Commits:
f858875e by Zubin Duggal at 2024-10-15T04:41:35+05:30
testsuite: normalise windows file seperators

- - - - -
aa2cf781 by Zubin Duggal at 2024-10-15T04:41:35+05:30
Prepare 9.12.1 alpha

- - - - -


3 changed files:

- configure.ac
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- testsuite/tests/profiling/should_run/all.T


Changes:

=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.12], [glasgow-hask
 AC_CONFIG_MACRO_DIRS([m4])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the


=====================================
testsuite/tests/ghc-e/should_fail/T9930fail.stderr
=====================================
@@ -3,46 +3,46 @@ ghc: Exception:
 default output name would overwrite the input file; must specify -o explicitly
 Usage: For basic information, try the `--help' option.
 
-Package: ghc-9.11-inplace
+Package: ghc-9.12-8fe2
 Module: GHC.Utils.Panic
 Type: GhcException
 
 While handling default output name would overwrite the input file; must specify -o explicitly
   | Usage: For basic information, try the `--help' option.
   |
-  | Package: ghc-9.11-inplace
+  | Package: ghc-9.12-8fe2
   | Module: GHC.Utils.Panic
   | Type: GhcException
   |
   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   | Usage: For basic information, try the `--help' option.
   |   |
-  |   | Package: ghc-9.11-inplace
+  |   | Package: ghc-9.12-8fe2
   |   | Module: GHC.Utils.Panic
   |   | Type: GhcException
   |   |
   |   | While handling default output name would overwrite the input file; must specify -o explicitly
   |   |   | Usage: For basic information, try the `--help' option.
   |   |   |
-  |   |   | Package: ghc-9.11-inplace
+  |   |   | Package: ghc-9.12-8fe2
   |   |   | Module: GHC.Utils.Panic
   |   |   | Type: GhcException
   |   |   |
   |   |   | HasCallStack backtrace:
-  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.11-inplace:GHC.Utils.Panic
+  |   |   |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  |   |   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  |   |   |   throw, called at compiler/GHC/Utils/Panic.hs:180:21 in ghc-9.12-8fe2:GHC.Utils.Panic
   |   |
   |   | HasCallStack backtrace:
-  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-inplace:System.Semaphore
+  |   |   bracket_, called at libraries/semaphore-compat/src/System/Semaphore.hs:320:23 in semaphore-compat-1.0.0-c856:System.Semaphore
   |
   | HasCallStack backtrace:
-  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
+  |   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
   |   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:284:11 in ghc-internal:GHC.Internal.IO
-  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  |   onException, called at compiler/GHC/Driver/Make.hs:2986:23 in ghc-9.11-inplace:GHC.Driver.Make
+  |   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:860:84 in exceptions-0.10.7-71b0:Control.Monad.Catch
+  |   onException, called at compiler/GHC/Driver/Make.hs:2988:23 in ghc-9.12-8fe2:GHC.Driver.Make
 
 HasCallStack backtrace:
-  bracket, called at compiler/GHC/Driver/Make.hs:2953:3 in ghc-9.11-inplace:GHC.Driver.Make
+  bracket, called at compiler/GHC/Driver/Make.hs:2955:3 in ghc-9.12-8fe2:GHC.Driver.Make
 


=====================================
testsuite/tests/profiling/should_run/all.T
=====================================
@@ -145,11 +145,13 @@ test('T7275', test_opts_dot_prof, makefile_test, [])
 test('callstack001',
      # unoptimised results are different w.r.t. CAF attribution
      [test_opts_dot_prof # produces a different stack
+     ,normalise_fun(lambda s: re.sub(r"(?

From gitlab at gitlab.haskell.org  Mon Oct 14 23:26:06 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Mon, 14 Oct 2024 19:26:06 -0400
Subject: [Git][ghc/ghc][wip/9.12.1-alpha1] 8 commits: testsuite: normalise
 some versions in callstacks
Message-ID: <670da88e61104_1d5aec10a25d4114988@gitlab.mail>



Zubin pushed to branch wip/9.12.1-alpha1 at Glasgow Haskell Compiler / GHC


Commits:
f230e29f by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: normalise some versions in callstacks

- - - - -
b19de476 by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
fbf0889e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
473a201c by Zubin Duggal at 2024-10-15T04:26:11+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
a79a587e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -
f858875e by Zubin Duggal at 2024-10-15T04:41:35+05:30
testsuite: normalise windows file seperators

- - - - -
24e5761e by Zubin Duggal at 2024-10-15T04:55:36+05:30
testsuite: Mark 25300A as broken on windows

- - - - -
ca2b21c3 by Zubin Duggal at 2024-10-15T04:55:41+05:30
Prepare 9.12.1 alpha

- - - - -


30 changed files:

- compiler/ghc.cabal.in
- configure.ac
- libraries/Cabal
- libraries/array
- libraries/base/base.cabal.in
- libraries/deepseq
- libraries/directory
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/unix
- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/exceptions/all.T
- testsuite/tests/gadt/all.T


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/193d7c0e673e04576686c69b875823501c587816...ca2b21c3429a5ff780cb6c58c33c171a3c0af82b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/193d7c0e673e04576686c69b875823501c587816...ca2b21c3429a5ff780cb6c58c33c171a3c0af82b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 02:16:04 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 22:16:04 -0400
Subject: [Git][ghc/ghc][master] 3 commits: Desugaring, plus
 -Wincomplete-record-selectors
Message-ID: <670dd064b399b_f26a224fbd0415f8@gitlab.mail>



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


Commits:
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e9cc469954eb19c5c131f9cfc1f0ede6ea9e9848...6a067226d094fbe59fd71c502c6977619f546953

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e9cc469954eb19c5c131f9cfc1f0ede6ea9e9848...6a067226d094fbe59fd71c502c6977619f546953
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 02:16:34 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 22:16:34 -0400
Subject: [Git][ghc/ghc][master] users-guide: Document field coalescence
Message-ID: <670dd08234096_f26a228ac4444880@gitlab.mail>



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


Commits:
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -


1 changed file:

- docs/users_guide/exts/pragmas.rst


Changes:

=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -959,6 +959,35 @@ effect of adding ``{-# UNPACK #-}`` to every strict constructor field which is
 of a single-constructor data type. Sum types won't be unpacked automatically
 by this though, only with the explicit pragma.
 
+Also note that GHC will coalesce adjacent sub-word size fields into
+words. For instance, consider (on a 64-bit platform) ::
+
+    data T = T {-# UNPACK #-} !Word32 {-# UNPACK #-} !Word32
+
+As ``Word32`` is represented by the unlifted 32-bit ``Word32#`` type, the ``T``
+constructor will represent its two ``Word32`` fields using only a single
+64-bit word.
+
+Note that during coalescence padding will be inserted to ensure that each field
+remains naturally aligned. For instance, on a 64-bit platform ::
+
+    data T = T {-# UNPACK #-} !Word32
+               {-# UNPACK #-} !Word8
+               {-# UNPACK #-} !Word32
+
+the fields of ``T`` require two 64-bit words since padding is necessary after
+the ``Word8`` to ensure that the subsequent ``Word64`` is naturally aligned:
+
+.. code-block:: none
+
+     ┌───────────────────────────────────┐
+     │ Header                            │
+     ├─────────────────┬────────┬────────┤
+     │ Word32          │ Word8  │ padding│
+     ├─────────────────┼────────┴────────┤
+     │ Word32          │ padding         │
+     └─────────────────┴─────────────────┘
+
 .. [1]
    In fact, :pragma:`UNPACK` has no effect without :ghc-flag:`-O`, for technical
    reasons (see :ghc-ticket:`5252`).



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 02:17:17 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 14 Oct 2024 22:17:17 -0400
Subject: [Git][ghc/ghc][master] LLVM backend: Use correct rounding for Float
 literals
Message-ID: <670dd0ad5ed58_f26a2282be850047@gitlab.mail>



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


Commits:
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -


5 changed files:

- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- + testsuite/tests/llvm/should_run/T22033.hs
- + testsuite/tests/llvm/should_run/T22033.stdout
- testsuite/tests/llvm/should_run/all.T


Changes:

=====================================
compiler/GHC/CmmToLlvm/CodeGen.hs
=====================================
@@ -2107,10 +2107,17 @@ genLit opt (CmmInt i w)
         --                 ]
     in return (mkIntLit width i, nilOL, [])
 
-genLit _ (CmmFloat r w)
-  = return (LMLitVar $ LMFloatLit (fromRational r) (widthToLlvmFloat w),
+genLit _ (CmmFloat r W32)
+  = return (LMLitVar $ LMFloatLit (widenFp (fromRational r :: Float)) (widthToLlvmFloat W32),
               nilOL, [])
 
+genLit _ (CmmFloat r W64)
+  = return (LMLitVar $ LMFloatLit (fromRational r :: Double) (widthToLlvmFloat W64),
+              nilOL, [])
+
+genLit _ (CmmFloat _r _w)
+  = panic "genLit (CmmLit:CmmFloat), unsupported float lit"
+
 genLit opt (CmmVec ls)
   = do llvmLits <- mapM toLlvmLit ls
        return (LMLitVar $ LMVectorLit llvmLits, nilOL, [])


=====================================
compiler/GHC/CmmToLlvm/Data.hs
=====================================
@@ -10,6 +10,7 @@ module GHC.CmmToLlvm.Data (
 import GHC.Prelude
 
 import GHC.Llvm
+import GHC.Llvm.Types (widenFp)
 import GHC.CmmToLlvm.Base
 import GHC.CmmToLlvm.Config
 
@@ -193,8 +194,14 @@ genStaticLit :: CmmLit -> LlvmM LlvmStatic
 genStaticLit (CmmInt i w)
     = return $ LMStaticLit (LMIntLit i (LMInt $ widthInBits w))
 
-genStaticLit (CmmFloat r w)
-    = return $ LMStaticLit (LMFloatLit (fromRational r) (widthToLlvmFloat w))
+genStaticLit (CmmFloat r W32)
+    = return $ LMStaticLit (LMFloatLit (widenFp (fromRational r :: Float)) (widthToLlvmFloat W32))
+
+genStaticLit (CmmFloat r W64)
+    = return $ LMStaticLit (LMFloatLit (fromRational r :: Double) (widthToLlvmFloat W64))
+
+genStaticLit (CmmFloat _r _w)
+    = panic "genStaticLit (CmmLit:CmmFloat), unsupported float lit"
 
 genStaticLit (CmmVec ls)
     = do sls <- mapM toLlvmLit ls


=====================================
testsuite/tests/llvm/should_run/T22033.hs
=====================================
@@ -0,0 +1,16 @@
+-- Minimal reproducer for https://gitlab.haskell.org/ghc/ghc/-/issues/22033
+{-# LANGUAGE MagicHash #-}
+import Numeric
+import GHC.Exts
+
+a :: Float
+a = F# (int2Float# 0xFFFFFF7FFFFFFFF#)
+
+f :: Int# -> Float#
+f x = int2Float# x
+{-# NOINLINE f #-}
+
+main :: IO ()
+main = do
+    putStrLn (showHFloat a "")
+    putStrLn (showHFloat (F# (f 0xFFFFFF7FFFFFFFF#)) "")


=====================================
testsuite/tests/llvm/should_run/T22033.stdout
=====================================
@@ -0,0 +1,2 @@
+0x1.fffffep59
+0x1.fffffep59


=====================================
testsuite/tests/llvm/should_run/all.T
=====================================
@@ -13,3 +13,4 @@ def ignore_llvm_and_vortex( msg ):
      return re.sub(r".* is not a recognized processor for this target.*\n",r"",msg)
 
 test('T22487', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])
+test('T22033', [normal, normalise_errmsg_fun(ignore_llvm_and_vortex)], compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55b83587d7a7288b243b8d3e5ec79a411bffdcbd

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 06:36:22 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Tue, 15 Oct 2024 02:36:22 -0400
Subject: [Git][ghc/ghc][wip/T23479] JS: Re-add optimization for literal
 strings in genApp (fixes #23479)
Message-ID: <670e0d66d280f_f26a210534987189e@gitlab.mail>



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


Commits:
0cc2c9e9 by Serge S. Gulin at 2024-10-15T09:35:51+03:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -


24 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- testsuite/tests/javascript/T24495.hs
- testsuite/tests/javascript/T24495.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1517,6 +1517,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,51 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
+
+    -- Test case T24495 with single occurrence at -02 and third occurrence at -01
+    -- Moved back from removal at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12308
+    -- See commit hash b36ee57bfbecc628b7f0919e1e59b7066495034f
+    --
+    -- Case: unpackCStringAppend# "some string"# str
+    --
+    -- Generates h$appendToHsStringA(str, "some string"), which has a faster
+    -- decoding loop.
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendIdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -765,7 +765,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -5,5 +5,28 @@ include $(TOP)/mk/test.mk
 T24495:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T24495
-	# check that the optimization occurred
+	# check that the optimization occurred for -01 3 times (2 for cases + 1 for unfloated lits)
+	grep -c appendToHsStringA T24495.dump-js
+
+	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T24495
+	# check that the optimization occurred for -02 1 time (1 for unfloated lits)
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js || true
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local_once" T23479_2.dump-js
+	# check that the optimization occurred
+	grep -c "h\$$r1 = h\$$decodeUtf8z" T23479_2.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+test_val_80_global :: String
+test_val_80_global = "test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val"
+
+main :: IO ()
+main = do
+  -- Direct usage
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## "test_val_1"#))
+  -- Requires string sinker hit for strings shorter 80 symbols
+  js_log1 (toJSString test_val_2)
+  -- Requires rewrite hit "toJSString/literal"
+  js_log1 (toJSString test_val_3)
+  -- Locally defined strings become unfloatted at any length
+  js_log1 (toJSString test_val_80_local)
+  -- Globally defined strings with length >= 80 should not be unfloatted
+  js_log1 (toJSString test_val_80_global)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,10 @@
+test_val_1
+test_val_2
+test_val_3
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val
+1
+1
+1
+1
+0


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  -- When long string (>= 80) used once it is unfloatted
+  js_log1 (toJSString test_val_80_local_once)
+
+  -- When long string (>= 80) used more than once no unfloatting happened
+  js_log1 (toJSString test_val_80_local)
+  js_log1 (toJSString (testFn80 "testFn80:"))
+
+  -- Even if short string used more than once it is unfloatted anyway
+  js_log1 (toJSString test_val_1)
+  js_log1 (toJSString (testFn "testFn:"))
+  where
+    test_val_80_local_once :: String
+    test_val_80_local_once = "test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"
+
+    testFn80 s = s ++ test_val_80_local
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn80 #-}
+
+    test_val_1 :: String
+    test_val_1 = "test_val_1"
+
+    testFn s = s ++ test_val_1
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn #-}


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,8 @@
+test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+testFn80:test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_1
+testFn:test_val_1
+1
+1
+1


=====================================
testsuite/tests/javascript/T24495.hs
=====================================
@@ -1,6 +1,6 @@
 {-# LANGUAGE MagicHash #-}
-{-# OPTIONS_GHC -O1 #-}
 -- -O1 required to make "rest" thunk SingleEntry
+-- -O2 shows that it still do one optimization
 
 module Main where
 


=====================================
testsuite/tests/javascript/T24495.stdout
=====================================
@@ -1,2 +1,4 @@
 2 ab bd
-2
+3
+2 ab bd
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,6 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cc2c9e9ab8428e6182bd9d387f5eb887cff2c6c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 08:19:04 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 15 Oct 2024 04:19:04 -0400
Subject: [Git][ghc/ghc][wip/T25266] 49 commits: Handle exceptions from IO
 manager backend
Message-ID: <670e25785d7a0_f26a21531e10967b3@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
a9194c65 by Simon Peyton Jones at 2024-10-15T09:09:03+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
dc05fca9 by Simon Peyton Jones at 2024-10-15T09:09:03+01:00
Work in progress on #25266

- - - - -
bff5a7da by Simon Peyton Jones at 2024-10-15T09:09:03+01:00
Better generalisation

- - - - -
80f13d6e by Simon Peyton Jones at 2024-10-15T09:09:03+01:00
Wibbles to short cuts

- - - - -
a35e77e3 by Simon Peyton Jones at 2024-10-15T09:09:03+01:00
Iterating in decideAndPromote

- - - - -
f11d0645 by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibble

- - - - -
9ea896fe by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibble Solver

- - - - -
1b9b46e3 by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibble

- - - - -
9e002df7 by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Keep variables in correct order

- - - - -
bac757bc by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibble solver

- - - - -
9e9ed5fd by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibbles related to the MR

- - - - -
3e20e93a by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Respond to rae review

- - - - -
4326ca97 by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibbles

- - - - -
19faeb6e by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Add type sig

Acked-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
1b6b534d by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibble assert in approximateWC

- - - - -
e5953c7b by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Wibbles to solver and MR

- - - - -
160470d2 by Simon Peyton Jones at 2024-10-15T09:09:04+01:00
Fix build

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6045cee9c5bc0b146503a6dde1ad480bb2a50c49...160470d24e7ccd7cedd28cbf338dadcb28a36ce2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6045cee9c5bc0b146503a6dde1ad480bb2a50c49...160470d24e7ccd7cedd28cbf338dadcb28a36ce2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 08:25:39 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 15 Oct 2024 04:25:39 -0400
Subject: [Git][ghc/ghc][wip/ttg/fixity-import] 6 commits: Desugaring, plus
 -Wincomplete-record-selectors
Message-ID: <670e27036aec8_1b8fe9140190-328@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/fixity-import at Glasgow Haskell Compiler / GHC


Commits:
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Stats.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c742cf889f980af8a21ff85eb7acb845dd83f36d...e59fe5c6bd914f2da6c7d8bdfa87aafdc2f9d6e8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c742cf889f980af8a21ff85eb7acb845dd83f36d...e59fe5c6bd914f2da6c7d8bdfa87aafdc2f9d6e8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 08:48:54 2024
From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns))
Date: Tue, 15 Oct 2024 04:48:54 -0400
Subject: [Git][ghc/ghc][wip/aidylns/ttg-remove-hsunboundvar-via-hshole] 123
 commits: DmdAnal: Fast path for `multDmdType` (#25196)
Message-ID: <670e2c76d73ee_1b8fe9f33e048e5@gitlab.mail>



Adriaan Leijnse pushed to branch wip/aidylns/ttg-remove-hsunboundvar-via-hshole at Glasgow Haskell Compiler / GHC


Commits:
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
8404642f by Adriaan Leijnse at 2024-10-14T11:01:41+01:00
TTG: Replace HsUnboundVar with HsHole and HsVar HsVarVarOcc

Implication: Renamer now creates a Name at unbound var site, where before it was
left as RdrName.

- - - - -
02a854c0 by Adriaan Leijnse at 2024-10-14T11:02:02+01:00
Remove Id from HER, leaving just (IORef EvTerm)

Consequences of this change:
- We no longer duplicate the Id in both HsHole itself and it's HER
- Outputable couldn't should the Unique that was in the Id anymore
- `zonk_her` now updates the Located Name of HsVar (Unbound _) and HsHole,
  instead of the one contained in the ex-HER's Id. I hope this is correct.

- - - - -
90e0214c by Adriaan Leijnse at 2024-10-14T11:02:02+01:00
Make more HsHoles in Rn with NamedWildCards enabled

Specifically any unbound variable starting with underscore is turned into a
hole.

Now we don't have to check this in `expr_to_type` if all goes well.

- - - - -


25 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ed954d99ef1a3f3798630bb46d08b404567e9d1...90e0214cb3fc95ffc92b8479db12f59c2d2837ac

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ed954d99ef1a3f3798630bb46d08b404567e9d1...90e0214cb3fc95ffc92b8479db12f59c2d2837ac
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 09:30:23 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Tue, 15 Oct 2024 05:30:23 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] some test fies
Message-ID: <670e362fc6f30_1b8fe9561d0089fd@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
00bc8de1 by Matthew Pickering at 2024-10-15T10:26:41+01:00
some test fies

- - - - -


4 changed files:

- testsuite/tests/splice-imports/SI02.hs
- testsuite/tests/splice-imports/SI09.hs
- testsuite/tests/splice-imports/SI10.hs
- testsuite/tests/splice-imports/all.T


Changes:

=====================================
testsuite/tests/splice-imports/SI02.hs
=====================================
@@ -4,6 +4,7 @@
 module SI02 where
 
 import splice Prelude
+import Prelude
 
 main :: IO ()
 main = $(id [| pure () |])


=====================================
testsuite/tests/splice-imports/SI09.hs
=====================================
@@ -4,6 +4,9 @@ module SI09 where
 
 import splice InstanceA ()
 import splice ClassA
+import splice Prelude
+-- Why is implicit prelude import broken?
+import Prelude
 
 e :: IO ()
 -- Uses a non-splice imported instance


=====================================
testsuite/tests/splice-imports/SI10.hs
=====================================
@@ -4,6 +4,8 @@ module SI09 where
 
 import InstanceA ()
 import splice ClassA
+import ClassA
+import splice Prelude
 
 e :: X
 -- Uses a non-splice imported instance


=====================================
testsuite/tests/splice-imports/all.T
=====================================
@@ -14,7 +14,7 @@ test('SI07', [extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-in
 test('SI08', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile_fail, ['SI08', '-v0'])
 test('SI09', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile, ['SI09', '-v0'])
 test('SI10', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile, ['SI10', '-v0'])
-test('SI11', normal,  compile, [''])
-test('SI12', normal,  compile, [''])
+test('SI11', normal,  compile_fail, [''])
+test('SI12', normal,  compile_fail, [''])
 test('SI13', normal,  compile, [''])
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/00bc8de1e1eb200265825e449e9e614009100176

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 10:03:15 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Tue, 15 Oct 2024 06:03:15 -0400
Subject: [Git][ghc/ghc][wip/layouter] Implemented a layouter that does not work
Message-ID: <670e3de37200_1b8fe965e3ac117d4@gitlab.mail>



Sebastian Graf pushed to branch wip/layouter at Glasgow Haskell Compiler / GHC


Commits:
133923a6 by Sebastian Graf at 2024-10-15T12:03:04+02:00
Implemented a layouter that does not work

Counter example:

```hs
baz :: Bool -> Bool -> [Int]
baz p q = [case () of _ | p, q -> 0, 42]
```

- - - - -


6 changed files:

- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- + compiler/GHC/Parser/Layouter.hs
- + compiler/GHC/Parser/Layouter.hs-boot
- compiler/GHC/Parser/Lexer.x
- compiler/ghc.cabal.in


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -83,6 +83,7 @@ import GHC.Core.DataCon ( DataCon, dataConName )
 
 import GHC.Parser.PostProcess
 import GHC.Parser.PostProcess.Haddock
+import GHC.Parser.Layouter
 import GHC.Parser.Lexer
 import GHC.Parser.HaddockLex
 import GHC.Parser.Annotation
@@ -762,7 +763,7 @@ TH_QUASIQUOTE   { L _ (ITquasiQuote _) }
 TH_QQUASIQUOTE  { L _ (ITqQuasiQuote _) }
 
 %monad { P } { >>= } { return }
-%lexer { (lexer True) } { L _ ITeof }
+%lexer { layouter (lexer True) } { L _ ITeof }
   -- Replace 'lexer' above with 'lexerDbg'
   -- to dump the tokens fed to the parser.
 %tokentype { (Located Token) }
@@ -797,7 +798,7 @@ identifier :: { LocatedN RdrName }
 -- Backpack stuff
 
 backpack :: { [LHsUnit PackageName] }
-         : implicit_top units close { fromOL $2 }
+         : implicit_top units vccurly { fromOL $2 }
          | '{' units '}'            { fromOL $2 }
 
 units :: { OrdList (LHsUnit PackageName) }
@@ -867,7 +868,7 @@ rn :: { LRenaming }
 
 unitbody :: { OrdList (LHsUnitDecl PackageName) }
         : '{'     unitdecls '}'   { $2 }
-        | vocurly unitdecls close { $2 }
+        | vocurly unitdecls vccurly { $2 }
 
 unitdecls :: { OrdList (LHsUnitDecl PackageName) }
         : unitdecls ';' unitdecl { $1 `appOL` unitOL $3 }
@@ -944,13 +945,13 @@ body    :: { ([TrailingAnn]
              ,([LImportDecl GhcPs], [LHsDecl GhcPs])
              ,EpLayout) }
         :  '{'            top '}'      { (fst $2, snd $2, epExplicitBraces $1 $3) }
-        |      vocurly    top close    { (fst $2, snd $2, EpVirtualBraces (getVOCURLY $1)) }
+        |      vocurly    top vccurly    { (fst $2, snd $2, EpVirtualBraces (getVOCURLY $1)) }
 
 body2   :: { ([TrailingAnn]
              ,([LImportDecl GhcPs], [LHsDecl GhcPs])
              ,EpLayout) }
         :  '{' top '}'                          { (fst $2, snd $2, epExplicitBraces $1 $3) }
-        |  missing_module_keyword top close     { ([], snd $2, EpVirtualBraces leftmostColumn) }
+        |  missing_module_keyword top vccurly     { ([], snd $2, EpVirtualBraces leftmostColumn) }
 
 
 top     :: { ([TrailingAnn]
@@ -1467,11 +1468,11 @@ where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
 ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
         :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
                                                 ,Just (unLoc $2)) }
-        | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
+        | vocurly ty_fam_inst_eqns vccurly   { let (L loc _) = $2 in
                                              L loc ([],Just (unLoc $2)) }
         |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
                                                  ,mcc $3],Nothing) }
-        | vocurly '..' close               { let (L loc _) = $2 in
+        | vocurly '..' vccurly               { let (L loc _) = $2 in
                                              L loc ([mj AnnDotdot $2],Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
@@ -1724,7 +1725,7 @@ cvars1 :: { [RecordPatSynField GhcPs] }
 where_decls :: { LocatedL (OrdList (LHsDecl GhcPs)) }
         : 'where' '{' decls '}'       {% amsr (sLL $1 $> (snd $ unLoc $3))
                                               (AnnList (Just $ glR $3) (Just $ moc $2) (Just $ mcc $4) (mj AnnWhere $1: (fst $ unLoc $3)) []) }
-        | 'where' vocurly decls close {% amsr (sLL $1 $3 (snd $ unLoc $3))
+        | 'where' vocurly decls vccurly {% amsr (sLL $1 $3 (snd $ unLoc $3))
                                               (AnnList (Just $ glR $3) Nothing Nothing (mj AnnWhere $1: (fst $ unLoc $3)) []) }
 
 pattern_synonym_sig :: { LSig GhcPs }
@@ -1780,7 +1781,7 @@ decllist_cls
                      , EpLayout) }      -- Reversed
         : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
-        |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
+        |     vocurly decls_cls vccurly   { let { L l (anns, decls) = $2 }
                                            in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
@@ -1824,7 +1825,7 @@ decllist_inst
         :: { Located ([AddEpAnn]
                      , OrdList (LHsDecl GhcPs)) }      -- Reversed
         : '{'         decls_inst '}'    { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2),snd $ unLoc $2) }
-        |     vocurly decls_inst close  { L (gl $2) (unLoc $2) }
+        |     vocurly decls_inst vccurly  { L (gl $2) (unLoc $2) }
 
 -- Instance body
 --
@@ -1864,7 +1865,7 @@ decls   :: { Located ([AddEpAnn], OrdList (LHsDecl GhcPs)) }
 decllist :: { Located (AnnList,Located (OrdList (LHsDecl GhcPs))) }
         : '{'            decls '}'     { sLL $1 $> (AnnList (Just $ glR $2) (Just $ moc $1) (Just $ mcc $3)  (fst $ unLoc $2) []
                                                    ,sL1 $2 $ snd $ unLoc $2) }
-        |     vocurly    decls close   { L (gl $2) (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []
+        |     vocurly    decls vccurly   { L (gl $2) (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []
                                                    ,sL1 $2 $ snd $ unLoc $2) }
 
 -- Binding groups other than those of class and instance declarations
@@ -1879,7 +1880,7 @@ binds   ::  { Located (HsLocalBinds GhcPs) }
         | '{'            dbinds '}'     {% acs (comb3 $1 $2 $3) (\loc cs -> (L loc
                                              $ HsIPBinds (EpAnn (spanAsAnchor (comb3 $1 $2 $3)) (AnnList (Just$ glR $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) }
 
-        |     vocurly    dbinds close   {% acs (gl $2) (\loc cs -> (L loc
+        |     vocurly    dbinds vccurly   {% acs (gl $2) (\loc cs -> (L loc
                                              $ HsIPBinds (EpAnn (glR $1) (AnnList (Just $ glR $2) Nothing Nothing [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) }
 
 
@@ -2492,7 +2493,7 @@ gadt_constrlist :: { Located ([AddEpAnn]
                                                          ,moc $2
                                                          ,mcc $4]
                                                         , unLoc $3) }
-        | 'where' vocurly    gadt_constrs close  {% checkEmptyGADTs $
+        | 'where' vocurly    gadt_constrs vccurly  {% checkEmptyGADTs $
                                                       L (comb2 $1 $3)
                                                         ([mj AnnWhere $1]
                                                         , unLoc $3) }
@@ -3205,7 +3206,7 @@ acmd    :: { LHsCmdTop GhcPs }
 cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
         :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
                                                   ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+        |      vocurly    cvtopdecls0 vccurly    { ([],$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -3436,11 +3437,11 @@ altslist(PATS) :: { forall b. DisambECP b => PV (LocatedL [LMatch GhcPs (Located
         : '{'        alts(PATS) '}'    { $2 >>= \ $2 -> amsr
                                            (sLL $1 $> (reverse (snd $ unLoc $2)))
                                            (AnnList (Just $ glR $2) (Just $ moc $1) (Just $ mcc $3) (fst $ unLoc $2) []) }
-        | vocurly    alts(PATS)  close { $2 >>= \ $2 -> amsr
+        | vocurly    alts(PATS)  vccurly { $2 >>= \ $2 -> amsr
                                            (L (getLoc $2) (reverse (snd $ unLoc $2)))
                                            (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []) }
         | '{'              '}'   { amsr (sLL $1 $> []) (AnnList Nothing (Just $ moc $1) (Just $ mcc $2) [] []) }
-        | vocurly          close { return $ noLocA [] }
+        | vocurly          vccurly { return $ noLocA [] }
 
 alts(PATS) :: { forall b. DisambECP b => PV (Located ([AddEpAnn],[LMatch GhcPs (LocatedA b)])) }
         : alts1(PATS)              { $1 >>= \ $1 -> return $
@@ -3492,14 +3493,11 @@ gdpats :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) }
                          return $ sLL gdpats gdpat (gdpat : unLoc gdpats) }
         | gdpat        { $1 >>= \gdpat -> return $ sL1 gdpat [gdpat] }
 
--- layout for MultiWayIf doesn't begin with an open brace, because it's hard to
--- generate the open brace in addition to the vertical bar in the lexer, and
--- we don't need it.
 ifgdpats :: { Located ((EpToken "{", EpToken "}"), [LGRHS GhcPs (LHsExpr GhcPs)]) }
-         : '{' gdpats '}'                 {% runPV $2 >>= \ $2 ->
+         : '{'     gdpats '}'             {% runPV $2 >>= \ $2 ->
                                              return $ sLL $1 $> ((epTok $1,epTok $3),unLoc $2)  }
-         |     gdpats close               {% runPV $1 >>= \ $1 ->
-                                             return $ sL1 $1 ((NoEpTok, NoEpTok),unLoc $1) }
+         | vocurly gdpats vccurly         {% runPV $2 >>= \ $2 ->
+                                             return $ sL1 $1 ((NoEpTok, NoEpTok),unLoc $2) }
 
 gdpat   :: { forall b. DisambECP b => PV (LGRHS GhcPs (LocatedA b)) }
         : '|' guardquals '->' exp
@@ -3550,7 +3548,7 @@ apat    : aexp                  {% (checkPattern <=< runPV) (unECP $1) }
 stmtlist :: { forall b. DisambECP b => PV (LocatedL [LocatedA (Stmt GhcPs (LocatedA b))]) }
         : '{'           stmts '}'       { $2 >>= \ $2 ->
                                           amsr (sLL $1 $> (reverse $ snd $ unLoc $2)) (AnnList (stmtsAnchor $2) (Just $ moc $1) (Just $ mcc $3) (fromOL $ fst $ unLoc $2) []) }
-        |     vocurly   stmts close     { $2 >>= \ $2 -> amsr
+        |     vocurly   stmts vccurly   { $2 >>= \ $2 -> amsr
                                           (L (stmtsLoc $2) (reverse $ snd $ unLoc $2)) (AnnList (stmtsAnchor $2) Nothing Nothing (fromOL $ fst $ unLoc $2) []) }
 
 --      do { ;; s ; s ; ; s ;; }
@@ -4133,7 +4131,7 @@ unrelated tokens.
 -}
 close :: { () }
         : vccurly               { () } -- context popped in lexer.
-        | error                 {% popContext } -- See Note [Layout and error]
+--        | error                 {% popContext } -- See Note [Layout and error]
 
 -----------------------------------------------------------------------------
 -- Miscellaneous (mostly renamings)


=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -28,6 +28,7 @@ import GHC.Driver.Errors.Types -- Unfortunate, needed due to the fact we throw e
 
 import GHC.Parser.Errors.Types
 import GHC.Parser           ( parseHeader )
+import GHC.Parser.Layouter
 import GHC.Parser.Lexer
 
 import GHC.Hs
@@ -203,7 +204,7 @@ lazyGetToks popts filename handle = do
 
   lazyLexBuf :: Handle -> PState -> Bool -> Int -> IO [Located Token]
   lazyLexBuf handle state eof size =
-    case unP (lexer False return) state of
+    case unP (layouter (lexer False) return) state of
       POk state' t -> do
         -- pprTrace "lazyLexBuf" (text (show (buffer state'))) (return ())
         if atEnd (buffer state') && not eof
@@ -238,7 +239,7 @@ getToks popts filename buf = lexAll pstate
   pstate = initPragState popts buf loc
   loc  = mkRealSrcLoc (mkFastString filename) 1 1
 
-  lexAll state = case unP (lexer False return) state of
+  lexAll state = case unP (layouter (lexer False) return) state of
                    POk _      t@(L _ ITeof) -> [t]
                    POk state' t -> t : lexAll state'
                    _ -> [L (mkSrcSpanPs (last_loc state)) ITeof]


=====================================
compiler/GHC/Parser/Layouter.hs
=====================================
@@ -0,0 +1,275 @@
+{-# LANGUAGE MultiWayIf #-}
+
+module GHC.Parser.Layouter where
+
+import GHC.Prelude
+import GHC.Hs
+import GHC.Parser.Lexer
+import GHC.Types.SrcLoc
+import GHC.Utils.Panic
+import Data.Maybe
+import Control.Monad.Trans.Class
+import Control.Monad.Trans.Cont
+import GHC.Utils.Error
+import GHC.Parser.Errors.Types
+import Data.Sequence
+import Debug.Trace
+
+data LayItem
+  = LayFlexi !PsSpan !LayHerald
+  | LayImplicit !LayHerald !Int
+    -- ^ We are inside an implicit layout block.
+    -- We know the layout herald (e.g., `do`), the indentation level and have a
+    -- list of pending closing delimiters (such as `)`, `]`, `||]`) that must
+    -- be closed before closing the implicit layout context.
+  | LayExplicit
+    -- ^ We are inside an explicit layout block.
+    -- We know which delimiters must be closed before closing the layout block.
+
+data LayHerald
+  = LetHerald
+  | DoHerald
+  | IfHerald -- ^ For -XMultiWayIf
+  | RecHerald
+  | WhereHerald
+  | OfHerald
+  | LCaseHerald
+  | LCasesHerald
+  deriving (Eq, Ord, Show)
+
+type LayContext = (LayItem, [Token])
+
+data LayState = LS
+  { lay_stack   :: ![LayContext]
+  , lay_output  :: !(Seq (PsLocated Token))
+  }
+
+initLayState :: LayState
+initLayState = LS { lay_stack = [], lay_output = Empty }
+
+overLayState :: (LayState -> (a, LayState)) -> P a
+overLayState f = P $ \s -> case f (lay_state s) of (a, ls) -> POk s{lay_state=ls} a
+{-# INLINE overLayState #-}
+layouter, layouterDbg :: ((PsLocated Token -> P a) -> P a)
+                      -> ((Located Token -> P a) -> P a)
+
+getLayStack :: P [LayContext]
+getLayStack = P $ \s -> POk s (lay_stack (lay_state s))
+
+-- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
+layouterDbg lexer cont = layouter lexer contDbg
+  where
+    contDbg tok = trace ("token: " ++ show (unLoc tok)) (cont tok)
+
+layouter lexer = runContT $ yieldOutput $ ContT lexer >>= lift . interp lay
+
+data LayLang = PsLocated Token ::: LayLang | Done [LayContext]
+infixr :::
+
+interp :: ((ExtBits -> Bool) -> PsLocated Token -> [LayContext] -> LayLang) -> PsLocated Token -> P ()
+interp lay tok = do
+  stk <- getLayStack
+  bits <- pExtsBitmap <$> getParserOpts
+  go (lay (`xtest` bits) tok stk)
+  where
+    go (Done stk) = overLayState $ \s -> ((), s{lay_stack = stk})
+    go (tok ::: l) = enqueueOutput tok >> go l
+
+lay :: (ExtBits -> Bool) -> PsLocated Token -> [LayContext] -> LayLang
+lay ext ltok@(L span tok) = lay_module
+  where
+    offset | ITeof <- tok = 0
+           | otherwise    = srcSpanStartCol (psRealSpan span)
+    indent_decreasing h old new
+      | isLayHeraldNonDecreasing h      = old > new
+      | ext NondecreasingIndentationBit = old > new
+      | otherwise                       = old >= new
+
+    lay_module []
+      | ITocurly <- tok = ltok ::: Done [(LayExplicit,[])]
+      | ITwhere <- tok  = ltok ::: Done [(LayFlexi span WhereHerald,[])]
+      | otherwise       = ltok ::: Done []
+    lay_module stk      = lay_bol stk
+
+    lay_bol [] | ITeof <- tok = ltok ::: Done []
+               | otherwise    = panic (show span ++ " " ++ show tok)
+    lay_bol stk@((item,clos):stk') = case item of
+      LayImplicit herald offs -> case compare offset offs of
+        LT | LetHerald <- herald, ITin <- tok
+           -> L span ITvccurly ::: ltok ::: Done stk' -- So that `in` does not close multiple blocks
+           | otherwise
+           -> L span ITvccurly ::: lay_bol stk' -- NB: pop item
+        EQ | isInfixForm tok -- an (e.g.) `where` on the same indent would require something to the left of where; leave the current block
+           -> L span ITvccurly ::: lay_bol stk'
+           | generateSemis herald
+           -> L span ITsemi    ::: lay_rest ((item,clos):stk')
+        _  -> lay_rest ((item,clos):stk')
+      LayFlexi span herald
+        | ITocurly <- tok
+        -> ltok ::: Done ((LayExplicit,[]):stk')
+        | IfHerald <- herald, not (isVBar tok)
+        -> lay_rest stk' -- Vanilla If -> no layout
+        | (LayImplicit _ prev_off, _) : _ <- stk'
+        , indent_decreasing herald prev_off offset
+        -> L span ITvocurly ::: L span ITvccurly ::: lay_bol stk'
+        | [] <- stk'
+        , ITeof <- tok -- Directory.Internal.Windows: `module M where\n `
+        -> L span ITvocurly ::: L span ITvccurly ::: lay_bol stk'
+        | otherwise
+        -> L span ITvocurly ::: lay_rest ((LayImplicit herald offset,[]):stk')
+      LayExplicit{} -> lay_rest stk
+    lay_rest stk = case tok of
+      ITccurly | (LayExplicit,_):stk' <- stk -> ltok ::: Done stk'
+               | (LayImplicit{},_):stk' <- stk -> L span ITvccurly ::: lay_rest stk'
+      ITocurly -> ltok ::: Done ((LayExplicit,[]):stk)
+      _ | (item at LayImplicit{},clos):stk' <- stk, isClosingDelim tok
+        -> case clos of
+             clo:clos | clo `eqClosingDelim` tok
+               -> ltok ::: Done ((item,clos):stk')
+             _ -> L span ITvccurly ::: lay_rest stk'
+        | (LayImplicit LetHerald _,_):stk' <- stk, ITin <- tok
+        -> L span ITvccurly ::: ltok ::: Done stk' -- for let .. in
+        | (LayImplicit herald _,_):stk' <- stk, tok `killsLayoutOf` herald
+        -> L span ITvccurly ::: lay_rest stk'
+        | Just clo <- isOpeningDelim_maybe tok
+        , (item,clos):stk' <- stk
+        -> ltok ::: Done ((item,clo:clos):stk')
+        | Just herald <- isLayHerald_maybe tok
+        -> ltok ::: Done ((LayFlexi span herald,[]):stk)
+        | otherwise
+        -> ltok ::: Done stk
+
+yieldOutput :: ContT r P () -> ContT r P (Located Token)
+yieldOutput next = lift dequeueOutput >>= \mb_ltok -> case mb_ltok of
+  Nothing -> next >> yieldOutput (panic "should not need to do next twice")
+  Just (L span tok) -> return (L (mkSrcSpanPs span) tok)
+
+enqueueOutput :: PsLocated Token -> P ()
+enqueueOutput tk = overLayState $ \s -> trace ("token: " ++ show (unLoc tk)) ((), s{lay_output = lay_output s :|> tk})
+
+dequeueOutput :: P (Maybe (PsLocated Token))
+dequeueOutput = overLayState $ \s -> case lay_output s of
+  Empty -> (Nothing, s)
+  tk :<| tks -> (Just tk, s {lay_output = tks})
+
+pushLayStack :: LayItem -> P ()
+pushLayStack l = overLayState $ \s -> ((), s{lay_stack = (l,[]):lay_stack s})
+
+popLayStack :: P (Maybe LayContext)
+popLayStack = overLayState $ \s -> case lay_stack s of
+  []    -> (Nothing, s)
+  l:stk -> (Just l, s{lay_stack = stk})
+
+pushClosingTok :: Token -> P ()
+pushClosingTok tok = overLayState $ \s -> case lay_stack s of
+  []           -> panic "impossible"
+  (l,toks):stk -> ((), s{lay_stack = (l,tok:toks):stk})
+
+popClosingTok :: P ()
+popClosingTok = overLayState $ \s -> case lay_stack s of
+  (l,_:toks):stk -> ((), s{lay_stack = (l,toks):stk})
+  (l,[]):stk -> ((), s{lay_stack = (l,[]):stk}) -- genuinely can happen on error, I think. ex: `do foo)`
+  []         -> panic "impossible"
+
+isInfixForm :: Token -> Bool
+isInfixForm ITwhere    = True
+isInfixForm ITvarsym{} = True
+isInfixForm _          = False
+
+isOpeningDelim_maybe :: Token -> Maybe Token
+isOpeningDelim_maybe IToparen = Just ITcparen
+isOpeningDelim_maybe ITobrack = Just ITcbrack
+-- isOpeningDelim_maybe ITocurly = Just ITccurly
+isOpeningDelim_maybe IToubxparen = Just ITcubxparen
+isOpeningDelim_maybe (IToparenbar uni) = Just (ITcparenbar uni)
+isOpeningDelim_maybe (ITopenExpQuote _ uni) = Just (ITcloseQuote uni)
+isOpeningDelim_maybe ITopenTypQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenPatQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenDecQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenTExpQuote{} = Just ITcloseTExpQuote
+isOpeningDelim_maybe _ = Nothing
+
+isClosingDelim :: Token -> Bool
+isClosingDelim ITcparen = True
+isClosingDelim ITcbrack = True
+-- isClosingDelim ITccurly = True
+isClosingDelim ITcubxparen = True
+isClosingDelim ITcparenbar{} = True
+isClosingDelim ITcloseQuote{} = True
+isClosingDelim ITcloseTExpQuote = True
+isClosingDelim _ = False
+
+eqClosingDelim :: Token -> Token -> Bool
+eqClosingDelim ITcparen ITcparen = True
+eqClosingDelim ITcbrack ITcbrack = True
+-- eqClosingDelim ITccurly ITccurly = True
+eqClosingDelim ITcubxparen ITcubxparen = True
+eqClosingDelim (ITcparenbar uni1) (ITcparenbar uni2) = uni1 == uni2
+eqClosingDelim (ITcloseQuote uni1) (ITcloseQuote uni2) = uni1 == uni2
+eqClosingDelim ITcloseTExpQuote ITcloseTExpQuote = True
+eqClosingDelim _ _ = False
+
+separatesDelim :: Token -> Token -> Bool
+separatesDelim ITcomma ITcparen    = True
+separatesDelim ITcomma ITcbrack    = True
+separatesDelim ITcomma ITcubxparen = True
+separatesDelim _       _           = False
+
+generateSemis :: LayHerald -> Bool
+generateSemis IfHerald = False
+generateSemis _        = True
+
+isVBar :: Token -> Bool
+isVBar ITvbar = True
+isVBar _      = False
+
+isPragma :: Token -> Bool
+isPragma ITinline_prag{} = True
+isPragma ITopaque_prag{} = True
+isPragma ITspec_prag{} = True
+isPragma ITspec_inline_prag{} = True
+isPragma ITsource_prag{} = True
+isPragma ITrules_prag{} = True
+isPragma ITwarning_prag{} = True
+isPragma ITdeprecated_prag{} = True
+isPragma ITline_prag{} = True
+isPragma ITcolumn_prag{} = True
+isPragma ITscc_prag{} = True
+isPragma ITunpack_prag{} = True
+isPragma ITnounpack_prag{} = True
+isPragma ITann_prag{} = True
+isPragma ITcomplete_prag{} = True
+isPragma IToptions_prag{} = True
+isPragma ITinclude_prag{} = True
+isPragma ITlanguage_prag = True
+isPragma ITminimal_prag{} = True
+isPragma IToverlappable_prag{} = True
+isPragma IToverlapping_prag{} = True
+isPragma IToverlaps_prag{} = True
+isPragma ITincoherent_prag{} = True
+isPragma ITctype{} = True
+isPragma ITcomment_line_prag = True
+isPragma _ = False
+
+isLayHerald_maybe :: Token -> Maybe LayHerald
+isLayHerald_maybe (ITdo _)  = Just DoHerald
+isLayHerald_maybe (ITmdo _) = Just DoHerald
+isLayHerald_maybe ITof      = Just OfHerald
+isLayHerald_maybe ITlcase   = Just LCaseHerald
+isLayHerald_maybe ITlcases  = Just LCasesHerald
+isLayHerald_maybe ITlet     = Just LetHerald
+isLayHerald_maybe ITwhere   = Just WhereHerald
+isLayHerald_maybe ITrec     = Just RecHerald
+isLayHerald_maybe ITif      = Just IfHerald
+isLayHerald_maybe _         = Nothing
+
+isLayHeraldNonDecreasing :: LayHerald -> Bool
+isLayHeraldNonDecreasing DoHerald = True
+isLayHeraldNonDecreasing _        = False
+
+killsLayoutOf :: Token -> LayHerald -> Bool
+killsLayoutOf ITin LetHerald = True
+killsLayoutOf ITwhere DoHerald = True
+killsLayoutOf ITin OfHerald = True
+-- killsLayoutOf ITwhere OfHerald = True -- not true! `case x of True -> bar where ...; False -> foo where ...` is OK
+killsLayoutOf _ _ = False


=====================================
compiler/GHC/Parser/Layouter.hs-boot
=====================================
@@ -0,0 +1,6 @@
+module GHC.Parser.Layouter where
+
+import GHC.Prelude
+
+data LayState
+initLayState :: LayState


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -60,7 +60,7 @@ module GHC.Parser.Lexer (
    P(..), ParseResult(POk, PFailed),
    allocateComments, allocatePriorComments, allocateFinalComments,
    MonadP(..), getBit,
-   getRealSrcLoc, getPState,
+   getRealSrcLoc, getPState, getLastLoc,
    failMsgP, failLocMsgP, srcParseFail,
    getPsErrorMessages, getPsMessages,
    popContext, pushModuleContext, setLastToken, setSrcLoc,
@@ -93,6 +93,7 @@ import qualified Data.List.NonEmpty as NE
 import Data.Maybe
 import Data.Word
 import Debug.Trace (trace)
+import {-# SOURCE #-} GHC.Parser.Layouter
 
 import GHC.Data.EnumSet as EnumSet
 
@@ -1999,15 +2000,15 @@ do_bol span _str _len _buf2 = do
         if b then return (L span ITcomment_line_prag) else do
           (pos, gen_semic) <- getOffside
           case pos of
-              LT -> do
-                  --trace "layout: inserting '}'" $ do
-                  popContext
-                  -- do NOT pop the lex state, we might have a ';' to insert
-                  return (L span ITvccurly)
-              EQ | gen_semic -> do
-                  --trace "layout: inserting ';'" $ do
-                  _ <- popLexState
-                  return (L span ITsemi)
+--              LT -> do
+--                  --trace "layout: inserting '}'" $ do
+--                  popContext
+--                  -- do NOT pop the lex state, we might have a ';' to insert
+--                  return (L span ITvccurly)
+--              EQ | gen_semic -> do
+--                  --trace "layout: inserting ';'" $ do
+--                  _ <- popLexState
+--                  return (L span ITsemi)
               _ -> do
                   _ <- popLexState
                   lexToken
@@ -2024,15 +2025,15 @@ maybe_layout t = do -- If the alternative layout rule is enabled then
                     -- context.
                     alr <- getBit AlternativeLayoutRuleBit
                     unless alr $ f t
-    where f (ITdo _)    = pushLexState layout_do
-          f (ITmdo _)   = pushLexState layout_do
-          f ITof        = pushLexState layout
-          f ITlcase     = pushLexState layout
-          f ITlcases    = pushLexState layout
-          f ITlet       = pushLexState layout
-          f ITwhere     = pushLexState layout
-          f ITrec       = pushLexState layout
-          f ITif        = pushLexState layout_if
+    where f (ITdo _)    = return () -- pushLexState layout_do
+          f (ITmdo _)   = return () -- pushLexState layout_do
+          f ITof        = return () -- pushLexState layout
+          f ITlcase     = return () -- pushLexState layout
+          f ITlcases    = return () -- pushLexState layout
+          f ITlet       = return () -- pushLexState layout
+          f ITwhere     = return () -- pushLexState layout
+          f ITrec       = return () -- pushLexState layout
+          f ITif        = return () -- pushLexState layout_if
           f _           = return ()
 
 -- Pushing a new implicit layout context.  If the indentation of the
@@ -2469,6 +2470,8 @@ data PState = PState {
         -- token doesn't need to close anything:
         alr_justClosedExplicitLetBlock :: Bool,
 
+        lay_state :: LayState,
+
         -- The next three are used to implement Annotations giving the
         -- locations of 'noise' tokens in the source, so that users of
         -- the GHC API can do source to source conversions.
@@ -3009,6 +3012,7 @@ initParserState options buf loc =
       alr_context = [],
       alr_expecting_ocurly = Nothing,
       alr_justClosedExplicitLetBlock = False,
+      lay_state = initLayState,
       eof_pos = Strict.Nothing,
       header_comments = Strict.Nothing,
       comment_q = [],
@@ -3236,7 +3240,7 @@ lexError e = do
 -- This is the top-level function: called from the parser each time a
 -- new token is to be read from the input.
 
-lexer, lexerDbg :: Bool -> (Located Token -> P a) -> P a
+lexer, lexerDbg :: Bool -> (PsLocated Token -> P a) -> P a
 
 lexer queueComments cont = do
   alr <- getBit AlternativeLayoutRuleBit
@@ -3246,7 +3250,7 @@ lexer queueComments cont = do
 
   if (queueComments && isComment tok)
     then queueComment (L (psRealSpan span) tok) >> lexer queueComments cont
-    else cont (L (mkSrcSpanPs span) tok)
+    else cont (L span tok)
 
 -- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
 lexerDbg queueComments cont = lexer queueComments contDbg
@@ -3526,7 +3530,7 @@ lexTokenStream opts buf loc = unP go initState{ options = opts' }
       ltok <- lexer False return
       case ltok of
         L _ ITeof -> return []
-        _ -> liftM (ltok:) go
+        L span tk -> liftM (L (mkSrcSpanPs span) tk:) go
 
 linePrags = Map.singleton "line" linePrag
 


=====================================
compiler/ghc.cabal.in
=====================================
@@ -642,6 +642,7 @@ Library
         GHC.Parser.Errors.Ppr
         GHC.Parser.Errors.Types
         GHC.Parser.Header
+        GHC.Parser.Layouter
         GHC.Parser.Lexer
         GHC.Parser.HaddockLex
         GHC.Parser.PostProcess



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/133923a6c07fe8ce47716fa7ea7b5e934dd9e2ba

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 10:12:00 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Tue, 15 Oct 2024 06:12:00 -0400
Subject: [Git][ghc/ghc][wip/layouter] Implemented a layouter that does not work
Message-ID: <670e3ff023c80_1b8fe9603efc135f1@gitlab.mail>



Sebastian Graf pushed to branch wip/layouter at Glasgow Haskell Compiler / GHC


Commits:
5f102494 by Sebastian Graf at 2024-10-15T12:11:45+02:00
Implemented a layouter that does not work

Counter example:

```hs
baz :: Bool -> Bool -> [Int]
baz p q = [case () of _ | p, q -> 0, 42]
```

- - - - -


7 changed files:

- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- + compiler/GHC/Parser/Layouter.hs
- + compiler/GHC/Parser/Layouter.hs-boot
- compiler/GHC/Parser/Lexer.x
- compiler/ghc.cabal.in
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -83,6 +83,7 @@ import GHC.Core.DataCon ( DataCon, dataConName )
 
 import GHC.Parser.PostProcess
 import GHC.Parser.PostProcess.Haddock
+import GHC.Parser.Layouter
 import GHC.Parser.Lexer
 import GHC.Parser.HaddockLex
 import GHC.Parser.Annotation
@@ -762,7 +763,7 @@ TH_QUASIQUOTE   { L _ (ITquasiQuote _) }
 TH_QQUASIQUOTE  { L _ (ITqQuasiQuote _) }
 
 %monad { P } { >>= } { return }
-%lexer { (lexer True) } { L _ ITeof }
+%lexer { layouter (lexer True) } { L _ ITeof }
   -- Replace 'lexer' above with 'lexerDbg'
   -- to dump the tokens fed to the parser.
 %tokentype { (Located Token) }
@@ -797,7 +798,7 @@ identifier :: { LocatedN RdrName }
 -- Backpack stuff
 
 backpack :: { [LHsUnit PackageName] }
-         : implicit_top units close { fromOL $2 }
+         : implicit_top units vccurly { fromOL $2 }
          | '{' units '}'            { fromOL $2 }
 
 units :: { OrdList (LHsUnit PackageName) }
@@ -867,7 +868,7 @@ rn :: { LRenaming }
 
 unitbody :: { OrdList (LHsUnitDecl PackageName) }
         : '{'     unitdecls '}'   { $2 }
-        | vocurly unitdecls close { $2 }
+        | vocurly unitdecls vccurly { $2 }
 
 unitdecls :: { OrdList (LHsUnitDecl PackageName) }
         : unitdecls ';' unitdecl { $1 `appOL` unitOL $3 }
@@ -944,13 +945,13 @@ body    :: { ([TrailingAnn]
              ,([LImportDecl GhcPs], [LHsDecl GhcPs])
              ,EpLayout) }
         :  '{'            top '}'      { (fst $2, snd $2, epExplicitBraces $1 $3) }
-        |      vocurly    top close    { (fst $2, snd $2, EpVirtualBraces (getVOCURLY $1)) }
+        |      vocurly    top vccurly    { (fst $2, snd $2, EpVirtualBraces (getVOCURLY $1)) }
 
 body2   :: { ([TrailingAnn]
              ,([LImportDecl GhcPs], [LHsDecl GhcPs])
              ,EpLayout) }
         :  '{' top '}'                          { (fst $2, snd $2, epExplicitBraces $1 $3) }
-        |  missing_module_keyword top close     { ([], snd $2, EpVirtualBraces leftmostColumn) }
+        |  missing_module_keyword top vccurly     { ([], snd $2, EpVirtualBraces leftmostColumn) }
 
 
 top     :: { ([TrailingAnn]
@@ -1467,11 +1468,11 @@ where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
 ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
         :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
                                                 ,Just (unLoc $2)) }
-        | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
+        | vocurly ty_fam_inst_eqns vccurly   { let (L loc _) = $2 in
                                              L loc ([],Just (unLoc $2)) }
         |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
                                                  ,mcc $3],Nothing) }
-        | vocurly '..' close               { let (L loc _) = $2 in
+        | vocurly '..' vccurly               { let (L loc _) = $2 in
                                              L loc ([mj AnnDotdot $2],Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
@@ -1724,7 +1725,7 @@ cvars1 :: { [RecordPatSynField GhcPs] }
 where_decls :: { LocatedL (OrdList (LHsDecl GhcPs)) }
         : 'where' '{' decls '}'       {% amsr (sLL $1 $> (snd $ unLoc $3))
                                               (AnnList (Just $ glR $3) (Just $ moc $2) (Just $ mcc $4) (mj AnnWhere $1: (fst $ unLoc $3)) []) }
-        | 'where' vocurly decls close {% amsr (sLL $1 $3 (snd $ unLoc $3))
+        | 'where' vocurly decls vccurly {% amsr (sLL $1 $3 (snd $ unLoc $3))
                                               (AnnList (Just $ glR $3) Nothing Nothing (mj AnnWhere $1: (fst $ unLoc $3)) []) }
 
 pattern_synonym_sig :: { LSig GhcPs }
@@ -1780,7 +1781,7 @@ decllist_cls
                      , EpLayout) }      -- Reversed
         : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
-        |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
+        |     vocurly decls_cls vccurly   { let { L l (anns, decls) = $2 }
                                            in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
@@ -1824,7 +1825,7 @@ decllist_inst
         :: { Located ([AddEpAnn]
                      , OrdList (LHsDecl GhcPs)) }      -- Reversed
         : '{'         decls_inst '}'    { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2),snd $ unLoc $2) }
-        |     vocurly decls_inst close  { L (gl $2) (unLoc $2) }
+        |     vocurly decls_inst vccurly  { L (gl $2) (unLoc $2) }
 
 -- Instance body
 --
@@ -1864,7 +1865,7 @@ decls   :: { Located ([AddEpAnn], OrdList (LHsDecl GhcPs)) }
 decllist :: { Located (AnnList,Located (OrdList (LHsDecl GhcPs))) }
         : '{'            decls '}'     { sLL $1 $> (AnnList (Just $ glR $2) (Just $ moc $1) (Just $ mcc $3)  (fst $ unLoc $2) []
                                                    ,sL1 $2 $ snd $ unLoc $2) }
-        |     vocurly    decls close   { L (gl $2) (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []
+        |     vocurly    decls vccurly   { L (gl $2) (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []
                                                    ,sL1 $2 $ snd $ unLoc $2) }
 
 -- Binding groups other than those of class and instance declarations
@@ -1879,7 +1880,7 @@ binds   ::  { Located (HsLocalBinds GhcPs) }
         | '{'            dbinds '}'     {% acs (comb3 $1 $2 $3) (\loc cs -> (L loc
                                              $ HsIPBinds (EpAnn (spanAsAnchor (comb3 $1 $2 $3)) (AnnList (Just$ glR $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) }
 
-        |     vocurly    dbinds close   {% acs (gl $2) (\loc cs -> (L loc
+        |     vocurly    dbinds vccurly   {% acs (gl $2) (\loc cs -> (L loc
                                              $ HsIPBinds (EpAnn (glR $1) (AnnList (Just $ glR $2) Nothing Nothing [] []) cs) (IPBinds noExtField (reverse $ unLoc $2)))) }
 
 
@@ -2492,7 +2493,7 @@ gadt_constrlist :: { Located ([AddEpAnn]
                                                          ,moc $2
                                                          ,mcc $4]
                                                         , unLoc $3) }
-        | 'where' vocurly    gadt_constrs close  {% checkEmptyGADTs $
+        | 'where' vocurly    gadt_constrs vccurly  {% checkEmptyGADTs $
                                                       L (comb2 $1 $3)
                                                         ([mj AnnWhere $1]
                                                         , unLoc $3) }
@@ -3205,7 +3206,7 @@ acmd    :: { LHsCmdTop GhcPs }
 cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
         :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
                                                   ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+        |      vocurly    cvtopdecls0 vccurly    { ([],$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -3436,11 +3437,11 @@ altslist(PATS) :: { forall b. DisambECP b => PV (LocatedL [LMatch GhcPs (Located
         : '{'        alts(PATS) '}'    { $2 >>= \ $2 -> amsr
                                            (sLL $1 $> (reverse (snd $ unLoc $2)))
                                            (AnnList (Just $ glR $2) (Just $ moc $1) (Just $ mcc $3) (fst $ unLoc $2) []) }
-        | vocurly    alts(PATS)  close { $2 >>= \ $2 -> amsr
+        | vocurly    alts(PATS)  vccurly { $2 >>= \ $2 -> amsr
                                            (L (getLoc $2) (reverse (snd $ unLoc $2)))
                                            (AnnList (Just $ glR $2) Nothing Nothing (fst $ unLoc $2) []) }
         | '{'              '}'   { amsr (sLL $1 $> []) (AnnList Nothing (Just $ moc $1) (Just $ mcc $2) [] []) }
-        | vocurly          close { return $ noLocA [] }
+        | vocurly          vccurly { return $ noLocA [] }
 
 alts(PATS) :: { forall b. DisambECP b => PV (Located ([AddEpAnn],[LMatch GhcPs (LocatedA b)])) }
         : alts1(PATS)              { $1 >>= \ $1 -> return $
@@ -3492,14 +3493,11 @@ gdpats :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) }
                          return $ sLL gdpats gdpat (gdpat : unLoc gdpats) }
         | gdpat        { $1 >>= \gdpat -> return $ sL1 gdpat [gdpat] }
 
--- layout for MultiWayIf doesn't begin with an open brace, because it's hard to
--- generate the open brace in addition to the vertical bar in the lexer, and
--- we don't need it.
 ifgdpats :: { Located ((EpToken "{", EpToken "}"), [LGRHS GhcPs (LHsExpr GhcPs)]) }
-         : '{' gdpats '}'                 {% runPV $2 >>= \ $2 ->
+         : '{'     gdpats '}'             {% runPV $2 >>= \ $2 ->
                                              return $ sLL $1 $> ((epTok $1,epTok $3),unLoc $2)  }
-         |     gdpats close               {% runPV $1 >>= \ $1 ->
-                                             return $ sL1 $1 ((NoEpTok, NoEpTok),unLoc $1) }
+         | vocurly gdpats vccurly         {% runPV $2 >>= \ $2 ->
+                                             return $ sL1 $1 ((NoEpTok, NoEpTok),unLoc $2) }
 
 gdpat   :: { forall b. DisambECP b => PV (LGRHS GhcPs (LocatedA b)) }
         : '|' guardquals '->' exp
@@ -3550,7 +3548,7 @@ apat    : aexp                  {% (checkPattern <=< runPV) (unECP $1) }
 stmtlist :: { forall b. DisambECP b => PV (LocatedL [LocatedA (Stmt GhcPs (LocatedA b))]) }
         : '{'           stmts '}'       { $2 >>= \ $2 ->
                                           amsr (sLL $1 $> (reverse $ snd $ unLoc $2)) (AnnList (stmtsAnchor $2) (Just $ moc $1) (Just $ mcc $3) (fromOL $ fst $ unLoc $2) []) }
-        |     vocurly   stmts close     { $2 >>= \ $2 -> amsr
+        |     vocurly   stmts vccurly   { $2 >>= \ $2 -> amsr
                                           (L (stmtsLoc $2) (reverse $ snd $ unLoc $2)) (AnnList (stmtsAnchor $2) Nothing Nothing (fromOL $ fst $ unLoc $2) []) }
 
 --      do { ;; s ; s ; ; s ;; }
@@ -4133,7 +4131,7 @@ unrelated tokens.
 -}
 close :: { () }
         : vccurly               { () } -- context popped in lexer.
-        | error                 {% popContext } -- See Note [Layout and error]
+--        | error                 {% popContext } -- See Note [Layout and error]
 
 -----------------------------------------------------------------------------
 -- Miscellaneous (mostly renamings)


=====================================
compiler/GHC/Parser/Header.hs
=====================================
@@ -28,6 +28,7 @@ import GHC.Driver.Errors.Types -- Unfortunate, needed due to the fact we throw e
 
 import GHC.Parser.Errors.Types
 import GHC.Parser           ( parseHeader )
+import GHC.Parser.Layouter
 import GHC.Parser.Lexer
 
 import GHC.Hs
@@ -203,7 +204,7 @@ lazyGetToks popts filename handle = do
 
   lazyLexBuf :: Handle -> PState -> Bool -> Int -> IO [Located Token]
   lazyLexBuf handle state eof size =
-    case unP (lexer False return) state of
+    case unP (layouter (lexer False) return) state of
       POk state' t -> do
         -- pprTrace "lazyLexBuf" (text (show (buffer state'))) (return ())
         if atEnd (buffer state') && not eof
@@ -238,7 +239,7 @@ getToks popts filename buf = lexAll pstate
   pstate = initPragState popts buf loc
   loc  = mkRealSrcLoc (mkFastString filename) 1 1
 
-  lexAll state = case unP (lexer False return) state of
+  lexAll state = case unP (layouter (lexer False) return) state of
                    POk _      t@(L _ ITeof) -> [t]
                    POk state' t -> t : lexAll state'
                    _ -> [L (mkSrcSpanPs (last_loc state)) ITeof]


=====================================
compiler/GHC/Parser/Layouter.hs
=====================================
@@ -0,0 +1,275 @@
+{-# LANGUAGE MultiWayIf #-}
+
+module GHC.Parser.Layouter where
+
+import GHC.Prelude
+import GHC.Hs
+import GHC.Parser.Lexer
+import GHC.Types.SrcLoc
+import GHC.Utils.Panic
+import Data.Maybe
+import Control.Monad.Trans.Class
+import Control.Monad.Trans.Cont
+import GHC.Utils.Error
+import GHC.Parser.Errors.Types
+import Data.Sequence
+import Debug.Trace
+
+data LayItem
+  = LayFlexi !PsSpan !LayHerald
+  | LayImplicit !LayHerald !Int
+    -- ^ We are inside an implicit layout block.
+    -- We know the layout herald (e.g., `do`), the indentation level and have a
+    -- list of pending closing delimiters (such as `)`, `]`, `||]`) that must
+    -- be closed before closing the implicit layout context.
+  | LayExplicit
+    -- ^ We are inside an explicit layout block.
+    -- We know which delimiters must be closed before closing the layout block.
+
+data LayHerald
+  = LetHerald
+  | DoHerald
+  | IfHerald -- ^ For -XMultiWayIf
+  | RecHerald
+  | WhereHerald
+  | OfHerald
+  | LCaseHerald
+  | LCasesHerald
+  deriving (Eq, Ord, Show)
+
+type LayContext = (LayItem, [Token])
+
+data LayState = LS
+  { lay_stack   :: ![LayContext]
+  , lay_output  :: !(Seq (PsLocated Token))
+  }
+
+initLayState :: LayState
+initLayState = LS { lay_stack = [], lay_output = Empty }
+
+overLayState :: (LayState -> (a, LayState)) -> P a
+overLayState f = P $ \s -> case f (lay_state s) of (a, ls) -> POk s{lay_state=ls} a
+{-# INLINE overLayState #-}
+layouter, layouterDbg :: ((PsLocated Token -> P a) -> P a)
+                      -> ((Located Token -> P a) -> P a)
+
+getLayStack :: P [LayContext]
+getLayStack = P $ \s -> POk s (lay_stack (lay_state s))
+
+-- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
+layouterDbg lexer cont = layouter lexer contDbg
+  where
+    contDbg tok = trace ("token: " ++ show (unLoc tok)) (cont tok)
+
+layouter lexer = runContT $ yieldOutput $ ContT lexer >>= lift . interp lay
+
+data LayLang = PsLocated Token ::: LayLang | Done [LayContext]
+infixr :::
+
+interp :: ((ExtBits -> Bool) -> PsLocated Token -> [LayContext] -> LayLang) -> PsLocated Token -> P ()
+interp lay tok = do
+  stk <- getLayStack
+  bits <- pExtsBitmap <$> getParserOpts
+  go (lay (`xtest` bits) tok stk)
+  where
+    go (Done stk) = overLayState $ \s -> ((), s{lay_stack = stk})
+    go (tok ::: l) = enqueueOutput tok >> go l
+
+lay :: (ExtBits -> Bool) -> PsLocated Token -> [LayContext] -> LayLang
+lay ext ltok@(L span tok) = lay_module
+  where
+    offset | ITeof <- tok = 0
+           | otherwise    = srcSpanStartCol (psRealSpan span)
+    indent_decreasing h old new
+      | isLayHeraldNonDecreasing h      = old > new
+      | ext NondecreasingIndentationBit = old > new
+      | otherwise                       = old >= new
+
+    lay_module []
+      | ITocurly <- tok = ltok ::: Done [(LayExplicit,[])]
+      | ITwhere <- tok  = ltok ::: Done [(LayFlexi span WhereHerald,[])]
+      | otherwise       = ltok ::: Done []
+    lay_module stk      = lay_bol stk
+
+    lay_bol [] | ITeof <- tok = ltok ::: Done []
+               | otherwise    = panic (show span ++ " " ++ show tok)
+    lay_bol stk@((item,clos):stk') = case item of
+      LayImplicit herald offs -> case compare offset offs of
+        LT | LetHerald <- herald, ITin <- tok
+           -> L span ITvccurly ::: ltok ::: Done stk' -- So that `in` does not close multiple blocks
+           | otherwise
+           -> L span ITvccurly ::: lay_bol stk' -- NB: pop item
+        EQ | isInfixForm tok -- an (e.g.) `where` on the same indent would require something to the left of where; leave the current block
+           -> L span ITvccurly ::: lay_bol stk'
+           | generateSemis herald
+           -> L span ITsemi    ::: lay_rest ((item,clos):stk')
+        _  -> lay_rest ((item,clos):stk')
+      LayFlexi span herald
+        | ITocurly <- tok
+        -> ltok ::: Done ((LayExplicit,[]):stk')
+        | IfHerald <- herald, not (isVBar tok)
+        -> lay_rest stk' -- Vanilla If -> no layout
+        | (LayImplicit _ prev_off, _) : _ <- stk'
+        , indent_decreasing herald prev_off offset
+        -> L span ITvocurly ::: L span ITvccurly ::: lay_bol stk'
+        | [] <- stk'
+        , ITeof <- tok -- Directory.Internal.Windows: `module M where\n `
+        -> L span ITvocurly ::: L span ITvccurly ::: lay_bol stk'
+        | otherwise
+        -> L span ITvocurly ::: lay_rest ((LayImplicit herald offset,[]):stk')
+      LayExplicit{} -> lay_rest stk
+    lay_rest stk = case tok of
+      ITccurly | (LayExplicit,_):stk' <- stk -> ltok ::: Done stk'
+               | (LayImplicit{},_):stk' <- stk -> L span ITvccurly ::: lay_rest stk'
+      ITocurly -> ltok ::: Done ((LayExplicit,[]):stk)
+      _ | (item at LayImplicit{},clos):stk' <- stk, isClosingDelim tok
+        -> case clos of
+             clo:clos | clo `eqClosingDelim` tok
+               -> ltok ::: Done ((item,clos):stk')
+             _ -> L span ITvccurly ::: lay_rest stk'
+        | (LayImplicit LetHerald _,_):stk' <- stk, ITin <- tok
+        -> L span ITvccurly ::: ltok ::: Done stk' -- for let .. in
+        | (LayImplicit herald _,_):stk' <- stk, tok `killsLayoutOf` herald
+        -> L span ITvccurly ::: lay_rest stk'
+        | Just clo <- isOpeningDelim_maybe tok
+        , (item,clos):stk' <- stk
+        -> ltok ::: Done ((item,clo:clos):stk')
+        | Just herald <- isLayHerald_maybe tok
+        -> ltok ::: Done ((LayFlexi span herald,[]):stk)
+        | otherwise
+        -> ltok ::: Done stk
+
+yieldOutput :: ContT r P () -> ContT r P (Located Token)
+yieldOutput next = lift dequeueOutput >>= \mb_ltok -> case mb_ltok of
+  Nothing -> next >> yieldOutput (panic "should not need to do next twice")
+  Just (L span tok) -> return (L (mkSrcSpanPs span) tok)
+
+enqueueOutput :: PsLocated Token -> P ()
+enqueueOutput tk = overLayState $ \s -> trace ("token: " ++ show (unLoc tk)) ((), s{lay_output = lay_output s :|> tk})
+
+dequeueOutput :: P (Maybe (PsLocated Token))
+dequeueOutput = overLayState $ \s -> case lay_output s of
+  Empty -> (Nothing, s)
+  tk :<| tks -> (Just tk, s {lay_output = tks})
+
+pushLayStack :: LayItem -> P ()
+pushLayStack l = overLayState $ \s -> ((), s{lay_stack = (l,[]):lay_stack s})
+
+popLayStack :: P (Maybe LayContext)
+popLayStack = overLayState $ \s -> case lay_stack s of
+  []    -> (Nothing, s)
+  l:stk -> (Just l, s{lay_stack = stk})
+
+pushClosingTok :: Token -> P ()
+pushClosingTok tok = overLayState $ \s -> case lay_stack s of
+  []           -> panic "impossible"
+  (l,toks):stk -> ((), s{lay_stack = (l,tok:toks):stk})
+
+popClosingTok :: P ()
+popClosingTok = overLayState $ \s -> case lay_stack s of
+  (l,_:toks):stk -> ((), s{lay_stack = (l,toks):stk})
+  (l,[]):stk -> ((), s{lay_stack = (l,[]):stk}) -- genuinely can happen on error, I think. ex: `do foo)`
+  []         -> panic "impossible"
+
+isInfixForm :: Token -> Bool
+isInfixForm ITwhere    = True
+isInfixForm ITvarsym{} = True
+isInfixForm _          = False
+
+isOpeningDelim_maybe :: Token -> Maybe Token
+isOpeningDelim_maybe IToparen = Just ITcparen
+isOpeningDelim_maybe ITobrack = Just ITcbrack
+-- isOpeningDelim_maybe ITocurly = Just ITccurly
+isOpeningDelim_maybe IToubxparen = Just ITcubxparen
+isOpeningDelim_maybe (IToparenbar uni) = Just (ITcparenbar uni)
+isOpeningDelim_maybe (ITopenExpQuote _ uni) = Just (ITcloseQuote uni)
+isOpeningDelim_maybe ITopenTypQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenPatQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenDecQuote = Just (ITcloseQuote NormalSyntax)
+isOpeningDelim_maybe ITopenTExpQuote{} = Just ITcloseTExpQuote
+isOpeningDelim_maybe _ = Nothing
+
+isClosingDelim :: Token -> Bool
+isClosingDelim ITcparen = True
+isClosingDelim ITcbrack = True
+-- isClosingDelim ITccurly = True
+isClosingDelim ITcubxparen = True
+isClosingDelim ITcparenbar{} = True
+isClosingDelim ITcloseQuote{} = True
+isClosingDelim ITcloseTExpQuote = True
+isClosingDelim _ = False
+
+eqClosingDelim :: Token -> Token -> Bool
+eqClosingDelim ITcparen ITcparen = True
+eqClosingDelim ITcbrack ITcbrack = True
+-- eqClosingDelim ITccurly ITccurly = True
+eqClosingDelim ITcubxparen ITcubxparen = True
+eqClosingDelim (ITcparenbar uni1) (ITcparenbar uni2) = uni1 == uni2
+eqClosingDelim (ITcloseQuote uni1) (ITcloseQuote uni2) = uni1 == uni2
+eqClosingDelim ITcloseTExpQuote ITcloseTExpQuote = True
+eqClosingDelim _ _ = False
+
+separatesDelim :: Token -> Token -> Bool
+separatesDelim ITcomma ITcparen    = True
+separatesDelim ITcomma ITcbrack    = True
+separatesDelim ITcomma ITcubxparen = True
+separatesDelim _       _           = False
+
+generateSemis :: LayHerald -> Bool
+generateSemis IfHerald = False
+generateSemis _        = True
+
+isVBar :: Token -> Bool
+isVBar ITvbar = True
+isVBar _      = False
+
+isPragma :: Token -> Bool
+isPragma ITinline_prag{} = True
+isPragma ITopaque_prag{} = True
+isPragma ITspec_prag{} = True
+isPragma ITspec_inline_prag{} = True
+isPragma ITsource_prag{} = True
+isPragma ITrules_prag{} = True
+isPragma ITwarning_prag{} = True
+isPragma ITdeprecated_prag{} = True
+isPragma ITline_prag{} = True
+isPragma ITcolumn_prag{} = True
+isPragma ITscc_prag{} = True
+isPragma ITunpack_prag{} = True
+isPragma ITnounpack_prag{} = True
+isPragma ITann_prag{} = True
+isPragma ITcomplete_prag{} = True
+isPragma IToptions_prag{} = True
+isPragma ITinclude_prag{} = True
+isPragma ITlanguage_prag = True
+isPragma ITminimal_prag{} = True
+isPragma IToverlappable_prag{} = True
+isPragma IToverlapping_prag{} = True
+isPragma IToverlaps_prag{} = True
+isPragma ITincoherent_prag{} = True
+isPragma ITctype{} = True
+isPragma ITcomment_line_prag = True
+isPragma _ = False
+
+isLayHerald_maybe :: Token -> Maybe LayHerald
+isLayHerald_maybe (ITdo _)  = Just DoHerald
+isLayHerald_maybe (ITmdo _) = Just DoHerald
+isLayHerald_maybe ITof      = Just OfHerald
+isLayHerald_maybe ITlcase   = Just LCaseHerald
+isLayHerald_maybe ITlcases  = Just LCasesHerald
+isLayHerald_maybe ITlet     = Just LetHerald
+isLayHerald_maybe ITwhere   = Just WhereHerald
+isLayHerald_maybe ITrec     = Just RecHerald
+isLayHerald_maybe ITif      = Just IfHerald
+isLayHerald_maybe _         = Nothing
+
+isLayHeraldNonDecreasing :: LayHerald -> Bool
+isLayHeraldNonDecreasing DoHerald = True
+isLayHeraldNonDecreasing _        = False
+
+killsLayoutOf :: Token -> LayHerald -> Bool
+killsLayoutOf ITin LetHerald = True
+killsLayoutOf ITwhere DoHerald = True
+killsLayoutOf ITin OfHerald = True
+-- killsLayoutOf ITwhere OfHerald = True -- not true! `case x of True -> bar where ...; False -> foo where ...` is OK
+killsLayoutOf _ _ = False


=====================================
compiler/GHC/Parser/Layouter.hs-boot
=====================================
@@ -0,0 +1,6 @@
+module GHC.Parser.Layouter where
+
+import GHC.Prelude
+
+data LayState
+initLayState :: LayState


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -60,7 +60,7 @@ module GHC.Parser.Lexer (
    P(..), ParseResult(POk, PFailed),
    allocateComments, allocatePriorComments, allocateFinalComments,
    MonadP(..), getBit,
-   getRealSrcLoc, getPState,
+   getRealSrcLoc, getPState, getLastLoc,
    failMsgP, failLocMsgP, srcParseFail,
    getPsErrorMessages, getPsMessages,
    popContext, pushModuleContext, setLastToken, setSrcLoc,
@@ -93,6 +93,7 @@ import qualified Data.List.NonEmpty as NE
 import Data.Maybe
 import Data.Word
 import Debug.Trace (trace)
+import {-# SOURCE #-} GHC.Parser.Layouter
 
 import GHC.Data.EnumSet as EnumSet
 
@@ -1999,15 +2000,15 @@ do_bol span _str _len _buf2 = do
         if b then return (L span ITcomment_line_prag) else do
           (pos, gen_semic) <- getOffside
           case pos of
-              LT -> do
-                  --trace "layout: inserting '}'" $ do
-                  popContext
-                  -- do NOT pop the lex state, we might have a ';' to insert
-                  return (L span ITvccurly)
-              EQ | gen_semic -> do
-                  --trace "layout: inserting ';'" $ do
-                  _ <- popLexState
-                  return (L span ITsemi)
+--              LT -> do
+--                  --trace "layout: inserting '}'" $ do
+--                  popContext
+--                  -- do NOT pop the lex state, we might have a ';' to insert
+--                  return (L span ITvccurly)
+--              EQ | gen_semic -> do
+--                  --trace "layout: inserting ';'" $ do
+--                  _ <- popLexState
+--                  return (L span ITsemi)
               _ -> do
                   _ <- popLexState
                   lexToken
@@ -2024,15 +2025,15 @@ maybe_layout t = do -- If the alternative layout rule is enabled then
                     -- context.
                     alr <- getBit AlternativeLayoutRuleBit
                     unless alr $ f t
-    where f (ITdo _)    = pushLexState layout_do
-          f (ITmdo _)   = pushLexState layout_do
-          f ITof        = pushLexState layout
-          f ITlcase     = pushLexState layout
-          f ITlcases    = pushLexState layout
-          f ITlet       = pushLexState layout
-          f ITwhere     = pushLexState layout
-          f ITrec       = pushLexState layout
-          f ITif        = pushLexState layout_if
+    where f (ITdo _)    = return () -- pushLexState layout_do
+          f (ITmdo _)   = return () -- pushLexState layout_do
+          f ITof        = return () -- pushLexState layout
+          f ITlcase     = return () -- pushLexState layout
+          f ITlcases    = return () -- pushLexState layout
+          f ITlet       = return () -- pushLexState layout
+          f ITwhere     = return () -- pushLexState layout
+          f ITrec       = return () -- pushLexState layout
+          f ITif        = return () -- pushLexState layout_if
           f _           = return ()
 
 -- Pushing a new implicit layout context.  If the indentation of the
@@ -2469,6 +2470,8 @@ data PState = PState {
         -- token doesn't need to close anything:
         alr_justClosedExplicitLetBlock :: Bool,
 
+        lay_state :: LayState,
+
         -- The next three are used to implement Annotations giving the
         -- locations of 'noise' tokens in the source, so that users of
         -- the GHC API can do source to source conversions.
@@ -3009,6 +3012,7 @@ initParserState options buf loc =
       alr_context = [],
       alr_expecting_ocurly = Nothing,
       alr_justClosedExplicitLetBlock = False,
+      lay_state = initLayState,
       eof_pos = Strict.Nothing,
       header_comments = Strict.Nothing,
       comment_q = [],
@@ -3236,7 +3240,7 @@ lexError e = do
 -- This is the top-level function: called from the parser each time a
 -- new token is to be read from the input.
 
-lexer, lexerDbg :: Bool -> (Located Token -> P a) -> P a
+lexer, lexerDbg :: Bool -> (PsLocated Token -> P a) -> P a
 
 lexer queueComments cont = do
   alr <- getBit AlternativeLayoutRuleBit
@@ -3246,7 +3250,7 @@ lexer queueComments cont = do
 
   if (queueComments && isComment tok)
     then queueComment (L (psRealSpan span) tok) >> lexer queueComments cont
-    else cont (L (mkSrcSpanPs span) tok)
+    else cont (L span tok)
 
 -- Use this instead of 'lexer' in GHC.Parser to dump the tokens for debugging.
 lexerDbg queueComments cont = lexer queueComments contDbg
@@ -3526,7 +3530,7 @@ lexTokenStream opts buf loc = unP go initState{ options = opts' }
       ltok <- lexer False return
       case ltok of
         L _ ITeof -> return []
-        _ -> liftM (ltok:) go
+        L span tk -> liftM (L (mkSrcSpanPs span) tk:) go
 
 linePrags = Map.singleton "line" linePrag
 


=====================================
compiler/ghc.cabal.in
=====================================
@@ -642,6 +642,7 @@ Library
         GHC.Parser.Errors.Ppr
         GHC.Parser.Errors.Types
         GHC.Parser.Header
+        GHC.Parser.Layouter
         GHC.Parser.Lexer
         GHC.Parser.HaddockLex
         GHC.Parser.PostProcess


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
=====================================
@@ -13,6 +13,7 @@ import GHC.Data.Bag (bagToList)
 import GHC.Data.FastString (mkFastString)
 import GHC.Data.StringBuffer (StringBuffer, atEnd)
 import GHC.Parser.Errors.Ppr ()
+import GHC.Parser.Layouter as Layouter
 import GHC.Parser.Lexer as Lexer
   ( P (..)
   , PState (..)
@@ -76,7 +77,7 @@ parse parserOpts sDocContext fpath bs = case unP (go False []) initState of
 
     -- \| Like 'Lexer.lexer', but slower, with a better API, and filtering out empty tokens
     wrappedLexer :: P (RealLocated Lexer.Token)
-    wrappedLexer = Lexer.lexer False andThen
+    wrappedLexer = Layouter.layouter (Lexer.lexer False) andThen
       where
         andThen (L (RealSrcSpan s _) t)
           | srcSpanStartLine s /= srcSpanEndLine s
@@ -104,7 +105,7 @@ parse parserOpts sDocContext fpath bs = case unP (go False []) initState of
     parsePlainTok :: Bool -> MaybeT P ([T.Token], Bool) -- return list is only ever 0-2 elements
     parsePlainTok inPrag = do
       (bInit, lInit) <- lift getInput
-      L sp tok <- tryP (Lexer.lexer False return)
+      L sp tok <- tryP (Layouter.layouter (Lexer.lexer False) return)
       (bEnd, _) <- lift getInput
       case sp of
         UnhelpfulSpan _ -> pure ([], False) -- pretend the token never existed



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f102494dbe42179ae9453d801d8c490b4c3596e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 10:51:33 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Tue, 15 Oct 2024 06:51:33 -0400
Subject: [Git][ghc/ghc][wip/T23479] 6 commits: Desugaring, plus
 -Wincomplete-record-selectors
Message-ID: <670e493514dad_35167fbcf70914e5@gitlab.mail>



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


Commits:
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
1d0c0ea5 by Serge S. Gulin at 2024-10-15T13:51:23+03:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc2c9e9ab8428e6182bd9d387f5eb887cff2c6c...1d0c0ea515c2e1d865240cfa4dec564a9d6442fb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc2c9e9ab8428e6182bd9d387f5eb887cff2c6c...1d0c0ea515c2e1d865240cfa4dec564a9d6442fb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 11:22:50 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 15 Oct 2024 07:22:50 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Desugaring, 
 plus -Wincomplete-record-selectors
Message-ID: <670e508a77e9a_35167f28e3bc94387@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
ad1d8e12 by ARATA Mizuki at 2024-10-15T07:22:41-04:00
Handle implications between x86 feature flags

This includes:

* Multiple -msse* options can be specified
* -mavx implies -msse4.2
* -mavx2 implies -mavx
* -mfma implies -mavx
* -mavx512f implies -mavx2 and -mfma

Closes #24989

Co-authored-by: sheaf <sam.derbyshire at gmail.com>

- - - - -
d045238b by Hassan Al-Awwadi at 2024-10-15T07:22:42-04:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42ab1a1709cdc78a4d64f4c1c3009f907df39487...d045238bf74edfb4fabd2ca4f8086f56e44ffd8a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42ab1a1709cdc78a4d64f4c1c3009f907df39487...d045238bf74edfb4fabd2ca4f8086f56e44ffd8a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 13:17:14 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 15 Oct 2024 09:17:14 -0400
Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 16 commits:
 users-guide: Document GHCi :where command
Message-ID: <670e6b5ad2b30_35167f8bcb1c1349a3@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC


Commits:
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
0bc12c92 by Matthew Pickering at 2024-10-15T14:16:24+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
3ca1c173 by Rodrigo Mesquita at 2024-10-15T14:16:24+01:00
Add test for #25300

- - - - -
9abd0999 by Rodrigo Mesquita at 2024-10-15T14:16:25+01:00
exceptions: Improve the message layout as per #285

This commit fixes the layout of the additional information included when
displaying an exception, namely the type of the exception.

It also fixes the default handler's heading message to work well
together with the improved display message of SomeException.

CLC proposal#285

- - - - -
b51efaee by Rodrigo Mesquita at 2024-10-15T14:16:25+01:00
Display type and callstack of exception on handler

This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.

At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.

However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).

This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.

The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.

Discussion of the ammendment is part of CLC#285.

- - - - -
2228bf1c by Rodrigo Mesquita at 2024-10-15T14:16:25+01:00
Remove redundant CallStack from exceptions

Before the exception backtraces proposal was implemented, ErrorCall
accumulated its own callstack via HasCallStack constraints, but
ExceptionContext is now accumulated automatically.

The original ErrorCall mechanism is now redundant and we get a duplicate
CallStack

Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall

CLC proposal#285

Fixes #25283

- - - - -
a88c8e47 by Rodrigo Mesquita at 2024-10-15T14:16:25+01:00
Freeze call stack in error throwing functions

CLC proposal#285

- - - - -
f5dbcdbf by Rodrigo Mesquita at 2024-10-15T14:16:26+01:00
De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too,
which was missing.

- - - - -
a68fb87b by Rodrigo Mesquita at 2024-10-15T14:16:26+01:00
Re-export NoBacktrace from Control.Exception

This was originally proposed and accepted in section
    "2.7   Capturing Backtraces on Exceptions"
of the CLC proposal for exception backtraces.

However, the implementation missed this re-export, which this commit now
fixes.

- - - - -
68b4fe07 by Rodrigo Mesquita at 2024-10-15T14:16:26+01:00
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b66cb06bc842e45ba39183cd7bd34d2186b92dbe...68b4fe075d2847f1ef7b49cd51a4cdcaff77c31a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b66cb06bc842e45ba39183cd7bd34d2186b92dbe...68b4fe075d2847f1ef7b49cd51a4cdcaff77c31a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 13:45:26 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 15 Oct 2024 09:45:26 -0400
Subject: [Git][ghc/ghc][wip/T25281] 21 commits: testsuite: Normalise trailing
 digits from hole fits output
Message-ID: <670e71f6cb134_13c4271deb8886194@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
0b3536db by Simon Peyton Jones at 2024-10-15T14:43:15+01:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9acd713c8f452ac4196906db8edcc7452f71054e...0b3536db1484b1d5763e8a15dc7a5ee8ddfc61b4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9acd713c8f452ac4196906db8edcc7452f71054e...0b3536db1484b1d5763e8a15dc7a5ee8ddfc61b4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 13:59:43 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 15 Oct 2024 09:59:43 -0400
Subject: [Git][ghc/ghc][wip/T25266] Wibble error messages
Message-ID: <670e754f6f7c3_13c4271deb881003b6@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
edd61fdc by Simon Peyton Jones at 2024-10-15T14:59:32+01:00
Wibble error messages

- - - - -


3 changed files:

- testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/typecheck/should_compile/T13785.stderr


Changes:

=====================================
testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
=====================================
@@ -1,12 +1,12 @@
 ExtraTcsUntch.hs:23:18: error: [GHC-83865]
     • Couldn't match expected type: F Int
-                  with actual type: [[a0]]
+                  with actual type: [p0]
     • In the first argument of ‘h’, namely ‘[x]’
       In the expression: h [x]
       In an equation for ‘g1’: g1 _ = h [x]
     • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
+        x :: p0 (bound at ExtraTcsUntch.hs:21:3)
+        f :: p0 -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 
 ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • Couldn't match expected type: F Int
@@ -14,7 +14,4 @@ ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • In the first argument of ‘h’, namely ‘[[undefined]]’
       In the expression: h [[undefined]]
       In the expression: (h [[undefined]], op x [y])
-    • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,7 +1,9 @@
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
-      Where: ‘k0’ is an ambiguous type variable
-             ‘a'1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘a'’
+      Where: ‘a'’ is a rigid type variable bound by
+               the inferred type of
+                 traverseCompose :: (a -> f b) -> g a -> f (h a')
+               at T14172.hs:8:1-46
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -10,19 +12,18 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
-        Actual: (Unwrapped (Compose f'0 g'1 a'0)
-                 -> f (Unwrapped (h a'1)))
-                -> Compose f'0 g'1 a'0 -> f (h a'1)
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
+        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
+                -> Compose f'0 g'1 a'0 -> f (h a')
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+          traverseCompose :: (a -> f b) -> g a -> f (h a')
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+        traverseCompose :: (a -> f b) -> g a -> f (h a')
           (bound at T14172.hs:8:1)
 


=====================================
testsuite/tests/typecheck/should_compile/T13785.stderr
=====================================
@@ -1,12 +1,13 @@
-
-T13785.hs:16:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
+T13785.hs:21:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
     • The Monomorphism Restriction applies to the bindings
       for ‘bar2’, ‘baz2’
     • In an equation for ‘foo’:
           foo
-            = bar >> baz >> bar2
+            = bar >> baz >> bar1 >> bar2
             where
                 bar, baz :: m Char
                 (bar, baz) = c
+                (bar1, baz1) = c :: (m Char, m Char)
                 (bar2, baz2) = c
     Suggested fix: Consider giving ‘baz2’ and ‘bar2’ a type signature
+



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 14:02:47 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 15 Oct 2024 10:02:47 -0400
Subject: [Git][ghc/ghc][wip/T17910] 5407 commits: [haddock @ 2002-04-04
 16:23:43 by simonmar]
Message-ID: <670e76073345c_13c4274a86201010ca@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T17910 at Glasgow Haskell Compiler / GHC


Commits:
2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00
[haddock @ 2002-04-04 16:23:43 by simonmar]
This is Haddock, my stab at a Haskell documentation tool.  It's not
quite ready for release yet, but I'm putting it in the repository so
others can take a look.

It uses a locally modified version of the hssource parser, extended
with support for GHC extensions and documentation annotations.

- - - - -
99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00
[haddock @ 2002-04-04 16:24:10 by simonmar]
forgot one file

- - - - -
8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00
[haddock @ 2002-04-05 13:58:15 by simonmar]
Remap names in the exported declarations to be "closer" to the current
module.  eg. if an exported declaration mentions a type 'T' which is
imported from module A then re-exported from the current module, then
links from the type or indeed the documentation will point to the
current module rather than module A.

This is to support better hiding: module A won't be referred to in the
generated output.

- - - - -
1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00
[haddock @ 2002-04-05 13:58:23 by simonmar]
update the TODO list

- - - - -
3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00
[haddock @ 2002-04-05 14:11:51 by simonmar]
Fix the anchor for a class declaration

- - - - -
c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00
[haddock @ 2002-04-05 14:18:41 by simonmar]
remove underlines on visited links

- - - - -
97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00
[haddock @ 2002-04-05 16:11:47 by simonmar]
- Update to generate more correct HTML.

- Use our own non-overloaded table combinators, as the overloaded
  versions were giving me a headache.  The improved type safety
  caught several errors in the HTML generation.

- - - - -
9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00
[haddock @ 2002-04-05 16:32:19 by simonmar]
Add width property to the title, and add TD.children for the module
contents page.

- - - - -
ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00
[haddock @ 2002-04-08 16:39:56 by simonmar]
Fix a problem with exports of the form T(..).

- - - - -
e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00
[haddock @ 2002-04-08 16:41:37 by simonmar]
- Add our own versions of Html & BlockTable for the time being.
- Add support for generating an index to the HTML backend

- - - - -
2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00
[haddock @ 2002-04-09 11:23:24 by simonmar]
Add '-- /' as a synonym for '-- |', for compatibility with IDoc.

- - - - -
3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00
[haddock @ 2002-04-09 11:33:54 by simonmar]
- add the <...> syntax for marking up URLs in documentation

- Make the output for data & class declarations more compact when
  there aren't any documentation annotations on the individual
  methods or constructors respectively.

- - - - -
5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00
[haddock @ 2002-04-09 11:36:04 by simonmar]
Update the TODO list

- - - - -
9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00
[haddock @ 2002-04-10 10:50:06 by simonmar]
Use explicit 'px' suffix on pixel sizes; IE seems to prefer them

- - - - -
052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00
[haddock @ 2002-04-10 13:23:13 by simonmar]
Lex URLs as a single token to avoid having to escape special
characters inside the URL string.

- - - - -
47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00
[haddock @ 2002-04-10 13:23:55 by simonmar]
Not sure why I made the constructor name for a record declaration into
a TyCls name, but change it back into a Var name anyhow.

- - - - -
3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00
[haddock @ 2002-04-10 13:26:09 by simonmar]
Lots of changes, including:

- add index support to the HTML backend
- clean up the renamer, put it into a monad
- propogate unresolved names to the top level and report them in a nicer way
- various bugfixes

- - - - -
c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00
[haddock @ 2002-04-10 13:32:39 by simonmar]
Skeleton documentation

- - - - -
50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00
[haddock @ 2002-04-10 13:37:23 by simonmar]
Update the TODO list, separate into pre-1.0 and post-1.0 items

- - - - -
f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00
[haddock @ 2002-04-10 14:30:58 by simonmar]
Add an introduction

- - - - -
cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00
[haddock @ 2002-04-10 14:59:51 by simonmar]
Sort the module tree

- - - - -
76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00
[haddock @ 2002-04-10 15:50:10 by simonmar]
Generate a little table of contents at the top of the module doc (only
if the module actually contains some section headings, though).

- - - - -
bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00
[haddock @ 2002-04-10 16:10:26 by simonmar]
Now we understand (or at least don't barf on) type signatures in
patterns such as you might find when scoped type variables are in use.

- - - - -
86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00
[haddock @ 2002-04-10 16:10:49 by simonmar]
more updates

- - - - -
1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00
[haddock @ 2002-04-10 16:28:05 by simonmar]
Parse errors in doc strings are now reported as warnings rather that
causing the whole thing to fall over.  It still needs cleaning up (the
warning is emitted with trace) but this will do for the time being.

- - - - -
ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00
[haddock @ 2002-04-10 16:38:03 by simonmar]
update again

- - - - -
69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00
[haddock @ 2002-04-11 13:38:02 by simonmar]
mention Opera

- - - - -
fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00
[haddock @ 2002-04-11 13:40:30 by simonmar]
- copy haddock.css into the same place as the generated HTML

- new option: --css <file>  specifies the style sheet to use

- new option:  -o <dir>  specifies the directory in which to
  generate the output.

- because Haddock now needs to know where to find its default stylesheet,
  we have to have a wrapper script and do the haddock-inplace thing
  (Makefile code copied largely from fptools/happy).

- - - - -
106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00
[haddock @ 2002-04-24 15:12:41 by simonmar]
Stop slurping comment lines when we see a row of dashes longer than
length 2: these are useful as separators.

- - - - -
995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00
[haddock @ 2002-04-24 15:14:11 by simonmar]
Grok the kind of module headers we use in fptools/libraries, and pass
the "portability", "stability", and "maintainer" strings through into
the generated HTML.  If the module header doesn't match the pattern,
then we don't include the info in the HTML.

- - - - -
e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00
[haddock @ 2002-04-24 15:16:57 by simonmar]
Done module headers now.

- - - - -
2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00
[haddock @ 2002-04-24 15:57:47 by simonmar]
Handle gcons in export lists (a common extension).

- - - - -
044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00
[haddock @ 2002-04-25 14:20:12 by simonmar]
Add the little lambda icon

- - - - -
63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00
[haddock @ 2002-04-25 14:40:05 by simonmar]
- Add support for named chunks of documentation which can be
  referenced from the export list.

- Copy the icon from $libdir to the destination in HTML mode.

- - - - -
36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00
[haddock @ 2002-04-25 16:48:36 by simonmar]
More keyboard bashing

- - - - -
7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00
[haddock @ 2002-04-26 08:43:33 by simonmar]
Package util reqd. to compile with 4.08.2

- - - - -
bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00
[haddock @ 2002-04-26 10:13:00 by simonmar]
Include $(GHC_HAPPY_OPTS) when compiling HsParser

- - - - -
31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00
[haddock @ 2002-04-26 11:18:56 by simonmar]
- support for fundeps (partially contributed by Brett Letner - thanks
  Brett).

- make it build with GHC 4.08.2

- - - - -
c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00
[haddock @ 2002-04-26 13:15:02 by simonmar]
Move the explicit formatting of the little table for the
stability/portability/maintainer info from the HTML into the CSS, and
remove the explicit table size (just right-align it).

- - - - -
520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00
[haddock @ 2002-04-26 16:01:44 by simonmar]
Yet more keyboard bashing - this is pretty much complete now.

- - - - -
2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00
[haddock @ 2002-04-26 16:02:14 by simonmar]
Add a couple of things I forgot about

- - - - -
b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00
[haddock @ 2002-04-29 15:28:12 by simonmar]
bugfix for declBinders on a NewTypeDecl

- - - - -
640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00
[haddock @ 2002-04-29 15:28:54 by simonmar]
Allow '-- |' style annotations on constructors and record fields.

- - - - -
393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00
[haddock @ 2002-04-29 15:37:32 by simonmar]
syntax fix

- - - - -
8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00
[haddock @ 2002-04-29 15:37:48 by simonmar]
Add an example

- - - - -
db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00
[haddock @ 2002-04-29 15:55:46 by simonmar]
remove a trace

- - - - -
2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00
[haddock @ 2002-04-29 15:56:19 by simonmar]
Fix for 'make install'

- - - - -
120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00
[haddock @ 2002-04-29 15:56:39 by simonmar]
Install the auxilliary bits

- - - - -
950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00
[haddock @ 2002-04-29 15:57:30 by simonmar]
Add BinDist bits

- - - - -
154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00
[haddock @ 2002-05-01 11:02:52 by simonmar]
update

- - - - -
ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00
[haddock @ 2002-05-01 11:03:26 by simonmar]
Add another item

- - - - -
bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00
[haddock @ 2002-05-03 08:50:00 by simonmar]
Fix some typos.

- - - - -
54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00
[haddock @ 2002-05-05 19:40:51 by panne]
As a temporary hack/workaround for a bug in GHC's simplifier, don't
pass Happy the -c option for generating the parsers in this
subdir. Furthermore, disable -O for HaddocParse, too.

- - - - -
e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00
[haddock @ 2002-05-06 09:51:10 by simonmar]
Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>)

- - - - -
7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00
[haddock @ 2002-05-06 12:29:26 by simonmar]
Add missing type signature (a different workaround for the bug in
GHC's simplifier).

- - - - -
cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00
[haddock @ 2002-05-06 12:30:09 by simonmar]
Remove workaround for simplifier bug in previous revision.

- - - - -
687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00
[haddock @ 2002-05-06 12:32:32 by simonmar]
Allow empty data declarations (another GHC extension).

- - - - -
8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00
[haddock @ 2002-05-06 12:49:21 by simonmar]
Fix silly bug in named documentation block lookup.

- - - - -
8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00
[haddock @ 2002-05-06 13:02:42 by simonmar]
Add another named chunk with a different name

- - - - -
68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00
[haddock @ 2002-05-06 13:32:32 by simonmar]
Be more lenient about extra paragraph breaks

- - - - -
65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00
[haddock @ 2002-05-07 15:36:36 by simonmar]
DocEmpty is a right and left-unit of DocAppend (remove it in the smart
constructor).

- - - - -
adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00
[haddock @ 2002-05-07 15:37:15 by simonmar]
Allow code blocks to be denoted with bird-tracks in addition to [...].

- - - - -
1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00
[haddock @ 2002-05-08 11:21:56 by simonmar]
Add a facility for specifying options that affect Haddock's treatment
of the module.  Options are given at the top of the module in a
comma-separated list, beginning with '-- #'.  eg.

	-- # prune, hide, ignore-exports

Options currently available, with their meanings:

  prune:
	ignore declarations which have no documentation annotations

  ignore-exports:
	act as if the export list were not specified (i.e. export
   	everything local to the module).

  hide:
	do not include this module in the generated documentation, but
 	propagate any exported definitions to modules which re-export
	them.

There's a slight change in the semantics for re-exporting a full
module by giving 'module M' in the export list: if module M does not
have the 'hide' option, then the documentation will now just contain a
reference to module M rather than the full inlined contents of that
module.

These features, and some other changes in the pipeline, are the result
of discussions between myself and Manuel Chakravarty
<chak at cse.unsw.edu.au> (author of IDoc) yesterday.

Also: some cleanups, use a Writer monad to collect error messages in
some places instead of just printing them with trace.

- - - - -
a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00
[haddock @ 2002-05-08 11:22:30 by simonmar]
Update to test new features.

- - - - -
6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00
[haddock @ 2002-05-08 13:37:25 by simonmar]
Change the markup for typewriter-font from [...] to @... at .  The
reasoning is that the '@' symbol is much less likely to be needed than
square brackets, and we don't want to have to escape square brackets
in code fragments.

This will be mildly painful in the short term, but it's better to get
the change out of the way as early as possible.

- - - - -
cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00
[haddock @ 2002-05-08 13:39:56 by simonmar]
Allow nested-style comments to be used as documentation annotations too. eg.

	{-| ... -}

is equivalent to

	-- | ...

An extra space can also be left after the comment opener: {- | ... -}.
The only version that isn't allowed is {-# ... -}, because this syntax
overlaps with Haskell pragmas;  use {- # ... -} instead.

- - - - -
db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00
[haddock @ 2002-05-08 14:48:39 by simonmar]
Add support for existential quantifiers on constructors.

- - - - -
adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00
[haddock @ 2002-05-08 15:43:25 by simonmar]
update

- - - - -
62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00
[haddock @ 2002-05-08 15:44:10 by simonmar]
Update to version 0.2

- - - - -
f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00
[haddock @ 2002-05-09 08:48:29 by simonmar]
typo

- - - - -
9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00
[haddock @ 2002-05-09 10:33:14 by simonmar]
oops, left out '/' from the special characters in the last change.

- - - - -
14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00
[haddock @ 2002-05-09 10:34:44 by simonmar]
Fix buglet

- - - - -
b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00
[haddock @ 2002-05-09 10:35:00 by simonmar]
Give a more useful instance of Show for Module.

- - - - -
f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00
[haddock @ 2002-05-09 10:37:07 by simonmar]
The last commit to Main.lhs broke the delicate balance of laziness
which was being used to avoid computing the dependency graph of
modules.

So I finally bit the bullet and did a proper topological sort of the
module graph, which turned out to be easy (stealing the Digraph module
from GHC - this really ought to be in the libraries somewhere).

- - - - -
b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00
[haddock @ 2002-05-09 10:37:25 by simonmar]
another item done

- - - - -
032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00
[haddock @ 2002-05-09 10:44:15 by simonmar]
Don't consider a module re-export as having documentation, for the
purposes of deciding whether we need a Synopsis section or not.

- - - - -
5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00
[haddock @ 2002-05-09 11:10:55 by simonmar]
Add a special case for list types in ppHsAType

- - - - -
1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00
[haddock @ 2002-05-09 12:43:06 by simonmar]
Type synonyms can accept a ctype on the RHS, to match GHC.

- - - - -
0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00
[haddock @ 2002-05-09 12:45:19 by simonmar]
Add 'stdcall' keyword

- - - - -
29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00
[haddock @ 2002-05-09 13:35:45 by simonmar]
Add System Requirements section

- - - - -
bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00
[haddock @ 2002-05-09 13:36:11 by simonmar]
Test existential types, amongst other things

- - - - -
502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00
[haddock @ 2002-05-09 13:37:35 by simonmar]
Print the module name in a doc-string parse error

- - - - -
ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00
[haddock @ 2002-05-09 13:38:04 by simonmar]
Add dependency

- - - - -
8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00
[haddock @ 2002-05-09 15:37:57 by simonmar]
Add the changelog/release notes

- - - - -
f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00
[haddock @ 2002-05-09 15:47:47 by simonmar]
mention the backquote-style of markup

- - - - -
089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00
[haddock @ 2002-05-09 15:59:45 by simonmar]
update

- - - - -
bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00
[haddock @ 2002-05-09 15:59:56 by simonmar]
Document changes since 0.1

- - - - -
00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00
[haddock @ 2002-05-10 08:22:48 by simonmar]
oops, update to version 0.2

- - - - -
a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00
[haddock @ 2002-05-10 16:05:08 by simonmar]
Only include a mini-contents if there are 2 or more sections

- - - - -
06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00
[haddock @ 2002-05-13 09:13:12 by simonmar]
fix typos

- - - - -
1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00
[haddock @ 2002-05-13 10:14:22 by simonmar]
Allow backquote as the right-hand quote as well as the left-hand
quote, as suggested by Dean Herrington.

Clean up the grammar a litte.

- - - - -
dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00
[haddock @ 2002-05-13 10:44:10 by simonmar]
a couple more things, prioritise a bit

- - - - -
a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00
[haddock @ 2002-05-13 15:19:03 by simonmar]
Cope with datatypes which have documentation on the constructor but
not the type itself, and records which have documentation on the
fields but not the constructor.  (Thanks to Ross Paterson for pointing
out the bugs).

- - - - -
a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00
[haddock @ 2002-05-13 15:20:54 by simonmar]
Fix one of the record examples

- - - - -
2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00
[haddock @ 2002-05-15 12:44:35 by simonmar]
Preserve the newline before a bird-track, but only within a paragraph.

- - - - -
1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00
[haddock @ 2002-05-15 13:03:01 by simonmar]
Reworking of the internals to support documenting function arguments
(the Most Wanted new feature by the punters).

The old method of keeping parsed documentation in a Name -> Doc
mapping wasn't going to cut it for anntations on type components,
where there's no name to attach the documentation to, so I've moved to
storing all the documentation in the abstract syntax.  Previously some
of the documentation was left in the abstract syntax by the parser,
but was later extracted into the mapping.

In order to avoid having to parameterise the abstract syntax over the
type of documentation stored in it, we have to parse the documentation
at the same time as we parse the Haskell source (well, I suppose we
could store 'Either String Doc' in the HsSyn, but that's clunky).  One
upshot is that documentation is now parsed eagerly, and documentation
parse errors are fatal (but have better line numbers in the error
message).

The new story simplifies matters for the code that processes the
source modules, because we don't have to maintain the extra Name->Doc
mapping, and it should improve efficiency a little too.

New features:

  - Function arguments and return values can now have doc annotations.

  - If you refer to a qualified name in a doc string, eg. 'IO.putStr',
    then Haddock will emit a hyperlink even if the identifier is not
    in scope, so you don't have to make sure everything referred to
    from the documentation is imported.

  - several bugs & minor infelicities fixed.

- - - - -
57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00
[haddock @ 2002-05-15 13:03:19 by simonmar]
Bump to version 0.3

- - - - -
b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00
[haddock @ 2002-05-15 13:03:41 by simonmar]
update

- - - - -
fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00
[haddock @ 2002-05-15 13:10:15 by simonmar]
Rename Foo.hs to Test.hs, and add a Makefile

- - - - -
b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00
[haddock @ 2002-05-15 13:16:07 by simonmar]
- Remove the note about function argument docs not being implemented

- Note that qualified identifiers can be used to point to entities
  that aren't in scope.

- - - - -
5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00
[haddock @ 2002-05-15 13:28:46 by simonmar]
Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson.

- - - - -
0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00
[haddock @ 2002-05-17 10:51:57 by simonmar]
Fix bugs in qualified name handling (A.B.f was returned as B.f)

- - - - -
10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00
[haddock @ 2002-05-21 10:24:52 by simonmar]
- Use an alternate tabular layout for datatypes, which is more compact
- Fix some problems with the function argument documentation

- - - - -
2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00
[haddock @ 2002-05-21 10:27:40 by simonmar]
add a few more test cases

- - - - -
01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00
[haddock @ 2002-05-21 10:28:33 by simonmar]
Rearrange a bit, and add support for tabular datatype rendering

- - - - -
a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00
[haddock @ 2002-05-27 09:03:51 by simonmar]
Lots of changes:

 - instances of a class are listed with the class, and
   instances involving a datatype are listed with that type.
   Derived instances aren't included at the moment: the calculation
   to find the instance head for a derived instance is non-trivial.

 - some formatting changes; use rows with specified height rather than
   cellspacing in some places.

 - various fixes (source file links were wrong, amongst others)

- - - - -
48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00
[haddock @ 2002-05-27 12:30:37 by simonmar]
- Put function arguments *before* the doc for the function, as suggested
  by Sven Panne.  This looks nicer when the function documentation is
  long.

- Switch to using bold for binders at the definition site, and use
  underline for keywords.  This makes the binder stand out more.

- - - - -
657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00
[haddock @ 2002-05-27 13:19:49 by simonmar]
Fix bug: we weren't renaming HsDocCommentNamed in renameDecl

- - - - -
592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00
[haddock @ 2002-05-27 14:10:27 by simonmar]
Fix some bugs in the rendering of qualified type signatures.

- - - - -
69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00
[haddock @ 2002-05-27 14:36:45 by simonmar]
warning message tweak

- - - - -
16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00
[haddock @ 2002-05-27 14:53:53 by simonmar]
hyperlinked identifiers should be in <tt>

- - - - -
8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00
[haddock @ 2002-05-27 15:56:45 by simonmar]
Do something sensible for modules which don't export anything (except
instances).

- - - - -
9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00
[haddock @ 2002-05-28 10:12:50 by simonmar]
Rename the module documentation properly (bug reported by Sven Panne).

- - - - -
ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00
[haddock @ 2002-05-28 10:13:04 by simonmar]
Add some more test cases

- - - - -
92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00
[haddock @ 2002-05-28 11:17:55 by simonmar]
If an identifier doesn't lex, then just replace it by a DocString.

- - - - -
a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00
[haddock @ 2002-05-28 16:16:19 by simonmar]
Only link to names in the current module which are actually listed in
the documentation.  A name may be exported but not present in the
documentation if it is exported as part of a 'module M' export
specifier.

- - - - -
31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00
[haddock @ 2002-05-28 16:17:11 by simonmar]
update

- - - - -
7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00
[haddock @ 2002-05-28 22:42:08 by sof]
Handle lone occurrences of '/', e.g.,

  -- | This/that.

[did this in the lexer rather than in the parser, as I couldn't
 see a way not to introduce an S/R conflict that way.]

- - - - -
093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00
[haddock @ 2002-05-29 09:09:49 by simonmar]
Back out previous change until we can find a better way to do this.

- - - - -
9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00
[haddock @ 2002-05-29 13:19:06 by simonmar]
Make the markup syntax a little more friendly:

  - single quotes are now interpreted literally unless they surround a
    valid Haskell identifier.  So for example now there's no need to
    escape a single quote used as an apostrophe.

  - text to the right of a bird track is now literal (if you want
    marked-up text in a code block, use @...@).

- - - - -
b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00
[haddock @ 2002-05-29 13:38:51 by simonmar]
Document recent changes to markup syntax

- - - - -
f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00
[haddock @ 2002-05-29 15:27:18 by simonmar]
Include the instances in abstract data types too

- - - - -
613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00
[haddock @ 2002-06-03 13:05:57 by simonmar]
Allow exporting of individual class methods and record selectors.  For
these we have to invent the correct type signature, which we do in the
simplest possible way (i.e. no context reduction nonsense in the class
case).

- - - - -
14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00
[haddock @ 2002-06-03 13:20:00 by simonmar]
Fix linking to qualified names again (thanks to Sven Panne for
pointing out the bug).

- - - - -
95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00
[haddock @ 2002-06-03 13:46:48 by simonmar]
Fix for exporting record selectors from a newtype declaration

- - - - -
272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00
[haddock @ 2002-06-03 13:56:38 by simonmar]
update to version 0.3

- - - - -
1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00
[haddock @ 2002-06-03 14:05:07 by simonmar]
Add changes in version 0.3

- - - - -
145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00
[haddock @ 2002-06-03 14:12:38 by simonmar]
Render class names as proper binders

- - - - -
052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00
[haddock @ 2002-06-03 14:15:10 by simonmar]
update, and separate into bugs, features, and cosmetic items.

- - - - -
854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00
[haddock @ 2002-06-03 14:16:13 by simonmar]
More test cases

- - - - -
466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00
[haddock @ 2002-06-03 14:16:56 by simonmar]
Example from the paper

- - - - -
9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00
[haddock @ 2002-06-03 14:17:49 by simonmar]
A debugging version of the style-sheet, which gives some tables
coloured backgrounds so we can see what's going on.

- - - - -
f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00
[haddock @ 2002-06-03 14:19:46 by simonmar]
typo

- - - - -
620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00
[haddock @ 2002-06-03 14:48:32 by simonmar]
oops, fix markup bugs

- - - - -
53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00
[haddock @ 2002-06-05 09:05:07 by simonmar]
Keep foreign imports when there is no export list (bug reported by
Sven Panne).

- - - - -
6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00
[haddock @ 2002-06-05 09:12:02 by simonmar]
Identifiers in single quotes can be symbol names too (bug reported by
Hal Daume).

- - - - -
001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00
[haddock @ 2002-06-08 14:03:36 by panne]
Tiny workaround for the fact that Haddock currently ignores
HsImportSpecs: Let the local_orig_env take precedence.
This is no real solution at all, but improves things sometimes,
e.g. in my GLUT documentation.  :-)

- - - - -
504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00
[haddock @ 2002-06-11 09:23:25 by simonmar]
portability nit

- - - - -
e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00
[haddock @ 2002-06-20 12:38:07 by simonmar]
Empty declaration fixes.

- - - - -
f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00
[haddock @ 2002-06-20 12:39:01 by simonmar]
Add support for a "prologue" - a description for the whole library,
placed on the contents page before the module list.

- - - - -
b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00
[haddock @ 2002-06-21 12:43:06 by simonmar]
When we have a single code block paragraph, don't place it in
<pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical
white space in some browsers.

- - - - -
4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00
[haddock @ 2002-06-21 15:50:42 by simonmar]
Add support for reading and writing interface files(!)

This turned out to be quite easy, and necessary to get decent
hyperlinks between the documentation for separate packages in the
libraries.

The functionality isn't quite complete yet: for a given package of
modules, you'd like to say "the HTML for these modules lives in
directory <dir>" (currently they are assumed to be all in the same
place).

Two new flags:

	--dump-interface=FILE   dump an interface file in FILE
	--read-interface=FILE	read interface from FILE

an interface file describes *all* the modules being processed.  Only
the exported names are kept in the interface: if you re-export a name
from a module in another interface the signature won't be copied.
This is a compromise to keep the size of the interfaces sensible.

Also, I added another useful option:

	--no-implicit-prelude

avoids trying to import the Prelude.  Previously this was the default,
but now importing the Prelude from elsewhere makes sense if you also
read in an interface containing the Prelude module, so Haddock imports
the Prelude implicitly according to the Haskell spec.

- - - - -
d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00
[haddock @ 2002-06-23 14:54:00 by panne]
Make it compile with newer GHCs

- - - - -
780c506b by Sven Panne at 2002-06-23T15:44:31+00:00
[haddock @ 2002-06-23 15:44:31 by panne]
Cleaned up build root handling and added more docs

- - - - -
45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00
[haddock @ 2002-06-24 14:37:42 by simonmar]
When reading an interface, allow a file path offset to be specified
which represents the path to the HTML files for the modules specified
by that interface.  The path may be either relative (to the location
of the HTML for this package), or absolute.

The syntax is

	--read-interface=PATH,FILE

where PATH is the path to the HTML, and FILE is the filename
containing the interface.

- - - - -
4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00
[haddock @ 2002-07-03 16:01:07 by simonmar]
Handle import specs properly, include 'hiding'.  Haddock now has a
complete implementation of the Haskell module system (more or less; I
won't claim it's 100% correct).

- - - - -
9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00
[haddock @ 2002-07-03 16:18:16 by simonmar]
Update

- - - - -
560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00
[haddock @ 2002-07-04 14:56:10 by simonmar]
Clean up the code that constructs the exported declarations, and fix a
couple of bugs along the way.  Now if you import a class hiding one of
the methods, then re-export the class, the version in the
documentation will correctly have the appropriate method removed.

- - - - -
2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00
[haddock @ 2002-07-04 15:26:13 by simonmar]
More bugfixes to the export handling

- - - - -
03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00
[haddock @ 2002-07-09 10:12:10 by simonmar]
Don't require that the list type comes from "Prelude" for it to be
treated as special syntax (sometimes it comes from Data.List or maybe
even GHC.Base).

- - - - -
44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00
[haddock @ 2002-07-09 10:12:51 by simonmar]
commented-out debugging code

- - - - -
97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00
[haddock @ 2002-07-09 16:33:31 by krasimir]
'Microsoft HTML Help' support

- - - - -
3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00
[haddock @ 2002-07-10 09:40:56 by simonmar]
Fix for rendering of the (->) type constructor, from Ross Paterson.

- - - - -
c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00
[haddock @ 2002-07-10 10:26:11 by simonmar]
Tweaks to the MS Help support: the extra files are now only generated
if you ask for them (--ms-help).

- - - - -
e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00
[haddock @ 2002-07-10 10:57:10 by simonmar]
Document all the new options since 0.3

- - - - -
8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00
[haddock @ 2002-07-10 10:58:31 by simonmar]
Sort the options a bit

- - - - -
abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00
[haddock @ 2002-07-15 09:19:38 by simonmar]
Fix a bug in mkExportItems when processing a module without an
explicit export list.  We were placing one copy of a declaration for
each binder in the declaration, which for a data type would mean one
copy of the whole declaration per constructor or record selector.

- - - - -
dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00
[haddock @ 2002-07-15 09:54:16 by simonmar]
merge rev. 1.35

- - - - -
bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00
[haddock @ 2002-07-15 10:14:30 by simonmar]
Be a bit more liberal in the kind of commenting styles we allow, as
suggested by Malcolm Wallace.  Mostly this consists of allowing doc
comments either side of a separator token.

In an export list, a section heading is now allowed before the comma,
as well as after it.  eg.

 	module M where (
	    T(..)
	  -- * a section heading
	  , f
	  -- * another section heading
	  , g
        )

In record fields, doc comments are allowed anywhere (previously a
doc-next was allowed only after the comma, and a doc-before was
allowed only before the comma).  eg.

	data R = C {
		-- | describes 'f'
		  f :: Int
		-- | describes 'g'
		, g :: Int
		}

- - - - -
8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00
[haddock @ 2002-07-15 10:21:56 by simonmar]
Mention alternative commenting styles.

- - - - -
fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00
[haddock @ 2002-07-15 16:16:50 by simonmar]
Allow multiple sections/subsections before and after a comma in the
export list.

Also at the same time I made the syntax a little stricter (multiple
commas now aren't allowed between export specs).

- - - - -
80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00
[haddock @ 2002-07-19 09:13:10 by simonmar]
Allow special id's ([], (), etc.) to be used in an import declaration.

- - - - -
a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00
[haddock @ 2002-07-19 09:59:02 by simonmar]
Allow special id's ([], (), etc.) to be used in an import declarations.

- - - - -
d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00
[haddock @ 2002-07-19 10:00:16 by simonmar]
Relax the restrictions which require doc comments to be followed by
semi colons - in some cases this isn't necessary.  Now you can write

	module M where {
 	  -- | some doc
	  class C where {}
 	}

without needing to put a semicolon before the class declaration.

- - - - -
e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00
[haddock @ 2002-07-23 08:24:09 by simonmar]
A new TODO list item

- - - - -
e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00
[haddock @ 2002-07-23 08:40:56 by simonmar]
- update the acknowledgements

- remove the paragraph that described how to use explicit layout with
  doc comments; it isn't relevant any more.

- - - - -
78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00
[haddock @ 2002-07-23 08:43:02 by simonmar]
more tests

- - - - -
5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00
[haddock @ 2002-07-23 08:43:26 by simonmar]
Updates for version 0.4

- - - - -
488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00
[haddock @ 2002-07-23 09:10:46 by simonmar]
Fix the %changelog (rpm complained that it wasn't in the right order)

- - - - -
a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00
[haddock @ 2002-07-23 09:12:38 by simonmar]
Another item for the TODO list

- - - - -
f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00
[haddock @ 2002-07-23 10:18:46 by simonmar]
Add a version banner when invoked with -v

- - - - -
1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00
[haddock @ 2002-07-24 09:28:19 by simonmar]
Remove ^Ms

- - - - -
4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00
[haddock @ 2002-07-24 09:42:17 by simonmar]
Patches to quieten ghc -Wall, from those nice folks at Galois.

- - - - -
d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00
[haddock @ 2002-07-25 14:37:28 by simonmar]
Patch to allow simple hyperlinking to an arbitrary location in another
module's documentation, from Volker Stolz.

Now in a doc comment:

  #foo#

creates

  <a name="foo"></a>

And you can use the form "M\#foo" to hyperlink to the label 'foo' in
module 'M'.  Note that the backslash is necessary for now.

- - - - -
b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00
[haddock @ 2002-08-02 09:08:22 by simonmar]
The <TT> and <PRE> environments seem to use a font that is a little
too small in IE.  Compensate.

(suggestion from Daan Leijen).

- - - - -
8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00
[haddock @ 2002-08-02 09:25:20 by simonmar]
Remove <P>..</P> from around list items, to reduce excess whitespace
between the items of bulleted and ordered lists.

(Suggestion from Daan Leijen).

- - - - -
c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00
[haddock @ 2002-08-05 09:03:49 by simonmar]
update

- - - - -
f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00
[haddock @ 2002-11-11 09:32:57 by simonmar]
Fix cut-n-pasto

- - - - -
12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00
[haddock @ 2002-11-13 09:49:46 by simonmar]
Small bugfix in the --read-interface option parsing from Brett Letner.

- - - - -
30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00
[haddock @ 2003-01-16 15:07:57 by ross]
Adjust for the new exception libraries (as well as the old ones).

- - - - -
871f65df by Sven Panne at 2003-02-20T21:31:40+00:00
[haddock @ 2003-02-20 21:31:40 by panne]
* Add varsyms and consyms to index
* Exclude empty entries from index

- - - - -
bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00
[haddock @ 2003-02-24 21:26:29 by panne]
Don't convert a "newtype" to a single-constructor "data" for
non-abstractly exported types, they are quite different regarding
strictness/pattern matching. Now a "data" without any constructors is
only emitted for an abstractly exported type, regardless if it is
actually a "newtype" or a "data".

- - - - -
0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00
[haddock @ 2003-03-08 19:02:38 by panne]
Fixed some broken/redirected/canonicalized links found by a very picky
link checker.

- - - - -
25459269 by Sven Panne at 2003-03-09T21:13:43+00:00
[haddock @ 2003-03-09 21:13:43 by panne]
Don't append a fragment to non-defining index entries, only documents
with a defining occurrence have a name anchor.

- - - - -
6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00
[haddock @ 2003-03-10 21:34:24 by panne]
Escape fragments. This fixes e.g. links to operators.

- - - - -
eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00
[haddock @ 2003-04-25 10:50:05 by ross]
An 80% solution to generating derived instances.  A complete solution
would duplicate the instance inference logic, but if a type variable
occurs as a constructor argument, then we can just propagate the derived
class to the variable.  But we know nothing of the constraints on any
type variables that occur elsewhere.  For example, the declarations

	data Either a b = Left a | Right b deriving (Eq, Ord)
	data Ptr a = Ptr Addr# deriving (Eq, Ord)
	newtype IORef a = IORef (STRef RealWorld a) deriving Eq

yield the instances

	(Eq a, Eq b) => Eq (Either a b)
	(Ord a, Ord b) => Ord (Either a b)
	Eq (Ptr a)
	Ord (Ptr a)
	(??? a) => Eq (IORef a)

The last example shows the limits of this local analysis.
Note that a type variable may be in both categories: then we know a
constraint, but there may be more, or a stronger constraint, e.g.

	data Tree a = Node a [Tree a] deriving Eq
yields
	(Eq a, ??? a) => Eq (Tree a)

- - - - -
de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00
[haddock @ 2003-04-25 11:17:55 by simonmar]
Some updates, including moving the derived instance item down to the
bottom of the list now that Ross has contributed some code that does
the job for common cases.

- - - - -
1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00
[haddock @ 2003-04-30 14:02:32 by simonmar]
When installing on Windows, run cygpath over $(HADDOCKLIB) so that
haddock (a mingw program, built by GHC) can understand it.

You still need to be in a cygwin environment to run Haddock, because
of the shell script wrapper.

- - - - -
d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00
[haddock @ 2003-05-06 10:04:47 by simonmar]
Catch another case of a paragraph containing just a DocMonospaced that
should turn into a DocCodeBlock.

- - - - -
4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00
[haddock @ 2003-05-06 10:11:44 by simonmar]
Add some more code-block tests.

- - - - -
4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00
[haddock @ 2003-05-06 10:14:52 by simonmar]
Don't turn a single DocCodeBlock into a DocMonospaced, because that
tends to remove the line breaks in the code.

- - - - -
ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00
[haddock @ 2003-05-21 15:07:21 by simonmar]
Only omit the module contents when there are no section headings at all.

- - - - -
bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00
[haddock @ 2003-05-30 16:50:45 by sof]
cygpath: for now, steer clear of --mixed

- - - - -
30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00
[haddock @ 2003-05-30 17:59:28 by sof]
oops, drop test defn from prev commit

- - - - -
b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00
[haddock @ 2003-06-03 09:55:26 by simonmar]
Two small fixes to make the output valid HTML 4.01 (transitional).

Thanks to Malcolm Wallace for pointing out the problems.

- - - - -
70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00
[haddock @ 2003-07-28 13:30:35 by simonmar]
Add tests for a couple of bugs.

- - - - -
122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00
[haddock @ 2003-07-28 13:31:25 by simonmar]
Add documentation for anchors.

- - - - -
0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00
[haddock @ 2003-07-28 13:31:46 by simonmar]
Update

- - - - -
08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00
[haddock @ 2003-07-28 13:32:12 by simonmar]
layout tweak.

- - - - -
13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00
[haddock @ 2003-07-28 13:33:03 by simonmar]
Differentiate links to types/classes from links to
variables/constructors with a prefix ("t:" and "v:" respectively).

- - - - -
d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00
[haddock @ 2003-07-28 13:35:16 by simonmar]
When a module A exports another module's contents via 'module B', then
modules which import entities from B re-exported by A should link to
B.foo rather than A.foo.  See examples/Bug2.hs.

- - - - -
d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00
[haddock @ 2003-07-28 13:36:14 by simonmar]
Update to version 0.5

- - - - -
dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00
[haddock @ 2003-07-28 14:02:43 by panne]
* Updated to version 0.5
* Automagically generate configure if it is not there

- - - - -
6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00
[haddock @ 2003-07-28 14:32:42 by simonmar]
Update to avoid using hslibs with GHC >= 5.04

- - - - -
a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00
[haddock @ 2003-07-28 14:33:37 by simonmar]
Update for 0.5

- - - - -
c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00
[haddock @ 2003-07-28 14:53:22 by simonmar]
Markup fix

- - - - -
6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00
[haddock @ 2003-07-28 16:40:45 by panne]
Make it compile with GHC >= 6.01

- - - - -
afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00
[haddock @ 2003-07-30 15:04:52 by simonmar]
Pay attention to import specs when building the the import env, as
well as the orig env.  This may fix some wrong links in documentation
when import specs are being used.

- - - - -
17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00
[haddock @ 2003-07-30 16:05:40 by simonmar]
Rename instances based on the import_env for the module in which they
are to be displayed.  This should give, in many cases, better links
for the types and classes mentioned in the instance head.

This involves keeping around the import_env in the iface until the
end, because instances are not collected up until all the modules have
been processed.  Fortunately it doesn't seem to affect performance
much.

Instance heads are now attached to ExportDecls, rather than the HTML
backend passing around a separate mapping for instances.  This is a
cleanup.

- - - - -
3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00
[haddock @ 2003-08-04 10:18:24 by panne]
Don't print parentheses around one-element contexts

- - - - -
9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00
[haddock @ 2003-08-04 12:59:47 by simonmar]
A couple of TODOs.

- - - - -
e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00
[haddock @ 2003-08-05 14:10:31 by simonmar]
I'm not sure why, but it seems that the index entries for non-defining
occurrences of entities did not have an anchor - the link just pointed
to the module.  This fixes it.

- - - - -
ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00
[haddock @ 2003-08-15 14:42:59 by simonmar]
Convert the lexer to Alex, and fix a bug in the process.

- - - - -
1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00
[haddock @ 2003-08-15 15:00:18 by simonmar]
Update

- - - - -
d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00
[haddock @ 2003-08-15 15:01:03 by simonmar]
wibbles

- - - - -
b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00
[haddock @ 2003-08-18 10:04:47 by simonmar]
Lex the 'mdo' keyword as 'do'.

- - - - -
8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00
[haddock @ 2003-08-18 11:48:24 by simonmar]
Two bugs from Sven.

- - - - -
ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00
[haddock @ 2003-08-18 11:48:46 by simonmar]
Fixes to the new lexer.

- - - - -
d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00
[haddock @ 2003-08-19 09:09:03 by simonmar]
Further wibbles to the syntax.

- - - - -
6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00
[haddock @ 2003-08-26 18:45:35 by panne]
Use autoreconf instead of autoconf

- - - - -
32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00
[haddock @ 2003-08-26 19:01:18 by panne]
Made option handling a bit more consistent with other tools, in
particular: Every program in fptools should output
   * version info on stdout and terminate successfully when -V or --version
   * usage info on stdout and terminate successfully when -? or --help
   * usage info on stderr and terminate unsuccessfully when an unknown option
is given.

- - - - -
5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00
[haddock @ 2003-08-26 19:20:55 by panne]
Make it *very* clear that we terminate when given a -V/--version flag

- - - - -
e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00
[haddock @ 2003-08-27 07:50:02 by panne]
* Made -D a short option for --dump-interface.
* Made -m a short option for --ms-help.
* Made -n a short option for --no-implicit-prelude.
* Made -c a short option for --css.
* Removed DocBook options from executable (they didn't do anything),
  but mark them as reserved in the docs. Note that the short option
  for DocBook output is now -S (from SGML) instead of -d. The latter
  is now a short option for --debug.
* The order of the Options in the documentation now matches the order
  printed by Haddock itself.

Note: Although changing the names of options is often a bad idea, I'd
really like to make the options for the programs in fptools more
consistent and compatible to the ones used in common GNU programs.

- - - - -
d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00
[haddock @ 2003-09-10 08:23:48 by simonmar]
Add doc subdir.

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00
[haddock @ 2003-09-10 08:24:32 by simonmar]
Install these files in $(datadir), not $(libdir), since they're
architecture independent.

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00
[haddock @ 2003-09-10 08:25:31 by simonmar]
Haddock's supplementary HTML bits now live in $(datadir), not
$(libdir).

Patch contributed by: Ian Lynagh <igloo at earth.li>.

- - - - -
3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00
[haddock @ 2003-09-22 10:34:38 by simonmar]
Allow installing of docs.

- - - - -
d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00
[haddock @ 2003-10-11 08:10:44 by panne]
Include architecture-independent files in file list

- - - - -
187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00
[haddock @ 2003-10-20 17:19:22 by sof]
support for i-parameters + zip comprehensions

- - - - -
b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00
[haddock @ 2003-11-03 14:24:24 by simonmar]
Update TODO file.

- - - - -
58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00
[haddock @ 2003-11-05 11:22:04 by simonmar]
Remove the last of the uses of 'trace' to emit warnings, and tidy up a
couple of places where duplicate warnings were being emitted.

- - - - -
33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00
[haddock @ 2003-11-05 11:30:52 by simonmar]
- Suppress warnings about unknown imported modules by default.
- Add a -v/--verbose flag to re-enable these warnings.

The general idea is to suppress the "Warning: unknown module: Prelude"
warnings which most Haddock users will see every time, and which
aren't terribly useful.

- - - - -
a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00
[haddock @ 2003-11-05 12:30:28 by simonmar]
- Remove the emboldening of index entries for defining locations.
  This isn't useful, and breaks abstractions.

- If an entity is re-exported by a module but the module doesn't
  include documentation for that entity (perhaps because it is
  re-exported by 'module M'), then don't attempt to hyperlink to
  the documentation from the index.  Instead, just list that module
  in the index, to indicate that the entity is exported from there.

- - - - -
f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00
[haddock @ 2003-11-05 15:15:59 by simonmar]
Index overhaul:

  - no more separate type/class and variable/function indices

  - the index now makes a distinction between different entities
    with the same name.  One example is a type constructor with
    the same name as a data constructor, but another example is
    simply a function with the same name exported by two different
    modules.  For example, the index entry for 'catch' now looks like
    this:

    catch
      1 (Function)	Control.Exception
      2 (Function)	GHC.Exception, Prelude, System.IO, System.IO.Error

    making it clear that there are two different 'catch'es, but one
    of them is exported by several modules.

  - Each index page now has the index contents (A B C ...) at the top.

Please let me know if you really hate any of this.

- - - - -
01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00
[haddock @ 2003-11-05 15:16:38 by simonmar]
Update

- - - - -
1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00
[haddock @ 2003-11-05 17:16:04 by simonmar]
Support for generating a single unified index for several packages.

  --use-index=URL  turns off normal index generation, causes Index
 		   links to point to URL.

  --gen-index      generates an combined index from the specified
                   interfaces.

Currently doesn't work exactly right, because the interfaces don't
contain the iface_reexported info.  I'll need to fix that up.

- - - - -
a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00
[haddock @ 2003-11-06 10:44:52 by simonmar]
Include iface_reexported in the .haddock file.  This unfortunately
bloats the file (40% for base).  If this gets to be a problem we can
always apply the dictionary trick that GHC uses for squashing .hi
files.

- - - - -
0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00
[haddock @ 2003-11-06 12:39:46 by simonmar]
- Add definition lists, marked up like this:

	-- | This is a definition list:
	--
	--   [@foo@] The description of @foo at .
	--
	--   [@bar@] The description of @bar at .

  Cunningly, the [] characters are not treated specially unless a [ is
  found at the beginning of a paragraph, in which case the ] becomes
  special in the following text.


- Add --use-contents and --gen-contents, along the lines of
  --use-index and --gen-index added yesterday.  Now we can generate a
  combined index and contents for the whole of the hierarchical
  libraries, and in theory the index/contents on the system could
  be updated as new packages are added.

- - - - -
fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00
[haddock @ 2003-11-06 14:47:36 by simonmar]
Remove the 'Parent' button - it is of dubious use, and often points
into thin air.

- - - - -
db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00
[haddock @ 2003-11-06 16:48:11 by simonmar]
- Include the OptHide setting in the interface, so we don't include
  hidden modules in the combined index/contents.

- Add a -k/--package flag to set the package name for the current set
  of modules.  The package name for each module is now shown in the
  right-hand column of the contents, in a combined contents page.

- - - - -
7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00
[haddock @ 2003-11-06 16:50:28 by simonmar]
Add -k/--package docs

- - - - -
ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00
[haddock @ 2003-11-06 16:51:23 by simonmar]
Bump to 0.6

- - - - -
1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00
[haddock @ 2003-11-06 16:51:50 by simonmar]
update

- - - - -
69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00
[haddock @ 2003-11-10 14:41:05 by simonmar]
Re-exporting names from a different package is problematic, because we
don't have access to the full documentation for the entity.  Currently
Haddock just ignores entities with no documentation, but this results
in bogus-looking empty documentation for many of the modules in the
haskell98 package.  So:

  - the documentation will now just list the name, as a link
    pointing to the location of the actual documentation.

  - now we don't attempt to link to these re-exported entities if
    they are referred to by the current module.

Additionally:

  - If there is no documentation in the current module, include
    just the Synopsis section (rather than just the documentation
    section, as it was before).  This just looks nicer and was on
    the TODO list.

- - - - -
3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00
[haddock @ 2003-11-10 14:51:59 by simonmar]
Fix for getReExports: take into account names which are not visible
because they are re-exported from a different package.

- - - - -
31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00
[haddock @ 2003-11-10 15:10:53 by simonmar]
Version 0.6 changes

- - - - -
a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00
[haddock @ 2003-11-10 15:15:58 by simonmar]
getReExports: one error case that isn't

- - - - -
00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00
[haddock @ 2003-11-10 16:15:18 by simonmar]
copyright update

- - - - -
ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00
[haddock @ 2003-11-11 09:57:25 by simonmar]
Version 0.6

- - - - -
3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00
[haddock @ 2003-11-11 12:10:44 by simonmar]
Go back to producing just the documentation section, rather than just
the synopsis section, for a module with no documentation annotations.

One reason is that the synopsis section tries to link each entity to
its documentation on the same page.  Also, the doc section anchors
each entity, and it lists instances which the synopsis doesn't.

- - - - -
6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00
[haddock @ 2003-11-12 10:03:39 by simonmar]
2002 -> 2003

- - - - -
090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00
[haddock @ 2003-11-28 12:08:00 by simonmar]
update

- - - - -
8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00
[haddock @ 2003-11-28 12:09:58 by simonmar]
Fix some of the problems with Haddock generating pages that are too
wide.  Now we only specify 'nowrap' when it is necessary to avoid a
code box getting squashed up by the text to the right of it.

- - - - -
35294929 by Sven Panne at 2003-12-29T17:16:31+00:00
[haddock @ 2003-12-29 17:16:31 by panne]
Updated my email address

- - - - -
cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00
[haddock @ 2004-01-08 10:14:24 by simonmar]
Add instructions for using GHC to pre-process source for feeding to Haddock.

- - - - -
8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00
[haddock @ 2004-01-09 12:45:46 by simonmar]
Add -optP-P to example ghc command line.

- - - - -
ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00
[haddock @ 2004-02-03 11:02:03 by simonmar]
Fix bug in index generation

- - - - -
f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00
[haddock @ 2004-02-10 11:51:16 by simonmar]
Don't throw away whitespace at the beginning of a line (experimental fix).

- - - - -
68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00
[haddock @ 2004-02-10 12:10:08 by simonmar]
Fix for previous commit: I now realise why the whitespace was stripped
from the beginning of the line.  Work around it.

- - - - -
e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00
[haddock @ 2004-02-10 18:38:45 by panne]
Make Haddock link with the latest relocated monad transformer package

- - - - -
992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00
[haddock @ 2004-02-16 10:21:35 by simonmar]
Add a TODO

- - - - -
1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00
[haddock @ 2004-03-12 11:33:39 by simonmar]
Add an item.

- - - - -
0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00
[haddock @ 2004-03-15 12:24:05 by simonmar]
Add an item.

- - - - -
6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00
[haddock @ 2004-03-18 14:21:29 by simonmar]
Fix URL

- - - - -
19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00
[haddock @ 2004-03-22 14:09:03 by simonmar]
getReExports was bogus: we should really look in the import_env to
find the documentation for an entity which we are re-exporting without
documentation.

Suggested by: Ross Paterson (patch modified by me).

- - - - -
5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00
[haddock @ 2004-03-24 09:42:10 by simonmar]
hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs)

- - - - -
1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00
[haddock @ 2004-03-24 10:10:50 by simonmar]
mkExportItems fix & simplification: we should be looking at the actual
exported names (calculated earlier) to figure out which subordinates
of a declaration are exported.

This means that if you export a record, and name its fields separately
in the export list, the fields will still be visible in the
documentation for the constructor.

- - - - -
90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00
[haddock @ 2004-03-24 10:12:08 by simonmar]
Make restrictCons take into account record field names too (removing a ToDo).

- - - - -
2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00
[haddock @ 2004-03-24 10:16:17 by simonmar]
Record export tests.

- - - - -
6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00
[haddock @ 2004-03-25 09:35:14 by simonmar]
restrictTo: fix for restricting a newtype with a record field.

- - - - -
dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00
[haddock @ 2004-03-25 10:01:42 by simonmar]
Fix duplicate instance bug

- - - - -
f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00
[haddock @ 2004-03-25 10:02:41 by simonmar]
Duplicate instance bug.

- - - - -
7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00
[haddock @ 2004-03-25 10:29:56 by simonmar]
If a name is imported from two places, one hidden and one not, choose
the unhidden one to link to.  Also, when there's only a hidden module
to link to, don't try linking to it.

- - - - -
40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00
[haddock @ 2004-03-25 15:17:23 by simonmar]
Add support for collaspible parts of the page, with a +/- button and a
bit of JavaScript.  Make the instances collapsible, and collapse them
by default.

This makes documentation with long lists of instances (eg. the
Prelude) much easier to read.  Maybe we should give other
documentation sections the same treatment.

- - - - -
9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00
[haddock @ 2004-03-25 15:20:55 by simonmar]
Update

- - - - -
c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00
[haddock @ 2004-03-25 15:45:10 by simonmar]
Eliminate some unnecessary spaces in the HTML rendering

- - - - -
b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00
[haddock @ 2004-03-25 16:00:36 by simonmar]
Remove all that indentation in the generated HTML to keep the file sizes down.

- - - - -
da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00
[haddock @ 2004-03-27 09:57:57 by panne]
Added the new-born haddock.js to the build process and the documentation.

- - - - -
b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00
[haddock @ 2004-03-27 10:32:20 by panne]
"type" is a required attribute of the "script" element

- - - - -
562b185a by Sven Panne at 2004-03-27T12:52:34+00:00
[haddock @ 2004-03-27 12:52:34 by panne]
Add a doctype for the contents page, too.

- - - - -
f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00
[haddock @ 2004-04-14 10:03:25 by simonmar]
fix for single-line comment syntax

- - - - -
de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00
[haddock @ 2004-04-20 13:08:04 by simonmar]
Allow a 'type' declaration to include documentation comments.  These
will be ignored by Haddock, but at least one user (Johannes Waldmann)
finds this feature useful, and it's easy to add.

- - - - -
fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00
[haddock @ 2004-05-07 15:14:56 by simonmar]
- update copyright
- add version to abstract

- - - - -
59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00
[haddock @ 2004-05-09 14:39:53 by panne]
Fix the fix for single-line comment syntax,
-------------------------------------------
is now a valid comment line again.

- - - - -
8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00
[haddock @ 2004-05-10 10:11:51 by simonmar]
Update

- - - - -
225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00
[haddock @ 2004-05-19 13:10:23 by ross]
Make the handling of "deriving" slightly smarter, by ignoring data constructor
arguments that are identical to the lhs.  Now handles things like

data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ...

- - - - -
37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00
[haddock @ 2004-05-21 06:38:14 by mthomas]
Windows exe extensions (bin remains for Unix).

- - - - -
cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00
[haddock @ 2004-05-25 09:34:54 by simonmar]
Add some TODO items

- - - - -
4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00
[haddock @ 2004-05-25 10:41:46 by simonmar]
Complain if -h is used with --gen-index or --gen-contents, because
it'll overwrite the new index/contents.

- - - - -
2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00
[haddock @ 2004-05-28 20:17:55 by mthomas]
Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg.

- - - - -
8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00
[haddock @ 2004-06-05 16:53:34 by panne]
Misc. rpm spec file cleanup, including:
* make BuildRoot handling more consistent
* added default file attributes
* consistent defines and tags

- - - - -
59974349 by Sven Panne at 2004-06-05T18:01:00+00:00
[haddock @ 2004-06-05 18:01:00 by panne]
More rpm spec file cleanup, including:
* added some BuildRequires
* changed packager to me, so people can complain at the right place :-]
* consistently refer to haskell.org instead of www.haskell.org

- - - - -
b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00
[haddock @ 2004-07-01 11:08:57 by simonmar]
Update to the +/- buttons: use a resized image rather than a <button>.
Still seeing some strange effects in Konqueror, so might need to use a
fixed-size image instead.

- - - - -
d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00
[haddock @ 2004-07-04 15:15:55 by panne]
Install pictures for +/- pictures, too (JPEG is a strange format for graphics
like this, I would have expected GIF or PNG here.)

Things look fine with Konqueror and Netscape on Linux now, the only downside is
that the cursor doesn't change when positioned above the "button".

- - - - -
46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00
[haddock @ 2004-07-13 17:59:28 by panne]
A quote is a valid part of a Haskell identifier, but it would interfere with an
ECMA script string delimiter, so escape it there.

- - - - -
1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00
[haddock @ 2004-07-22 08:54:06 by simonmar]
Add single quote to $ident, so you can say eg. 'foldl'' to refer to
foldl' (the longest match rule is our friend).

Bug reported by Adrian Hey <ahey at iee.org>

- - - - -
f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00
[haddock @ 2004-07-27 22:58:23 by krasimir]
Add basic support for Microsoft HTML Help 2.0

- - - - -
d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00
[haddock @ 2004-07-27 23:02:36 by krasimir]
escape names in the index

- - - - -
a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00
[haddock @ 2004-07-27 23:05:21 by krasimir]
Add jsFile, plusFile and minusFile to the file list

- - - - -
c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00
[haddock @ 2004-07-28 22:12:09 by krasimir]
bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to
HaddockUtil.hs module to make them accessible from HaddockHH2.hs

- - - - -
64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00
[haddock @ 2004-07-30 22:15:45 by krasimir]
more stuffs

  - support for separated compilation of packages
  - the contents page now uses DHTML TreeView
  - fixed copyFile bug

- - - - -
133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00
[haddock @ 2004-07-31 12:04:37 by krasimir]
make the DHtmlTree in contents page more portable. The +/- buttons are replaced
with new images which looks more beatiful.

- - - - -
79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00
[haddock @ 2004-07-31 13:10:20 by krasimir]
Make DHtmlTree compatible with Mozila browser

- - - - -
1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00
[haddock @ 2004-07-31 14:52:55 by krasimir]
fix

- - - - -
85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00
[haddock @ 2004-07-31 14:53:28 by krasimir]
HtmlHelp 1.x

- - - - -
3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00
[haddock @ 2004-07-31 20:35:21 by krasimir]
Added support for DevHelp

- - - - -
d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00
[haddock @ 2004-07-31 21:17:51 by krasimir]
Document new features in HtmlHelp

- - - - -
790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00
[haddock @ 2004-08-01 15:14:02 by krasimir]
add missing imports

- - - - -
fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00
[haddock @ 2004-08-01 19:52:06 by krasimir]
fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format.

- - - - -
94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00
[haddock @ 2004-08-01 19:53:50 by krasimir]
I forgot to add the new +/- images

- - - - -
f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00
[haddock @ 2004-08-02 16:25:53 by krasimir]
Add root node to the table of contents. All modules in tree are not children of
the root

- - - - -
f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00
[haddock @ 2004-08-02 18:17:46 by panne]
Mainly DocBook fixes

- - - - -
09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00
[haddock @ 2004-08-02 20:02:29 by panne]
Fixed -o/--odir handling. Generating the output, especially the
directory handling, is getting a bit convoluted nowadays...

- - - - -
c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00
[haddock @ 2004-08-02 20:31:13 by panne]
Warning police

- - - - -
37830bff by Sven Panne at 2004-08-02T20:32:29+00:00
[haddock @ 2004-08-02 20:32:28 by panne]
Nuked dead code

- - - - -
13847171 by Sven Panne at 2004-08-02T21:12:27+00:00
[haddock @ 2004-08-02 21:12:25 by panne]
Use pathJoin instead of low-level list-based manipulation for FilePaths

- - - - -
c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00
[haddock @ 2004-08-02 21:16:02 by panne]
Removed WinDoze CRs

- - - - -
b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00
[haddock @ 2004-08-03 19:35:59 by panne]
Fixed spelling of "http-equiv" attribute

- - - - -
dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00
[haddock @ 2004-08-03 19:44:03 by panne]
Pacify W3C validator:
* Added document encoding (currently UTF-8, not sure if this is completely correct)
* Fixed syntax of `id' attributes
* Added necessary `alt' attribute for +/- images

Small layout improvement:
* Added space after +/- images (still not perfect, but better than before)

- - - - -
919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00
[haddock @ 2004-08-03 19:45:11 by sof]
make it compile with <= ghc-6.1

- - - - -
4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00
[haddock @ 2004-08-03 19:45:30 by sof]
ffi wibble

- - - - -
4770643a by Sven Panne at 2004-08-03T20:47:46+00:00
[haddock @ 2004-08-03 20:47:46 by panne]
Fixed CSS for button style. Note that only "0" is a valid measure without a unit!

- - - - -
14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00
[haddock @ 2004-08-03 21:07:58 by panne]
Improved spacing of dynamic module tree

- - - - -
97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00
[haddock @ 2004-08-09 11:03:04 by simonmar]
Add FormatVersion

Patch submitted by: George Russell <ger at informatik.uni-bremen.de>

- - - - -
af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00
[haddock @ 2004-08-09 11:55:05 by simonmar]
Add support for a short description for each module, which is included
in the contents.

The short description should be given in a "Description: " field of
the header.  Included in this patch are changes that make the format
of the header a little more flexible.  From the comments:

-- all fields in the header are optional and have the form
--
-- [spaces1][field name][spaces] ":"
--    [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")*
-- where each [spaces2] should have [spaces1] as a prefix.
--
-- Thus for the key "Description",
--
-- > Description : this is a
-- >    rather long
-- >
-- >    description
-- >
-- > The module comment starts here
--
-- the value will be "this is a .. description" and the rest will begin
-- at "The module comment".

The header fields must be in the following order: Module, Description,
Copyright, License, Maintainer, Stability, Portability.

Patches submitted by: George Russell <ger at informatik.uni-bremen.de>,
with a few small changes be me, mostly to merge with other recent
changes.

ToDo: document the module header.

- - - - -
7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00
[haddock @ 2004-08-10 14:09:57 by simonmar]
Fixes for DevHelp/HtmlHelp following introduction of short module description.

- - - - -
814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00
[haddock @ 2004-08-10 14:33:45 by simonmar]
Fixes to installation under Windows.

- - - - -
39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00
[haddock @ 2004-08-12 12:08:23 by simonmar]
Avoid using string-gap tricks.

- - - - -
b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00
[haddock @ 2004-08-13 10:53:21 by simonmar]
Update

- - - - -
eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00
[haddock @ 2004-08-13 10:53:50 by simonmar]
Test for primes in quoted links

- - - - -
68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00
[haddock @ 2004-08-16 19:59:36 by panne]
XMLification

- - - - -
7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00
[haddock @ 2004-08-18 16:42:54 by panne]
Re-added indices + minor fixes

- - - - -
8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00
[haddock @ 2004-08-25 17:15:42 by sof]
backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw

- - - - -
4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00
[haddock @ 2004-08-26 20:08:49 by panne]
SGML is dead, long live DocBook XML!

Note: The BuildRequires tags in the spec files are still incomplete
and the documentation about the DocBook tools needs to be updated,
too. Stay tuned...

- - - - -
8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00
[haddock @ 2004-08-26 21:03:19 by panne]
Updated BuildRequires tags. Alas, there seems to be no real standard here, so
your mileage may vary... At least the current specs should work on SuSE Linux.

- - - - -
e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00
[haddock @ 2004-08-30 15:44:59 by sof]
escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x

- - - - -
b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00
[haddock @ 2004-08-31 13:09:42 by simonmar]
Avoid GHC/shell versionitis and create Version.hs

- - - - -
c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00
[haddock @ 2004-09-05 19:12:32 by panne]
* HTML documentation for "foo.xml" goes into directory "foo" again,
  not "foo-html". This is nicer and consistent with the behaviour for
  building the docs from SGML.

* Disabled building PostScript documentation in the spec files for
  now, there are some strange issues with the FO->PS conversion for
  some files which have to be clarified first.

- - - - -
c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00
[haddock @ 2004-09-24 07:04:38 by panne]
Switched the default state for instances and the module hierarchy to
non-collapsed. This can be reversed when we finally use cookies from
JavaScript to have a more persistent state. Previously going back and forth
in the documentation was simply too annoying because everything was
collapsed again and therefore the documentation was not easily navigatable.

- - - - -
dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00
[haddock @ 2004-09-30 08:21:29 by simonmar]
Add a feature request

- - - - -
45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00
[haddock @ 2004-10-23 19:54:00 by panne]
Improved the Cygwin/MinGW chaos a little bit. There is still confusion
about host platform vs. target platform...

- - - - -
5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00
[haddock @ 2004-10-28 16:01:51 by krasimir]
update for ghc-6.3+

- - - - -
92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00
[haddock @ 2004-11-01 16:39:01 by panne]
Revert previous commit: It's Network.URI which should be changed, not Haddock.

- - - - -
05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00
[haddock @ 2005-01-04 16:15:51 by simonmar]
parser fix: allow qualified specialids.

- - - - -
47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00
[haddock @ 2005-01-04 16:16:54 by simonmar]
Add a test

- - - - -
ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00
[haddock @ 2005-01-10 19:18:22 by ross]
Render non-ASCII characters using numeric character references, to simplify
charset issues.  There's a META tag saying the charset is UTF-8, but GHC
outputs characters as raw bytes.

Ideally we need an encoding on the input side too, primarily in comments,
because source files containing non-ASCII characters aren't portable between
locales.

- - - - -
eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00
[haddock @ 2005-01-11 10:44:37 by simonmar]
Remove string gap

- - - - -
b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00
[haddock @ 2005-01-13 11:41:33 by ross]
recognize SGML-style numeric character references &#ddd; or &#xhhhh; and
translate them into Chars.

- - - - -
106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00
[haddock @ 2005-01-13 14:43:41 by ross]
also allow uppercase X in hexadecimal character references (like SGML)

- - - - -
e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00
[haddock @ 2005-01-13 14:44:24 by ross]
Describe numeric character references.

- - - - -
914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00
[haddock @ 2005-01-15 18:44:45 by panne]
Make Haddock compile again after the recent base package changed. The Map/Set
legacy hell has been factored out, so that all modules can simply use the new
non-deprecated interfaces. Probably a lot of things can be improved by a little
bit of Map/Set/List algebra, this can be done later if needed.

Small note: Currently the list of instances in HTML code is reversed. This will
hopefully be fixed later.

- - - - -
6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00
[haddock @ 2005-01-16 12:18:26 by panne]
Trim imports

- - - - -
efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00
[haddock @ 2005-01-16 12:58:03 by panne]
Correctly handle the new order of arguments for the combining function
given to fromListWith.

- - - - -
e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00
[haddock @ 2005-01-16 14:14:39 by panne]
Data.Map.unions is left-biased.

- - - - -
dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00
[haddock @ 2005-01-16 14:22:44 by panne]
Added the last missing "flip" to get identical HTML output as previous versions.

- - - - -
951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00
[haddock @ 2005-01-16 14:37:10 by panne]
Refactored Text.PrettyPrint legacy hell into a separate module.

- - - - -
f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00
[haddock @ 2005-01-16 15:41:21 by panne]
Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway.

- - - - -
60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00
[haddock @ 2005-01-18 10:02:48 by simonmar]
Add a TODO

- - - - -
a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00
[haddock @ 2005-01-28 23:19:39 by krasimir]
import Foreign/Foreign.C are required for Windows

- - - - -
d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00
[haddock @ 2005-02-02 16:23:00 by simonmar]
Revamp the linking strategy in Haddock.

Now name resolution is done in two phases:

 - first resolve everything to original names, like a Haskell compiler
   would.

 - then, figure out the "home" location for every entity, and point
   all the links to there.  The home location is the lowest non-hidden
   module in the import hierarchy that documents the entity.  If there
   are multiple candidates, one is chosen at random.

Also:

 - Haddock should not generate any HTML with dangling links any more.
   Unlinked references are just rendered as plain text.

 - Error reporting is better: if we can't find a link destination for
   an entity reference, we now emit a warning.

- - - - -
1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00
[haddock @ 2005-02-03 13:42:19 by simonmar]
- add --ignore-all-exports flag, which behaves as if every module
  has the ignore-exports attribute (requested by Chris Ryder).

- add --hide option to hide a module on the command line.

- add --use-package option to get Haddock info for a package from
  ghc-pkg (largely untested).

- remove reexports from the .haddock file, they aren't used any more.

- - - - -
767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00
[haddock @ 2005-02-03 16:17:37 by ross]
fix typo for < 6.3

- - - - -
0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00
[haddock @ 2005-02-04 12:03:31 by simonmar]
Fix bug in renameExportItems that meant links in instances weren't
being renamed properly.

- - - - -
ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00
[haddock @ 2005-02-04 12:15:52 by simonmar]
Add attribute #not-home, to indicate that the current module should
not be considered to be a home module for the each entity it exports,
unless there is no other module that exports the entity.

- - - - -
fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00
[haddock @ 2005-02-04 12:40:02 by simonmar]
Update the documentation w.r.t. home modules and the not-home attribute.

- - - - -
26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00
[haddock @ 2005-02-04 13:36:05 by ross]
sort lists of instances by
- arity of the type constructors (so higher-kinded instances come first)
- name of the class
- argument types

- - - - -
26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00
[haddock @ 2005-02-23 15:57:12 by simonmar]
Fix documentation regarding the module attributes.

- - - - -
9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00
[haddock @ 2005-02-28 16:18:17 by simonmar]
version 0.7

- - - - -
a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00
[haddock @ 2005-02-28 16:22:08 by simonmar]
Attempt to fix the layout of the package names in the contents.

Having tried just about everything, the only thing I can get to work
reliably is to make the package names line up on a fixed offset from
the left margin.  This obviously isn't ideal, so anyone else that
would like to have a go at improving it is welcome.  One option is to
remove the +/- buttons from the contents list and go back to a plain
table.

The contents page now uses CSS for layout rather than tables.  It
seems that most browsers have different interpretations of CSS layout,
so only the simplest things lead to consistent results.

- - - - -
905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00
[haddock @ 2005-03-01 17:16:40 by simonmar]
Another attempt at lining up the package names on the contents page.
Now, they line up with Konqueror, and almost line up with Firefox & IE
(different layout in each case).

- - - - -
a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00
[haddock @ 2005-03-09 08:28:39 by wolfgang]
Hack haddock's lexer to accept the output from Apple's broken version of
cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output).

- - - - -
9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00
[haddock @ 2005-04-22 14:27:15 by simonmar]
Add a TODO item

- - - - -
23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00
[haddock @ 2005-05-18 12:41:59 by ross]
fix 3 bugs in --use-package, and document it.

- - - - -
00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00
[haddock @ 2005-05-21 12:35:29 by panne]
Warning/versionitis police

- - - - -
341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00
[haddock @ 2005-06-15 15:43:21 by simonmar]
Allow "licence" as an alternate spelling of "license"

- - - - -
3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00
[haddock @ 2005-06-16 08:14:12 by simonmar]
wibble

- - - - -
abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00
[haddock @ 2005-06-27 14:46:40 by simonmar]
name hierarchical HTML files as A-B-C.html instead of A.B.C.html.  The
old way confused Apache because the extensions are sometimes
interpreted as having special meanings.

- - - - -
a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00
[haddock @ 2005-08-04 13:59:40 by simonmar]
0.7 changes

- - - - -
170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00
[haddock @ 2005-08-04 15:08:03 by simonmar]
spec file from Jens Peterson

- - - - -
7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00
[haddock @ 2005-08-04 15:59:30 by simonmar]
replace mingw tests with $(Windows)

- - - - -
a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00
[haddock @ 2005-08-05 07:01:12 by panne]
Reverted to previous version (but with bumped version number), the last
commit broke RPM building on SuSE systems due to differently named
dependencies.

As a clarification: All .spec files in the repository have to work at least
on SuSE, because that's the system I'm using. And as "Mr. Building Police",
I reserve me the right to keep them that way... >:-) It might very well be
the case that we need different .spec files for different platforms, so
packagers which are unhappy with the current .spec files should contact me,
stating the actual problems.

- - - - -
4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00
[haddock @ 2005-10-05 10:51:45 by simonmar]
Add a bug

- - - - -
60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00
[haddock @ 2005-10-05 12:52:03 by simonmar]
Document new behaviour of -s option

- - - - -
f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00
[haddock @ 2005-10-10 15:02:55 by simonmar]
extractRecSel: ignore non-record constructors (fixes a crash when
using datatypes with a mixture of record and non-record style
constructors).

- - - - -
b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00
Start CHANGES for 0.8
- - - - -
21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00
First cut of Cabal build system
- - - - -
766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00
Add configure script and Makefile for the docs

Add a separate configure script and build system for building the
documentation.  The configure and Makefile code is stolen from
fptools.  This is left as a separate build system so that the main
Cabal setup doesn't require a Unix build environment or DocBook XML
tools.


- - - - -
aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00
Add a --wiki=URL flag to add a per-module link to a correspondng wiki page.
So each html page gets an extra link (placed next to the source code and
contents links) to a corresponding wiki page. The idea is to let readers
contribute their own notes, examples etc to the documentation.

Also slightly tidy up the code for the --source option.

- - - - -
e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00
TODO: documnet --wiki
- - - - -
17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00
Add an optional wiki link for each top level exported name.
In each module, for each "top level" exported entity we add a hyper link to a
corresponding wiki page. The link url gets the name of the exported entity as
a '#'-style anchor, so if there is an anchor in the page with that name then
the users browser should jump directly to it. By "top level" we mean functions,
classes, class members and data types (data, type, newtype), but not data
constructors, class instances or data type class membership.

The link is added at the right of the page and in a small font. Hopefully this
is the right balance of visibility/distraction.

We also include a link to the wiki base url in the contents and index pages.

- - - - -
f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00
Rewrite pathJoin to only add a path separator when necessary.
When the path ends in a file seperator there is no need to add another.
Now using "--wiki=http://blah.com/foo/" should do the right thing.
(Code snippet adapted from Isaac's FilePath package.)

- - - - -
43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00
Teach haddock about line pragmas and add accurate source code links
Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's
source location tracking to include the file name as well as line/column. This
way each AST item that is tagged with a SrcLoc gets the original file name too.

Use this original file name to add source links to each exported item, in the
same visual style as the wiki links. Note that the per-export source links are
to the defining module rather than whichever module haddock pretends it is
exported from. This is what we want for source code links. The source code link
URL can also contain the name of the export so one could implement jumping to
the actual location of the function in the file if it were linked to an html
version of the source rather than just plain text. The name can be selected
with the %N wild card.

So for linking to the raw source code one might use:
--source=http://darcs/haskell.org/foo/%F

Or for linking to html syntax highlighted code:
--source=http://darcs/haskell.org/foo/%M.html#%N

- - - - -
edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00
Extend URL variable expansion syntax and add source links to the contents page
Like the wiki link on the contents and index page, add a source code link too.
Extend the wiki & source URL variable expansion syntax.

The original syntax was:
%F for the source file name (the .hs version only, not the .lhs or .hs.pp one)
%M for the module name (with '.' replaced by '/')

The new syntax is:
%F or %{FILE} for the original source file name
%M or %{MODULE} for the module name (no replacements)
%N or %{NAME} for the function/type export name
%K or %{KIND} for a type/value flag "t" or "v"

with these extensions:
%{MODULE/./c} to replace the '.' module seperator with any other char c

%{VAR|some text with the % char in it} which means if the VAR is not in use in
this URL context then "" else replace the given text with the '%' char
replaced by the string value of the VAR. This extension allows us to construct
URLs wit optional parts, since the module/file name is not available for the
URL in the contents/index pages and the value/type name is not available for
the URL at the top level of each module.

- - - - -
eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00
Remove the complex substitutions and add more command line flags instead.
Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now
use three seperate command line flags for the top level, per-module and
per-entity source and wiki links. They are:
--source-base, --source-module, --source-entity
--comments-base, --comments-module, --comments-entity

We leave -s, --source as an alias for --source-module which is how that option
behaved previously.

The long forms of the substitutions are still available, ${FILE} ${MODULE} etc
and the only non-trivial substitution is ${MODULE/./c} to replace the '.'
characters in the module name with any other character c. eg ${MODULE/./-}

Seperating the source and wiki url flags has the added bonus that they can
be turned on or off individually. So users can have per-module links for
example without having to also have per-entity links.`

- - - - -
a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00
Make the --help output fit in 80 columns.
This is a purely cosmetic patch, feel free to ignore it.
The only trickery going on is that we don't display the deprecated -s, --source
flags in the help message, but we do still accept them.

- - - - -
2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00
Add documentation for the new --source-* and --comments-* command line options
- - - - -
1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00
fix markup
- - - - -
100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00
remove a couple TODO items that have been done
The --wiki, or rather the --comment-* options are now documented.
There is probably no need to have haddock invoke unlit or cpp itself since
it can now pick up the line pragmas to get the source locations right. Tools
like Cabal will arrange for preprocessors to be run so there is less of a need
for tools like haddock to do it themselves.

- - - - -
3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00
add a test I had lying around
- - - - -
98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00
add scabal-version field
- - - - -
c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00
Add Hoogle output option
- - - - -
f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00
add haskell.vim
Contributed by Brad Bowman <bsb at bereft.net>, thanks!

- - - - -
35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00
fixed libdir (/html was missing)
- - - - -
4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00
add PatternGuards extension
- - - - -
3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00
bug fixes from Brad Bowman
- - - - -
8610849d by Sven Panne at 2006-03-19T17:02:56+00:00
Fixed Cabal/RPM build
- - - - -
34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00
Avoid pattern guards

Due to the use of pattern guards in Haddock, GHC was called with
-fglasgow-exts. This in turn enables bang patterns, too, which broke the
Haddock build. Removing some unnecessary pattern guards seemed to be the
better way of fixing this instead of using a pragma to disable pattern
guards.

- - - - -
bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00
extend 'deriving' heuristic a little
If an argument of a data constructor has a type variable head, it is
irreducible and the same type class can be copied into the constraint.
(Formerly we just did this for type variable arguments.)

- - - - -
dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00
record an idea
- - - - -
748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00
add section about deriving
- - - - -
11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00
replace a fatal error in lexChar with a parseError
- - - - -
382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00
add a bug
- - - - -
b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00
add a bug report
- - - - -
912edf65 by David Waern at 2006-07-10T19:09:23+00:00
Initial modifications -- doesn't compile
- - - - -
a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00
More porting work -- doesn't compile
- - - - -
0a173d19 by David Waern at 2006-07-11T11:30:03+00:00
Make the repos temporarily compile and illustrate a problem
- - - - -
bad316de by David Waern at 2006-07-11T15:43:47+00:00
Progress on the porting process 
- - - - -
bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00
More progress on the porting -- first pass starting to shape up
- - - - -
de580ba2 by David Waern at 2006-07-20T17:48:30+00:00
More progress -- still on phase1
- - - - -
75a917a2 by David Waern at 2006-07-23T18:22:43+00:00
More work on pass1 -- mostly done
- - - - -
6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00
More work, started working on the renaming phase -- this code will need a cleanup soon :)
- - - - -
82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00
Add instances, build renaming environment, start on the renamer
- - - - -
c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00
Complete the renamer
- - - - -
7e00d464 by David Waern at 2006-07-30T21:01:57+00:00
Start porting the Html renderer
- - - - -
f04ce121 by David Waern at 2006-08-09T20:04:56+00:00
More Html rendering progress
- - - - -
20c21b53 by David Waern at 2006-08-10T17:37:47+00:00
More progress
- - - - -
d7097e0d by David Waern at 2006-08-11T20:31:51+00:00
Cleanup
- - - - -
a7351e86 by David Waern at 2006-08-12T11:44:47+00:00
Render H98 Data declarations
- - - - -
3fb2208e by David Waern at 2006-08-12T17:15:34+00:00
Perfect rendering of Test.hs
- - - - -
454fd062 by David Waern at 2006-08-13T21:57:08+00:00
Misc fixes and interface load/save
- - - - -
7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00
Some refactoring
- - - - -
a7d3efef by David Waern at 2006-08-19T20:07:55+00:00
Adapt to latest GHC 
- - - - -
5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00
Move interface read/write to its own module + some cleanup
- - - - -
037e011c by David Waern at 2006-08-20T21:38:24+00:00
Small cleanup
- - - - -
da3a1023 by David Waern at 2006-09-03T16:05:22+00:00
Change mode to BatchCompile to avoid GHC API bug
- - - - -
3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00
Starting work on GADT rendering
- - - - -
94506037 by David Waern at 2006-09-03T20:02:48+00:00
Compensate for change of export list order in GHC
- - - - -
c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00
Rename a function
- - - - -
9a9735ba by David Waern at 2006-09-05T15:51:21+00:00
Change version number to 2.0
- - - - -
3758a714 by David Waern at 2006-09-05T15:51:49+00:00
Align comment properly
- - - - -
68478d9e by David Waern at 2006-09-15T18:03:00+00:00
Remove interface reading/writing code and use the GHC api for creating package environments instead
- - - - -
d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00
Change the executable name to haddock-ghc-nolib
- - - - -
fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00
Small source code cleanup
- - - - -
d08eb017 by David Waern at 2006-09-15T18:06:21+00:00
Remove handling of --package flag
- - - - -
b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00
Remove commented-out code
- - - - -
bef0a684 by David Waern at 2006-09-15T18:37:57+00:00
Don't warn about missing links to ()
- - - - -
e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00
Remove Interface and Binary2 modules 
- - - - -
9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00
Remove debug printing from HaddockHtml
- - - - -
a0e7455d by David Waern at 2006-09-16T00:16:29+00:00
Comments only
- - - - -
d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00
Refactor PackageData creation code and start on building the doc env propery (unfinished)
- - - - -
06aaa779 by David Waern at 2006-09-16T00:19:25+00:00
Better comments in Main.hs
- - - - -
1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00
Comments and spacing change
- - - - -
e5a97767 by David Waern at 2006-09-21T17:02:45+00:00
Remove unnecessary fmapM import in Main
- - - - -
9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00
Make import list in HaddockHtml prettier
- - - - -
3452f662 by David Waern at 2006-09-22T18:08:47+00:00
Refactor context rendering
- - - - -
12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00
Do proper HsType rendering (inser parentheses correctly)
- - - - -
2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00
Fix a bug in Main.toHsType
- - - - -
c5396443 by David Waern at 2006-09-22T18:11:16+00:00
Skip external package modules sort for now
- - - - -
3fb95547 by David Waern at 2006-09-22T20:35:40+00:00
Take away trailin "2" on all previously clashing type names
- - - - -
2174755f by David Waern at 2006-09-22T20:51:43+00:00
Remove unused imports in Main
- - - - -
1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00
Fix a comment in Main
- - - - -
32d9e028 by David Waern at 2006-10-05T16:40:11+00:00
Merge with changes to ghc HEAD
- - - - -
3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00
Comment fixes
- - - - -
b9c217ec by David Waern at 2006-10-05T16:49:59+00:00
Filter out more builtin type constructors from warning messages
- - - - -
67e7d252 by David Waern at 2006-10-05T19:38:22+00:00
Refactoring -- better structured pass1
- - - - -
cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00
Remove read/dump interface flags
- - - - -
313f9e69 by David Waern at 2006-10-05T19:49:26+00:00
Remove unused pretty printing
- - - - -
480f09d1 by David Waern at 2006-12-28T13:22:24+00:00
Update to build with latest GHC HEAD
- - - - -
63dccfcb by David Waern at 2007-01-05T01:38:45+00:00
Fixed a bug so that --ghc-flag works correctly
- - - - -
3117dadc by David Waern at 2006-12-29T18:53:39+00:00
Automatically get the GHC lib dir
- - - - -
9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00
Comments
- - - - -
0b0237cc by David Waern at 2007-01-05T16:48:30+00:00
Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC
- - - - -
a962c256 by David Waern at 2007-01-05T17:02:47+00:00
Add tabs in haddock.cabal
- - - - -
0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00
Add GHCUtils.hs
- - - - -
c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00
Change package name to haddock-ghc, version 0.1
- - - - -
38e18b27 by David Waern at 2007-01-12T12:03:52+00:00
No binder name for foreign exports
- - - - -
d18587ab by David Waern at 2007-01-12T12:08:15+00:00
Temp record
- - - - -
ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00
Remove read/dump-interface (again)
- - - - -
f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00
Remove DocOption, use the GHC type
- - - - -
511be8bd by David Waern at 2007-01-12T18:32:41+00:00
Use exceptions instead of Either when loading package info
- - - - -
0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00
Small type change
- - - - -
77507eb7 by David Waern at 2007-01-12T18:33:59+00:00
Remove interface file read/write
- - - - -
0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00
Add trace_ppr to GHCUtils
- - - - -
3878b493 by David Waern at 2007-01-17T21:40:53+00:00
Sort external package modules and build a doc env
- - - - -
8dc323fc by David Waern at 2007-01-17T21:42:41+00:00
Remove comment
- - - - -
f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00
Add haddock-ghc.cabal and remove ghc option pragma in source file
- - - - -
da242b2c by David Waern at 2007-01-18T23:22:46+00:00
Remove some tabs
- - - - -
288ed096 by David Waern at 2007-01-18T23:39:28+00:00
Moved the defaultErrorHandler to scope only over sortAndCheckModules for now
- - - - -
4dd150fe by David Waern at 2007-02-03T21:23:56+00:00
Let restrictCons handle infix constructors
- - - - -
97893442 by David Waern at 2007-02-04T16:26:00+00:00
Render infix data constructors
- - - - -
da89db72 by David Waern at 2007-02-04T16:26:33+00:00
CHange project name to Haddock-GHC
- - - - -
e93d48af by David Waern at 2007-02-04T16:59:08+00:00
Render infix type constructors properly
- - - - -
357bc99b by David Waern at 2007-02-04T17:37:08+00:00
Insert spaces around infix function names
- - - - -
ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00
Do not list entities without documentation
- - - - -
04249c7e by David Waern at 2007-02-04T19:16:25+00:00
Add GADT support (quite untested)
- - - - -
2c223f8d by David Waern at 2007-02-04T19:25:10+00:00
Add package file write/save again!
- - - - -
b07ed218 by David Waern at 2007-02-04T19:33:02+00:00
Comment out minf_iface based stuff
- - - - -
953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00
Solve conflicts
- - - - -
593247fc by David Waern at 2007-02-06T19:48:48+00:00
Remove -package flag, GHC's can be used instead
- - - - -
f658ded2 by David Waern at 2007-02-06T20:50:44+00:00
Start for support of ATs
- - - - -
97f9e913 by David Waern at 2007-02-06T20:52:27+00:00
Wibble
- - - - -
2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00
Add the DocOptions change
- - - - -
dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00
Wibble
- - - - -
7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00
Change version to 2.0 and executable name to haddock
- - - - -
c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00
Go back to -B flag 
- - - - -
3a349201 by David Waern at 2007-03-09T13:31:59+00:00
Better exception handling and parsing of GHC flags
- - - - -
05a69b71 by David Waern at 2007-03-09T17:45:44+00:00
Remove commented-out DocEntity printing
- - - - -
755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00
Remove a file that shouldn't be here
- - - - -
a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00
Remove an import
- - - - -
6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00
Start work on Haddock API
- - - - -
f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00
Prettify some comments
- - - - -
f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00
Remove ppr in HaddockTypes
- - - - -
bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00
Remove commented out doc env inference
- - - - -
11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00
De-flatten the namespace
- - - - -
f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00
Add missing stuff to API
- - - - -
9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00
Wibble
- - - - -
7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00
Avoid a GHC bug with parseStaticFlags []
- - - - -
4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00
Add fall-through case to mkExportItem
- - - - -
6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00
Add shebang line to Setup.lhs
- - - - -
80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00
Fix stupid compile error
- - - - -
1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00
Do save/read of interface files properly
- - - - -
0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00
Add version to ghc dependency
- - - - -
b0499b63 by David Waern at 2007-04-10T21:37:08+00:00
Change package name to haddock
- - - - -
9d50d27e by David Waern at 2007-04-24T00:22:14+00:00
Use filepath package instead of FilePath
- - - - -
87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00
Add new package dependencies
- - - - -
4768709c by David Waern at 2007-07-11T20:37:11+00:00
Follow changes to record constructor representation
- - - - -
b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00
update to compile with the latest GHC & Cabal
- - - - -
c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00
Fix conflicts
- - - - -
97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00
Follow changes to the GHC API
- - - - -
a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00
Call parseStaticFlags before newSession
- - - - -
f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00
Better indentation in haddock.cabal
- - - - -
d84e52ad by David Waern at 2007-08-02T00:08:18+00:00
Wibble
- - - - -
a23f494a by David Waern at 2007-08-02T00:08:24+00:00
Be better at trying to load all module dependencies (debugging)
- - - - -
ee917f13 by David Waern at 2007-08-03T18:48:08+00:00
Load all targets explicitly (checkModule doesn't chase dependencies anymore)
- - - - -
5182d631 by David Waern at 2007-08-16T16:48:55+00:00
Finalize support for links to other packages
- - - - -
dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00
Fix haddock comment errors in Haddock.Types
- - - - -
50c0d83e by David Waern at 2007-08-16T16:51:37+00:00
Remove a debug import
- - - - -
d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00
Rename PackageData to HaddockPackage
- - - - -
3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00
Simplify some comments
- - - - -
66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00
Comment the HaddockPackage definition
- - - - -
8674c761 by David Waern at 2007-08-16T17:25:54+00:00
Improve code layout in Main
- - - - -
571a3a0b by David Waern at 2007-08-16T17:32:13+00:00
Remove explict module imports in Main
- - - - -
d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00
Correct comments
- - - - -
7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00
Fix layout problems in Haddock.Types
- - - - -
9f421d7f by David Waern at 2007-08-17T11:16:48+00:00
Move options out of Main into Haddock.Options
- - - - -
80042b63 by David Waern at 2007-08-17T11:26:59+00:00
Small comment/layout fixes
- - - - -
b141b982 by David Waern at 2007-08-17T11:28:28+00:00
Change project name from Haddock-GHC to Haddock
- - - - -
dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00
Add top module comment to all files
- - - - -
ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00
Factor out typechecking phase into Haddock.Typecheck
- - - - -
6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00
Factor out package code to Haddock.Packages
- - - - -
b396db37 by David Waern at 2007-08-29T22:40:23+00:00
Major refactoring
- - - - -
3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00
Rename HaddockModule to Interface and a few more refactorings
- - - - -
c55326db by David Waern at 2007-08-29T23:48:03+00:00
Some comment cleanup
- - - - -
9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00
Add some modules that I forgot to add earlier
- - - - -
4536dce2 by David Waern at 2007-08-29T23:55:24+00:00
Wibble
- - - - -
9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00
Wibble
- - - - -
c52c050a by David Waern at 2007-08-30T16:30:37+00:00
Rename HaddockModule to Interface
- - - - -
eae2995f by David Waern at 2007-08-30T16:42:59+00:00
Simplify createInterfaces
- - - - -
53f99caa by David Waern at 2007-09-29T00:04:31+00:00
Add build-type: Simple to the cabal file
- - - - -
0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00
Add containers and array dependency
- - - - -
6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00
Prettify the cabal file
- - - - -
87c1e378 by David Waern at 2007-09-29T13:16:39+00:00
FIX: consym data headers with more than two variables
- - - - -
b67fc16a by David Waern at 2007-09-29T14:01:32+00:00
FIX: prefix types used as operators should be quoted
- - - - -
a8f925bc by David Waern at 2007-09-29T14:02:26+00:00
Use isSymOcc from OccName instead of isConSym
- - - - -
fc330701 by David Waern at 2007-09-29T14:15:37+00:00
Use isLexConSym/isLexVarSym from OccName
- - - - -
e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00
FIX: do not quote varsym type operators
- - - - -
402207d2 by David Waern at 2007-09-29T15:01:50+00:00
Wibble
- - - - -
f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00
Take care when pp tyvars - add parens on syms
- - - - -
849e2a77 by David Waern at 2007-10-01T21:56:39+00:00
Go back to using a ModuleMap instead of LookupMod - fixes a bug
- - - - -
549dbac6 by David Waern at 2007-10-02T01:05:19+00:00
Improve parsing of doc options
- - - - -
a36021b8 by David Waern at 2007-10-02T23:05:00+00:00
FIX: double arrows in constructor contexts
- - - - -
d03bf347 by David Waern at 2007-10-09T16:14:05+00:00
Add a simple test suite
- - - - -
c252c140 by David Waern at 2007-10-17T16:02:28+00:00
Add --optghc=.. style flag passing to GHC
- - - - -
cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00
Add support for --read-interface again
- - - - -
33d059c0 by David Waern at 2007-10-18T22:30:18+00:00
Refactoring -- get rid of Haddock.Packages
- - - - -
f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00
Name changes
- - - - -
8a1c816f by David Waern at 2007-10-20T14:24:23+00:00
Add --ghc-version option
- - - - -
4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00
Add some Outputable utils
- - - - -
69e7e47f by David Waern at 2007-10-21T14:35:49+00:00
FIX: Ord for OrdName was not comparing modules
- - - - -
5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00
Wibble
- - - - -
03d48e20 by David Waern at 2007-10-24T15:52:56+00:00
Remove Main from "other modules"
- - - - -
c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00
Make it possible to run haddock on itself
- - - - -
21d156d8 by David Waern at 2007-10-25T14:02:14+00:00
Don't set boot modules as targets
- - - - -
f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00
Add optimisation flags
- - - - -
7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00
Go back to loading only targets (seems to work now)
- - - - -
4862aae1 by David Waern at 2007-11-05T22:24:57+00:00
Do full compilation of modules -- temporary fix for GHC API problem
- - - - -
697e1517 by David Waern at 2007-11-05T22:25:50+00:00
Don't warn about not being able to link to wired/system/builtin-names
- - - - -
892186da by David Waern at 2007-11-06T00:49:21+00:00
Filter out instances with TyCons that are not exported
- - - - -
9548314c by David Waern at 2007-11-06T09:37:14+00:00
Wibble
- - - - -
5cafd627 by David Waern at 2007-11-08T01:43:07+00:00
Filter out all non-vanilla type sigs
- - - - -
04621830 by David Waern at 2007-11-08T01:45:13+00:00
Synch loading of names from .haddock files with GHC's name cache
- - - - -
88d37f77 by David Waern at 2007-11-08T01:46:21+00:00
Remove commented-out code
- - - - -
6409c911 by David Waern at 2007-11-08T01:56:00+00:00
Small bugfix and cleanup in getDeclFromTyCls
- - - - -
af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00
Remove OrdName stuff
- - - - -
3a615e2e by David Waern at 2007-11-08T02:13:41+00:00
Update runtests.hs following changes to haddock
- - - - -
01f3314e by David Waern at 2007-11-08T02:33:01+00:00
Complain if we can't link to wired-in names
- - - - -
fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00
Don't exit when there are no file arguments
- - - - -
194bc332 by David Waern at 2007-11-09T02:55:37+00:00
Wibble
- - - - -
dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00
Wibble
- - - - -
82869fda by David Waern at 2007-11-10T17:01:43+00:00
Introduce InstalledInterface structure and add more stuff to the .haddock files

We introduce InstalledInterface capturing the part of Interface that is stored
in the interface files. We change the ppHtmlContents and ppHtmllIndex to take
this structure instead of a partial Interface. We add stuff like the doc map
and exported names to the .haddock file (via InstalledInterface).

- - - - -
d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00
FIX: contents and index should include external package modules when --gen-contents/--gen-index
- - - - -
e8814716 by David Waern at 2007-11-11T00:29:27+00:00
Remove lDocLinkName and its use in Html backend
- - - - -
6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00
Do some refactoring in the html backend
This also merges an old patch by Augustsson:
  
  Wed Jul 12 19:54:36 CEST 2006  lennart.augustsson at credit-suisse.com
    * Print type definitions like signatures if given arrows.



- - - - -
09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00
mention HsColour in the docs, next to option flags for linking to source code
- - - - -
24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00
change doc references to CVS to give darcs repository location instead
- - - - -
74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00
Update copyright
- - - - -
fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00
Eliminate dep on network by doing a little cut'n'paste
haddock depending on the network causes a circular dependency
at least if you want to build the network lib with haddock docs.

- - - - -
10cc9bda by David Waern at 2007-11-11T02:09:41+00:00
Fix conflicts
- - - - -
4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00
Manual merge of a patch from Duncan Coutts that removes the dependency on mtl 
- - - - -
fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00
Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01
- - - - -
d7431c85 by David Waern at 2007-11-11T02:28:50+00:00
Fix conflicts
- - - - -
f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00
changes for 0.8
- - - - -
db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00
fix the name of the source file


- - - - -
8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00
Rename haddock.js to haddock-util.js
haddock.js will be run automatically by Windows when you type
'haddock' if it is found on the PATH, so rename to avoid confusion.
Spotted by Adrian Hey.

- - - - -
6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00
Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones
- - - - -
d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00
add todo item for --maintainer
- - - - -
2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00
TODO: do something better about re-exported symbols from another package
- - - - -
42d85549 by David Waern at 2007-11-11T02:30:59+00:00
Fix conflicts
- - - - -
5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00
Never do spliting index files into many
- - - - -
f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00
Add searching on the index page
- - - - -
bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00
Delete dead code, now there is only one index page
- - - - -
cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00
Delete more stuff that is no longer required
- - - - -
e2806646 by David Waern at 2007-11-11T02:41:53+00:00
Fix conflicts
- - - - -
a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00
Make the index be in case-insensitive alphabetic order
- - - - -
8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00
Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance
- - - - -
036b8120 by David Waern at 2007-11-11T02:56:58+00:00
Fix conflicts
- - - - -
f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00
added substitution %{FILE///c}
- - - - -
402e166a by David Waern at 2007-11-11T03:35:46+00:00
Manual merge of old patch:

Sat Apr 21 04:36:43 CEST 2007  Roberto Zunino <zunrob at users.sf.net>
  * URL expansion for %%, %L, %{LINE}


- - - - -
2f264fbd by David Waern at 2007-11-11T03:40:33+00:00
Manual merge of an old patch:
  Thu Apr 19 20:23:40 CEST 2007  Wolfgang Jeltsch <g9ks157k at acme.softbase.org>
    * bug fix
    When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for 
  non-exported names.
  
    This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional
  OptIgnoreExports option for every module) but at least the bug seems to be resolved now.

- - - - -
7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00
Install LICENSE in the correct place
- - - - -
66eaa924 by David Waern at 2007-11-11T19:02:46+00:00
Fix a bug that made haddock loop
- - - - -
4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00
Rename java-script file (this wasn't merge correctly)
- - - - -
d569534a by David Waern at 2007-11-11T19:06:44+00:00
Don't require -B <ghc-libdir> when no argument files
Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B 
<ghc-libdir> to Haddock when there're no source files to process. This is nice when 
computing contents/index for external packages.

- - - - -
373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00
Change from tabs to spaces in the ppHtmlIndex function
- - - - -
6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00
Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n))
- - - - -
bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00
Fix conflicts
- - - - -
cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00
Make the max number of results 75 instead of 50, to allow map searching in the base library to work
- - - - -
3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00
Make the search box in a form so that enter does the default search
- - - - -
142103e5 by David Waern at 2007-11-12T00:03:18+00:00
Merge patch from the old branch:

Fri Aug 31 13:21:45 CEST 2007  Duncan Coutts <duncan at haskell.org>
  * Add category: Development to .cabal file
  Otherwise it appears on the hackage website in the "Unclassified" category.


- - - - -
22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00
A a list of small improvements to the TODO file
- - - - -
eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00
addition of type equality support (at least for HTML generation)
- - - - -
816a7e22 by David Waern at 2007-12-08T15:46:26+00:00
Handle class operators correctly when rendering predicates
- - - - -
68baaad2 by David Waern at 2007-12-08T16:15:54+00:00
Code layout changes
- - - - -
09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00
Handle infix operators correctly in the Type -> HsType translation
- - - - -
31c36da2 by David Waern at 2007-12-08T16:24:27+00:00
Add ppLParendTypes/ppLParendType
- - - - -
b17cc818 by David Waern at 2007-12-08T16:26:12+00:00
Use ppParendType when printing types args in predicates
- - - - -
ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00
Fix rendering of instance heads to handle infix operators
This is also a refactoring to share this code for rendering predicates.


- - - - -
ff886d45 by David Waern at 2007-12-08T17:27:46+00:00
Fix rendering of class operators
- - - - -
e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00
Fix a bug (use ppTyName instead of ppName to print names in type apps)
- - - - -
79a1056e by David Waern at 2007-12-08T21:25:18+00:00
Update tests
- - - - -
867741ac by David Waern at 2007-12-08T21:25:49+00:00
Give a diff on test failure
- - - - -
7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00
Add DrIFT commands
- - - - -
3656454d by David Waern at 2008-01-05T20:26:00+00:00
Add "cabal-version: >= 1.2" to the cabal file
- - - - -
77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00
add an item
- - - - -
f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00
Source links must point to the original module, not the referring module
- - - - -
eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00
Manual merge of a patch to the 0.8 branch

  Thu Dec  6 15:00:10 CET 2007  Simon Marlow <simonmar at microsoft.com>
    * Source links must point to the original module, not the referring 
      module


- - - - -
378f4085 by David Waern at 2008-01-06T16:03:45+00:00
Change stability from stable to experimental
- - - - -
8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00
Add haskell.vim (it had been removed somehow)
- - - - -
ea34d02e by David Waern at 2008-01-06T16:36:57+00:00
Change version to 2.0.0.0
- - - - -
34631ac0 by David Waern at 2008-01-06T16:44:57+00:00
Add missing modules to the cabal file
- - - - -
9e142935 by David Waern at 2008-01-06T17:25:42+00:00
Depend on ghc >= 6.8.2 && < 6.9
- - - - -
59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00
add build scripts
- - - - -
1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00
update version number
- - - - -
fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00
update version
- - - - -
f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00
doc updates
- - - - -
ce71b611 by David Waern at 2008-01-07T13:46:32+00:00
Change version in docs and spec
- - - - -
03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00
Manually merge over changes to CHANGES for 0.9
- - - - -
39f1b042 by David Waern at 2008-01-07T15:17:41+00:00
Remove the -use-package flag, we don't support it anyway
- - - - -
7274a544 by David Waern at 2008-01-07T15:33:05+00:00
Update CHANGES for 2.0.0.0
- - - - -
96594f5d by David Waern at 2008-01-07T15:46:49+00:00
Wibble
- - - - -
f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00
Change url to repo in documentation
- - - - -
8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00
Update CHANGES
- - - - -
cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00
Documentation fix
- - - - -
d8e45539 by David Waern at 2008-01-07T16:12:00+00:00
Update docs to say that Haddock accets .lhs files and module names
- - - - -
4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00
Document -B option
- - - - -
47274262 by David Waern at 2008-01-07T16:23:07+00:00
Update CHANGES
- - - - -
7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00
Remove --use-package, --package & --no-implicit.. flags from docs
- - - - -
6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00
Remove --no-implicit-prelide flag
- - - - -
1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00
Update the "Using literate or pre-processed source" section
- - - - -
0117f620 by David Waern at 2008-01-07T16:41:55+00:00
Document the --optghc flag
- - - - -
087ab1cf by David Waern at 2008-01-07T16:42:10+00:00
Remove the documenation section on derived instances
The problem mentioned there doesn't exist in Haddock 2.0.0.0

- - - - -
7253951e by David Waern at 2008-01-07T16:48:40+00:00
Document OPTIONS_HADDOCK
- - - - -
3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00
Wibble
- - - - -
3025adf9 by David Waern at 2008-01-07T17:08:14+00:00
Wibble
- - - - -
5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00
Change synopsis field to description
- - - - -
1673f54b by David Waern at 2008-01-07T17:18:21+00:00
Change my email address in the cabal file
- - - - -
55aa9808 by David Waern at 2008-01-07T18:18:02+00:00
Add documentation for readInterfaceFile
- - - - -
eaea417f by David Waern at 2008-01-07T18:21:30+00:00
Export necessary stuff from Distribution.Haddock
- - - - -
7ea18759 by David Waern at 2008-01-07T18:31:49+00:00
Remove dep on Cabal
- - - - -
7b79c74e by David Waern at 2008-01-07T18:33:49+00:00
Remove dep on process
- - - - -
ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00
Add feature-requsts from Henning Thielemann to TODO
- - - - -
0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00
Record a bug in TODO
- - - - -
b04605f3 by David Waern at 2008-01-23T16:59:06+00:00
Add a bug reported by Ross to TODO
- - - - -
5b17c030 by David Waern at 2008-01-23T18:05:53+00:00
A a bug report to TODO
- - - - -
1c993b0d by David Waern at 2008-01-25T16:30:25+00:00
Accept test output
- - - - -
c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00
Accept test output
- - - - -
4b795811 by David Waern at 2008-01-25T16:38:37+00:00
Change Hidden.hs (test) to use OPTIONS_HADDOCK
- - - - -
c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00
Accept test output
- - - - -
ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00
Add Hidden.html.ref to tests
- - - - -
1dc9610c by David Waern at 2008-02-02T20:50:51+00:00
Add a comment about UNPACK bug in TODO
- - - - -
2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00
Change the representation of DocNames

Ross Paterson reported a bug where links would point to the defining module
instead of the "best" module for an identifier (e.g Int pointing to GHC.Base
instead of Data.Int). This patch fixes this problem by refactoring the way
renamed names are represented. Instead of representing them by:

> data DocName = Link Name | NoLink Name

they are now represented as such:

> data DocName = Documented Name Module | Undocumented Name

and the the link-env looks like this:

> type LinkEnv = Map Name Module

There are several reasons for this. First of all, the bug was caused by
changing the module part of Names during the renaming process, without changing
the Unique field. This caused names to be overwritten during the loading of
.haddock files (which caches names using the NameCache of the GHC session).
So we might create new Uniques during renaming to fix this (but I'm not
sure that would be problem-free). Instead, we just keep the Name and add the
Module where the name is best documented, since it can be useful to keep
the original Name around (for e.g. source-code location info and for users of
the Haddock API).

Also, the names Link/NoLink don't really make sense, since wether to use
links or not is entirely up to the users of DocName.

In the process of following this change into H.Backends.Html I removed the
assumption that binder names are Undocumented (which was just an unnecessary
assumption, the OccName is the only thing needed to render these). This will
probably make it possible to get rid of the renamer and replace it with a
traversal from SYB or Uniplate.

Since DocName has changed, InterfaceFile has changed so this patch also
increments the file-format version. No backwards-compatibility is implemented.

- - - - -
0f28c921 by David Waern at 2008-02-09T23:00:36+00:00
H.GHC.Utils: remove unused imports/exports
- - - - -
0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00
H.GHC.Utils: add some functions that were removed by mistake
- - - - -
e3452f49 by David Waern at 2008-02-10T00:28:48+00:00
Fix some trivial warnings in H.InterfaceFile
- - - - -
a6d74644 by David Waern at 2008-02-10T00:48:06+00:00
Update the version message to fit in small terminals
- - - - -
76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00
Remove bugs from TODO that don't apply anymore since the port
- - - - -
5e10e090 by David Waern at 2008-02-10T15:22:47+00:00
Remove bugs from TODO that weren't actual bugs
- - - - -
fef70878 by David Waern at 2008-02-10T15:23:44+00:00
Remove yet another item from TODO that was not an actual bug
- - - - -
e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00
Bump the version number to 2.1.0

Since the exported datatype DocName has changed, we need to bump the
major version number.

Let's also drop the fourth version component, it's not that useful.

- - - - -
e3be7825 by David Waern at 2008-04-11T14:29:04+00:00
Add a bug to TODO
- - - - -
cb6574be by David Waern at 2008-04-11T16:00:45+00:00
Use the in-place haddock when running tests
- - - - -
c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00
Turn off GHC warnings when running tests
- - - - -
7f61b546 by David Waern at 2008-04-11T17:24:00+00:00
Add a flag for turning off all warnings
- - - - -
883b8422 by David Waern at 2008-04-12T14:02:18+00:00
Fix printing of data binders
- - - - -
2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00
Fix missing parenthesis in constructor args bug
- - - - -
1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00
Simplify test suite and add tests
I move all tests into one single directory to simplify things, and add a test
for the last bug that was fixed.

- - - - -
8f178376 by David Waern at 2008-04-12T19:00:15+00:00
Add a script for copying test output to "expected" output
- - - - -
193e3a03 by David Waern at 2008-04-12T19:16:37+00:00
Remove two fixed bugs from TODO
- - - - -
ddc9130c by David Waern at 2008-04-12T19:37:06+00:00
Update test README
- - - - -
956069c0 by David Waern at 2008-05-01T12:16:14+00:00
Update version number in spec and docs
- - - - -
5478621c by David Waern at 2008-05-01T12:28:12+00:00
 Remove claim of backwards compatibility from docs for readInterfaceFile
- - - - -
4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00
Update CHANGES
- - - - -
804216fb by David Waern at 2008-05-01T12:43:16+00:00
Add a synopsis
- - - - -
fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00
Add Haddock.DocName to the cabal file
- - - - -
9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00
Remove -fglasgow-exts and -fasm
- - - - -
aee7c145 by David Waern at 2008-05-01T12:54:01+00:00
Add LANGUAGE pragmas to source files
- - - - -
9a58428b by David Waern at 2008-05-01T12:54:19+00:00
Add extensions to cabal file
- - - - -
494f1bee by David Waern at 2008-05-01T13:12:09+00:00
Export DocName in the API
- - - - -
c938196b by David Waern at 2008-05-01T13:12:19+00:00
Add hide options to some source files
- - - - -
236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00
Rewrite the --hoogle flag support
- - - - -
6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00
Simplify the newtype/data outputting in Hoogle, as haddock does it automatically
- - - - -
f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00
Add initial structure for outputting documentation as well, but does not yet output anything
- - - - -
7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00
Remove <document comment> from the Hoogle output
- - - - -
9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00
Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info
- - - - -
4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00
Change packageName to packageStr, as it better reflects the information stored in it
- - - - -
7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00
Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info
- - - - -
8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00
Change Hoogle to take the package name and package version separately
- - - - -
a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00
In Hoogle do not list things that are not local to this module
- - - - -
974b76b7 by David Waern at 2008-06-19T18:40:13+00:00
Be more consistent with GHC API naming in H.GHC.Utils
- - - - -
2facb4eb by David Waern at 2008-06-19T19:03:03+00:00
Update test output
- - - - -
c501de72 by David Waern at 2008-06-26T20:26:49+00:00
Use ghc-paths to get the lib dir

The path can still be overridden using the -B flag. It's not longer
required to pass the lib dir to the program that runs the test suite.

- - - - -
ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00
Update CHANGES
- - - - -
9d21c60a by David Waern at 2008-06-26T20:34:53+00:00
Update README
- - - - -
741448f0 by David Waern at 2008-06-26T21:12:57+00:00
Improve wording in the help message
- - - - -
b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00
Rename ForeignType
- - - - -
6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00
Rename TyFamily
- - - - -
8d1125ed by David Waern at 2008-06-30T10:37:21+00:00
Rename type patterns
- - - - -
7610a4cb by David Waern at 2008-06-30T10:45:07+00:00
Rename associated types
- - - - -
8eeba14c by David Waern at 2008-06-30T10:47:41+00:00
Remove the TODO file now that we have a trac
- - - - -
1af5b25b by David Waern at 2008-07-02T18:19:28+00:00
Render type family declarations (untested)
- - - - -
ceb99797 by David Waern at 2008-07-02T18:24:06+00:00
Remove redundant check for summary when rendering data types
- - - - -
b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00
More support for type families and associated types
Now we just need to render the instances

- - - - -
78784879 by David Waern at 2008-07-07T22:13:58+00:00
Remove filtering of instances
We were filtering out all instances for types with unknown names. This was probably an
attempt to filter out instances for internal types. I am removing the filtering for the
moment, and will try to fix this properly later.


- - - - -
3e758dad by David Waern at 2008-06-30T18:50:30+00:00
Run haddock in-place during testing
- - - - -
d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00
Remove index.html and doc-index.html from output, they should not be versioned
- - - - -
3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00
Update test output following change to instance filtering
- - - - -
e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00
Stop using the map from exported names to declarations

During creation of the interface, we were using two maps: one from 
exported names to declarations, and one from all defined names in the 
module to declarations. The first contained subordinate names while the 
second one didn't. The first map was never used to look up names not 
defined in the associated module, so if we add subordinate names to the
second map, we could use it everywhere. That's that this patch does.

This simplifies code because we don't have to pass around two maps 
everywhere.

We now store the map from locally defined things in the interface
structure instead of the one from exported names.

- - - - -
2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00
Get the all locally defined names from GHC API

We previously had some code to compute all locally defined names in 
a module including subordinate names. We don't need it since we can
get the names from modInfoTyThings in the GHC API.

- - - - -
bf637994 by David Waern at 2008-07-13T13:09:16+00:00
Refactoring in H.Interface.Create

We were creating a doc map, a declaration map and a list of entities
separately by going through the HsGroup. These structures were all used
to build the interface of a module.

Instead of doing this, we can start by creating a list of declarations
from the HsGroup, then collect the docs directly from this list 
(instead of using the list of entities), creating a documentation map.

We no longer need the Entity data type, and we can store a single
map from names to declarations and docs in the interface, instead of
the declaration map and the doc map.

This way, there is only one place where we filter out the declarations
that we don't want, and we can remove a lot of code.

Another advantage of this is that we can create the exports directly
out of the list of declarations when we export the full module contents.
(Previously we did a look up for each name to find the declarations).
This is faster and removes another point where we depend on names to
identify exported declarations, which is good because it eliminates
problems with instances (which don't have names).

- - - - -
547e410e by David Waern at 2008-07-13T13:34:51+00:00
Remove FastString import and FSLIT macro in H.I.Create -- they were unused
- - - - -
693759d1 by David Waern at 2008-07-13T13:36:23+00:00
Remove unused import from H.I.Create
- - - - -
cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00
Small touches
- - - - -
96de8f1d by David Waern at 2008-07-20T11:21:46+00:00
Preparation for rendering instances as separate declarations

We want to be able to render instances as separate declarations. So we remove
the Name argument of ExportDecl, since instances are nameless.

This patch also contains the first steps needed to gather type family instances 
and display them in the backend, but the implementation is far from complete.
Because of this, we don't actually show the instances yet.

- - - - -
b0f824fb by David Waern at 2008-07-20T15:53:08+00:00
Follow changes to ExportDecl in Hoogle
- - - - -
1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00
Change how the Hoogle backend outputs classes, adding the context in
- - - - -
7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00
Remove the indent utility function from Hoogle backend
- - - - -
3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00
Add support for Hoogle writing ForeignImport/ForeignExport properly
- - - - -
795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00
Flesh out the Hoogle code to render documentation
- - - - -
23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00
Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u>
- - - - -
db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00
Remove any white space around a <li> element
- - - - -
f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00
Remove the TODO in the Hoogle HTML generation, was already done
- - - - -
693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00
Put brackets round operators in more places in the Hoogle output
- - - - -
842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00
Print type signatures with brackets around the name
- - - - -
cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00
Bump version number to 2.2.0
- - - - -
30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00
Resolve conflicts in H.B.Hoogle
- - - - -
1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00
Add "all" command to runtests.hs that runs all tests despite failures
- - - - -
f2723023 by David Waern at 2008-07-23T23:08:39+00:00
Update tests/README
- - - - -
c0304a11 by David Waern at 2008-07-23T23:21:15+00:00
Be compatible with GHC 6.8.3
    
The cabal file is converted to use the "new" syntax with explicit Library
and Executable sections.

We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field
in the cabal file. (Ideally, Cabal would define the symbol for us, like it does
for __GLASGOW_HASKELL__).

We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3.
    
Previously, we only supported GHC 6.8.2 officially but the dependencies field
said "ghc <= 6.9". This was just for convenience when testing against the (then 
compatible) HEAD version of GHC, and was left in the release by mistake.
  
Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field
correctly reflects this.

- - - - -
88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00
Depend on the currently available ghc-paths versions only
- - - - -
8738d97b by David Waern at 2008-07-24T10:50:44+00:00
FIX haskell/haddock#44: Propagate parenthesis level when printing documented types
- - - - -
05339119 by David Waern at 2008-07-24T16:06:18+00:00
Drop unnecessary parenthesis in types, put in by the user
 
We were putting in parenthesis were the user did. Let's remove this since
it just clutters up the types. The types are readable anyway since we print
parens around infix operators and do not rely on fixity levels.
  
When doing this I discovered that we were relying on user parenthesis when
printin types like (a `O` b) c. This patchs fixes this problem so that
parenthesis are always inserted around an infix op application in case it
is applied to further arguments, or if it's an arguments to a type constructor.

Tests are updated.

- - - - -
b3a99828 by David Waern at 2008-07-24T10:19:43+00:00
Print parenthesis around non-atomic banged types

Fixes half of haskell/haddock#44

- - - - -
ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00
Add a reference file for the TypeFamilies test
- - - - -
1941cc11 by David Waern at 2008-07-25T17:15:53+00:00
Simplify definition of pretty and trace_ppr
- - - - -
e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00
Warning messages

Output a warning when filtering out data/type instances and associated types
in instances. We don't show these in the documentation yet, and we need to
let the user know.

- - - - -
9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00
Doc: Mention Hoogle in the Introduction
- - - - -
afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00
Doc: update -B description
- - - - -
584c0c91 by David Waern at 2008-07-25T18:11:38+00:00
Doc: describe -w flag
- - - - -
77619c24 by David Waern at 2008-07-28T12:29:07+00:00
Remove TODO from cabal file
- - - - -
96717d5f by David Waern at 2008-07-28T12:29:27+00:00
Support type equality predicates
- - - - -
c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00
Move unL from H.B.Hoogle to H.GHC.Utils

I like Neil's shorter unL better than unLoc from the GHC API.

- - - - -
c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00
Do not export ATs when not in list of subitems
- - - - -
bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00
Filter out ForeignExports
- - - - -
df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00
Filter out more declarations

The previous refactorings in H.I.Create introduced a few bugs. Filtering
of some types of declarations that we don't handle was removed. This patch
fixes this.

- - - - -
2f8a958b by David Waern at 2008-08-03T15:24:07+00:00
Move reL to H.GHC.Utils so we can use it everywhere
- - - - -
8ec15efd by David Waern at 2008-08-03T15:25:00+00:00
 Use isVanillaLSig from GHC API instead of home brewn function
- - - - -
300f93a2 by David Waern at 2008-08-03T15:25:27+00:00
Filter out separately exported ATs

This is a quick and dirty hack to get rid of separately exported ATs.
We haven't decided how to handle them yet. No warning message is given.

- - - - -
8776d1ec by David Waern at 2008-08-03T16:21:21+00:00
Filter out more declarations and keep only vanilla type sigs in classes
- - - - -
ea07eada by David Waern at 2008-08-03T16:48:00+00:00
Fix layout
- - - - -
dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00
Move some utility functions from H.I.Create to H.GHC.Utils
- - - - -
4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00
Do not filter out doc declarations
- - - - -
0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00
Filter out separately exported ATs (take two)
- - - - -
af970fe8 by David Waern at 2008-08-03T22:39:17+00:00
Update CHANGES
- - - - -
5436ad24 by David Waern at 2008-08-03T22:40:20+00:00
Bump version number to 2.2.1
- - - - -
d66de448 by David Waern at 2008-08-05T19:00:32+00:00
Remove version restriction on ghc-paths
- - - - -
534b1364 by David Waern at 2008-08-05T19:04:35+00:00
Bump version to 2.2.2 and update CHANGES
- - - - -
549188ff by David Waern at 2008-08-05T19:16:49+00:00
Fix CHANGES
- - - - -
0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00
invoking haddock clarification and help
- - - - -
748295cc by David Waern at 2008-08-11T18:56:37+00:00
Doc: say that the --hoogle option is functional
- - - - -
43301db4 by David Waern at 2008-08-05T19:26:08+00:00
Change ghc version dependency to >= 6.8.2
- - - - -
3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00
Make H.GHC.Utils build with GHC HEAD
- - - - -
7568ace0 by David Waern at 2008-08-11T19:41:54+00:00
Import Control.OldException instead of C.Exception when using ghc >= 6.9

We should really test for base version instead, but I don't currently
know which version to test for.

- - - - -
b71ae991 by David Waern at 2008-08-12T22:40:39+00:00
Make our .haddock file version number depend on the GHC version

We need to do this, since our .haddock format can potentially
change whenever GHC's version changes (even when only the patchlevel
changes).

- - - - -
6307ce3f by David Waern at 2008-08-12T22:49:57+00:00
Remove matching on NoteTy in AttachInstances, it has been removed
- - - - -
2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00
Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9
- - - - -
c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00
Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3
- - - - -
69a44ebb by David Waern at 2008-08-12T23:11:12+00:00
Follow changes to parseDynamic/StaticFlags
- - - - -
5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00
Add __GHC_PATCHLEVEL__ symbol also when building the library
- - - - -
8574dc11 by David Waern at 2008-08-13T21:44:17+00:00
Follow move of package string functions from PackageConfig to Module
- - - - -
c9baa77f by David Waern at 2008-08-13T21:45:29+00:00
Follow extensible exceptions changes
- - - - -
9092de15 by David Waern at 2008-08-13T21:46:20+00:00
Update test following Haddock version change
- - - - -
ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00
Follow changes to parseDynamic- parseStaticFlags in GHC
- - - - -
b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00
Follow changes to Binary in GHC 6.9
- - - - -
edfda1cc by David Waern at 2008-08-13T21:50:17+00:00
Change ghc version dependency to >= 6.8.2 && <= 6.9
- - - - -
d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00
Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base
- - - - -
dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00
Add support for type synonyms to Hoogle, was accidentally missing before (woops!)
- - - - -
b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00
Generalise Hoogle.doc and add a docWith
- - - - -
415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00
Make Hoogle add documentation to a package
- - - - -
790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00
Use the same method to put out signatures as class methods in the Hoogle backend
- - - - -
ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00
Remove Explicit top-level forall's when pretty-printing signatures
- - - - -
6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00
Simplify the code by removing not-to-important use of <.> in the Hoogle back end
- - - - -
788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00
In the hoogle back end, markup definition lists using <i>, not <b>
- - - - -
77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00
Add a Makefile for GHC's build system. Still won't work yet, but we're closer
- - - - -
920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00
Add haddock.wrapper
- - - - -
bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00
Add a manual Cabal flag to control the ghc-paths dependency
- - - - -
04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00
Update extensions in Cabal file
Use ScopedTypeVariables instead of PatternSignatures

- - - - -
12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00
Increase the upper bound on the GHC version number
- - - - -
b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00
Fix some warnings
- - - - -
aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00
Fixes for using haddock in a GHC build tree
- - - - -
ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00
Don't use Cabal wrappers on Windows
- - - - -
35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00
Fix in-tree haddock on Windows
- - - - -
c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00
follow library changes
- - - - -
2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00
bindist fixes
- - - - -
3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00
We need to tell haddock that its datasubdir is . or it can't find package.conf
- - - - -
388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00
Fix haddock inplace on Windows
- - - - -
70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00
Fix installed haddock on Windows
- - - - -
83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00
Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better
- - - - -
b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00
Add a LANGUAGE ForeignFunctionInterface pragma
- - - - -
afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00
Wibble imports
- - - - -
547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00
Add a "#!/bin/sh" to haddock.wrapper
- - - - -
f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00
Use "exec" when calling haddock in the wrapper
- - - - -
2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00
Port Haddock.Interface to new GHC API.

This required one bigger change: 'readInterfaceFile' used to take an
optional 'Session' argument.  This was used to optionally update the
name cache of an existing GHC session.  This does not work with the
new GHC API, because an active session requires the function to return
a 'GhcMonad' action, but this is not possible if no session is
provided.

The solution is to use an argument of functions for reading and
updating the name cache and to make the function work for any monad
that embeds IO, so it's result type can adapt to the calling context.

While refactoring, I tried to make the code a little more
self-documenting, mostly turning comments into function names.

- - - - -
3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00
Reflect GHC API changes.
- - - - -
2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00
Port Haddock.GHC.Typecheck to new GHC API.
- - - - -
9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00
Port Haddock.GHC to new GHC API.
- - - - -
caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00
Port Main to new GHC API.
- - - - -
069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00
Fix paths used on Windows frmo a GHC tree: There is no whare directory
- - - - -
7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00
Fix the in-tree haddock on Windows
- - - - -
0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00
Increase the GHC upper bound from 6.11 to 6.13
- - - - -
f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00
Do not wrap __ in brackets
- - - - -
036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00
Fix building haddock when GhcProfiled=YES
- - - - -
01434a89 by David Waern at 2008-09-24T20:24:21+00:00
Add PatternSignatures LANGUAGE pragma to Main and Utils
- - - - -
1671a750 by David Waern at 2008-10-02T22:57:25+00:00
For source links, get original module from declaration name instead of environment.

Getting it from the environment must have been a remnant from the
times when we were using unqualified names (versions 0.x).

- - - - -
a25dde99 by David Waern at 2008-10-02T22:59:57+00:00
Remove ifaceEnv from Interface - it's no longer used
- - - - -
610993da by David Waern at 2008-10-02T23:04:58+00:00
Write a comment about source links for type instance declarations
- - - - -
5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00
Follow GHC API change of parseModule.
- - - - -
5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00
TAG 2008-10-03
- - - - -
76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00
Only load modules once when typechecking with GHC.
  
This still doesn't fix the memory leak since the typechecked source is
retained and then processed separately.  To fix the leak, modules must
be processed directly after typechecking.

- - - - -
7074d251 by David Waern at 2008-10-09T23:53:54+00:00
Interleave typechecking with interface creation

At the same time, we fix a bug where the list of interfaces were
processed in the wrong order, when building the links and renaming
the interfaces.

- - - - -
4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00
Add some strictness annotations in Interface

We add some strictness annotations to the fields of Interface,
so that less GHC data is hold on to during processing.

- - - - -
22035628 by David Waern at 2008-10-10T20:02:31+00:00
Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck
- - - - -
be637ad3 by David Waern at 2008-10-10T20:33:38+00:00
Make Haddock build with GHC 6.8.2
- - - - -
523b3404 by David Waern at 2008-10-10T21:08:09+00:00
Fix documentation for createInterfaces
- - - - -
e1556702 by David Waern at 2008-10-10T21:26:19+00:00
Hide H.Utils in library
- - - - -
a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00
Add back .haddock file versioning based on GHC version

It was accidentally removed in the patch for GHC 6.8.2 compatibility

- - - - -
06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00
Bump version number to 2.3.0
- - - - -
ff087fce by David Waern at 2008-10-10T22:35:49+00:00
Add support for DocPic

The support for DocPic was merged into the GHC source long ago,
but the support in Haddock was forgotten. Thanks Peter Gavin for
submitting this fix!

- - - - -
3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00
Update tests
- - - - -
0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00
no need for handleErrMsg now, we don't throw any ErrMsgs
- - - - -
f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00
Compile with wrapper but remove it for dist-install
- - - - -
7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00
Remove interface from LinksInfo

It was there to know the documentation home module when creating
a wiki link, but we already know this since we have the DocName.

- - - - -
e5729e6a by David Waern at 2008-10-15T20:49:18+00:00
Wibble
- - - - -
b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00
Use type synonyms for declarations and docs in H.I.Create
- - - - -
be71a15b by David Waern at 2008-10-15T21:12:17+00:00
Comment out unused type family stuff completely
- - - - -
91aaf075 by David Waern at 2008-10-15T21:49:04+00:00
Wibble
- - - - -
42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00
Move convenient type synonym to H.Types
- - - - -
db11b723 by David Waern at 2008-10-15T22:14:07+00:00
Add DeclInfo to H.Types
- - - - -
193552b6 by David Waern at 2008-10-15T22:15:01+00:00
Add subordinates with docs to the declaration map

The only place in the code where we want the subordinates for a declaration is
right after having looked up the declaration in the map.

And since we include subordinates in the map, we might as well take the
opportunity to store those subordinates that belong to a particular declaration
together with that declaration.

We also store the documentation for each subordinate.

- - - - -
31e6eebc by David Waern at 2008-10-16T17:18:47+00:00
Wibble
- - - - -
0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00
Fix haskell/haddock#61

We were not getting docs for re-exported class methods. This was because we
were looking up the docs in a map made from the declarations in the current
module being rendered. Obviously, re-exported class methods come from another
module.

Class methods and ATs were the only thing we were looking up using the doc map,
everything else we found in the ExporItems. So now I've put subordinate docs
in the ExportItem's directly, to make things a bit more consistent.

To do this, I added subordinates to the the declarations in the declaration
map. This was easy since we were computing subordinates anyway, to store
stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we
call what is now stored in the map. 

This little refactoring removes duplicate code to retrieve subordinates and
documentation from the HsGroup.

- - - - -
de47f20a by David Waern at 2008-10-16T22:06:35+00:00
Document function and improve its layout
- - - - -
e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00
Force interface more aggressively.

For running Haddock on GHC this reduces memory usage by about 50 MB on
a 32 bit system.  A heap profile shows total memory usage peak at
about 100 MB, but actual usage is at around 300 MB even with
compacting GC (+RTS -c).

- - - - -
b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00
Make renamer consistent

Instead of explicitly making some binders Undocumented, treat all names the
same way (that is, try to find a Documented name).

- - - - -
f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00
TAG GHC 6.10 fork
- - - - -
74599cd0 by David Waern at 2008-10-20T21:13:24+00:00
Do not save hidden modules in the .haddock file

We were saving interfaces of all processed modules including those hidden using
{-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links
when generating the index for the libraries that come with GHC.

This patch excludes modules with hidden documentation when writing .haddock
files. It should fix the above problem. 

- - - - -
7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00
Do not save hidden modules in the .haddock file (also for ghc >= 6.9)

When writing the first patch, I forgot to do the fix in both branches of an #if
macro.

- - - - -
b99b1951 by David Waern at 2008-10-22T20:04:18+00:00
Remove subordinate map and its usage

It is not needed now that we store subordinate names in the DeclInfo map.

- - - - -
da97cddc by David Waern at 2008-10-22T20:11:46+00:00
Tidy up code in H.I.Create a little

Remove commented out half-done type instance support, and remove DeclWithDoc
synonym.

- - - - -
6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00
Fix warnings in H.GHC.Utils
- - - - -
171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00
Fix warnings in H.Utils
- - - - -
c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00
Wibble
- - - - -
767fa06a by David Waern at 2008-10-27T19:59:04+00:00
Make named doc comments into ExportDoc instead of ExportDecl

Fixes a crash when processing modules without export lists containing named
docs.

- - - - -
e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00
Add HCAR entry
- - - - -
92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00
Update CHANGES
- - - - -
84d4da6e by David Waern at 2008-11-03T11:25:04+00:00
Add failing test for template haskell crash
- - - - -
2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00
Add tests/TH.hs
- - - - -
8a59348e by David Waern at 2008-11-04T21:30:26+00:00
TAG 2.3.0
- - - - -
54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00
Enable framed view of the HTML documentation.

This patch introduces:

 - A page that displays the documentation in a framed view.  The left
   side will show a full module index.  Clicking a module name will
   show it in the right frame.  If Javascript is enabled, the left
   side is split again to show the modules at the top and a very short
   synopsis for the module currently displayed on the right.

 - Code to generate the mini-synopsis for each module and the mini
   module index ("index-frames.html").

 - CSS rules for the mini-synopsis.

 - A very small amount of javascript to update the mini-synopsis (but
   only if inside a frame.)

Some perhaps controversial things:

 - Sharing code was very difficult, so there is a small amount of code
   duplication.

 - The amount of generated pages has been doubled, since every module
   now also gets a mini-synopsis.  The overhead should not be too
   much, but I haven't checked.  Alternatively, the mini-synopsis
   could also be generated using Javascript if we properly annotate
   the actual synopsis.

- - - - -
5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00
Follow change to ExportDecl in frames code
- - - - -
60e16308 by David Waern at 2008-11-04T23:35:26+00:00
Update CHANGES
- - - - -
d63fd26d by David Waern at 2008-11-04T23:37:43+00:00
Bump version number
- - - - -
c1660c39 by David Waern at 2008-11-04T23:44:46+00:00
Update CHANGES
- - - - -
995ab384 by David Waern at 2008-11-04T23:55:21+00:00
Remove .ref files from tests/output/
- - - - -
1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00
Output version info before running tests
- - - - -
649b182f by David Waern at 2008-11-05T22:45:37+00:00
Add ANNOUNCE message
- - - - -
c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00
Update ANNOUNCE
- - - - -
9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00
Wibble
- - - - -
5aac87ce by David Waern at 2008-11-06T21:07:48+00:00
Depend on base 4.* when using GHC >= 6.9, otherwise 3.*
- - - - -
b9796a74 by David Waern at 2008-11-06T21:13:40+00:00
Bump version to 2.4.1 and update CHANGES
- - - - -
d4b26baa by David Waern at 2008-11-06T21:26:33+00:00
Depend on base 4.0.* instead of 4.*
- - - - -
2cb0903c by David Waern at 2008-11-06T21:46:53+00:00
Fix warnings in H.B.HH and H.B.HH2
- - - - -
e568e89a by David Waern at 2008-11-06T21:47:12+00:00
Fix warnings in Haddock.ModuleTree
- - - - -
9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00
Fix warnings in Haddock.Version
- - - - -
02ac197c by David Waern at 2008-11-06T21:51:31+00:00
Fix warnings in H.InterfaceFile and H.Options
- - - - -
63e7439a by David Waern at 2008-11-06T21:59:45+00:00
Fix warnings in H.GHC.Typecheck
- - - - -
4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00
Set HscTarget to HscNothing instead of HscAsm

There used to be a bug in the GHC API that prevented us from setting this
value.

- - - - -
07357aec by David Waern at 2008-11-09T22:27:00+00:00
Re-export NameCache and friends from Distribution.Haddock
- - - - -
ea554b5a by David Waern at 2008-11-09T23:14:10+00:00
Add Haddock.GHC.Utils to other-modules in library
- - - - -
74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00
Export DocName in the library
- - - - -
241a58b3 by David Waern at 2008-11-10T01:19:18+00:00
Document the functions in H.DocName
- - - - -
edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00
Export H.DocName in the library
- - - - -
4f588d55 by David Waern at 2008-11-10T01:29:14+00:00
Make DocName an instance of NamedThing
- - - - -
b4647244 by David Waern at 2008-11-15T22:58:18+00:00
Reflect version bump in test suite
- - - - -
4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00
Update tests

For unknown reasons, test output for Bug1 and Test has changed for the better.

- - - - -
1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00
Store hidden modules in .haddock files

We store documentation for an entity in the 'InstalledInterface' of the
definition site module, and never in the same structure for a module which
re-exports the entity. So when a client of the Haddock library wants to look up
some documentation, he/she might need to access a hidden module. But we
currently don't store hidden modules in the .haddock files.

So we add the hidden modules and the Haddock options to the .haddock files.
The options will be used to filter the module list to obtain the visible
modules only, which is necessary for generating the contents and index for
installed packages.

- - - - -
8add6435 by David Waern at 2008-11-16T14:35:50+00:00
Bump major version number due to .haddock file format change
- - - - -
48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00
Update tests to account for version number bump
- - - - -
0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00
HADDOCK_DATA_DIR changed to haddock_datadir
- - - - -
5088b78c by David Waern at 2008-11-23T17:13:21+00:00
FIX haskell/haddock#45: generate two anchors for each name

We generate two anchor tags for each name, one where we don't escape the name
and one where we URI-encode it. This is for compatibility between IE and Opera.
Test output is updated.

- - - - -
5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00
Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584)
- - - - -
51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00
Allow referring to a specific section within a module in a module link
Fixes haskell/haddock#65

- - - - -
4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00
Update tests following anchor change
- - - - -
f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00
Haddock really shouldn't try to overwrite files.
- - - - -
98127499 by David Waern at 2008-12-07T14:09:15+00:00
Solve conflict
- - - - -
319356c5 by David Waern at 2008-10-22T21:16:55+00:00
Add -Wall -Werror to ghc-options
- - - - -
3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00
TAG 2.4.0
- - - - -
4b21e003 by David Waern at 2008-11-06T21:14:04+00:00
TAG 2.4.1
- - - - -
8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00
Remove -Werror
- - - - -
299d6deb by David Waern at 2008-12-07T14:25:18+00:00
Remove -Wall, we'll focus on warnings after 6.10.2 is out
- - - - -
5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00
Resolve conflict properly
- - - - -
67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00
Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a}
- - - - -
61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00
Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library
- - - - -
2fab8554 by David Waern at 2008-12-08T23:19:48+00:00
Make visible names from ExportItems

Instead of a complicated calculation of visible names out of GHC's export
items, we can get them straight out of the already calculated ExportItems.  The
ExportItems should represent exactly those items that are visible in an
interface. 

If store all the exported sub-names in ExportDecl instead of only those with
documentation, the calculation becomes very simple. So we do this change as
well (should perhaps have been a separate patch).
 
This should fix the problem with names from ghc-prim not appearing in the link
environment.

- - - - -
7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00
Wrap the GHC usage with defaultCleanupHandler
This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned.

- - - - -
7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00
Show re-exported names from external packages again

This fixes GHC ticket 2746.

In order to also link to the exported subordinate names of a declaration, we
need to re-introduce the sub map in the .haddock files.

- - - - -
119e4e05 by David Waern at 2009-01-06T23:34:17+00:00
Do not process boot modules

We should of course not try to produce documentation for boot modules! The
reason this has worked in the past is that the output of "real" modules
overwrites the output of boot modules later in the process. However, this
causes a subtle link environment problem. So let's get rid of this stupid
behaviour.
  
We avoid processing boot modules, but we continue to typecheck them.

- - - - -
c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00
Export modules also when coming from external packages

This seems to have regressed since a refactoring that was
part of the 2.3.0 release.

- - - - -
24031c17 by David Waern at 2009-01-10T15:26:26+00:00
Change version to 2.4.2 - no need to go to 2.5.0
- - - - -
864d1c3f by David Waern at 2009-01-10T15:35:20+00:00
Update tests to account for version number change
- - - - -
524ba886 by David Waern at 2009-01-10T18:29:17+00:00
Add test for Template Haskell splicing
- - - - -
05e6e003 by David Waern at 2009-01-10T19:35:42+00:00
Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages

We can't use HscNothing if we need to run code coming from modules inside
the processed package during typechecking, which is the case for some packages
using Template Haskell. This could be improved, to e.g. use HscInterpreted and
HscNothing where possible, instead of using HscC for all modules in the
package.

- - - - -
2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00
Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above
- - - - -
bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00
Fix the location of INPLACE_PKG_CONF; fixes the build
Spotted by Conal Elliott

- - - - -
943107c8 by David Waern at 2009-01-20T19:27:39+00:00
Document H.I.Create.collectDocs better
- - - - -
c6252e37 by David Waern at 2009-01-20T19:29:51+00:00
Fix Trac haskell/haddock#59: TH-generated declarations disappearing

This patch was contributed by Joachim Breitner (nomeata).

- - - - -
3568a6af by David Waern at 2009-01-21T21:41:48+00:00
Do not indicate that a constructor argument is unboxed

We only show the strictness annotation for an unboxed constructor argument. The
fact that it is unboxed is an implementation detail and should not be part of
the module interface.

- - - - -
562a4523 by David Waern at 2009-01-22T18:53:49+00:00
Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations

We now filter out everything that is not a proper Haskell declaration before
collecting the docs and attaching them to declarations.

- - - - -
6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00
Add test for quasi quotation. No reference output yet.
- - - - -
dc4100fd by David Waern at 2009-01-22T19:57:47+00:00
Improve quasi-quotation test and add reference output
- - - - -
908b74bb by David Waern at 2009-01-23T23:22:03+00:00
Filter out separately exported associated types in a smarter way
- - - - -
f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00
Correct spelling mistake in error message
- - - - -
24e4245d by David Waern at 2009-01-24T17:48:03+00:00
Correct comment
- - - - -
b5e8462f by David Waern at 2009-02-07T13:22:29+00:00
Do not show a subordinate at the top level if its parent is also exported

See note in the source code for more info.

- - - - -
4b09de57 by David Waern at 2009-02-07T13:53:53+00:00
Update test following change to top level subordinates
- - - - -
76379896 by David Waern at 2009-02-07T13:58:04+00:00
Remove html files in the tests/output/ directory which have been accidentally added
- - - - -
1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00
Typo in comment
- - - - -
fec367d0 by David Waern at 2009-02-24T20:21:17+00:00
Fix small bug

The rule is to prefer type constructors to other things when an identifier in a
doc string can refer to multiple things. This stopped working with newer GHC
versions (due to a tiny change in the GHC renamer). We implement this rule
in the HTML backend for now, instead of fixing it in GHC, since we will move
renaming of doc strings to Haddock in the future anyway. 

- - - - -
9b4172eb by David Waern at 2009-02-25T20:04:38+00:00
Fix bad error handling with newer GHCs

When support for GHC 6.10 was added, an error handler was installed only around
the typechecking phase. This had the effect that errors thrown during
dependency chasing were caught in the top-level exception handler and not
printed with enough detail.  With this patch we wrap the error handler around
all our usage of the Ghc monad. 

- - - - -
de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00
Hide funTyConName, now exported by TypeRep
- - - - -
4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00
Don't build the library when building in the GHC tree
- - - - -
1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00
Add a ghc.mk
- - - - -
3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00
do .depend generation for haddock with the stage1 compiler
This is a bit of a hack. We mkdepend with stage1 as if .depend
depends on the stage2 compiler then make goes wrong: haddock's
.depend gets included, which means that make won't reload until
it's built, but we can't build it without the stage2 compiler. We
therefore build the stage2 compiler before its .depend file is
available, and so compilation fails.

- - - - -
b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00
Give haddock a wrapper on unix in the new GHC build system
- - - - -
9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00
Create inplace/lib/html in the new GHC build system
- - - - -
93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00
TAG GHC 6.10.1 release
- - - - -
06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00
Define __GHC_PATCHLEVEL__ for recent version of GHC (stable).
- - - - -
680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00
'needsTemplateHaskell' is not defined in current stable GHC.
- - - - -
6c5619df by David Waern at 2009-02-25T22:15:23+00:00
Hide fynTyConName only for recent GHC versions
- - - - -
6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00
Add the module to one of haddocks warnings
- - - - -
e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00
Bug fix
We tried to filter out subordinates that were already exported through their parent.

This didn't work properly since we were in some cases looking at the
grand-parent and not the parent.  We now properly compute all the parent-child
relations of a declaration, and use this information to get the parent of a
subordinate.

We also didn't consider record fields with multiple parents. This is now
handled correctly.

We don't currently support separately exported associated types. But when we
do, they should be handled correctly by this process too.

Also slightly improved the warning message that we give when filtering out
subordinates.

- - - - -
10a79a60 by David Waern at 2009-02-27T22:08:08+00:00
Fix error message conflict

The module name is already written in the beginning of the message, as
seems to be the convention in Haddock. Perhaps not so clear, but we
should change it everywhere in that case. Leaving it as it is for now.

- - - - -
c5055c7f by David Waern at 2009-02-27T22:15:17+00:00
Shorten warning message
- - - - -
a72fed3a by David Waern at 2009-02-28T00:53:55+00:00
Do not show package name in warning message
- - - - -
a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00
Install haddock in the new GHC build system
- - - - -
dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00
Relax base dependency to < 4.2, not < 4.1
- - - - -
5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00
Bump .haddock file version number (due to change of format)
- - - - -
f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00
Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1
- - - - -
23f78831 by David Waern at 2009-03-21T16:40:52+00:00
Update CHANGES
- - - - -
7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00
Update ANNOUNCE
- - - - -
0771e00a by David Waern at 2009-03-21T16:54:40+00:00
Update ANNOUNCE, again
- - - - -
81a6942a by David Waern at 2009-03-21T17:50:06+00:00
Don't be too verbose in CHANGES
- - - - -
29861dcf by David Waern at 2009-03-21T18:03:31+00:00
TAG 2.4.2
- - - - -
a585f285 by David Waern at 2009-03-21T19:20:29+00:00
Require Cabal >= 1.2.3
- - - - -
7c611662 by David Waern at 2009-03-21T19:21:48+00:00
TAG 2.4.2 with cabal-version >= 1.2.3
- - - - -
23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00
new GHC build system: use shell-wrappers macro
- - - - -
25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00
Fix (with a hack?) haddock in teh new build system
- - - - -
6a29a37e by David Waern at 2009-03-24T22:10:15+00:00
Remove unnecessary LANGUAGE pragma
- - - - -
954da57d by David Waern at 2009-03-24T22:21:23+00:00
Fix warnings in H.B.DevHelp
- - - - -
1619f1df by David Waern at 2009-03-26T23:20:44+00:00
-Wall police in H.B.Html
- - - - -
b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00
install Haddock's html stuff
- - - - -
78e0b107 by David Waern at 2008-12-07T19:58:53+00:00
Add verbosity flag and utils, remove "verbose" flag
- - - - -
913dae06 by David Waern at 2008-12-07T20:01:05+00:00
Add some basic "verbose" mode logging in H.Interface
- - - - -
1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00
Fix conflicts
- - - - -
22f82032 by David Waern at 2009-03-27T21:15:11+00:00
Remove H.GHC.Typecheck
- - - - -
81557804 by David Waern at 2009-03-27T21:19:22+00:00
Remove docNameOrig and use getName everywhere instead
- - - - -
d8267213 by David Waern at 2009-03-27T21:21:46+00:00
Use docNameOcc instead of nameOccName . getName
- - - - -
5d55deab by David Waern at 2009-03-27T21:33:04+00:00
Remove H.DocName and put DocName in H.Types
- - - - -
8ba72611 by David Waern at 2009-03-27T22:06:26+00:00
Document DocName
- - - - -
605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00
-Wall police
- - - - -
e4da93ae by David Waern at 2009-03-27T23:12:53+00:00
-Wall police in H.B.Hoogle
- - - - -
bb255519 by David Waern at 2009-03-27T23:41:28+00:00
Define Foldable and Traversable instances for Located
- - - - -
f1195cfe by David Waern at 2009-03-27T23:51:34+00:00
Wibble
- - - - -
23818d7c by David Waern at 2009-03-28T00:03:55+00:00
-Wall police in H.I.Rename
- - - - -
0f050d67 by David Waern at 2009-03-28T00:15:15+00:00
-Wall police in H.I.AttachInstances
- - - - -
0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00
Wibble
- - - - -
275d4865 by David Waern at 2009-03-28T21:27:06+00:00
Layout fix
- - - - -
54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00
-Wall police in H.I.Create
- - - - -
7f58b117 by David Waern at 2009-03-28T22:10:19+00:00
-Wall police in H.Interface
- - - - -
f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00
-Wall police in Main
- - - - -
29da355c by David Waern at 2009-03-28T22:23:39+00:00
Turn on -Wall -Werror
- - - - -
446d3060 by David Waern at 2009-04-01T20:40:30+00:00
hlint police
- - - - -
3867c9fc by David Waern at 2009-04-01T20:48:42+00:00
hlint police
- - - - -
bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00
hlint police
- - - - -
e0e90866 by David Waern at 2009-04-05T12:42:53+00:00
Move H.GHC.Utils to H.GhcUtils
- - - - -
9cbd426b by David Waern at 2009-04-05T12:57:21+00:00
Remove Haddock.GHC and move its (small) contents to Main
- - - - -
b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00
Fix whitespace and stylistic issues in Main
- - - - -
3c04aa56 by porges at 2008-12-07T08:22:19+00:00
add unicode output
- - - - -
607918da by David Waern at 2009-04-26T15:09:43+00:00
Resolve conflict
- - - - -
4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00
fix markup
- - - - -
436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00
clean up
- - - - -
bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00
new GHC build system: add $(exeext)
- - - - -
9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00
update for new GHC build system layout
- - - - -
d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00
GHC new build system fixes
- - - - -
5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00
Tweak new build system
- - - - -
9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00
add build instructions for GHC
- - - - -
66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00
Quote program paths in ghc.mk
- - - - -
bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00
Use a bang pattern on an unlifted binding
- - - - -
3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00
Include haddock in GHC bindists
- - - - -
ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00
Delete Haddock.Exception and move contents to Haddock.Types

Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types.

- - - - -
4464fb9b by David Waern at 2009-06-24T22:23:23+00:00
Add Haddock module headers

Add a proper Haddock module header to each module, with a more finegrained
copyright. If you feel mis-accreditted, please correct any copyright notice!

The maintainer field is set to haddock at projects.haskell.org.

Next step is to add a brief description to each module.

- - - - -
5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00
Fix spelling error
- - - - -
6d074cdb by David Waern at 2009-06-25T21:53:56+00:00
Document Interface and InstalledInterface better
- - - - -
d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00
Remove misplaced whitespace in H.I.Rename
- - - - -
fa381c49 by David Waern at 2009-06-27T13:26:03+00:00
Fix haskell/haddock#104 - create output directory if missing
- - - - -
91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00
TAG 2009-06-25
- - - - -
0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00
Follow extra field in ConDecl
- - - - -
b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00
Update Makefile for the new GHC build system
- - - - -
df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00
Resolve conflicts
- - - - -
1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00
Remove the -Wwarn hack in the GHC build system
- - - - -
7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00
Fix warnings
- - - - -
5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00
Bump version number
Cabal needs to distinguish between haddocks having a --verbose and
--verbosity flag

- - - - -
6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00
Wibble
- - - - -
2308b66f by David Waern at 2009-07-06T20:24:20+00:00
Clearer printing of versions by runtests.hs
- - - - -
d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00
Fix (invisible) bug introduced by unicode patch
- - - - -
2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00
Use HscAsm instead of HscC when using TH
- - - - -
18f3b755 by David Waern at 2009-07-06T22:10:22+00:00
Update HCAR entry (by Janis)
- - - - -
a72ac9db by David Waern at 2009-07-06T23:01:35+00:00
Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611
- - - - -
549135d2 by David Waern at 2009-07-06T23:11:41+00:00
Remove unused functions from Haddock.Utils
- - - - -
b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00
revert to split-index for large indices
- remove the search-box, because browsers have search-for-text
abilities anyway.
- pick 150 items in index as the arbitrary time at which to split it
- notice the bug that identifiers starting with non-ASCII characters
won't be listed in split-index, but don't bother to fix it yet (see
ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 )

- - - - -
78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00
Implement GADT records in HTML backend
- - - - -
4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00
add test for GADT records
- - - - -
79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00
Update test suite following version bump
- - - - -
5932c011 by David Waern at 2009-08-02T10:25:39+00:00
Fix documentation bug
- - - - -
a6970fca by David Waern at 2009-08-12T23:08:53+00:00
Remove support for ghc 6.8.* from .cabal file
- - - - -
c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00
Fix unused import warnings
- - - - -
fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00
Use cProjectVersion directly rather than going through compilerInfo
Fixes the build after changes in GHC

- - - - -
548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00
follow changes in GHC's ForeignType
- - - - -
9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00
Switch from PatternSignatures to ScopedTypeVariables in Main
- - - - -
eebf39bd by David Waern at 2009-08-14T17:14:28+00:00
Version .haddock files made with GHC 6.10.3/4 correclty
- - - - -
58f3e735 by David Waern at 2009-08-14T17:19:37+00:00
Support GHC 6.10.* and 6.11.* only
- - - - -
5f63cecc by David Waern at 2009-08-14T22:03:20+00:00
Do not version .haddock file based on GHC patchlevel version

We require that the instances of Binary that we use from GHC will not change
between patchlevel versions.

- - - - -
d519de9f by David Waern at 2009-08-14T23:50:00+00:00
Update CHANGES
- - - - -
35dccf5c by David Waern at 2009-08-14T23:51:38+00:00
Update version number everywhere
- - - - -
6d363fea by David Waern at 2009-08-15T09:46:49+00:00
Update ANNOUNCE
- - - - -
c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00
Remove -Werror

Forgot that Hackage doesn't like it.

- - - - -
a125c12b by David Waern at 2009-08-15T09:49:50+00:00
Require Cabal >= 1.6
- - - - -
adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00
Cross-Package Documentation version 4
- - - - -
3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00
Put all the IN_GHC_TREE stuff inside getGhcLibDir
- - - - -
56624097 by David Waern at 2009-08-15T23:52:03+00:00
Add --print-ghc-libdir
- - - - -
f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00
Read base.haddock when running tests

We can now test cross-package docs.

- - - - -
283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00
Update test output - we now have more links
- - - - -
673d1004 by David Waern at 2009-08-16T01:26:08+00:00
Read process.haddock when running tests
- - - - -
0d127f82 by David Waern at 2009-08-16T01:43:04+00:00
Add a test for cross-package documentation
- - - - -
f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00
Follow GHC build system changes
- - - - -
5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00
make cross-package list types look nicer
- - - - -
c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00
Haddock.Convert: export more functions
This lets us remove some code in Haddock.Interface.AttachInstances

- - - - -
2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00
switch AttachInstances to use synify code
It changed an instance from showing ((,) a b) to (a, b)
because my synify code is more sophisticated; I hope the latter
is a good thing rather than a bad thing aesthetically, here.

But this definitely reduces code duplication!

- - - - -
b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00
Find instances using GHC, which is more complete.
In particular, it works cross-package.

An intermediate patch also moved the instance-finding into
createInterface, but that move turned out not to be necessary,
so if we want to do that, it'd go in a separate patch.
(Is that possible? Or will we need GHC to have loaded all the modules
first, before we can go searching for the instances (e.g. if the
modules are recursive or something)?)

- - - - -
6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00
fix preprocessor conditional sense
- - - - -
942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00
remove ghc 6.8 conditionals from Haddock.Interface
- - - - -
4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00
Fix GHC 6.11 build in Haddock.Convert
- - - - -
0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00
hacks to make it compile without fnArgDocsn
- - - - -
7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00
less big-Map-based proper extraction of constructor subdocs
- - - - -
b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00
Html: remove unnecessary+troublesome GHC. qualifications
- - - - -
96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00
Move doc parsing/lexing into Haddock for ghc>=6.11
- - - - -
e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00
get rid of unused DocMap parameter in Html
- - - - -
66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00
fix horrible named-docs-disappearing bug :-)
- - - - -
a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00
re-implement function-argument docs
..on top of the lexParseRn work.
This patch doesn't change the InstalledInterface format, and thus,
it does not work cross-package, but that will be easy to add
subsequently.

- - - - -
8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00
cross-package fnArgDocs. WARNING: changes .haddock binary format
While breaking the format, I took the opportunity to unrename the
DocMap that's saved to disk, because there's really no reason that
we want to know what *another* package's favorite place to link a
Name to was.  (Is that true? Or might we want to know, someday?)

Also, I added instance Binary Map in InterfaceFile.
It makes the code a little simpler without changing anything of
substance.  Also it lets us add another Map hidden inside another
Map (fnArgsDocs in instDocMap) without having really-convoluted
serialization code.  Instances are neat!
I don't understand why this change to InterfaceFile seemed to
subtly break binary compatibility all by itself, but no matter,
I'll just roll it into the greater format-changing patch. Done!

- - - - -
30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00
Improve behavior for unfindable .haddock
- - - - -
aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00
add comment for FnArgsDoc type
- - - - -
49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00
bugfix: restore fnArgDocs for type-synonyms
- - - - -
f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00
Backends.Hoogle: eliminate warnings
- - - - -
a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00
Haddock.Convert: eliminate warnings
- - - - -
5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00
Haddock.Interface.Rename: eliminate warnings
- - - - -
0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00
Main.hs: remove ghc<6.9 conditionals
- - - - -
e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00
Main.hs: eliminate warnings (except for OldException)
- - - - -
61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00
move get*LibDir code in Main.hs, to +consistent code, -duplication
- - - - -
948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00
Main.hs: OldException->Exception: which eliminates warnings
- - - - -
3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00
GhcUtils: ghc >= 6.10
- - - - -
2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00
InterfaceFile: ghc >= 6.10
- - - - -
d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00
Types: ghc >= 6.10
- - - - -
ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00
ModuleTree: ghc >= 6.10
- - - - -
883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00
Backends.DevHelp: ghc >= 6.10
- - - - -
04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00
Backends.Html: ghc >= 6.10
- - - - -
a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00
Utils: ghc >= 6.10
- - - - -
b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00
eliminate haskell98 dependency, following GHC's example
It turns out I/we already had, and it was only a matter of
deleting it from the cabal file.

- - - - -
292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00
refactor out subordinatesWithNoDocs
dep of inferenced-decls fix

- - - - -
c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00
Eradicate wrong runtime warning for type-inferenced exported-functions
see the long comment in the patch for why I did it this way :-)

- - - - -
4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00
Clean up tyThingToHsSynSig a little

Factor out noLoc and use the case construct. Also rename the function to
tyThingToLHsDecl, since it doesn't just create type signatures.

- - - - -
28ab9201 by David Waern at 2009-09-04T22:58:50+00:00
Wibble
- - - - -
0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00
Add more copyright owners to H.I.AttachInstances
- - - - -
122441b1 by David Waern at 2009-09-06T18:44:12+00:00
Style police
- - - - -
1fa79463 by David Waern at 2009-09-06T18:57:45+00:00
Move toHsInstHead to Haddock.Convert and call it synifyInstHead
- - - - -
0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00
Use colordiff to display test results if available
- - - - -
ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00
Follow changes in GHC's interface file format
Word32 instead of Int for FastString and Name offsets

- - - - -
537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00
define unpackPackageId (it was removed from GHC)
- - - - -
50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00
Remove commented-out code
- - - - -
511631fe by David Waern at 2009-09-09T23:19:05+00:00
Correct copyright in H.I.ParseModuleHeader
- - - - -
898ec768 by David Waern at 2009-09-11T11:22:29+00:00
Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps
  
This fixes the missing docs problem. The Eq and Ord instances for Name uses the
unique number in Name. This number is created at deserialization time by GHC's
magic Binary instance for Name, and it is random. Thus, fromAscList can't be used
at deserialization time, even though toAscList was used at serialization time.

- - - - -
37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00
Track change in HsType
- - - - -
eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00
Allow building with base 4.2
- - - - -
bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00
Loosen the GHC dependency
- - - - -
5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00
Fix building with GHC >= 6.12
- - - - -
fb131481 by David Waern at 2009-09-11T11:24:48+00:00
Update runtests.hs to work with GHC 6.11
- - - - -
ac3a419d by David Waern at 2009-09-11T11:25:14+00:00
Update CrossPackageDocs test
- - - - -
ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00
Add reference output for CrossPackageDocs
- - - - -
520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00
Fix installation in the GHC build system
- - - - -
28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00
GHC build system: Make *nix installation work in paths containing spaces
- - - - -
5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00
Track change in HsType for the right compiler version
- - - - -
905097ce by David Waern at 2009-11-14T12:10:47+00:00
hlint police
- - - - -
04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00
Use defaultObjectTarget rather than HscAsm
This fixes haddock when we don't have a native code generator

- - - - -
966eb079 by David Waern at 2009-11-15T12:32:21+00:00
Remove commented-out code
- - - - -
37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00
Make runtests.hs strip links before diffing

Generates easier to read diffs when tests fail. The content of the links
is not important anyway since it is not taken into account by the tests.

- - - - -
3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00
Follow findProgramOnPath signature change in runtests.hs
- - - - -
b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00
Follow removal of GHC.MVar from base in CrossPackageDocs 
- - - - -
f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00
Make copy.hs strip link contents before copying

No more updating of reference files when URLs in links changes.

- - - - -
4c9c420d by David Waern at 2009-11-22T15:26:41+00:00
Update test reference output

* More links (Int, Float etc)
* Stripped link contents 

- - - - -
a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00
Update CrossPackageDocs reference output

- Remove GHC.MVar import (removed from base)
- Strip link contents

- - - - -
43491394 by David Waern at 2009-11-23T23:20:00+00:00
Update test reference files with comments on instances
- - - - -
0d370a0b by David Waern at 2009-11-23T23:25:16+00:00
Bump version number
- - - - -
2293113e by David Waern at 2009-11-24T20:55:49+00:00
Comments on instances

Implementing this was a little trickier than I thought, since we need to match
up instances from the renamed syntax with instances represented by
InstEnv.Instance. This is due to the current design of Haddock, which matches
comments with declarations from the renamed syntax, while getting the list of
instances of a class/family directly using the GHC API.

- Works for class instances only (Haddock has no support for type family
  instances yet)
- The comments are rendered to the right of the instance head in the HTML output
- No change to the .haddock file format
- Works for normal user-written instances only. No comments are added on
  derived or TH-generated instances

- - - - -
bf586f29 by David Waern at 2009-11-27T22:05:15+00:00
Whitespace police
- - - - -
b8f03afa by David Waern at 2009-11-27T22:11:46+00:00
Remove bad whitespace and commented-out pieces
- - - - -
90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00
Whitespace police
- - - - -
b5ede900 by David Waern at 2009-11-27T22:15:50+00:00
Whitespace police
- - - - -
e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00
Remove Name from DocInstance

It's not used.

- - - - -
9502786c by David Waern at 2009-11-28T13:56:54+00:00
Require at least GHC 6.12

While regression testing Haddock, I found a bug that happens with GHC 6.10.3,
but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it
down.

I think we should just always require the latest major GHC version. The time
spent on making Haddock work with older versions is too high compared to the
time spent on bugfixing, refactoring and features.

- - - - -
8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00
Remove cruft due to compatibility with older GHCs
- - - - -
46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00
Add a documentation header to Haddock.Convert
- - - - -
c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00
Remove unused H.Utils.FastMutInt2
- - - - -
490aba80 by David Waern at 2009-11-28T15:36:36+00:00
Rename Distribution.Haddock into Documentation.Haddock
- - - - -
33ee2397 by David Waern at 2009-11-28T15:36:47+00:00
Fix error message
- - - - -
a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00
Add a test flag that brings in QuickCheck
- - - - -
fa049e13 by David Waern at 2009-11-28T19:32:18+00:00
Say that we want quickcheck 2
- - - - -
f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00
Add an Arbitrary instance for HsDoc
- - - - -
da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00
Rename HsDoc back into Doc
- - - - -
edb60101 by David Waern at 2009-11-28T22:16:16+00:00
Move H.Interface.Parse/Lex to H.Parse/Lex

These are not just used to build Interfaces.

- - - - -
0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00
Update version number in test suite
- - - - -
5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00
Improve doc of DocName
- - - - -
7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00
TAG GHC 6.12-branch created
- - - - -
0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00
TAG GHC 6.12.1 release
- - - - -
65e9be62 by David Waern at 2009-12-21T16:58:58+00:00
Update CHANGES
- - - - -
145cee32 by David Waern at 2009-12-21T16:59:09+00:00
TAG 2.6.0
- - - - -
3c552008 by David Waern at 2009-12-22T17:11:14+00:00
Update ANNOUNCE
- - - - -
931f9db4 by David Waern at 2010-01-22T19:57:17+00:00
Convert haddock.vim to use unix newlines
- - - - -
4e56588f by David Waern at 2010-01-22T22:11:17+00:00
Remove unnecessary (and inexplicable) uses of nub
- - - - -
744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00
Follow move of parser and lexer
- - - - -
e34bab14 by David Waern at 2010-01-22T22:49:13+00:00
Use findProgramLocation instead of findProgramOnPath in runtests.hs
- - - - -
8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00
fix html arg-doc off-by-one and silliness
- - - - -
9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00
Create a test for function argument docs
- - - - -
507a82d7 by David Waern at 2010-01-22T23:24:47+00:00
Put parenthesis around type signature arguments of function type
- - - - -
8a305c28 by David Waern at 2010-01-23T17:26:59+00:00
Add reference file for the FunArgs test
- - - - -
1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00
Improve FunArg test and update Test.html.ref
- - - - -
2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00
Do not generate illegal character in HTML ID attribute.
- - - - -
c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00
Fix Haddock markup error in comment
- - - - -
c6416a73 by David Waern at 2010-02-24T22:55:08+00:00
Large additions to the Haddock API

Also improved and added more doc comments.

- - - - -
57d289d7 by David Waern at 2010-02-24T22:58:02+00:00
Remove unused ifaceLocals
- - - - -
80528d93 by David Waern at 2010-02-25T21:05:09+00:00
Add HaddockModInfo to the API
- - - - -
82806848 by David Waern at 2010-02-25T21:05:27+00:00
Wibble
- - - - -
744cad4c by David Waern at 2010-02-25T23:30:59+00:00
Make it possible to run a single test
- - - - -
6a806e4c by David Waern at 2010-03-14T14:19:39+00:00
Bump version number
- - - - -
a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00
Update ANNOUNCE
- - - - -
6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00
Add missing dependencies for 'library' in haddock.cabal
- - - - -
faefe2bd by David Waern at 2010-03-15T22:29:37+00:00
Solve conflicts
- - - - -
9808ad52 by David Waern at 2010-03-15T22:51:21+00:00
Bump version number
- - - - -
eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00
Update CHANGES
- - - - -
f95cd891 by David Waern at 2010-03-15T23:01:06+00:00
Add Paths_haddock to other-modules of library
- - - - -
65997b0a by David Waern at 2010-03-15T23:14:59+00:00
Update CHANGES
- - - - -
7e251731 by David Waern at 2010-03-15T23:15:30+00:00
Bump version number
- - - - -
c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00
Fix warning
- - - - -
1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00
Fix imports for new location of splitKindFunTys
- - - - -
474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00
Update Haddock for quasiquotes
- - - - -
0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00
Track changes in HsTyVarBndr
- - - - -
2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00
Track HsSyn chnages
- - - - -
9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00
Resolve conflicts
- - - - -
a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00
Track change in HsUtils; and use a nicer function not an internal one
- - - - -
27994854 by David Waern at 2010-03-18T22:22:27+00:00
Fix build with GHC 6.12.1
- - - - -
11f6e488 by David Waern at 2010-03-18T22:24:09+00:00
Bump version in test reference files
- - - - -
0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00
Fix library part of cabal file when in ghc tree
- - - - -
3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00
First, experimental XHTML rendering
    switch to using the xhtml package

    copied Html.hs to Xhtml.hs
        and split into sub-modules under Haddock/Backends/Xhtml
        and detabify

    moved footer into div, got ready for iface change
    headers converted to semantic markup
    contents in semantic markup
    summary as semantic markup
    description in semantic markup, info block in header fixed

    factored out rendering so during debug it can be readable
        (see renderToString)


- - - - -
b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00
apply changes to Html.hs to Xhtml/*.hs
	incorporate changes that were made between the time Html.hs
	was copied and split into Xhtml.hs and Xhtml/*.hs
	includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1"

- - - - -
73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00
Follow LazyUniqFM->UniqFM in GHC
- - - - -
db4f602b by David Waern at 2010-03-29T22:00:01+00:00
Fix build with GHC 6.12
- - - - -
d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00
Add missing dependencies to cabal file
- - - - -
e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00
Add markup support for interactive examples
- - - - -
e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00
Add tests for interactive examples
- - - - -
5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00
Propagate source positions from Lex.x to Parse.y
- - - - -
6493b46f by David Waern at 2010-04-07T21:48:57+00:00
Let runtests.hs die when haddock has not been built
- - - - -
5e34423e by David Waern at 2010-04-07T22:01:13+00:00
Make runtests.hs slightly more readable
- - - - -
321d59b3 by David Waern at 2010-04-07T22:13:27+00:00
Fix haskell/haddock#75

Add colons to the $ident character set. 

- - - - -
37b08b8d by David Waern at 2010-04-08T00:32:52+00:00
Fix haskell/haddock#118

Avoid being too greedy when lexing URL markup (<..>), in order to allow
multiple URLs on the same line. Do the same thing with <<..>> and #..#.

- - - - -
df8feac9 by David Waern at 2010-04-08T00:57:33+00:00
Make it easier to add new package deps to test suite

This is a hack - we should use Cabal to get the package details instead.

- - - - -
1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00
Add ghc-prim to test suite deps
- - - - -
27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00
Let parsing fails on paragraphs that are immediately followed by an
example

This is more consistent with the way we treat code blocks.

- - - - -
83096e4a by David Waern at 2010-04-08T21:20:00+00:00
Improve function name
- - - - -
439983ce by David Waern at 2010-04-10T10:46:14+00:00
Fix haskell/haddock#112

No link was generated for 'Addr#' in a doc comment. The reason was simply that
the identifier didn't parse. We were using parseIdentifier from the GHC API,
with a parser state built from 'defaultDynFlags'. If we pass the dynflags of
the module instead, the right options are turned on on while parsing the
identifer (in this case -XMagicHash), and the parse succeeds.

- - - - -
5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00
Rename startGhc into withGhc
- - - - -
dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00
Add documentation for interactive examples
- - - - -
c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00
Slight fix to the documentation of examples
- - - - -
06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00
Rename Interactive Examples into Examples (and simplify explanation)
- - - - -
264830cb by David Waern at 2010-05-10T20:07:27+00:00
Update CHANGES with info about 2.6.1
- - - - -
8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00
Add unit tests for parser
- - - - -
68297f40 by David Waern at 2010-05-10T21:53:37+00:00
Improve testsuite README
- - - - -
f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00
Re-organise the testsuite structure
- - - - -
a360f710 by David Waern at 2010-05-11T19:18:03+00:00
Shorten function name
- - - - -
1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00
Update runtests.hs following testsuite re-organisation
- - - - -
ffebe217 by David Waern at 2010-05-11T21:40:10+00:00
Update runtests.hs to use base-4.2.0.1
- - - - -
635de402 by David Waern at 2010-05-11T21:41:11+00:00
Update runparsetests.hs following testsuite reorganisation
- - - - -
72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00
Fix build
- - - - -
1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00
Remove redundant import
- - - - -
1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00
Minor wibbles to HsBang stuff
- - - - -
dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00
GHC build system: Follow "rm" variable changes
- - - - -
7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00
Fix build with GHC 6.12.2
- - - - -
7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00
Fixes to comments only
- - - - -
8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00
ModuleMap -> IfaceMap
- - - - -
1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00
Fix whitespace style issues
- - - - -
e96783c0 by David Waern at 2010-05-13T19:08:53+00:00
Fix comment
- - - - -
c998a78b by David Waern at 2010-05-13T19:39:00+00:00
Position the module header the same way everywhere
Silly, but nice with some consistency :-)

- - - - -
b48a714e by David Waern at 2010-05-13T19:41:32+00:00
Position of module header, this time in the HTML backends
- - - - -
f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00
Two newlines between declarations in Main
- - - - -
071d44c7 by David Waern at 2010-05-13T19:44:21+00:00
Newlines in Convert
- - - - -
036346db by David Waern at 2010-05-13T19:46:47+00:00
Fix a few stylistic issues in H.InterfaceFile
- - - - -
f0b8379e by David Waern at 2010-05-13T19:47:53+00:00
Add newlines to H.ModuleTree
- - - - -
27409f8e by David Waern at 2010-05-13T19:51:10+00:00
Fix stylistic issues in H.Utils
- - - - -
24774a11 by David Waern at 2010-05-13T20:00:43+00:00
Structure H.Types better
- - - - -
7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00
Remove bad Arbitrary instance
- - - - -
fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00
Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead
- - - - -
fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00
Export a couple of more types from the API
- - - - -
b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00
Improve doc comment for Interface
- - - - -
c585f2ce by David Waern at 2010-05-13T21:30:14+00:00
Improve documentation of Haddock.Interface
- - - - -
e6791db2 by David Waern at 2010-05-13T22:07:35+00:00
Remove meaningless comments
- - - - -
7801b390 by David Waern at 2010-05-14T17:53:33+00:00
Remove unused modules
- - - - -
f813e937 by David Waern at 2010-05-14T17:55:17+00:00
Re-direct compilation output to a temporary directory
Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of
writing compilation files to GHC's output directory (default ".").

- - - - -
e56737ec by David Waern at 2010-05-14T18:06:11+00:00
Wibble
- - - - -
e40b0447 by David Waern at 2010-05-14T19:01:52+00:00
Move flag evaluation code from Main to Haddock.Options
Determining the value of "singular" flags (by e.g. taking the last occurrence
of the flag) and other flag evaluation should done in Haddock.Options which is
the module that is supposed to define the command line interface. This makes
Main a bit easier on the eyes as well.

- - - - -
27091f57 by David Waern at 2010-05-14T19:05:10+00:00
Wibble
- - - - -
c658cf61 by David Waern at 2010-05-14T19:06:49+00:00
Re-order things in Haddock.Options a bit
- - - - -
8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00
De-tabify Haddock.Options and fix other whitespace issues
- - - - -
0df16b62 by David Waern at 2010-05-14T19:25:07+00:00
Improve comments
- - - - -
80b38e2b by David Waern at 2010-05-14T19:26:42+00:00
Whitespace police
- - - - -
fe580255 by David Waern at 2010-05-14T19:31:23+00:00
Wibbles to comments
- - - - -
a2b43fad by David Waern at 2010-05-14T20:24:32+00:00
Move some more flag functions to Haddock.Options
- - - - -
3f895547 by David Waern at 2010-05-14T20:37:12+00:00
Make renderStep a top-level function in Main
- - - - -
5cdca11d by David Waern at 2010-05-14T20:39:27+00:00
Spelling in comment
- - - - -
ad98d14c by David Waern at 2010-05-14T20:40:26+00:00
Comment fixes
- - - - -
0bb9218f by David Waern at 2010-05-14T20:49:01+00:00
Whitespace police
- - - - -
0f0a533f by David Waern at 2010-05-15T16:42:29+00:00
Improve description of --dump-interface
- - - - -
5b2833ac by David Waern at 2010-05-15T17:16:53+00:00
Document --no-tmp-comp-dir
- - - - -
8160b170 by David Waern at 2010-05-15T17:18:59+00:00
Wibble
- - - - -
570dbe33 by David Waern at 2010-05-18T21:15:38+00:00
HLint police
- - - - -
204e425f by David Waern at 2010-05-18T21:16:30+00:00
HLint police
- - - - -
6db657ac by David Waern at 2010-05-18T21:16:37+00:00
Wibble
- - - - -
b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00
Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100)
- - - - -
3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00
Allow base-4.3
- - - - -
c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00
Fix compilation with GHC 6.13
- - - - -
6181296c by David Waern at 2010-06-08T21:09:05+00:00
Display name of prologue file when parsing it fails
- - - - -
7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00
Remove redundant imports
- - - - -
980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00
isLocalAndTypeInferenced: fix for local module names overlapping package modules
- - - - -
d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00
Unresolved identifiers in Doc get replaced with DocMonospaced
rather than plain strings

- - - - -
d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00
LaTeX backend (new options: --latex, --latex-style=<style>)
- - - - -
437afa9e by David Waern at 2010-07-01T12:02:44+00:00
Fix a few stylistic whitespace issues in LaTeX backend
- - - - -
85bc1fae by David Waern at 2010-07-01T15:42:45+00:00
Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this)
- - - - -
7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00
Update test following Simon's patch to render unresolved names in monospaced font
- - - - -
08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00
Warning police
- - - - -
d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00
Fix a bug in attachInstances

We didn't look for instance docs in all the interfaces of the package. This had
the effect of instance docs not always showing up under a declaration. I took
the opportunity to clean up the code in H.I.AttachInstances a bit as well. More
cleanup is needed, however.

- - - - -
d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00
Add missing dependencies to cabal file
- - - - -
24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00
add exports to Xhtml modules
- - - - -
84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00
clean up Doc formatting code
- add CSS for lists 
- renderToString now uses showHtml since prettyHtml messes up <pre> sections

- - - - -
bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00
tweak list css
- - - - -
0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00
all decls now generate Html not HtmlTable
	- ppDecl return Html, and so now do all of the functions it calls
	- added some internal tables to some decls, which is wrong, and will have
		to be fixed
	- decl "Box" functions became "Elem" functions to make clear they aren't
		in a table anymore (see Layout.hs)
	- docBox went away, as only used in one place (and its days are numbered)
	- cleaned up logic in a number of places, removed dead code
	- added maybeDocToHtml which simplified a number of places in the code

- - - - -
dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00
clean up processExport and place a div around each decl
- - - - -
e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00
data decls are now a sequence of paragraphs, not a table
- - - - -
89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00
removed commented out code that can't be maintained
- - - - -
d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00
removed declWithDoc and cleaned up data decls in summary
- - - - -
ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00
merge in markupExample changes
- - - - -
c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00
made record fields be an unordList, not a table
- - - - -
ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00
fixed surround of instance and constructor tables
- - - - -
0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00
fix class member boxes in summary
- - - - -
5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00
remove unused bodyBox
- - - - -
e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00
fixed javascript quoting/escpaing issue
- - - - -
f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00
adjust css for current markup
- - - - -
e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00
added assoicated types and methods back into class decls
- - - - -
84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00
merge in changes from the big-whitespace cleanup
- - - - -
3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00
adjust synopsis and bottom bar spacing
- - - - -
3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00
fix missing space in "module" lines in synoposis
- - - - -
9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00
changed tt elements to code elements
- - - - -
50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00
factored out ppInstances
- - - - -
3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00
push single constructors (newtype) onto line with decl
- - - - -
e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00
remove <++> connector
- - - - -
56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00
change to new page structure
- - - - -
04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00
constructors and args as dl lists, built in Layout.hs
- - - - -
65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00
better interface to subDecls
- - - - -
72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00
made subDecl tables looks just so
- - - - -
b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00
convert args to SubDecl format
- - - - -
cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00
convert instances to SubDecl
- - - - -
34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00
removing old table cruft from Layout.hs
- - - - -
d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00
methods and associated types in new layout scheme
- - - - -
65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00
clean up synopsis lists
- - - - -
e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00
clean up of anchors
- - - - -
1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00
added two new themes and rough css switcher
- - - - -
7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00
fixed package catpion, added style menu
- - - - -
0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00
new output for mini_ pages
- - - - -
64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00
reformat index-frames
- - - - -
3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00
convert index to new markup
- - - - -
b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00
convert index.html to new markup, adjust module markup
- - - - -
8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00
classing styling of ancillary pages
- - - - -
2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00
clean up Layout.hs: no more vanillaTable
- - - - -
87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00
clean up Util.hs
- - - - -
d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00
qualify import of XHtml as XHtml
- - - - -
7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00
factored out head element generation
- - - - -
9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00
refactored out main page body generation
- - - - -
8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00
moved footer into only place that used it
- - - - -
efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00
styling auxillary pages for tibbe and snappy themes
- - - - -
81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00
fixed alphabet on index page, and styling of it and packages in module lists
- - - - -
20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00
cleaned up div functions in Layout.hs
- - - - -
60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00
added content div to main pages
- - - - -
ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00
add .doc class to documentation blocks
- - - - -
f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00
refactoring of anchor ID and fragment handling
- - - - -
a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00
remove an explicit bold tag - replace with .def class
- - - - -
d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00
rename Haddock.Backends.Xhtml.Util to Utils
- - - - -
5a58c0da by David Waern at 2010-07-21T13:30:54+00:00
Remove trailing whitespace in Haddock.Backends.Xhtml
- - - - -
0652aa17 by David Waern at 2010-07-21T13:33:21+00:00
Align a few comments
- - - - -
785776c3 by David Waern at 2010-07-21T13:39:04+00:00
Remove trailing whitespace in H.B.X.Decl
- - - - -
71a30710 by David Waern at 2010-07-21T13:44:27+00:00
Remove more trailing whitespace
- - - - -
38750394 by David Waern at 2010-07-21T13:50:43+00:00
Style police
- - - - -
3023d940 by David Waern at 2010-07-21T14:01:22+00:00
Style police in H.B.X.Decl
- - - - -
df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00
Style police in H.B.X.DocMarkup
- - - - -
6020e321 by David Waern at 2010-07-21T14:17:32+00:00
More style police
- - - - -
86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00
Style police in H.B.Xhtml
- - - - -
aea27d03 by David Waern at 2010-07-21T14:42:03+00:00
Fix warnings in LaTeX backend
- - - - -
2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00
Style police in LaTeX backend (mainly more newlines)
- - - - -
e517162d by David Waern at 2010-07-21T15:05:47+00:00
Doc sections in Main
- - - - -
b971aa0c by David Waern at 2010-07-21T15:06:17+00:00
Trailing whitespace in Documentation.Haddock
- - - - -
f11628fb by David Waern at 2010-07-21T15:07:06+00:00
Trailing whitespace in Haddock.Convert
- - - - -
cbaf284c by David Waern at 2010-07-21T15:08:11+00:00
Style police in Haddock.GhcUtils
- - - - -
71feb77b by David Waern at 2010-07-21T15:09:06+00:00
Style police in Haddock.InterfaceFile
- - - - -
0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00
Whitespace police
- - - - -
6168376c by David Waern at 2010-07-21T15:16:35+00:00
Style police in Haddock.Utils
- - - - -
9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00
Add -fwarn-tabs
- - - - -
a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00
move CSS Theme functions into Themes.hs
- - - - -
b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00
add Thomas Schilling's theme
- - - - -
e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00
correct icon used with Snappy theme
- - - - -
ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00
apply Tibbe's updates to his theme
- - - - -
7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00
space between "Style" and the downward triangle
- - - - -
7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00
merge with David's source cleanups
- - - - -
ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00
Fix a bug where we allowed --hoogle, --latex, etc without input files
- - - - -
e413ff7a by David Waern at 2010-07-22T17:21:58+00:00
Improve function name
- - - - -
a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00
fix warnings
- - - - -
31f73d2a by David Waern at 2010-07-22T19:29:41+00:00
Solve conflicts
- - - - -
d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00
fix warning
- - - - -
412b6469 by David Waern at 2010-07-22T19:31:28+00:00
Solve conflict
- - - - -
35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00
Follow mkPState argument order change
- - - - -
b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00
common up code for instance rendering
- - - - -
d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00
fix warnings
- - - - -
a6d88695 by David Waern at 2010-07-24T15:33:33+00:00
Fix build with ghc < 6.13
- - - - -
94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00
Remove conflict left-over
- - - - -
313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00
reorganization of nhaddock.css with tibbe
- - - - -
9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00
further cleanup of nhaddock.css, float TOC, support aux. pages
- - - - -
6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00
remove old HTML backend
- - - - -
b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00
remove --html-help support - it was old, out-of-date, and mostly missing
- - - - -
d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00
tweaks to nhaddock.css
- - - - -
f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00
command like processing for theme selection
  The bulk of the change is threadnig the selected theme set through functions
  in Xhtml.hs so that the selected themes can be used when generating the page
  output. There isn't much going on in most of these changes, just passing it
  along. The real work is all done in Themes.hs.

- - - - -
8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00
drop --themes support, add named theme support
  decided that --themes was silly - no one would do that, just use
    multiple --theme arguments
  made --theme a synonym for --css and -c
  made those arguments, if no file is found, look up the argument as the
    name of a built in theme

  all of this let's haddock be invoked with "--theme=classic" for example.

- - - - -
20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00
rename --default-themes to --built-in-themes
- - - - -
0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00
tweaks to theme for info table, headings, and tables
- - - - -
cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00
tweaks for dl layout, though still not used
- - - - -
463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00
tweak look of mini pages, keywords, and preblocks
- - - - -
5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00
slide out Synopsis drawer
- - - - -
9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00
extend package header and footer to edges of page
- - - - -
a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00
fields are def lists, tweak css for style menu, mini pages, arguments
- - - - -
ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00
excisting last vestiges of the --xhtml flag
- - - - -
71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00
change how collapsing sections are done
  make whole .caption be the target
  improve javascript for class toggling
  have plus/minus images come from .css, not img tags

- - - - -
c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00
reorganize files in the html lib data dir
- - - - -
93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00
cleaned up Themes.hs
- - - - -
ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00
make module list use new collapsers
- - - - -
1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00
remove Tibbe theme
- - - - -
8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00
move themes into html dir with .theme and .std-theme extensions
- - - - -
a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00
give a class to empty dd elements so they can be hidden
- - - - -
a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00
remove custom version of copyFile in Xhtml.hs
- - - - -
b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00
apply margin changes to pre and headings as per group decision, and small cleanups
- - - - -
e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00
make info block and package bar links be floatable by placing them first in the dom tree
- - - - -
c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00
styling source links on declarations
- - - - -
88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00
styling tweaks
	don't generate an empty li for absent style menu in links area
	update css for Classic and Snappy to handle:
		dl lists
		links in package header and in declarations
		floating of links and info block in package and module headers

- - - - -
8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00
Fix build in GHC tree
- - - - -
ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00
Adapt paths to data files in cabal file
- - - - -
9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00
Add missing dependency to cabal file
- - - - -
01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00
improved synopsis drawer: on click, not hover
- - - - -
7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00
put the synopsis back in the other themes
- - - - -
7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00
close arrows on expanded synopsis drawer
- - - - -
ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00
width and font changes
	removed the max width restrictions on the page as a whole and the synopsis
	made the main font size smaller (nominally 14pt) and then tweaked most
	font sizes (relative) to be more consistent

- - - - -
5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00
implemented YUI's CSS font approach
- - - - -
2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00
adjusted margin to 2em, 1 wasn't enough
- - - - -
58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00
removed underlining on hover for named anchors
	headings in interface lost thier a element, no need, just put id on heading
	css for a elements now only applies to those with href attribute

- - - - -
7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00
more space between elements
- - - - -
5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00
adjusted font sizes of auxilary pages per new scheme
- - - - -
487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00
add Frames button and clean up frames.html
- - - - -
c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00
move frames button to js 
- - - - -
b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00
build style menu in javascript
	moved to javascript, so as to not polute the content with the style menu
	removed menu building code in Themes.hs
	removed onclick in Utils.hs
changed text of button in header from "Source code" to "Source"
	more consistent with links in rest of page

- - - - -
43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00
font size and margin tweaks
- - - - -
c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00
clean up collapser logics
	javascript code for collapasble sections cleaned up
	rewrote class utilities in javascript to be more robust
	refactored utilities for generating collapsable sections
made toc be same color as synopsis
module list has needed clear attribute in CSS

- - - - -
5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00
don't collapse entries in module list when clicking on links
- - - - -
8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00
add missing data file to .cabal
- - - - -
414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00
remove synopsis when in frames
- - - - -
ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00
layout tweeks - mini page font size, toc color, etc.
- - - - -
63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00
margin fiddling
- - - - -
c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00
better synopsis handling logic - no flashing
- - - - -
f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00
fix small layout issues
	mini frames should have same size top heading
	give info block dts some padding so they don't collide in some browsers

- - - - -
0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00
made style changing and cookies storage robust
- - - - -
1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00
Make synopsis frame behave properly in Firefox.

In Firefox, pressing the back button first reverted the synopsis
frame, and only clicking the back button a second time would update
the main frame.

- - - - -
dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00
remove Snappy theme
- - - - -
2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00
fix occasional v.scroll bars on pre blocks (I think)
- - - - -
459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00
Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API
- - - - -
b1b68675 by David Waern at 2010-08-26T20:31:58+00:00
Follow recent API additions with some refactorings

Simon Hegel's patch prompted me to do some refactorings in Main,
Haddock.Documentation and Haddock.Interface. 

- - - - -
264d4d67 by David Waern at 2010-08-26T21:40:59+00:00
Get rid of GhcModule and related cruft

We can get everything we need directly from TypecheckedModule.

- - - - -
0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00
fixed CSS for ordered lists and def lists in doc blocks
- - - - -
2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00
support both kinds of enumerated lists in doc markup
	The documentation for Haddock says enumerated lists can use either of
		(1) first item
		2. second item
	The second form wasn't actually supported


- - - - -
5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00
fix broken header link margins
- - - - -
614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00
fix table of contents CSS
- - - - -
03f329a2 by David Waern at 2010-08-28T16:36:09+00:00
Update tests following switch to the Xhtml backend
- - - - -
ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00
fix def lists
- - - - -
18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00
push footer to bottom of window
- - - - -
b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00
Whitespace police
- - - - -
2d217977 by David Waern at 2010-08-29T12:44:45+00:00
Remove Snappy data files
- - - - -
01e27d5f by David Waern at 2010-08-29T13:03:28+00:00
Add source entity path to --read-interface

You can now use this flag like this:

  --read-interface=<html path>,<source entity path>,<.haddock file> 

By "source entity path" I mean the same thing that is specified with the
--source-entity flag. The purpose of this is to be able to specify the source
entity path per package, to allow source links to work in the presence of
cross-package documentation.

When given two arguments or less the --read-interface flag behaves as before.

- - - - -
20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00
Naming wibbles
- - - - -
ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00
make portability block be a table - solves layout issues
- - - - -
97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00
update golden test for Test due to portability box change
- - - - -
d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00
move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs
- - - - -
acf52501 by David Waern at 2010-08-29T17:32:36+00:00
Allow building with ghc < 6.16
- - - - -
1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00
Flatten the dynflags before parsing
- - - - -
b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00
Follow flattenLanguageFlags -> flattenExtensionFlags rename
- - - - -
7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00
Use flattenExtensionFlags with ghc >= 6.13 only
- - - - -
13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00
Make the main haddock script versioned, and make plain "haddock" a symlink
- - - - -
495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00
Fix installation in the GHC build system
Data-files are now in subdirectories, so we need to handle that

- - - - -
88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00
GHC build system: Add all the data files to BINDIST_EXTRAS
- - - - -
65837172 by David Waern at 2010-08-29T20:12:34+00:00
Update Test
- - - - -
094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00
Revert update to Test
- - - - -
a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00
Bump version number
- - - - -
1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00
Update ANNOUNCE
- - - - -
ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00
Update CHANGES
- - - - -
394cc854 by David Waern at 2010-08-31T22:33:23+00:00
Update interface file versioning to work with ghc 6.14/15
- - - - -
7d03b79b by David Waern at 2010-08-31T22:36:00+00:00
Update test output following version change
- - - - -
a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00
sort options in doc to match --help output
	removed --html-help option, as it is no longer supported

- - - - -
06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00
update options documentation
	rewrote doc for --html
	added doc for --theme and --built-in-themes
	added --use-contents and --gen-contents

- - - - -
57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00
slight wording change about Frames mode
- - - - -
fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00
Update doc configure script to find docbook stylesheets on arch linux
- - - - -
addff770 by David Waern at 2010-09-01T11:02:29+00:00
Wibble
- - - - -
8399006d by David Waern at 2010-09-01T11:19:21+00:00
Replace ghci> with >>> in example syntax
- - - - -
35074cf8 by David Waern at 2010-09-01T19:03:27+00:00
Improve docs for --no-tmp-comp-dir
- - - - -
0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00
Add a list of contributors to the user guide

Break out everyone thanked in the `Acknowledgements` chapter into a
separate contributor list and add everyone from `darcs show authors`.
We consider everyone who is thanked to be a contributor as a conservative
estimation :-)

I have added some more contributors that I know about, who were not in the
darcs history, but others may be missing. So please add anyone that you think 
is missing from the list.

- - - - -
42ccf099 by David Waern at 2010-09-02T11:29:22+00:00
Update copyright years in license
- - - - -
0d560479 by David Waern at 2010-09-02T11:38:52+00:00
Update release instructions
- - - - -
72ab7796 by David Waern at 2010-09-02T19:27:08+00:00
Add a note to ANNOUNCE
- - - - -
bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00
H.Utils needs FFI on Win+MinGW 
- - - - -
048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00
make TOC group header identifiers validate
- - - - -
8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00
add hints for cleaner darcs show authors output
- - - - -
9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00
print haddock coverage info on stdout when generating docs
A module's haddockable items are its exports and the module itself.
The output is lightly formatted so you can align the :'s and sort
for readability.

- - - - -
6da72171 by David Waern at 2010-10-03T21:31:24+00:00
Style wibble
- - - - -
2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00
adding the option to fully qualify identifiers
- - - - -
833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00
adding support for local and relative name qualification
- - - - -
df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00
corrected qualification help message
- - - - -
449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00
Solve conflicts
- - - - -
3469bda5 by David Waern at 2010-10-16T18:42:40+00:00
Use "qual" as an abbreviation for qualification instead of "quali" for consistency
- - - - -
97c2d728 by David Waern at 2010-10-16T18:47:07+00:00
Style police
- - - - -
ce14fbea by David Waern at 2010-10-16T21:15:25+00:00
Style police
- - - - -
fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00
Add a pointer to the style guide
- - - - -
8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00
Change to index pages: include an 'All' option even when subdividing A-Z.
- - - - -
755b131c by David Waern at 2010-11-14T19:39:36+00:00
Bump version
- - - - -
d0345a04 by David Waern at 2010-11-14T19:41:59+00:00
TAG 2.8.1
- - - - -
f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00
Adapt to minor changes in internal GHC functions
- - - - -
1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00
Remove duplicate Outputable instance for Data.Map.Map
- - - - -
87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00
Bump GHC dep upper bound
- - - - -
af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00
Fix up __GLASGOW_HASKELL__ tests
- - - - -
ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00
Don't build haddock is HADDOCK_DOCS is NO
- - - - -
63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00
Fixes for when HADDOCK_DOCS=NO
- - - - -
e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00
Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353
- - - - -
66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00
Tidy up haddock symlink installation
In particular, it now doesn't get created if we aren't installing
haddock.

- - - - -
549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00
Follow extension-flattening change in GHC
- - - - -
d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00
Bump version to 2.8.2
- - - - -
6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00
Solve conflict
- - - - -
055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00
Bump GHC dep
- - - - -
c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00
follow changes in the GHC API
- - - - -
45907129 by David Waern at 2010-11-07T14:00:58+00:00
Update the HCAR entry
- - - - -
61940b95 by David Waern at 2010-11-07T14:07:34+00:00
Make the HCAR entry smaller
- - - - -
aa590b7d by David Waern at 2010-11-14T21:30:59+00:00
Update HCAR entry with November 2010 version
- - - - -
587f9847 by David Waern at 2010-11-14T23:48:17+00:00
Require ghc >= 7.0
- - - - -
ff5c647c by David Waern at 2010-11-14T23:49:09+00:00
TAG 2.8.2
- - - - -
937fcb4f by David Waern at 2010-11-14T23:49:45+00:00
Solve conflict
- - - - -
8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00
Remove code for ghc < 7
- - - - -
3d47b70a by David Waern at 2010-11-15T21:11:06+00:00
Fix bad merge
- - - - -
7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00
Remove more ghc < 7 code
- - - - -
9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00
Match all AsyncExceptions in exception handler
- - - - -
42849c70 by David Waern at 2010-11-15T21:35:31+00:00
Just say "internal error" instead of "internal Haddock or GHC error"
- - - - -
c88c809b by David Waern at 2010-11-15T21:44:19+00:00
Remove docNameOcc under the motto "don't name compositions"
- - - - -
b798fc7c by David Waern at 2010-11-15T23:27:13+00:00
Wibble
- - - - -
2228197e by David Waern at 2010-11-15T23:28:24+00:00
Rename the HCAR entry file
- - - - -
8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00
Remove Haskell 2010 extensions from .cabal file
- - - - -
c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00
Style wibbles
- - - - -
cde707a5 by David Waern at 2010-11-16T00:12:00+00:00
Remove LANGUAGE ForeignFunctionInterface pragmas
- - - - -
1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00
Make a little more use of DoAndIfThenElse
- - - - -
4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00
hlint police
- - - - -
d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00
hlint police
- - - - -
99876e97 by David Waern at 2010-11-20T19:06:00+00:00
Haddock documentation updates
- - - - -
65ce6987 by David Waern at 2010-11-20T19:42:51+00:00
Follow the style guide closer in Haddock.Types and improve docs
- - - - -
28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00
add full qualification for undocumented names
- - - - -
d61341e3 by David Waern at 2010-11-20T20:04:15+00:00
Re-structure qualification code a little
- - - - -
0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00
Re-order functions
- - - - -
d7279afd by David Waern at 2010-11-21T03:39:54+00:00
Add BangPatterns to alex and happy source files
- - - - -
629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00
documentation for qualification
- - - - -
37031cee by David Waern at 2010-11-23T21:06:44+00:00
Update CHANGES - don't mention 2.8.2, we won't release it
- - - - -
f2489e19 by David Waern at 2010-12-01T21:57:11+00:00
Update deps of runtests.hs to work with ghc 7.0.1
- - - - -
d3657e9a by David Waern at 2010-12-01T22:04:57+00:00
Make tests compile with ghc 7.0.1
- - - - -
a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00
Update tests following version bump
- - - - -
50883ebb by David Waern at 2010-12-06T14:09:18+00:00
Update tests following recent changes
- - - - -
fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00
Add a flag --pretty-html for rendering indented html with newlines
- - - - -
30832ef2 by David Waern at 2010-12-06T14:17:35+00:00
Use --pretty-html when running the test suite. Makes it easier to compare output
- - - - -
a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00
Wibble
- - - - -
3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00
Haddockify ppHtml comments
- - - - -
24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00
Remove --debug. It was't used, and --verbosity should take its place
- - - - -
6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00
Rename golden-tests into html-tests. "golden tests" sounds strange
- - - - -
53301e55 by David Waern at 2010-12-06T14:26:26+00:00
QUALI -> QUAL in the description --qual for consistency
- - - - -
98b6affb by David Waern at 2010-12-06T21:54:02+00:00
Bump version
- - - - -
371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00
Update tests following version bump
- - - - -
25be762d by David Waern at 2010-12-06T22:21:03+00:00
Update CHANGES
- - - - -
7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00
Update ANNOUNCE
- - - - -
30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00
Alex generates BangPatterns, so make Lex.x accept them

(It'd be better for Alex to generate this pragma.)

- - - - -
605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00
Add {-# LANGUAGE BangPatterns #-} to mollify GHC
- - - - -
a46607ba by David Waern at 2010-12-07T14:08:10+00:00
Solve conflicts
- - - - -
b28cda66 by David Waern at 2010-12-09T20:41:35+00:00
Docs: Mention that \ is a special character in markup
- - - - -
a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00
TAG GHC 7.0.1 release
- - - - -
5a15a05a by David Waern at 2010-12-11T17:51:19+00:00
Fix indentation problem
- - - - -
4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00
Revise haddock.cabal given that we now require ghc-7
default-language should be Haskell2010, slight new semantics for extensions.
Rewrite into clearer dependencies of base and Cabal.

- - - - -
a36302dc by David Waern at 2010-12-19T17:12:37+00:00
Update CHANGES
- - - - -
7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00
Bump version
- - - - -
cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00
Write hoogle output in utf8; fixes GHC build on Windows
- - - - -
c7e762ea by David Waern at 2011-01-22T00:00:35+00:00
Put title outside doc div when HTML:fying title+prologue

Avoids indenting the title, and makes more sense since the title
is not a doc string anyway.

- - - - -
5f639054 by David Waern at 2011-01-22T16:09:44+00:00
Fix spelling error - contributed by Marco Silva
- - - - -
c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00
Follow GHC build system changes
- - - - -
101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00
Bump version
- - - - -
af62348b by David Waern at 2011-01-08T14:07:07+00:00
TAG 2.9.2
- - - - -
4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00
Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882
"7.0.2" looked like a haddock version number before

- - - - -
8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00
Update Haddock to reflect change in hs_tyclds field of HsGroup
- - - - -
06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00
TAG GHC 7.0.2 release
- - - - -
7de0667d by David Waern at 2011-03-10T22:47:13+00:00
Update CHANGES
- - - - -
33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00
Fix build with ghc 7.0.1
- - - - -
4616f861 by David Waern at 2011-03-10T22:47:50+00:00
TAG 2.9.2-actual
- - - - -
0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00
Set shell script for unit tests back to work
- - - - -
85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00
Set unit tests back to work

Here "ghci>" was still used instead of ">>>".

- - - - -
1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00
Update runtests.hs for GHC 7.0.2
- - - - -
8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00
Update Haddock version in *.html.ref
- - - - -
2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00
Add support for blank lines in the result of examples

Result lines that only contain the string "<BLANKLINE>" are treated as a blank
line.

- - - - -
adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00
Add documentation for "support for blank lines in the result of examples"
- - - - -
c51352ca by David Waern at 2011-05-21T23:57:56+00:00
Improve a haddock comment
- - - - -
7419cf2c by David Waern at 2011-05-22T15:41:52+00:00
Use cabal's test suite support to run the test suite

This gives up proper dependency tracking of the test script.

- - - - -
7770070c by David Waern at 2011-05-22T01:45:44+00:00
We don't need to send DocOptions nor a flag to mkExportItems
- - - - -
9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00
Fix a bug
- - - - -
1f93699b by David Waern at 2011-05-22T21:40:21+00:00
Break out fullContentsOf, give it a better name and some documentation

The documentation describes how we want this function to eventually behave,
once we have fixed a few problems with the current implementation.

- - - - -
9a86432f by David Waern at 2011-05-22T21:53:52+00:00
Fix some stylistic issues in mkExportItems
- - - - -
c271ff0c by David Waern at 2011-05-22T22:09:11+00:00
Indentation
- - - - -
93e602b1 by David Waern at 2011-06-10T01:35:31+00:00
Add git commits since switchover:

  darcs format (followed by a conflict resolution):

  commit 6f92cdd12d1354dfbd80f8323ca333bea700896a
  Merge: f420cc4 28df3a1
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Thu May 19 17:54:34 2011 +0100

      Merge remote branch 'origin/master' into ghc-generics

  commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0
  Author: Max Bolingbroke <batterseapower at hotmail.com>
  Date:   Sat May 14 22:37:02 2011 +0100

      Unicode fix for getExecDir on Windows

  commit 89813e729be8bce26765b95419a171a7826f6d70
  Merge: 6df3a04 797ab27
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 9 11:55:17 2011 +0100

      Merge branch 'ghc-new-co'

  commit 6df3a040da3dbddee67c6e30a892f87e6b164383
  Author: Ian Lynagh <igloo at earth.li>
  Date:   Sun May 8 17:05:50 2011 +0100

      Follow changes in SDoc

  commit f420cc48b9259f0b1afd2438b12f9a2bde57053d
  Author: Jose Pedro Magalhaes <jpm at cs.uu.nl>
  Date:   Wed May 4 17:31:52 2011 +0200

      Adapt haddock to the removal of HsNumTy and TypePat.

  commit 797ab27bdccf39c73ccad374fea265f124cb52ea
  Merge: 1d81436 5a91450
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 2 12:05:03 2011 +0100

      Merge remote branch 'origin/master' into ghc-new-co

  commit 1d8143659a81cf9611668348e33fd0775c7ab1d2
  Author: Simon Peyton Jones <simonpj at microsoft.com>
  Date:   Mon May 2 12:03:46 2011 +0100

      Wibbles for ghc-new-co branch

  commit 5a91450e2ea5a93c70bd3904b022445c9cc82488
  Author: Ian Lynagh <igloo at earth.li>
  Date:   Fri Apr 22 00:51:56 2011 +0100

      Follow defaultDynFlags change in GHC

- - - - -
498da5ae by David Waern at 2011-06-11T00:33:33+00:00
* Merge in git patch from Michal Terepeta

>From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001
From: Michal Terepeta <michal.terepeta at gmail.com>
Date: Sat, 14 May 2011 19:18:22 +0200
Subject: [PATCH] Follow the change of TypeSig in GHC.

This follows the change in GHC to make TypeSig take a list
of names (instead of just one); GHC ticket haskell/haddock#1595. This
should also improve the Haddock output in case the user
writes a type signature that refers to many names:
  -- | Some comment..
  foo, bar :: ...
will now generate the expected output with one signature for
both names.

- - - - -
094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00
Fix build

- - - - -
8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00
Bump GHC dep to allow 7.2

- - - - -
e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00
Relax base dep

- - - - -
b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00
GHC build system: Don't install the datafiles twice

- - - - -
f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00
Hack this to make it work with both Alex 2.x and Alex 3.x.  Unicode in
documentation strings is (still) mangled.  I don't think it's possible
to make it so that we get the current behaviour with Alex 2.x but
magic Unicode support if you use Alex 3.x.  At some point we have to
decide that Alex 3.x is a requirement, then we can do Unicode.

- - - - -
b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00
Fix compilation with no-pred-ty GHC

- - - - -
30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00
Remaining fixes for PredTy removal

- - - - -
0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00
Rename factKind to constraintKind

- - - - -
a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00
Deal with change to IParam handling in GHC

- - - - -
f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00
Adapt Haddock for the ConstraintKind extension changes

- - - - -
8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00
Ignore associated type defaults (just as we ignore default methods)

- - - - -
31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00
Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty

- - - - -
dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00
Merge branch 'no-pred-ty'

Conflicts:
	src/Haddock/Convert.hs

- - - - -
5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00
Replace FactTuple with ConstraintTuple

- - - - -
cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00
Bump to version 2.9.3

- - - - -
4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00
Follow changes to BinIface Name serialization

- - - - -
92257d90 by David Waern at 2011-09-30T23:45:07+02:00
Fix problem with test files not added to distribution tarball

- - - - -
00255bda by David Waern at 2011-09-30T23:48:24+02:00
Merge branch 'development'

- - - - -
5421264f by David Waern at 2011-10-01T01:25:39+02:00
Merge in darcs patch from Simon Meier:

  Wed Jun  1 19:41:16 CEST 2011  iridcode at gmail.com
    * prettier haddock coverage info
    The new coverage info rendering uses less horizontal space. This reduces the
    number of unnecessary line-wrappings. Moreover, the most important information,
    how much has been documented already, is now put up front. Hopefully, this
    makes it more likely that a library author is bothered by the low coverage of
    his modules and fixes that issue ;-)

- - - - -
07d318ef by David Waern at 2011-10-01T01:34:10+02:00
Use printException instead of deprecated printExceptionAndWarnings

- - - - -
40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00
Merge in darcs pach:

  Mon Apr 11 18:09:54 JST 2011  Liyang HU <haddock at liyang.hu>
    * Remember collapsed sections in index.html / haddock-util.js

- - - - -
279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00
Merge in darcs patch:

  Joachim Breitner <mail at joachim-breitner.de>**20110619201645
  Ignore-this: f6c51228205b0902ad5bfad5040b989a

  As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301,
  generating the global index takes much too long if type-level (with lots of
  auto-generated types) is installed. The patch avoids a quadratic runtime in the
  subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s.

- - - - -
d1612383 by David Waern at 2011-10-01T01:56:48+02:00
Merge branch 'development'

- - - - -
347520c1 by David Waern at 2011-10-01T01:56:54+02:00
Merge branch 'master' of http://darcs.haskell.org/haddock

- - - - -
9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00
Improve .cabal file

- - - - -
6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00
Follow changes to ForeignImport/ForeignExport in GHC

- - - - -
565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00
Hack this to make it work with both Alex 2.x and Alex 3.x.  Unicode in
documentation strings is (still) mangled.  I don't think it's possible
to make it so that we get the current behaviour with Alex 2.x but
magic Unicode support if you use Alex 3.x.  At some point we have to
decide that Alex 3.x is a requirement, then we can do Unicode.

- - - - -
8b74f512 by David Waern at 2011-10-04T00:18:17+02:00
Requre ghc >= 7.2

- - - - -
271d360c by David Waern at 2011-10-04T00:22:50+02:00
Bump version to 2.9.4

- - - - -
37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00
Add alex and happy to build-tools.

- - - - -
7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00
Add safe haskell indication to haddock output

- - - - -
42c91a47 by David Terei at 2011-10-12T14:06:03-07:00
Fix CSS issue with info table not being contained in module header

- - - - -
0eddab6c by David Terei at 2011-10-12T14:06:58-07:00
Add safe haskell indication to haddock output

- - - - -
3df058eb by David Terei at 2011-10-12T14:07:07-07:00
Fix CSS issue with info table not being contained in module header

- - - - -
a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00
Bump .haddock file version since the format has changed recently

- - - - -
8a6254be by David Waern at 2011-10-22T11:30:42+02:00
Merge branch 'development'

- - - - -
642e3e02 by David Waern at 2011-10-23T21:23:39+02:00
Sort import list

- - - - -
36371cf8 by David Waern at 2011-10-23T22:48:18+02:00
Remove NEW_GHC_LAYOUT conditional.

- - - - -
5604b499 by David Waern at 2011-10-27T00:15:03+02:00
Add --print-ghc-path.

- - - - -
463499fa by David Waern at 2011-10-27T00:16:22+02:00
Make testsuite able to find its dependencies automatically.

- - - - -
a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00
Improved declNames internal error.  Added a case to handle DocD.

- - - - -
001b8baf by David Waern at 2011-11-05T20:37:29+01:00
Rename copy.hs -> accept.hs.

- - - - -
55d808d3 by David Waern at 2011-11-05T23:30:02+01:00
Fix build.

- - - - -
deb5c3be by David Waern at 2011-11-06T00:01:47+01:00
Merge branch 'master' of http://darcs.haskell.org/haddock

- - - - -
9b663554 by David Waern at 2011-11-06T00:03:45+01:00
Merge https://github.com/rrnewton/haddock

- - - - -
1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00
Use getDeclMainBinder instead of declNames.

- - - - -
4b005c01 by David Waern at 2011-11-06T19:09:53+01:00
Fix build.

- - - - -
c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00
Remove -DNEW_GHC_LAYOUT in ghc.mk

- - - - -
f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00
New kind-polymorphic core

This big patch implements a kind-polymorphic core for GHC. The current
implementation focuses on making sure that all kind-monomorphic programs still
work in the new core; it is not yet guaranteed that kind-polymorphic programs
(using the new -XPolyKinds flag) will work.

For more information, see http://haskell.org/haskellwiki/GHC/Kinds

- - - - -
7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00
Follow changes to tuple sorts in master

- - - - -
8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00
Remove redundant imports

- - - - -
d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00
Follow GHC build system change to the way we call rm

- - - - -
9e2230ed by David Waern at 2011-11-24T15:00:24+01:00
Fix a bug in test runner and get rid of regex-compat dependency.

- - - - -
52039b21 by David Waern at 2011-11-24T23:55:36+01:00
Avoid haskell98 dependency in test

- - - - -
92e1220d by David Waern at 2011-11-25T00:03:33+01:00
Avoid depency on regex-compat also in accept.hs.

- - - - -
ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00
Accept test output.

- - - - -
5a720455 by David Waern at 2011-11-25T02:16:20+01:00
Some more changes to test scripts.

- - - - -
170a9004 by David Waern at 2011-11-25T02:30:41+01:00
Add flag --interface-version.

- - - - -
d225576c by David Waern at 2011-11-25T02:39:26+01:00
Remove #ifs for older compiler versions.

- - - - -
f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00
Give preference to type over data constructors for doc comment links at renaming time.

Previously this was done in the backends.

Also, warn when a doc comment refers to something that is in scope but which we
don't have the .haddock file for.

These changes mean we can make DocIdentifier [a] into DocIdentifier a.

- - - - -
eef0e776 by David Waern at 2011-11-26T17:01:06+01:00
Allow doc comments to link to out-of-scope things (#78).

(A bug that should have been fixed long ago.)

- - - - -
565ad529 by David Waern at 2011-11-26T19:56:21+01:00
Update tests.

- - - - -
fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00
Cleanup.

- - - - -
d0328126 by David Waern at 2011-11-26T22:10:28+01:00
Fix module reference bug.

- - - - -
c03765f8 by David Waern at 2011-12-03T05:20:20+01:00
Slightly better behaviour on top-levels without type signatures.

- Docs don't get attached to the next top-level with signature by
mistake.

- If there's an export list and the top-level is part of it,
its doc comment shows up in the documentation.

- - - - -
48461d31 by David Waern at 2011-12-03T05:38:10+01:00
Add a test for Unicode doc comments.

- - - - -
549c4b4e by David Waern at 2011-12-03T19:07:55+01:00
Cleanup.

- - - - -
7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00
More cleanup.

- - - - -
14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00
Update dependencies and binaryInterfaceVersion

- - - - -
469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00
Fix (untested) building from source tarball without alex/happy

haddock's .cabal file was declaring that it needed alex and happy to
build, but in the GHC source tarballs it doesn't.

- - - - -
895c9a8c by David Waern at 2011-12-27T12:57:43+01:00
Go back to having a doc, sub and decl map instead of one big decl map.

This setup makes more sense since when we add value bindings to the
processed declarations (for type inference), we will have multiple
declarations which should share documentation. Also, we already have
a separate doc map for instances which we can now merge into the
main doc map. Another benefit is that we don't need the DeclInfo
type any longer.

- - - - -
736767d9 by David Waern at 2011-12-27T13:33:41+01:00
Merge ../../../haddock

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
20016f79 by David Waern at 2011-12-27T13:57:23+01:00
Bump version.

- - - - -
31f276fb by David Waern at 2011-12-27T13:57:32+01:00
Merge ../ghc/utils/haddock

- - - - -
95b367cd by David Waern at 2011-12-27T14:57:29+01:00
Update tests following version bump.

- - - - -
fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00
Get rid of quite unnecessary use of different lists.

- - - - -
9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00
Cleanup.

- - - - -
2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00
Wibbles.

- - - - -
3757d09b by David Waern at 2011-12-27T20:50:26+01:00
Complete support for inferring types for top-level bindings.

- - - - -
53418734 by David Waern at 2011-12-28T15:02:13+01:00
Minor fixes and cleanup.

- - - - -
0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00
Follow rename of Instance to ClsInst in GHC

- - - - -
c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00
Make sure that generated xhtml is valid (close haskell/haddock#186)

Thanks to Phyx.

- - - - -
836a0b9a by David Waern at 2012-02-01T02:30:05+01:00
Fix bug introduced in my recent refactoring.

- - - - -
c7d733eb by David Waern at 2012-02-01T02:30:26+01:00
Cleanup mkMaps and avoid quadratic behaviour.

- - - - -
da3cda8f by David Waern at 2012-02-01T02:56:56+01:00
Require ghc >= 7.4.

- - - - -
83a3287e by David Waern at 2012-02-01T02:57:36+01:00
Update CHANGES.

- - - - -
93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00
Add reference renderings

- - - - -
49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00
Set unit tests for parser back to work

- - - - -
eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00
Add .gitignore

- - - - -
a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00
Add .ghci file

- - - - -
8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00
tests/html-tests/copy.hs: Use mapM_ instead of mapM

So we do net get a list of () on stdout when running with runhaskell.

- - - - -
b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00
Remove index files from golden tests

- - - - -
9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00
Add /tests/html-tests/tests/*index*.ref to .gitignore

- - - - -
a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00
Add DocWarning to Doc

The Xhtml backend has special markup for that, Hoogle and LaTeX reuse
what we have for DocEmphasis.

- - - - -
de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00
Add support for module warnings

- - - - -
0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00
Add tests for module warnings

- - - - -
30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00
Add support for warnings

- - - - -
bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00
Add tests for warnings

- - - - -
6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00
Expand type signatures in export list (fixes haskell/haddock#192)

- - - - -
a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00
Expand type signatures for modules without explicit export list

- - - - -
57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00
Remove obsolete TODO

- - - - -
270c3253 by David Waern at 2012-02-04T00:51:24+01:00
Fix issues in support for warnings.

* Match against local names only.
* Simplify (it's OK to map over the warnings).

- - - - -
683634bd by David Waern at 2012-02-04T00:55:11+01:00
Some cleanup and make sure we filter warnings through exports.

- - - - -
210cb4ca by David Waern at 2012-02-04T03:01:30+01:00
Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4

- - - - -
e8db9031 by David Waern at 2012-02-04T03:07:51+01:00
Style police.

- - - - -
261f9462 by David Waern at 2012-02-04T03:20:16+01:00
Update tests.

- - - - -
823cfc7c by David Waern at 2012-02-04T03:21:12+01:00
Use mapM_ in accept.hs as well.

- - - - -
873dd619 by David Waern at 2012-02-04T03:21:33+01:00
Remove copy.hs - use accept.hs instead.

- - - - -
0e31a14a by David Waern at 2012-02-04T03:47:33+01:00
Use <> instead of mappend.

- - - - -
2ff7544f by David Waern at 2012-02-04T03:48:55+01:00
Remove code for older ghc versions.

- - - - -
dacf2786 by David Waern at 2012-02-04T15:52:51+01:00
Clean up some code from last SoC project.

- - - - -
00cbb117 by David Waern at 2012-02-04T21:43:49+01:00
Mostly hlint-inspired cleanup.

- - - - -
7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00
Track changes in HsDecls

- - - - -
f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00
Follow changes in GHC caused by the CAPI CTYPE pragma

- - - - -
a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00
Follow changes in GHC

- - - - -
b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00
Follow changes in data representation from the big PolyKinds commit

- - - - -
43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00
Save/restore global state for static flags when running GHC actions

This is necessary if we want to run createInterfaces (from
Documentation.Haddock) multiple times in the same process.

- - - - -
9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00
Update .gitignore.

- - - - -
a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00
Follow changes to tcdKindSig (Trac haskell/haddock#5937)

- - - - -
fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00
Add support for type-level literals.

- - - - -
2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00
Follow changes to tcdKindSig (Trac haskell/haddock#5937)

- - - - -
93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00
Merge branch 'master' of http://darcs.haskell.org//haddock

Conflicts:
	src/Haddock/Convert.hs

- - - - -
d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00
Merge remote-tracking branch 'origin/master' into type-nats

- - - - -
fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00
Add a missing case for type literals.

- - - - -
fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00
Rename variable to avoid shadowing warning.

- - - - -
9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00
Follow refactoring of TyClDecl/HsTyDefn

- - - - -
38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00
Merge branch 'master' of http://darcs.haskell.org//haddock

- - - - -
4324ac0f by David Waern at 2012-04-01T01:51:19+02:00
Disable unicode test.

- - - - -
3165b750 by David Waern at 2012-04-01T01:51:34+02:00
Take reader environment directly from TypecheckedSource.

- - - - -
213b644c by David Waern at 2012-04-01T01:55:20+02:00
Cleanup.

- - - - -
3118b4ba by David Waern at 2012-04-01T02:16:15+02:00
Don't filter out unexported names from the four maps - fixes a regression.

- - - - -
d6524e17 by David Waern at 2012-04-01T02:40:34+02:00
Fix crash when using --qual. Naughty GHC API!

- - - - -
ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00
add QualOption type for distinction between qualification argument given by the user
and the actual qualification for a concrete module
- - - - -
5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00
emit an error message when the --qual option is used incorrectly
- - - - -
026e3404 by David Waern at 2012-04-01T18:10:30+02:00
Don't crash on unicode strings in doc comments.

- - - - -
ce006632 by David Waern at 2012-04-01T20:13:35+02:00
Add test for --ignore-all-exports flag/ignore-exports pragma.

- - - - -
6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00
Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4

- - - - -
734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00
'abbreviate' qualification style - basic support
Currently we ignore the package a module is imported from.
This means that a module import would shadow another one
with the same module name from a different package.
- - - - -
c85314ef by David Waern at 2012-04-01T22:05:12+02:00
Check qualification option before processing modules.

- - - - -
ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00
abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to
- - - - -
60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00
qualification style 'abbreviated' -> 'aliased'

- - - - -
f4192a64 by David Waern at 2012-04-02T01:05:47+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
7ba09067 by David Terei at 2012-04-04T15:08:21-07:00
Fix reporting of modules safe haskell mode (#5989)

- - - - -
d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00
Fix reporting of modules safe haskell mode (#5989)

- - - - -
6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00
Track changes in HsSyn

- - - - -
22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00
Follow changes to LHsTyVarBndrs

- - - - -
d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00
Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4

- - - - -
a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00
Update CHANGES.

- - - - -
8e181d29 by David Waern at 2012-05-16T02:27:56+02:00
Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4

- - - - -
e358210d by David Waern at 2012-05-16T02:35:33+02:00
Mention the new aliased --qual mode in CHANGES.

- - - - -
efd36a28 by David Waern at 2012-05-16T21:33:13+02:00
Bump version number.

- - - - -
d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00
Add test for deprecated record field

- - - - -
927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00
Use >>= instead of fmap and join

- - - - -
048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00
newtype-wrap Doc nodes for things that may have warnings attached

- - - - -
e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00
Attach warnings to `Documentation` type

- - - - -
5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00
Simplify lookupWarning

- - - - -
cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00
Add test for haskell/haddock#205

- - - - -
cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00
Follow changes in LHsTyVarBndrs

- - - - -
2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00
Add Applicative instance for (GenRnM a)

- - - - -
e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00
Use a map for warnings, as suggested by @waern

- - - - -
597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00
Add an optional label to URLs

- - - - -
ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00
Add support for hyperlink labels to parser

- - - - -
41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00
Add golden test for hyperlinks

- - - - -
83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00
Use LANGUAGE pragmas instead of default-extensions in cabal file

- - - - -
ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00
Fix typo in comment

- - - - -
110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00
Add a type signature for a where-binding

- - - - -
7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00
Follow changes in GHC

- - - - -
47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00
Follow changes in GHC

- - - - -
e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00
Follow changes for the implementation of implicit parameters

- - - - -
69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00
Follow changes in base

- - - - -
9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00
Use right docMap to get decl documentation.

- - - - -
e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00
Follow changes in GHC

- - - - -
ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00
Fix haddock following some GHC changes

Passing _|_ as the Settings for defaultDynFlags no longer works well
enough

- - - - -
9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00
Forward port changes from stable.

- - - - -
572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00
Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock

- - - - -
9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00
Update dependencies.

- - - - -
33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00
Build with GHC 7.7

- - - - -
925a2cea by David Waern at 2012-07-23T16:50:40+02:00
Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
d710ef97 by David Waern at 2012-07-23T16:52:07+02:00
Bump version number.

- - - - -
eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00
Update CHANGES.

- - - - -
b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00
Hide "internal" instances

This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37)

Precisely, we show an instance iff its class and all the types are exported by
non-hidden modules.

- - - - -
a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00
Tests for hiding instances (#37)

- - - - -
c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00
Add an other test for hiding instances (#37)

- - - - -
a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00
Follow changes in GHC

- - - - -
0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00
Improve haddock memory usage

- - - - -
0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00
Improve haddock memory usage

- - - - -
659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00
Remove some temporary pragmas I accidentally recorded

- - - - -
d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00
Add missing dependency to library

- - - - -
4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00
Move .ghci to project root

- - - - -
fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00
accept.hs: Ignore some files

- - - - -
1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00
Update reference renderings (bump version)

- - - - -
980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00
Update reference renderings (remove links for ())

- - - - -
33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00
Update documentation of `runInteractiveProcess` in reference rendering

- - - - -
7ab25078 by David Waern at 2012-09-07T10:38:50+02:00
Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6

- - - - -
c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00
Follow changes in GHC.

- - - - -
298c43ac by David Waern at 2012-09-07T14:59:24+02:00
Update CHANGES.

- - - - -
e797993a by David Waern at 2012-09-07T15:21:30+02:00
Update ANNOUNCE.

- - - - -
d0b44790 by David Waern at 2012-09-07T15:22:43+02:00
Merge branch 'hidden-instances' into ghc-7.6

- - - - -
41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00
Update doc/README

- - - - -
71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00
Add documentation for URL labels

- - - - -
9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00
Follow data type changes in the tc-untouchables branch

Relating entirely to SynTyConRhs

- - - - -
b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00
Disable Unicode test for now

- - - - -
a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00
Update TypeOperators test for GHC 7.6.1

Type operators can't be used as type variables anymore!

- - - - -
6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00
Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs

I do not really understand why the behavior changed, so I'll open a
ticket, so that we can further investigate.

- - - - -
b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00
Follow changes in GHC build system

- - - - -
b98eded0 by David Waern at 2012-09-27T15:37:02+02:00
Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6

- - - - -
76cc2051 by David Waern at 2012-09-27T15:48:19+02:00
Update hidden instances tests.

- - - - -
aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00
Make API buildable with GHC 7.6.

- - - - -
d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00
Merge remote-tracking branch 'origin/master' into tc-untouchables

- - - - -
a1922af8 by David Waern at 2012-09-28T19:50:20+02:00
Fix spurious superclass constraints bug.

- - - - -
bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00
Remove old examples

- - - - -
bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00
Adapt parsetests for GHC 7.6.1

- - - - -
dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00
Add test-suite section for parsetests to cabal file

+ get rid of HUnit dependency

- - - - -
1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00
Remove test flag from cabal file

This was not really used.

- - - - -
4beee98b by David Waern at 2012-09-28T23:42:28+02:00
Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6

- - - - -
11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00
Follow change in GHC build system

- - - - -
fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00
Remove redundant dependency from cabal file

- - - - -
09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00
Fix typo

- - - - -
93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00
Remove trailing whitespace from cabal file

- - - - -
c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00
Export Haddock's main entry point from library

- - - - -
b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00
Depend on library for executable

The main motivation for this is to increase build speed.  In GHC's
source tree the library is not build, but all modules are now required
for the executable, so that GHC's validate will now detect build
failures for the library.

- - - - -
f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00
Set executable flag for Setup.lhs

- - - - -
dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00
Extend rather than set environment when running HTML tests

On some platforms (e.g. ppc64) GHC requires gcc in the path.

- - - - -
7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00
cross-package test: re-export IsString instead of Monad

There is a monad instance for Q, which is not available on platforms
that do not have GHCi support.  This caused CrossPackageDocs to fail on
those platforms.  Re-exporting IsString should test the same thing, but
it works on all platforms.

- - - - -
0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Fix some warnings

- - - - -
f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Make -Wall proof

- - - - -
6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00
runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe

- - - - -
44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00
Follow changes in GHC

- - - - -
6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00
Update .ghci

- - - - -
9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00
Add markup support for properties

- - - - -
1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00
Simplify lexing/parsing of properties

In contrast to what we do for examples, we do not really need to capture
the "prompt" here.

- - - - -
bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00
Add HTML test for properties

- - - - -
2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00
Add unit tests for properties

- - - - -
874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00
Bump interface version

- - - - -
2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00
Fix parser bug

- - - - -
743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00
Allow to load interface files with compatible versions

- - - - -
981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00
Export more types from Documentation.Haddock (fixes haskell/haddock#216)

- - - - -
dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00
Update ANNOUNCE and CHANGES

- - - - -
edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00
Bump version

- - - - -
5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00
Fix typo in documentation

- - - - -
e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00
Add documentation for properties

- - - - -
9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00
Remove redundant if-defs, more source documentation

- - - - -
87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00
Adapt cabal file

- - - - -
c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00
Require ghc 7.6

- - - - -
8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00
Bump version

- - - - -
1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00
Update ANNOUNCE and CHANGES

- - - - -
74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00
Improve note about `binaryInterfaceVersion` (thanks David)

- - - - -
ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00
Update version in html tests, rpm spec file, and user manual

- - - - -
f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00
Remove unused MonadFix constraint

- - - - -
dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00
Minor code simplification

- - - - -
4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00
Increase code locality

- - - - -
f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00
Minor code simplification

- - - - -
e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00
Handle HsExplicitListTy in renameer (fixes haskell/haddock#213)

- - - - -
c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00
Better error messages

- - - - -
14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00
Simplify RnM type

- - - - -
6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00
Simplify lookupRn

- - - - -
bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00
Organize unite tests hierarchically

- - - - -
2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00
Handle more cases in renameType

- - - - -
8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00
Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref

- - - - -
3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00
Add /tests/html-tests/output/ to .gitignore

- - - - -
db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00
Allow haddock markup in deprecation messages

- - - - -
e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00
If parsing of deprecation message fails, include it verbatim

- - - - -
242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00
Add description for PruneWithWarning test

- - - - -
43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00
Minor formatting change

- - - - -
22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00
Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220)

- - - - -
cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00
Add build artifacts for documentation to .gitignore

- - - - -
854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00
unit-tests: Improve readability

Add IsString instance for (Doc RdrName) + use <> instead of DocAppend.

- - - - -
c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00
unit-tests: Minor refactoring

Rename parse to parseParas.

- - - - -
04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00
Fix typo

- - - - -
3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00
Add description for DeprecatedReExport test

- - - - -
84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00
Move resources to /resources directory

- - - - -
a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00
Move HTML tests to directory /html-test/

- - - - -
e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00
Move HTML reference renderings to /html-test/ref/

- - - - -
3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00
Copy css, images, etc. on accept

- - - - -
40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00
Move unit tests to /test directory

- - - - -
99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00
Fix Setup.lhs

/usr/bin/runhaskell is not installed on all systems.

- - - - -
95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00
Make test management scripts more robust

 * They are now independent from the current directory, and hence can be
   called from everywhere

 * On UNIX/Linux they can now be run as scripts

- - - - -
027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00
Add 'dev' flag to cabal file, that builds without -O2

That way --disable-optimization can be used, which decreases build time
considerably.

- - - - -
e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00
Add test case for "spurious superclass constraints bug"

- - - - -
52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00
Adapt accept.lhs, so that it ignores more index files

- - - - -
53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00
Rename html-test/runtests.lhs to html-test/run.lhs

- - - - -
84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00
Move source files for HTML tests to html-test/src

- - - - -
a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00
Adapt output directory for HTML tests

- - - - -
d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00
Follow dopt->gopt rename

- - - - -
956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00
Update html-test/README

- - - - -
903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00
Use markdown for html-test/README

- - - - -
150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00
Follow changes in GHC: 'flags' has been renamed 'generalFlags'

- - - - -
41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00
Export missing types from Documentation.Haddock

- - - - -
9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00
Update dependencies

- - - - -
e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00
Bump version

- - - - -
e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00
Add missing test files to cabal file (fixes haskell/haddock#230)

- - - - -
ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00
Update CHANGES

- - - - -
51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00
Track changes in UNPACK pragma stuff

- - - - -
f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00
Implement overlapping type family instances.

An ordered, overlapping type family instance is introduced by 'type
instance
where', followed by equations. See the new section in the user manual
(7.7.2.2) for details. The canonical example is Boolean equality at the
type
level:

type family Equals (a :: k) (b :: k) :: Bool
type instance where
  Equals a a = True
  Equals a b = False

A branched family instance, such as this one, checks its equations in
order
and applies only the first the matches. As explained in the note
[Instance
checking within groups] in FamInstEnv.lhs, we must be careful not to
simplify,
say, (Equals Int b) to False, because b might later unify with Int.

This commit includes all of the commits on the overlapping-tyfams
branch. SPJ
requested that I combine all my commits over the past several months
into one
monolithic commit. The following GHC repos are affected: ghc, testsuite,
utils/haddock, libraries/template-haskell, and libraries/dph.

Here are some details for the interested:

- The definition of CoAxiom has been moved from TyCon.lhs to a
  new file CoAxiom.lhs. I made this decision because of the
  number of definitions necessary to support BranchList.

- BranchList is a GADT whose type tracks whether it is a
  singleton list or not-necessarily-a-singleton-list. The reason
  I introduced this type is to increase static checking of places
  where GHC code assumes that a FamInst or CoAxiom is indeed a
  singleton. This assumption takes place roughly 10 times
  throughout the code. I was worried that a future change to GHC
  would invalidate the assumption, and GHC might subtly fail to
  do the right thing. By explicitly labeling CoAxioms and
  FamInsts as being Unbranched (singleton) or
  Branched (not-necessarily-singleton), we make this assumption
  explicit and checkable. Furthermore, to enforce the accuracy of
  this label, the list of branches of a CoAxiom or FamInst is
  stored using a BranchList, whose constructors constrain its
  type index appropriately.

I think that the decision to use BranchList is probably the most
controversial decision I made from a code design point of view.
Although I provide conversions to/from ordinary lists, it is more
efficient to use the brList... functions provided in CoAxiom than
always to convert. The use of these functions does not wander far
from the core CoAxiom/FamInst logic.

BranchLists are motivated and explained in the note [Branched axioms] in
CoAxiom.lhs.

- The CoAxiom type has changed significantly. You can see the new
  type in CoAxiom.lhs. It uses a CoAxBranch type to track
  branches of the CoAxiom. Correspondingly various functions
  producing and consuming CoAxioms had to change, including the
  binary layout of interface files.

- To get branched axioms to work correctly, it is important to have a
  notion
  of type "apartness": two types are apart if they cannot unify, and no
  substitution of variables can ever get them to unify, even after type
family
  simplification. (This is different than the normal failure to unify
because
  of the type family bit.) This notion in encoded in tcApartTys, in
Unify.lhs.
  Because apartness is finer-grained than unification, the tcUnifyTys
now
  calls tcApartTys.

- CoreLinting axioms has been updated, both to reflect the new
  form of CoAxiom and to enforce the apartness rules of branch
  application. The formalization of the new rules is in
  docs/core-spec/core-spec.pdf.

- The FamInst type (in types/FamInstEnv.lhs) has changed
  significantly, paralleling the changes to CoAxiom. Of course,
  this forced minor changes in many files.

- There are several new Notes in FamInstEnv.lhs, including one
  discussing confluent overlap and why we're not doing it.

- lookupFamInstEnv, lookupFamInstEnvConflicts, and
  lookup_fam_inst_env' (the function that actually does the work)
  have all been more-or-less completely rewritten. There is a
  Note [lookup_fam_inst_env' implementation] describing the
  implementation. One of the changes that affects other files is
  to change the type of matches from a pair of (FamInst, [Type])
  to a new datatype (which now includes the index of the matching
  branch). This seemed a better design.

- The TySynInstD constructor in Template Haskell was updated to
  use the new datatype TySynEqn. I also bumped the TH version
  number, requiring changes to DPH cabal files. (That's why the
  DPH repo has an overlapping-tyfams branch.)

- As SPJ requested, I refactored some of the code in HsDecls:

 * splitting up TyDecl into SynDecl and DataDecl, correspondingly
   changing HsTyDefn to HsDataDefn (with only one constructor)

 * splitting FamInstD into TyFamInstD and DataFamInstD and
   splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl

 * making the ClsInstD take a ClsInstDecl, for parallelism with
   InstDecl's other constructors

 * changing constructor TyFamily into FamDecl

 * creating a FamilyDecl type that stores the details for a family
   declaration; this is useful because FamilyDecls can appear in classes
but
   other decls cannot

 * restricting the associated types and associated type defaults for a
 * class
   to be the new, more restrictive types

 * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts,
   according to the new types

 * perhaps one or two more that I'm overlooking

None of these changes has far-reaching implications.

- The user manual, section 7.7.2.2, is updated to describe the new type
  family
  instances.

- - - - -
f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00
Track changes in HsBang

- - - - -
ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00
Merge branch 'master' of http://darcs.haskell.org//haddock

- - - - -
f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00
Use InstEnv.instanceSig rather than instanceHead (name change)

- - - - -
88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00
Track change to HsBang type

- - - - -
e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00
Merge branch 'ghc-7.6' into ghc-7.6-merge-2

Conflicts:
	haddock.cabal
	src/Haddock/Interface/AttachInstances.hs
	src/Haddock/Interface/Create.hs
	src/Haddock/Interface/LexParseRn.hs
	src/Haddock/InterfaceFile.hs
	src/Haddock/Types.hs

Only GHC HEAD can compile this. GHC 7.6.x cannot compile this.

Some test fail.

- - - - -
62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00
Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.)

- - - - -
013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00
Refactoring instanceHead'.

- - - - -
3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00
Using new syntax in html-test/src/GADTRecords.hs.

- - - - -
626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00
Typo

- - - - -
1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00
Follow changes in base

- - - - -
3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00
Follow changes in GHC's build system

- - - - -
1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00
Follow changes in GHC build system

- - - - -
69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00
Use Alex 3's Unicode support to properly lex source files as UTF-8

Signed-off-by: David Waern <david.waern at gmail.com>

- - - - -
ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00
Adapt to tcRnGetInfo returning family instances too

This API change was part of the fix to Trac haskell/haddock#4175.  But it offers new
information to Haddock: the type-family instances, as well as the
class instances, of this type.

This patch just drops the new information on the floor, but there's an
open opportunity to use it in the information that Haddock displays.

- - - - -
971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00
Fix for haskell/haddock#7879.

Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory.

- - - - -
31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00
Use "cp -L" when making $(INPLACE_LIB)/latex too

- - - - -
e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00
Add -itest to .ghci

- - - - -
b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00
Workaround for a failing build with --enable-tests.

- - - - -
e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00
Fix broken test

- - - - -
0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00
Updates to reflect changes in HsDecls to support closed type families.

- - - - -
7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00
Fix failing test

- - - - -
53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00
Fix failing test

- - - - -
931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00
Remove (error "synifyKind") to use WithinType, to allow haddock to process base.

- - - - -
55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00
Changes to reflect changes in GHC's type HsTyVarBndr

- - - - -
b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00
Output Copright and License keys in Xhtml backend.

This information is as relevant in the documentation as it is in the
source files themselves.

Signed-off-by: David Waern <david.waern at gmail.com>

- - - - -
4c66028a by David Waern at 2013-08-04T15:27:36-07:00
Bump interface file version.

- - - - -
67340163 by David Waern at 2013-08-09T16:12:51-07:00
Update tests.

- - - - -
2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00
Add spec tests.

This adds tests for all elements we can create during regular
parsing. This also adds tests for text with unicode in it.

- - - - -
97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00
Fix ticket haskell/haddock#247.

I do the same thing that the XHTML backend does: give these no special
treatment and just act as if they are regular functions.

- - - - -
60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00
LaTeX tests setup

- - - - -
fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00
Fixes haskell/haddock#253

- - - - -
1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00
Use Hspec instead of nanospec

This is motivated by the fact that Haddock tests are not ran by the
GHC's ‘validate’ script so we're pretty liberal on dependencies in that
area. Full Hspec gives us some nice features such as Quickcheck integration.

- - - - -
8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00
Fix AMP warnings

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00
Update Git repo URL in `.cabal` file

- - - - -
16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00
Revision to reflect new role annotation syntax in GHC.

- - - - -
4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00
Add missing `traverse` method for `GenLocated`

As `Traversable` needs at least one of `traverse` or `sequenceA` to be
overridden.

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00
Add test helper

- - - - -
4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00
Fixes haskell/haddock#231

- - - - -
435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00
Fixes haskell/haddock#256

We inject -dynamic-too into flags before we run all our actions in the
GHC monad.

- - - - -
b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Add new field to DynFlags

- - - - -
49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00
Fallback to ./resources when Cabal data is not found

(so that themes are found during development)

- - - - -
bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Fixes haskell/haddock#5

- - - - -
e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00
Print missing documentation. Fixes haskell/haddock#258.

- - - - -
02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00
Don't consider StaticFlags when parsing arguments.

Instead, discard any static flags before parsing the command line using
GHC's DynFlags parser.

See http://ghc.haskell.org/trac/ghc/ticket/8276

Based off a patch from Simon Hengel.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00
Update HTML tests

- - - - -
f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00
Bump version

- - - - -
97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00
Track changes in HsSpliceTy data constructor

- - - - -
59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00
Adapt to small change in Pretty's exports

- - - - -
8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00
Some code simplification by using traverse

- - - - -
fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00
Fix warnings in test helper

- - - - -
6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Add ByteString version of Attoparsec

- - - - -
968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
One pass parser and tests.

We remove the HTML test as it is no longer necessary. We cover the
test case in spec tests and other HTML tests but keeping this around
fails: this is because the new parser has different semantics there.
In fact, I suspect the original behaviour was a bug that wasn't
caught/fixed but simply included as-is during the testing.

- - - - -
37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00
Rename Haddock.ParseSpec to Haddock.ParserSpec

- - - - -
f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00
Don't append newline to parseString input

We also check that we have parsed everything with endOfInput.

- - - - -
95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00
Fix totality, unicode, examples, paragraph parsing

Also simplify specs and parsers while we're at it. Some parsers were
made more generic.

This commit is a part of GHC pre-merge squash, email
fuuzetsu at fuuzetsu.co.uk if you need the full commit history.

- - - - -
7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00
Update acceptance tests

- - - - -
d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Support for bold.

Conflicts:
	src/Haddock/Backends/Hoogle.hs
	src/Haddock/Interface/Rename.hs
	src/Haddock/Parser.hs

- - - - -
4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Allow for headings inside function documentation.

LaTeX will treat the h3-h6 headings the same as we'd have to hack the
style file heavily otherwise and it would make the headings tiny
anyway.

Hoogle upstream said they will put in the functionality on their end.

Conflicts:
	src/Haddock/Interface/Rename.hs
	src/Haddock/Types.hs
	test/Haddock/ParserSpec.hs

- - - - -
fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00
Per-module extension flags and language listing.

Any extensions that are not enabled by a used language (Haskell2010
&c) will be shown. Furthermore, any implicitly enabled are also going
to be shown. While we could eliminate this either by using the GHC API
or a dirty hack, I opted not to: if a user doesn't want the implied
flags to show, they are recommended to use enable extensions more
carefully or individually. Perhaps this will encourage users to not
enable the most powerful flags needlessly. Enabled with show-extensions.

Conflicts:
	src/Haddock/InterfaceFile.hs

- - - - -
368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Bump interface version

There were some breaking changes over the last few patches so we bump
the interface version. This causes a big problem with testing:

1. To generate cross package docs, we first need to generate docs for
the package used.
2. To generate package docs with new interface version, we need to use
Haddock which has the version bumped.
3. To get Haddock with the version bump, we first need to test cross
package docs
4. GOTO 1

So the problem is the chicken and the egg problem. It seems that the
only solution would be to generate some interface files on the fly but
it is non-trivial.

To run this test, you'll have to:

* build Haddock without the test (make sure everything else passes)
* rebuild the packages used in the test with your shiny new binary
  making sure they are visible to Haddock
* remove the ‘_hidden’ suffix and re-run the tests

Note: because the packages currently used for this test are those
provided by GHC, it's probably non-trivial to just re-build them.
Preferably something less tedious to rebuild should be used and
something that is not subject to change.

- - - - -
124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Allow for nesting of paragraphs under lists.

The nesting rules are similar to Markdown's with the exception that we
can not simply indent the first line of a hard wrapped indented
paragraph and have it treated as if it was fully indented. The reason is
differences in markup as some of our constructs care about whitespace
while others just swallow everything up so it's just a lot easier to not
bother with it rather than making arbitrary rules.

Note that we now drop trailing for string entities inside of lists. They
weren't needed and it makes the output look uniform whether we use a
single or double newline between list elements.

Conflicts:
	src/Haddock/Parser.hs
	test/Haddock/ParserSpec.hs

- - - - -
c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Allow escaping in URLs and pictures.

Some tests were moved under parseString as they weren't about paragraph
level markup.

Conflicts:
	src/Haddock/Parser.hs
	test/Haddock/ParserSpec.hs

- - - - -
32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Update documentation.

- - - - -
fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00
Update maintainer

- - - - -
b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00
Fixes haskell/haddock#271

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00
Support for -XPatternSynonyms

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00
Update CPP check for __GLASGOW_HASKELL__

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00
<+>: Don't insert a space when concatenating empty nodes

- - - - -
a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00
Fix @ code blocks

In cases where we had some horizontal space before the closing ‘@’, the
parser would not accept the block as a code block and we'd get ugly
output.

- - - - -
0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00
Update tests

This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of
TypeHoles as an extension from GHC.

- - - - -
157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00
Handle infix vs prefix names correctly everywhere, by explicitly specifying the context

The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)"  or "`a`" and "+"

- - - - -
aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00
Correct whitespace in ‘hidden’ test for <+> change

- - - - -
121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00
Document module header.

Fixes Haddock Trac haskell/haddock#270.

- - - - -
e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00
Insert a space between module link and description

Fixes Haddock Trac haskell/haddock#277.

- - - - -
771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00
Ensure a space between type signature and ‘Source’

This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the
suggested fix _but_ it doesn't actually fix the reported issue. This
commit simply makes copying the full line a bit less of a pain.

- - - - -
8cda9eff by nand at 2014-02-11T15:48:30+00:00
Add support for type/data families

This adds support for type/data families with their respective
instances, as well as closed type families and associated type/data
families.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
3f22c510 by nand at 2014-02-11T15:53:50+00:00
Improve display of poly-kinded type operators

This now displays them as (==) k a b c ... to mirror GHC's behavior,
instead of the old (k == a) b c ... which was just wrong.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
effb2d6b by nand at 2014-02-11T15:56:50+00:00
Add test case for PatternSynonyms

This just tests various stuff including poly-kinded patterns and
operator patterns to make sure the rendering isn't broken.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00
Get rid of re-implementation of sortBy

I have no idea what this was doing lying around here, and due to the
usage of tuples it's actually slower, too.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00
Only warn about missing docs when docs are missing

This fixes the ‘Missing documentation for…’ message for modules with
100% coverage.

- - - - -
cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00
Add test case for inter-module type/data family instances

These should show up in every place where the class is visible, and
indeed they do right now.

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00
Use a bespoke data type to indicate fixity

This deals with what I imagine was an ancient TODO and makes it much
clearer what the argument actually does rather than having the user
chase down the comment.

- - - - -
5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00
Strip a single leading space from bird tracks (#201)

This makes bird tracks in the form

> foo
> bar
> bat

parse as if they had been written as

>foo
>bar
>bat

ie. without the leading whitespace in front of every line.

Ideally we also want to look into how leading whitespace affects code
blocks written using the @ @ syntax, which are currently unaffected by
this patch.

- - - - -
5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00
Turn a source code comment into specs

- - - - -
784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00
Update test case for lifted GADT type rendering

The parsing of these seems to have been fixed by GHC folk and it now
renders differently. IMHO it now renders in a better way so I'm updating
the test to reflect this.

- - - - -
c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00
Don't shadow ‘strip’.

-Wall complains

- - - - -
293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00
Make ImplicitParams render correctly (#260)

This introduces a new precedence level for single contexts (because
implicit param contexts always need parens around them, but other types
of contexts don't necessarily, even when alone)

- - - - -
4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00
Lower precedence of equality constraints

This drops them to the new precedence pREC_CTX, which makes single
eqaulity constraints show up as (a ~ b) => ty, in line with GHC's
rendering. Additional tests added to make sure other type operators
render as intended. Current behavior matches GHC

- - - - -
b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00
Add RankNTypes test case to ImplicitParams.hs

This test actually tests what haskell/haddock#260 originally reported - I omitted the
RankNTypes scenario from the original fix because I realized it's not
relevant to the underlying issue and indeed, this renders as intended
now. Still good to have more tests.

- - - - -
c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00
Fix rendering of Contents when links are present

Fixes Haddock Trac haskell/haddock#267.

- - - - -
9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00
Fix wording in the docs

- - - - -
4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00
Change rendering of duplicate record field docs

See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering
the documentation attached to the first instance of a duplicate field.

Perhaps we could improve this by rendering the first instance that has
documentation attached to it but for now, we'll stick with this.

- - - - -
ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00
Render fixity information

Affects functions, type synonyms, type families, class names, data type
names, constructors, data families, associated TFs/DFs, type synonyms,
pattern synonyms and everything else I could think of.

- - - - -
6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00
Reorder topDeclElem to move the source/wiki links to the top

They appear in the same position due to the float: right attribute but
now they're always at the top of the box instead of at the bottom.

- - - - -
2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00
Use optLast instead of listToMaybe for sourceUrls/wikiUrls

This lets you override them using eg. cabal haddock --haddock-options,
which can come in handy if you want to use a different layout or URL for
your source code links than cabal-install generates.

- - - - -
0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00
Differentiate between TH splices (line-links) and regular names

This adds a new type of source code link, to a specific line rather than
a specific declaration/name - this is used to link to the location of a
TH splice that defines a certain name.

Rather hefty changes throughout and still one unresolved issue (the line
URLs aren't parsed from the third form of --read-interface which means
they're currently restricted to same-interface links). Not sure if
this issue is really worth all the hassle, especially since we could
just use line links in general.

This commit also contains some cleanup/clarification of the types in
Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the
process. Notably, the Bool parameter was replaced by a Unicode type
synonym to help clarify its presence in type signatures.

- - - - -
66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00
Group similar fixities together

Identical fixities declared for the same line should now render using
syntax like: infix 4 <, >=, >, <=

- - - - -
6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00
Update changelog

- - - - -
7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00
Include fixity information in the Interface file

This resolves fixity information not appearing across package borders.

The binary file version has been increased accordingly.

- - - - -
ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00
Update changelog

- - - - -
565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00
Update appearance of fixity annotations

This moves them in-line with their corresponding lines, similar to a
presentation envision by @hvr and described in #ghc.

Redundant operator names are also omitted when no ambiguity is present.

- - - - -
5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00
Filter family instances of hidden types

Currently, this check does not extend to hidden right hand sides,
although it probably should hide them in that case.

- - - - -
ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00
Add documentation for --source-entity-line

- - - - -
0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00
Revert "Reorder topDeclElem to move the source/wiki links to the top"

This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d.

This change is no longer needed with the new rendering style, and it
messes with copy/pasting lines.

- - - - -
30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00
Bump version to 2.15.0

- - - - -
adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00
Fix up some whitespace

- - - - -
8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00
Hide RHS of TFs with non-exported right hand sides

Not sure what to do about data families yet, since technically it would
not make a lot of sense to display constructors that cannot be used by
the user.

- - - - -
5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00
Add UnicodeSyntax alternatives for * and ->

I could not find a cleaner way to do this other than checking for
string equality with the given built-in types. But seeing as it's
actually equivalent to string rewriting in GHC's implementation of
UnicodeSyntax, it's probably fitting.

- - - - -
b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00
Display minimal complete definitions for type classes

This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+.
I also cleaned up some of the places in which ExportDecl is used to make
adding fields easier in the future.

Lots of test cases have been updated since they now render with
minimality information.

- - - - -
a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00
Strip links from recently added html tests

These were accidentally left there when the tests were originally added

- - - - -
d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00
Update changelog

- - - - -
d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00
Always read in prologue files as UTF8 (#286).

- - - - -
54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00
Style only

- - - - -
fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00
Add Fuuzetsu maintainers field in cabal file

- - - - -
f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00
Hide minimal definition for only-method classes

Previously this was not covered by the All xs check since here it is not
actually an All, rather a single Var n.

This also adds the previously missing html-test/src/Minimal.hs.

- - - - -
0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00
Fix issue haskell/haddock#281

This is a regression from the data family instances change. Data
instances are now distinguished from regular lists by usage of the new
class "inst", and the style has been updated to only apply to those.

I've also updated the appropriate test case to test this a bit better,
including GADT instances with GADT-style records.

- - - - -
1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00
Please cabal sdist

- - - - -
75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00
Drop needless --split-objs which slows us down.

Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292.

- - - - -
31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00
Fix a few typos

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00
Print kind signatures on GADTs

- - - - -
2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00
Add default for new PlatformConstraints field

- - - - -
42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00
Drop leading whitespace in @-style blocks.

Fixes haskell/haddock#201.

- - - - -
98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00
Crash when exporting record selectors of data family instances

This fixes bug haskell/haddock#294.

This also fixes a related but never-before-mentioned bug about the
display of GADT record selectors with non-polymorphic type signatures.

Note: Associated data type constructors fail to show up if nothing is
exported that they could be attached to. Exporting any of the data types
in the instance head, or the class + data family itself, causes them to
show up, but in the absence of either of these, exporting just the
associated data type with the constructor itself will result in it
being hidden.

The only scenario I can come up that would involve this kind of
situation involved OverlappingInstances, and even then it can be
mitigated by just exporting the class itself, so I'm not going to solve
it since the logic would most likely be very complicated.

- - - - -
3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00
Make CHANGES consistent with what's now in 2.14.2

- - - - -
c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00
Actually bundle extra spec tests in sdist

- - - - -
bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00
Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188

The order of signature groups has been corrected upstream. Here we add a
test case and update some existing test-cases to reflect this change. We
remove grouped signature in test cases that we can (Minimal,
BugDeprecated &c) so that the test is as self-contained as possible.

- - - - -
708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00
Enforce strict GHC version in cabal file

This stops people with 7.6.3 trying to install 2.15.x which clearly
won't work. Unfortunately we shipped 2.14.x without realising this.

- - - - -
60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00
Initialise some new PlatformConstants fields

- - - - -
ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00
We don't actually want unicode here

- - - - -
0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00
Parse identifiers with ^ and ⋆ in them.

Fixes haskell/haddock#298.

- - - - -
e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00
Ignore version string during HTML tests.

- - - - -
de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00
Update CHANGES to follow 2.14.3

- - - - -
beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00
remove Origin flag from LHsBindsLR

- - - - -
cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00
Replace local `die` by new `System.Exit.die`

Starting with GHC 7.10, System.Exit exports the new `die`
which is essentially the same as Haddock.Util.die, so this
commit changes Haddock.Util.die to be a simple re-export
of System.Exit.die. See also

  https://ghc.haskell.org/trac/ghc/ticket/9016

for more details.

Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>

- - - - -
9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00
Disambiguate ‘die’ in test runners.

- - - - -
5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00
Prepare modules for parser split.

We have to generalise the Doc (now DocH) slightly to remove the
dependency on GHC-supplied type.

- - - - -
d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00
Move parser + parser tests out to own package.

We move some types out that are necessary as well and then
re-export and specialise them in the core Haddock.

Reason for moving out spec tests is that if we're working on the parser,
we can simply work on that and we can ignore the rest of Haddock. The
downside is that it's a little inconvenient if at the end of the day we
want to see that everything passes.

- - - - -
522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00
Move out Show and Eq instances to Types

They are much more useful to the users here.

- - - - -
11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00
Remove no longer necessary parser error handling.

We can now drop some Maybe tests and even lets us strip an error
handling monad away in a few places.

- - - - -
6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00
Please the GHC build-system.

As I can not figure out how to do this properly, if we're in GHC tree,
we treat the library as being the same package. If we're not in the
tree, we require that the library be installed separately.

- - - - -
7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00
Update issue tracker URL

- - - - -
f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00
Update issue tracker URL for haddock-library

- - - - -
66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00
Accomodate change in PatSyn representation

- - - - -
0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00
Revert "Accomodate change in PatSyn representation"

This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am
reverting this because I pushed it to master when it was meant to stay
on a wip-branch. Sorry Gergo and everyone who had trouble due to this.

- - - - -
e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00
Revert "Revert "Accomodate change in PatSyn representation""

This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295.

Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5
this was actually intended. Embarrasing for me.

- - - - -
5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00
Clear up highlighting of identifiers with ‘'’s.

- - - - -
d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00
Follow change in patSynSig

- - - - -
938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00
Slightly update the readme.

Style-sheets are no longer a recent thing, dead links, old maintainers,
different formats.

- - - - -
c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00
Update cabal files

Update repository urls, use subdir property for haddock-library and use
a separate versioning scheme for haddock-library in preparation for release.

- - - - -
a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00
Compatibility with older versions of base and bytestring

- - - - -
009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00
Enable travis-ci for haddock-library

- - - - -
9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00
haddock-library: Do not depend on haddock-library in test suite

I think you either add src to hs-source-dirs or the library to
build-depends.  But doing both does not make sense (AFAICT).

- - - - -
fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00
haddock-library: Use -Wall for specs

- - - - -
649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00
Use Travis with multiple GHC versions

When using HEAD, we build haddock-library directly from repository as a
dependency (and thanks to --enable-tests, the tests get ran anyway). In
all other cases, we manually run the tests on haddock-library only and
don't test the main project.

- - - - -
d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00
Comment improvements + few words in cabal file

- - - - -
0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00
Use doctest to check examples in documentation

- - - - -
2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00
Remove doctest dependency

(so that we can use haddock-library with doctest)

- - - - -
626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00
Travis tweaks

- - - - -
41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00
Don't actually forget to install specified GHC.

- - - - -
c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00
Removed reliance on LambdaCase (which breaks build with ghc 7.4).

- - - - -
b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00
Fixed haddock warnings.

- - - - -
a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00
Update Travis, bump version

- - - - -
864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00
Fix anchors. Closes haskell/haddock#308.

- - - - -
53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00
Drop DocParagraph from front of headers

I can not remember why they were wrapped in paragraphs to begin with and
it seems unnecessary now that I test it. Closes haskell/haddock#307.

- - - - -
29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00
Don't mangle append order for nested lists.

The benefit of this is that the ‘top-level’ element of such lists is
properly wrapped in <p> tags so any CSS working with these will be
applied properly. It also just makes more sense.

Pointed out at jgm/pandoc#1346.

- - - - -
05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00
Bump haddock-library to 1.1.0 for release

- - - - -
70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00
Propagate overloading-mode for instance declarations in haddock (#9242)

- - - - -
d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00
Adapt to new definition of HsDecls.TyFamEqn

This is a knock-on from the refactoring from Trac haskell/haddock#9063.
I'll push the corresponding changes to GHC shortly.

- - - - -
f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00
Track GHC PackageId to PackageKey renaming.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	src/Haddock/Interface/Create.hs

- - - - -
b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00
Track changes for module reexports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	src/Haddock/Interface/Create.hs

- - - - -
8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00
Catch mid-line URLs. Fixes haskell/haddock#314.

- - - - -
4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00
Track type signature change of lookupModuleInAllPackages

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00
If GhcProfiled, also build Haddock profiled.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00
Ignore TAGS files.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00
Update to attoparsec-0.12.1.1

There seems to be memory and speed improvement.

- - - - -
5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00
Fix forgotten src

- - - - -
3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00
Bump down the version for master to 2.14.4

- - - - -
dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00
Revert "Track type signature change of lookupModuleInAllPackages"

This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f.

- - - - -
3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00
Revert "Track changes for module reexports."

This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d.

- - - - -
56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00
Revert "Track GHC PackageId to PackageKey renaming."

This reverts commit 8ac42d3327473939c013551750425cac191ff0fd.

- - - - -
726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00
Revert "Adapt to new definition of HsDecls.TyFamEqn"

This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd.

- - - - -
61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00
Revert "Propagate overloading-mode for instance declarations in haddock (#9242)"

This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c.

- - - - -
a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00
Revert "Disambiguate ‘die’ in test runners."

This reverts commit dba02d6df32534aac5d257f2d28596238d248942.

- - - - -
f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00
Revert "Replace local `die` by new `System.Exit.die`"

This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5.

- - - - -
107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00
Merge branch 'reverts'

This reverts any changes that were made to have Haddock compile with
7.9. When 7.10 release comes, we can simply re-apply all the patches and
any patches that occur on ghc-head branch from now on.

This allows us to build master with 7.8.3

- - - - -
b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00
Fix haskell/haddock#313 by doing some list munging.

I get rid of the Monoid instance because we weren't satisfying the laws.
Convenience of having <> didn't outweigh the shock-factor of having it
behave badly.

- - - - -
e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00
Stop testing haskell/haddock#188.

Because the change is in GHC 7.9 and we now work against 7.8.3, this
test no longer makes sense. We revert it until 7.10 becomes the standard
version. If anything, there should be a test for this in GHC itself.

- - - - -
54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00
Add haskell/haddock#313 to CHANGES

- - - - -
9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00
Fix warning

- - - - -
ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00
Fix travis builds

- - - - -
384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00
Require GHC 7.8.3

- - - - -
d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00
Move Haddock API to a separate package

- - - - -
80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00
Bump version to 2.15.0 and add version constraints

- - - - -
309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00
Add deprecated compatibility module

- - - - -
4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00
export things to allow customizing how the Ghc session is run

- - - - -
47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00
ghc 7.8.2 compatibility

- - - - -
5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00
install dependencies for haddock-api on travis

- - - - -
9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00
Move sources under haddock-api/src

- - - - -
85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00
Remove compat stuff

- - - - -
151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00
Fix extra whitespace on signatures and update all test cases

This was long overdue, now running ./accept.lhs on a clean test from
master will not generate a bunch of changes.

- - - - -
d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00
Omit unnecessary foralls and fix haskell/haddock#315

This also fixes haskell/haddock#86.

- - - - -
bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00
Update CHANGES

- - - - -
fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00
Delete few unused/irrelevant/badly-place files.

- - - - -
3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00
Changes due to ghc api changes in package representation

Also fix a bug with finding the package name and version given a
module. This had become wrong due to the package key changes (it was
very hacky in the first place). We now look up the package key in the
package db to get the package info properly.

- - - - -
539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00
Import Data.Word w/o import-list

This is needed to keep the compilation warning free (and thus pass GHC's
./validate) regardless of whether Word is re-exported from Prelude or not

See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details

- - - - -
9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00
Bump version in doc

- - - - -
4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00
Bump haddock-library version

- - - - -
f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00
Remove references to deleted files

- - - - -
5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00
Make the doc parser not complain

- - - - -
2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00
CONTRIBUTING file for issues

- - - - -
88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00
Mention --print-missing-docs

- - - - -
42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00
Follow changes to TypeAnnot in GHC HEAD

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00
Fix import of 'empty' due to AMP.

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00
Bump `base` constraint for AMP

- - - - -
0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00
Delete stale ANNOUNCE

- - - - -
cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00
Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426)

- - - - -
4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00
Properly render package ID (not package key) in index, fixes haskell/haddock#329.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00
Disambiguate string-literals

GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem`
otherwise.

- - - - -
c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00
Revert "Followup changes to addition of -fwarn-context-quantification"

This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily
as the respective feature hasn't landed in GHC HEAD yet, but this commit
blocks later commits from being referenced in GHC HEAD.

- - - - -
38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00
Revert "Revert "Followup changes to addition of -fwarn-context-quantification""

This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc.
It's in HEAD now.

- - - - -
f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00
Revert "Fix import of 'empty' due to AMP."

This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since
it turns out we don't need to re-export `empty` from Control.Monad after
all.

- - - - -
467050f1 by David Feuer at 2014-10-09T20:07:36-04:00
Fix improper lazy IO use

Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results.
- - - - -
cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00
Fix use-after-close lazy IO bug

Make `getPrologue` force `parseParas dflags str` before returning. Without this,
it will attempt to read from the file after it is closed, with unspecified and
generally bad results.

Signed-off-by: David Feuer <David.Feuer at gmail.com>
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00
Add an .arcconfig file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00
Add .arclint file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00
Experimental support for collapsable headers

Closes haskell/haddock#335

- - - - -
849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00
Experimental support for collapsable headers

(cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc)

- - - - -
a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00
Collapse user-defined section by default (re haskell/haddock#335)

- - - - -
9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00
reflect ForeignType constructore removal

Reviewers: austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D358

- - - - -
c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00
Remove overlapping pattern match

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00
Remove -fobject-code from .ghci

(this slows down reloads on modifications)

- - - - -
d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00
Get rid of StandaloneDeriving

- - - - -
a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00
Derive more instances

- - - - -
8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00
Remove unused language extensions

- - - - -
3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00
Minor refactoring

- - - - -
4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00
parser: Try to parse definition lists right before text paragraphs

- - - - -
8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00
Add support for markdown links (closes haskell/haddock#336)

- - - - -
a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00
Allow markdown links at the beginning of a paragraph

- - - - -
53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00
Update documentation

- - - - -
652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00
Add support for markdown images

- - - - -
9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00
Allow an optional colon after the closing bracket of definition lists

This is to disambiguate them from markdown links and will be require
with a future release.

- - - - -
8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00
whitespace only

- - - - -
3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00
Fix re-exports of built-in type families

Fixes haskell/haddock#310

- - - - -
edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00
Turn some uses of error into recoverable warnings

This should at the very least not abort when something weird happens. It
does feel like we should have a type that carries these errors until the
end however as the user might not see them unless they are printed at
the end.

- - - - -
0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00
Fix warnings

- - - - -
d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00
Fix parsing of identifiers written in infix way

- - - - -
1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00
Minor code simplification

- - - - -
6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00
newtype-wrap parser monad

- - - - -
dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00
Make compatible with `deepseq-1.4.0.0`

...by not relying on the default method implementation of `rnf`

- - - - -
fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00
State intention rather than implementation details in Haddock comment

- - - - -
97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00
(wip) Add support for @since (closes haskell/haddock#26)

- - - - -
34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00
Update Haddock to new pattern synonym type signature syntax

- - - - -
304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00
Follow changes from haskell/haddock#9812

- - - - -
920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00
Changes to reflect refactoring in GHC as part of haskell/haddock#7484

- - - - -
0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00
Follow API changes in D426

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00
Support for PartialTypeSignatures

- - - - -
5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00
For pattern synonyms, render "pattern" as a keyword

- - - - -
fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00
List new module in cabal file

- - - - -
b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00
Allow the parser to spit out meta-info

Currently we only use it only for ‘since’ annotations but with these
patches it should be fairly simple to add new attributes if we wish to.

Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the
chance to do more exhaustive testing right now. The way the meta is
output (emphasis at the end of the whole comment) is fairly arbitrary
and subject to bikeshedding.

Note that this makes test for Bug310 fail due to interface version bump:
it can't find the docs for base with this interface version so it fails.
There is not much we can do to help this because it tests for ’built-in’
identifier, not something we can provide ourselves.

- - - - -
765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00
Update doctest parts of comments

- - - - -
8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00
header could contain several lines

Closes haskell/haddock#348

- - - - -
4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00
Revert "Merge branch 'reverts'"

This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing
changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06.

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00
Changes due to ghc api changes in package representation

Also fix a bug with finding the package name and version given a
module. This had become wrong due to the package key changes (it was
very hacky in the first place). We now look up the package key in the
package db to get the package info properly.

Conflicts:
	haddock-api/src/Haddock.hs

- - - - -
2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00
Import Data.Word w/o import-list

This is needed to keep the compilation warning free (and thus pass GHC's
./validate) regardless of whether Word is re-exported from Prelude or not

See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details

- - - - -
1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00
Follow changes to TypeAnnot in GHC HEAD

Signed-off-by: Austin Seipp <aseipp at pobox.com>

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00
Bump ‘base’ constraint

Follows the similar commit made on ghc-head branch

- - - - -
466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00
Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426)

- - - - -
97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00
Properly render package ID (not package key) in index, fixes haskell/haddock#329.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

Conflicts:
	haddock-api/src/Haddock/ModuleTree.hs

- - - - -
20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00
Disambiguate string-literals

GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem`
otherwise.

Conflicts:
	haddock-library/src/Documentation/Haddock/Parser.hs

- - - - -
b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00
Add an .arcconfig file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00
Add .arclint file.

Signed-off-by: Austin Seipp <austin at well-typed.com>

- - - - -
dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00
Collapse user-defined section by default (re haskell/haddock#335)

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs

- - - - -
f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00
reflect ForeignType constructore removal

Reviewers: austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D358

- - - - -
753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00
Remove overlapping pattern match

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00
Make compatible with `deepseq-1.4.0.0`

...by not relying on the default method implementation of `rnf`

- - - - -
d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00
Update Haddock to new pattern synonym type signature syntax

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs

- - - - -
1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00
Follow changes from haskell/haddock#9812

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00
Changes to reflect refactoring in GHC as part of haskell/haddock#7484

- - - - -
8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00
Follow API changes in D426

Signed-off-by: Austin Seipp <aseipp at pobox.com>

Conflicts:
	haddock-api/src/Haddock/Backends/LaTeX.hs
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs

- - - - -
95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00
Support for PartialTypeSignatures

Conflicts:
	haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
	haddock-api/src/Haddock/Convert.hs
	haddock-api/src/Haddock/Interface/Create.hs

- - - - -
45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00
For pattern synonyms, render "pattern" as a keyword

- - - - -
a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00
Various fixups and bumps for next release

- - - - -
22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00
Remove redundant wild-card pattern match

(this would otherwise cause a build-failure with `-Werror`)

- - - - -
1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00
Treat GHC 7.10 the same as GHC 7.9

...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway

- - - - -
f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00
Fixup ghc.mk (follow-up to 1739375eb23342)

This makes the GHC build-system aware of the data-files to be copied
into the bindist (as haddock.cabal doesn't list those anymore)

- - - - -
6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00
Only keep one Version instead of blindly appending

- - - - -
40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00
Fix dependency version

- - - - -
8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00
Print missing docs by default

Adds --no-print-missing-docs

- - - - -
59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00
update changelog

- - - - -
aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00
Update docs for @since

- - - - -
2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00
hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion

- - - - -
aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00
Add missing import for standalone haddock-api package

- - - - -
9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00
Reset ghc-head with master's tree

(this is an overwriting git merge of master into ghc-head)

- - - - -
fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00
Bump versions for ghc-7.11

- - - - -
525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00
travis-ci: test with HEAD

- - - - -
cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00
Eliminate instanceHead' in favour of GHC's instanceSig

This is made possible by the elimination of "silent superclass
parameters" in GHC

- - - - -
50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00
Make travis use 7.10.x

- - - - -
475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00
Turn the README into GitHub Markdown format.

Closes haskell/haddock#354

- - - - -
8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00
bump haddock-api ghc dependency to allow release candidate and first release

- - - - -
6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00
Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints

- - - - -
8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00
Track naming change in DataCon

- - - - -
23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00
Follow API changes in D538

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00
Ignore warnings, install Cabal 1.22

- - - - -
86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00
solve dataDir ambiguity

- - - - -
5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00
support GHC 7.10: no Safe-Inferred, Foldable instance

- - - - -
6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00
Update test files

Test: a correct behaviour for fields comma-separating values. I'm
surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders
now but I doubt.

Operators: Seems GHC is giving us a new order for operators, something
must have changed on their side again. cc @haasn , this makes the fixity
to the side not match the order on the LHS which is a bit unpleasant.
Maybe the fixity can be made to match the GHC order?

Bug335: We expand examples by default now.

Bug310: Now inferred safe.

- - - - -
708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00
Links to source location of class instance definitions

- - - - -
5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00
Filter '\r' from comments due to Windows problems.

On Windows this was causing newline to be rendered twice in code blocks.
Closes haskell/haddock#359, fixes haskell/haddock#356.

- - - - -
1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00
Changelog only

- - - - -
c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00
--package-name and --package-version flags

Used for --hoogle amongst other things. Now we need to teach cabal to
use it. The situation is still a bit sub-par because if the flags aren't
passed in, the crash will occur. Closes haskell/haddock#353.

- - - - -
14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00
Sort out some module import warnings

- - - - -
d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00
Track naming change in DataCon

(cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b)

- - - - -
d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00
Follow API changes in D538

Signed-off-by: Austin Seipp <aseipp at pobox.com>
(cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6)

- - - - -
4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00
Track changes in HsSyn for quasi-quotes

- - - - -
775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00
--package-name and --package-version flags

Used for --hoogle amongst other things. Now we need to teach cabal to
use it. The situation is still a bit sub-par because if the flags aren't
passed in, the crash will occur. Closes haskell/haddock#353.

(cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4)

- - - - -
f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00
Prevent Synopsis from using up too much horizontal space

When long type signatures occur in the Synopsis, the element is
stretched beyond the width of the window.  Scrollbars don't appear, so
it's impossible to read anything when this happens.

- - - - -
cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00
Update changelog

Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc

- - - - -
b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00
Make the error encountered when a package can't be found more
user-friendly

Closes haskell/haddock#369

- - - - -
b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00
Remove now redundant imports

- - - - -
5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00
Update test to account for \r filtering

- - - - -
6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00
Test for anchor defaulting

I delete the old tests because it turns out that:

* test runner would never put them in scope of each other even with
  imports so just one would suffice
* test runner actually needed some hacking to keep links so in the end
  we would end up with no anchors making them useless

- - - - -
1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00
Clearly default to variables in out of scope case

- - - - -
7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00
Fix Hoogle display of constructors

Fixes haskell/haddock#361

- - - - -
6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00
Fully qualify names in Hoogle instances output

Closes haskell/haddock#263

- - - - -
52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00
Update changelog

- - - - -
ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00
Output method documentation in Hoogle backend

One thing of note is that we no longer preserve grouping of methods and
print each method on its own line. We could preserve it if no
documentation is present for any methods in the group if someone asks
for it though.

Fixes haskell/haddock#259

- - - - -
a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00
Don't print instance safety information in Hoogle

Fixes haskell/haddock#168

- - - - -
df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00
Post-release version bumps and changelog

- - - - -
dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00
Loosen bounds on haddock-*

- - - - -
de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00
Expand response files in arguments

Closes haskell/haddock#285

- - - - -
1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00
Do not insert anchor for section headings in contents box

- - - - -
860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00
Track change in API of TyCon

- - - - -
a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00
Track API changes to support empty closed type familes

- - - - -
77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00
Ignore doc/haddock.{ps,pdf}

- - - - -
663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00
Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385

Signed-off-by: Austin Seipp <aseipp at pobox.com>

- - - - -
8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00
Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385

Signed-off-by: Austin Seipp <aseipp at pobox.com>
(cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899)

- - - - -
bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00
haddock-library: require GHC >= 7.4

`Data.Monoid.<>` was added in base-4.5/GHC-7.4

Closes haskell/haddock#394

Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>

- - - - -
daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00
Track the new location of setRdrNameSpace

- - - - -
1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00
ApiAnnotations : strings in warnings do not return SourceText

The strings used in a WARNING pragma are captured via

strings :: { Located ([AddAnn],[Located FastString]) }
    : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) }
..

The STRING token has a method getSTRINGs that returns the original
source text for a string.

A warning of the form

{-# WARNING Logic
          , mkSolver
          , mkSimpleSolver
          , mkSolverForLogic
          , solverSetParams
          , solverPush
          , solverPop
          , solverReset
          , solverGetNumScopes
          , solverAssertCnstr
          , solverAssertAndTrack
          , solverCheck
          , solverCheckAndGetModel
          , solverGetReasonUnknown
          "New Z3 API support is still incomplete and fragile: \
          \you may experience segmentation faults!"
  #-}

returns the concatenated warning string rather than the original source.

- - - - -
ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00
Create simple method for indentation parsing.
- - - - -
7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00
Make nested lists count indentation according to first item.
- - - - -
d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00
Add simple test case for arbitrary-depth list nesting.
- - - - -
2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00
Add arbitrary-indent spec test for parser.
- - - - -
9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00
Update docs with info on new list nesting rule

Fixes haskell/haddock#278 through commits from PR haskell/haddock#401

- - - - -
12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00
Update some meta data at the top of the docs

- - - - -
765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00
Add some Hacking docs for getting started

- - - - -
19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00
Fix markdown

- - - - -
2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00
Refine hacking instructions slightly

- - - - -
0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00
Update after wild card renaming refactoring in D613

Summary:
* Move `Post*` type instances to `Haddock.Types` as other modules than
  `Haddock.Interface.Rename` will rely on these type instances.
* Update after wild card renaming refactoring in D613.

Reviewers: simonpj, austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D954

GHC Trac Issues: haskell/haddock#10098

- - - - -
10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00
Build executable with '-threaded' (fixes haskell/haddock#399)

- - - - -
7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00
Update changelog for -threaded

Closes haskell/haddock#400

- - - - -
d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00
Fix haddock: internal error: spliceURL UnhelpfulSpan (#207)

Inferred type signatures don't have SrcSpans, so let's use the one from
the declaration.

I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at
trying to run the test-suite.

- - - - -
b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00
Changelog for haskell/haddock#207

Fixes haskell/haddock#207, closes haskell/haddock#402

- - - - -
841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00
Attach to instance location the name that has the same location file

Fixes haskell/haddock#383

- - - - -
98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00
Update changelog

Closes haskell/haddock#398

- - - - -
7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00
Fix alignment of Source links in instance table in Firefox

Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the
parent element with 'float: right' on the inner element can cause the
floated element to be displaced downwards for no apparent reason.

To work around this, the left side is wrapped in its own <span> and set
to 'float: left'.  As a precautionary measure to prevent the parent
element from collapsing entirely, we also add the classic "clearfix"
hack.  The latter is not strictly needed but it helps prevent bugs if
the layout is altered again in the future.

Fixes haskell/haddock#384.

Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to
        prevent confusion over the operator precedence of (<+>) vs (<<).

[1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725

- - - - -
cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00
Update tests for the CSS changes

- - - - -
2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create scaffolding for Haskell source parser module.

- - - - -
29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement function for tagging parsed chunks with source spans.
- - - - -
6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement simple string chunking based on HsColour library.
- - - - -
6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create basic token classification method.
- - - - -
da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Adapt source span tagging to work with current whitespace handling.
- - - - -
4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add record accessors to exports of hyperlinker parser module.
- - - - -
a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Make parser module export all types and associated accessors.
- - - - -
fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create simple HTML renderer for parsed source file.
- - - - -
80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for specifying the CSS file path in HTML source renderer.
- - - - -
994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix identifier recognition in Haskell source parser.
- - - - -
b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix comment recognition in Haskell source parser.
- - - - -
11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for recognizing compiler pragmas in source parser.
- - - - -
736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create scaffolding of module for associating tokens with AST names.

- - - - -
7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement utility method for extracting variable identifiers from AST.

- - - - -
32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Create simple mechanism for associating tokens with AST names.

- - - - -
d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add dummy support for hyperlinking named tokens.
- - - - -
2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix span matcher bug causing wrong items being hyperlinked.
- - - - -
2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Constrain elements exported by hyperlinker modules.
- - - - -
9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for type token recognition.
- - - - -
8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Add support for binding token recognition.
- - - - -
d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement go-to-definition mechanism for local bindings.
- - - - -
f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Implement module export- and import-list item hyperlinking.
- - - - -
c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix span matching to allow parenthesized operators hyperlinking.
- - - - -
03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00
Fix weird hyperlinking of parenthesized operators.
- - - - -
b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for type declaration anchors.
- - - - -
7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for top-level function declaration anchors.
- - - - -
dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix external anchors to contain HTML file extension.
- - - - -
a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Refactor the way AST names are handled within detailed tokens.
- - - - -
c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement hyperlinking of imported module names.
- - - - -
2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix parsing of single line comments with broken up newlines.
- - - - -
11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix bug with improper newline handling.
- - - - -
8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix issues with escaped newlines in comments.
- - - - -
34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for parsing C preprocessor macros.
- - - - -
09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add some documentation for parser module of source hyperlinker.
- - - - -
709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add some documentation for AST module of source hyperlinker.
- - - - -
4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add command line option for generating hyperlinked source.
- - - - -
7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Extend module interface with rich source token stream field.
- - - - -
494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement source tokenization during interface creation process.
- - - - -
5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Create hyperlinker module and plug it into the Haddock pipeline.
- - - - -
0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for providing custom CSS files for hyperlinked source.
- - - - -
a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add support for fancy highlighting upon hovering over identifier.
- - - - -
d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make source hyperlinker generate output in apropriate directory.
- - - - -
ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Create module with hyperlinker utility functions.
- - - - -
6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make external hyperlinks point to locations specified by source URLs.
- - - - -
8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Rewrite source generation to fixed links and directory structure.
- - - - -
ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Add basic support for cross-package hyperlink generation.
- - - - -
7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Disable generating hyperlinks for module references.
- - - - -
a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make Haddock generate source for all interfaces (also hidden ones).
- - - - -
f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Prevent source parser from throwing exception when lexing fails.
- - - - -
db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Implement workaround for Chrome highlighting issues.
- - - - -
0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make hyperlinker generate correct anchors for data constructors.
- - - - -
c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Make hyperlinker generate anchors for record field declarations.
- - - - -
063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00
Fix issue with hyperlink highlight styling in Chrome browser.
- - - - -
880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking constructor names in patters.
- - - - -
c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking field names in record patterns.
- - - - -
17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add support for hyperlinking field names in record expressions.
- - - - -
0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Make hyperlinker respect pretty-printer flag and add documentation.
- - - - -
f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Unexpose hyperlinker modules in Cabal configuration.
- - - - -
4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Setup HSpec framework for Haddock API package.
- - - - -
4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add basic tests related to comment parsing.
- - - - -
6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add tests related to parsing basic language constructs.

- - - - -
87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add simple tests for do-notation parsing.

- - - - -
e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add very simple QuickCheck properties for source parser spec.
- - - - -
c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Create simple test runner for hyperlinker tests.
- - - - -
76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for basic identifier hyperlinking.
- - - - -
0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for operator hyperlinking.
- - - - -
731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for constructor hyperlinking.
- - - - -
995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for record expressions and patterns hyperlinking.
- - - - -
3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00
Add test case for literal syntax highlighting.
- - - - -
68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Add hyperlinker test runner to .cabal and .gitignore files. 
- - - - -
aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Adapt hyperlinker test runner to have the same interface as HTML one.
- - - - -
ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Fix hyperlinker test runner file paths and add pretty-printing option.
- - - - -
0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00
Add reference files for hyperlinker test cases.
- - - - -
efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00
Make hyperlinker test runner strip local links from generated source.
- - - - -
3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00
Create simple script for accepting hyperlinker test case references.
- - - - -
526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00
Re-accept hyperlinker test cases with local references stripped out.
- - - - -
892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00
Fix bug with diffing wrong files in hyperlinker test runner.
- - - - -
9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00
Remove unused dependencies in Haddock API spec configuration.
- - - - -
47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00
Add support for hyperlinking synonyms in patterns.
- - - - -
a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00
Create test case for hyperlinking @-patterns.
- - - - -
c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00
Add support for hyperlinking universally quantified type variables.
- - - - -
68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00
Create hyperlinker test case with quantified type variables.
- - - - -
51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00
Add scoped type variables test for polymorphism test case.
- - - - -
13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00
Add record wildcards test for records hyperlinking test case.
- - - - -
991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00
Document some functions in XHTML utlity module.
- - - - -
98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00
Make hyperlinker render qualified names as one entity.
- - - - -
75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00
Add qualified name test for identifiers hyperlinking test case.
- - - - -
de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00
Fix crash happening when hyperlinking type family declarations.
- - - - -
7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00
Add support for anchoring data family constructor declarations.
- - - - -
3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00
Improve support for hyperlinking type families.
- - - - -
59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00
Add hyperlinker test case for checking type and type family declarations.
- - - - -
d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00
Fix issue with operators being recognized as preprocessor directives.
- - - - -
da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00
Fix broken tests for parsing and hyperlinking hash operators.
- - - - -
53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00
Add support for anchoring signatures in type class declarations.
- - - - -
1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00
Make hyperlinker generate anchors only to top-level value bindings.
- - - - -
a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00
Create hyperlinker test case for type classes.
- - - - -
b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00
Update docs with information about source hyperlinking.
- - - - -
9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00
Update docs on using `--read-interface` option.
- - - - -
9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00
Remove potentially dangerous record access in hyperlinker AST module.
- - - - -
fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00
Make Haddock generate warnings about potential misuse of hyperlinker.
- - - - -
a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00
Fix incorrect specification of source style option in doc file.
- - - - -
3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00
Refactor source path mapping to use modules as indices.
- - - - -
ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00
Fix bug where not all module interfaces were added to source mapping.
- - - - -
f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00
Extract main hyperlinker types to separate module.
- - - - -
43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00
Move source paths types to hyperlinker types module.
- - - - -
3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00
Add support for hyperlinking modules in import lists.
- - - - -
58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00
Add short documentation for hyperlinker source map type.
- - - - -
14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00
Fix bug with module name being hyperlinked to `Prelude`.
- - - - -
8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00
Fix problem with spec build in Haddock API configuration.
- - - - -
e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00
StrictData: print correct strictness marks

- - - - -
e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00
Update changelog

- - - - -
0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00
Relax upper bound on GHC a bit

- - - - -
7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00
Delete trailing whitespace

- - - - -
50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00
StrictData: changes in HsBang type

- - - - -
83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00
Fix expansion icon for user-collapsible sections

Closes haskell/haddock#412

- - - - -
b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00
Make some version changes after 2.16.1 release

- - - - -
a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00
Merge pull request haskell/haddock#422 from adamse/adamse-D1033

Merge for GHC D1033
- - - - -
c0173f17 by randen at 2015-07-30T14:49:08-07:00
Break the response file by line termination rather
than spaces, since spaces may be within the parameters.
This simple approach avoids having the need for any
quoting and/or escaping (although a newline char will
not be possible in a parameter and has no escape
mechanism to allow it).

- - - - -
47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00
Replace (SourceText,FastString) with WithSourceText data type

Phab:D907 introduced SourceText for a number of data types, by replacing
FastString with (SourceText,FastString). Since this has an Outputable
instance, no warnings are generated when ppr is called on it, but
unexpected output is generated. See Phab:D1096 for an example of this.

Replace the (SourceText,FastString) tuples with a new data type

data WithSourceText = WithSourceText SourceText FastString

Trac ticket: haskell/haddock#10692

- - - - -
45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00
Update changelog

- - - - -
347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00
Avoid JavaScript error during page load in non-frame mode

In non-frame mode, parent.window.synopsis refers to the synopsis div
rather than the nonexistent frame.  Unfortunately, the script wrongly
assumes that if it exists it must be a frame, leading to an error where
it tries to access the nonexistent attribute 'replace' of an undefined
value (synopsis.location).

Closes haskell/haddock#406

- - - - -
54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00
Link to the definitions to themselves

Currently, the definitions already have an anchor tag that allows URLs
with fragment identifiers to locate them, but it is rather inconvenient
to obtain such a URL (so-called "permalink") as it would require finding
the a link to the corresponding item in the Synopsis or elsewhere.  This
commit adds hyperlinks to the definitions themselves, allowing users to
obtain links to them easily.

To preserve the original aesthetics of the definitions, we alter the
color of the link so as to be identical to what it was, except it now
has a hover effect indicating that it is clickable.

Additionally, the anchor now uses the 'id' attribute instead of the
(obsolete) 'name' attribute.

Closes haskell/haddock#407

- - - - -
02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00
Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis

Closes haskell/haddock#408

- - - - -
2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00
Fix record field alignment when name is too long

Change <dl> to <ul> and use display:table rather than floats to layout
the record fields.  This avoids bug haskell/haddock#301 that occurs whenever the field
name gets too long.

Slight aesthetic change: the entire cell of the field's source code is
now shaded gray rather than just the area where text exists.

Fixes haskell/haddock#301. Closes haskell/haddock#421

- - - - -
7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00
Add some utility definitions for generating line anchors.

- - - - -
e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Make hyperlinked source renderer generate line anchors.
- - - - -
24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Re-accept test cases after adding line anchors for each of them.
- - - - -
0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00
Override source line flags when source hyperlinker is enabled.
- - - - -
a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00
Update tests to follow HTML changes

- - - - -
d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00
Fix quote syntax for promoted types.
- - - - -
668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00
Apply promoted type quoting to type-level consing.
- - - - -
89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00
Extend advanced types test case with other examples.
- - - - -
86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00
Rename advanced types test case and accept new output.
- - - - -
dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00
HsBang is split into HsSrcBang and HsImplBang

With recent changes in GHC handling of strictness annotations in Haddock
is simplified.

- - - - -
2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00
Merge pull request haskell/haddock#433 from adamse/split-hsbang

HsBang is split into HsSrcBang and HsImplBang
- - - - -
891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00
Follow changes in GHC build system

- - - - -
b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00
Make Travis use 7.10.2

- - - - -
97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Move SYB utilities to standalone module.
- - - - -
748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Implement `everywhere` transformation in SYB module.
- - - - -
011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Implement generic transformation constructor.
- - - - -
b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Create simple utility module for type specialization.
- - - - -
43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Make type of type specialization function more general.
- - - - -
fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00
Add basic HTML test case for checking instance specialization.
- - - - -
6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Make HTML class instance printer take optional signature argument.
- - - - -
65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Refactor instance head type to record instead of a meaningless tuple.
- - - - -
3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Add expandable method section for each class instance declaration.
- - - - -
99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Move dummy post-family instances for `DocName` to `Types` module.
- - - - -
e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create convenience functions for type specialization module.
- - - - -
b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Hook type specialization logic with HTML pretty-printer.
- - - - -
dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create stub functions for sugaring specialized types.
- - - - -
fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement list syntax sugaring logic for specialized types.
- - - - -
e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement tuple syntax sugaring logic for specialized types.
- - - - -
68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Get rid of code duplication in type specialization module.
- - - - -
4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create scaffolding of a framework for renaming specialized types.
- - - - -
271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fill in missing cases in specialized type renaming function.
- - - - -
bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Remove code duplication in specialized type renamer.
- - - - -
ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Change state of the type renaming monad.
- - - - -
77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Implement simple mechanism for generating new type names.
- - - - -
91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fill in stub behaviour with actual environment renaming.
- - - - -
d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fix logic behind binder type renaming.
- - - - -
f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Add SYB-like utility function for performing stateful queries.
- - - - -
eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Create function for retrieving free variables from given type.
- - - - -
a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00
Fix compilation error caused by incorrect type signature.
- - - - -
8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Move `SetName` class definition to types module.
- - - - -
5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Hook type renamer with instance method HTML pretty-printer.
- - - - -
6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add some test cases for type renamer.
- - - - -
839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make specialized signatures refer to original signature declaration.
- - - - -
4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make specialized methods be nicely formatted again.
- - - - -
ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Attach source locations to the specialized class methods.
- - - - -
43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Extend instances test case to also test multi-name type signatures.
- - - - -
59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix tab-based indentation in instances test case.
- - - - -
c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Improve placement of instance methods expander button.
- - - - -
0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add new data type declaration to instance specialization test case. 
- - - - -
5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Make type renamer first try single-letter names as  alternatives.
- - - - -
7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix type renamer bug with incorrect names being generated.
- - - - -
0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Add some documentation and refactor type specialization module.
- - - - -
da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix another bug where type renamer was generating incorrect names.
- - - - -
cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Refactor type renamer to rebinding and pure renaming phases.
- - - - -
850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00
Fix unwitting compilation bug.
- - - - -
e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Integrate instance specification type into class instance definition.
- - - - -
825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Get rid of no longer neccessary instance specification type.
- - - - -
cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix declaration converter to use more appropriate mode for methods.
- - - - -
bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix bug with types not being specialized at all.
- - - - -
5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix bug where instance expander was opening wrong section.
- - - - -
6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix another type renamer bug where not all names were rebound.
- - - - -
5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Fix yet another renamer bug where some names were not unique.
- - - - -
8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Split instance subsection layout method to top-level declarations.
- - - - -
e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Rearrange layout of instance methods in generated documentation.
- - - - -
a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Get rid of no longer used layout method.
- - - - -
2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Attach section title to the instance methods block.
- - - - -
7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Add basic tests for associated types in instances test case.
- - - - -
db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Attach associated types information to instance header.
- - - - -
71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Make instance details section contain associated types information.
- - - - -
deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Improve look of rendered associated families in instance details.
- - - - -
839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Introduce alternative type for family declarations.
- - - - -
d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Make instance details record use new type for family declarations.
- - - - -
2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Split printer of type family header to separate functions.
- - - - -
c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00
Implement HTML renderer for pseudo-family declarations.
- - - - -
c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Apply type specializer to associated type family declarations. 
- - - - -
2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Create helper method for specializing type signatures.
- - - - -
475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Refactor specializer module to be independent from XHTML backend.
- - - - -
f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add some documentation for instance head specializer.
- - - - -
a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix bug with missing space in documentation for associated types.
- - - - -
50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix issue with incorrect instance details sections being expanded.
- - - - -
e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Accept tests affected by adding instance details section.
- - - - -
75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Make section identifier of instance details more GHC-independent.
- - - - -
add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Re-accept tests after applying deterministic section identifiers.
- - - - -
878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Make identifier generation also architecture-independent.
- - - - -
48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Fix issue with instance expander hijacking type hyperlink click.
- - - - -
47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Get rid of dreadful hashing function for generating identifiers.
- - - - -
956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Move `InstOrigin` type declaration to more appropriate module.
- - - - -
bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Accept tests affected by changes related to instance expander.
- - - - -
8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add examples with type operators to the instances test case.
- - - - -
64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00
Add basic support for sugaring infix type operators.
- - - - -
747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00
Add support for sugaring built-in function syntax.
- - - - -
d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Remove default methods from Hoogle class output.
- - - - -
bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Add fixity declarations in Hoogle backend output.
- - - - -
90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Fix bug with incorrect fixities being generated in Hoogle backend.
- - - - -
48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Improve class type family declarations output in Hoogle backend.
- - - - -
661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Add missing default family equations in Hoogle output.
- - - - -
e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Improve formatting of class details output in Hoogle backend.
- - - - -
490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00
Fix weird-looking Hoogle output for familyless classes.
- - - - -
ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Create script file for new HTML test runner.
- - - - -
609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Set default behaviour if no arguments given.
- - - - -
dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add support for providing optional arguments for test runner.
- - - - -
d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Improve output of test runner error messages.
- - - - -
0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add support for executing Haddock process in test runner.
- - - - -
4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Add GHC path to test runner configuration.
- - - - -
d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make GHC path a test runner command-line argument.
- - - - -
c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Extend test runner configuration with Haddock arguments.
- - - - -
fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Refactor test runner and create stub functions.
- - - - -
ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make test runner actually run Haddock executable.
- - - - -
391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Fix bug with test runner not producing any output files.
- - - - -
81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Setup skeleton of framework for running tests.
- - - - -
f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Fix bug with modules not being found in global search mode.
- - - - -
7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make Haddock standard output redirection be more configurable.
- - - - -
53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Incorporate old, ugly functions for comparing output files.
- - - - -
8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Refactor architecture of test runner output checking functions.
- - - - -
587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Implement actual diffing mechanism.
- - - - -
9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Improve code style to match popular guidelines.
- - - - -
14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Make it possible to choose alternative diff tool.
- - - - -
5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Create stub methods for processing test output as XML documents.
- - - - -
7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00
Implement link-stripping logic as simple SYB transformation.
- - - - -
8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Incorporate link stripping to output diffing mechanism.
- - - - -
37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement footer-stripping logic.
- - - - -
9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Add missing dependencies in Cabal configuration file.
- - - - -
e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix issue with output being printed in incorrect order.
- - - - -
0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make it possible to run tests without generating diff.
- - - - -
76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Refactor HTML test suite boilerplate to external package.
- - - - -
af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create utilities for storing directory configuration.
- - - - -
d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Move IO-dependent config of HTML test suite to test package.
- - - - -
17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Enable all compiler warnings in Haddock test package configuration.
- - - - -
9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Move Haddock runner of HTML test suite to Haddock test package.
- - - - -
4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make Haddock test package more generic.
- - - - -
03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create convenience wrappers to simplify in test entry points.
- - - - -
27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adjust module visibility and items they export.
- - - - -
c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Remove no longer useful test option.
- - - - -
55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Change extension of test files used for diffing.
- - - - -
136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Refactor and simplify XHTML helper module of test package.
- - - - -
69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix typo in link stripper of HTML test suite runner.
- - - - -
0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create convenience script for running specific HTML tests.
- - - - -
489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement utility functions for conditional link stripping.
- - - - -
0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adapt `hypsrc-test` module to work with new testing framework.
- - - - -
927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Implement output accepting mechanism in test package.
- - - - -
8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Create utility function for recursive obtaining directory contents.
- - - - -
cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make Haddock test package more generic.
- - - - -
019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix path handling in test runner.
- - - - -
399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Make it possible to specify ignored files for test output.
- - - - -
41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Adapt HTML test runner to use new ignoring functionality.
- - - - -
e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Fix bug with not all test output files being checked.
- - - - -
b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00
Specify ignored files for hyperlinker source test runner.
- - - - -
3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Copy test runner script for hyperlinked source case.
- - - - -
d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with test runner invoking Haddock in incorrect mode.
- - - - -
f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix path handling in test module loader.
- - - - -
10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Make test runner ignore test packages with no modules.
- - - - -
5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create test runner entry points for LaTeX test suite.
- - - - -
58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with unnecessary checking old test output.
- - - - -
c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Re-implement test acceptance functionality.
- - - - -
13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix warning about no longer needed definition.
- - - - -
958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Adapt Cabal configuration to execute LaTeX suite with new runner.
- - - - -
550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Setup test suite for Hoogle backend.
- - - - -
3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Make Hoogle backend create output directory if needed.
- - - - -
eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Add appropriate .gitignore entry and configure Hoogle test suite.
- - - - -
a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Fix bug with test runner failing when run on multiple test packages.
- - - - -
bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create simple test cases for Hoogle backend.
- - - - -
6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Create helper function for conversion between XML and XHTML.
- - - - -
cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Refactor existing code to use XHTML printer instead of XML one.
- - - - -
e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00
Improve portability of test runner scripts.
- - - - -
9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00
Remove redundant import statement.
- - - - -
55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00
Fix bug with accepting to non-existing directory.
- - - - -
00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00
Accept output for Hoogle and LaTeX backends.
- - - - -
29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00
Get rid of obsolete testing utilities.
- - - - -
bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00
Update sandbox setup guide to work with Haddock test package.
- - - - -
cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00
Make Travis aware of Haddock test package.
- - - - -
74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00
Fix test suite failure when used with Stack.
- - - - -
18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00
Add sample Stack setup to the hacking guide.

- - - - -
22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00
Fix Markdown formatting of README file.
- - - - -
b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00
Setup Haddock executable path in Travis configuration.
- - - - -
5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00
account for changes to ipClass

- - - - -
f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00
Merge pull request haskell/haddock#443 from bgamari/ghc-head

account for changes to ipClass
- - - - -
a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00
Follow changes from haskell/haddock#6018

- - - - -
2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00
React to refactoring CoAxiom branch lists.

- - - - -
ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00
Track msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00
Create Process: removed PhaseFailed

- - - - -
7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00
Generate docs for orphan instances

- - - - -
32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00
Have source links for orphan instances

- - - - -
c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00
Print orphan instances header only if required

- - - - -
ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00
Add orphan instances link to contents box

- - - - -
d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00
Fix orphan instance collapsing

- - - - -
25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00
Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive

Remove PhaseFailed
- - - - -
1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00
s/PackageKey/UnitId/g and s/packageKey/unitId/g

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00
Roughly fix up haddock for DuplicateRecordFields changes

This compiles, but will probably need more work to produce good
documentation when the DuplicateRecordFields extension is used.

- - - - -
60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00
Track wip/spj-wildcard-refactor on main repo

- - - - -
4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00
Track change to PatSyn.patSynSig

- - - - -
25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00
Follow changes to HsTYpe

Not yet complete (but on a wip/ branch)

- - - - -
693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00
Account for Typeable changes

The treatment of type families changed.

- - - - -
cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00
Work on updating Haddock to wip/spj-wildard-recactor

Still incomplete

- - - - -
712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00
Relax upper bound on `base` to allow base-4.9

- - - - -
0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00
More adaption to wildcard-refactor

- - - - -
0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00
Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor

Conflicts:
	haddock-api/src/Haddock/Convert.hs

- - - - -
c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00
Matching change GHC haskell/haddock#11017 BooleanFormula located

- - - - -
42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00
Change for IEThingWith

- - - - -
f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00
Eliminate support for deprecated GADT syntax

Follows from GHC D1460.

- - - - -
e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00
Merge with origin/head

- - - - -
ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00
Undo msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00
Wibbles to Haddock

- - - - -
2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00
Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor

- - - - -
695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00
Update to match GHC wip/T11019

- - - - -
bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00
merge with origin/ghc-head

- - - - -
3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00
Wibble

- - - - -
e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00
Canonicalise Monad instances

- - - - -
a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00
Matching changes for haskell/haddock#11028

- - - - -
cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00
Placeholder for record style GADT declaration

A GADT Declaration is now presented as

    CmmCondBranch :: {..} -> CmmNode O C
        cml_pred :: CmmExpr
        cml_true, cml_false :: !Label
        cml_likely :: Maybe Bool
for

    CmmCondBranch :: {              -- conditional branch
        cml_pred :: CmmExpr,
        cml_true, cml_false :: ULabel,
        cml_likely :: Maybe Bool    -- likely result of the conditional,
                                    -- if known
    } -> CmmNode O C

- - - - -
95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00
Update for type=kinds

- - - - -
cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00
Bump versions for ghc-7.11

- - - - -
4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00
Eliminate instanceHead' in favour of GHC's instanceSig

This is made possible by the elimination of "silent superclass
parameters" in GHC

- - - - -
13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints

- - - - -
098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track changes in HsSyn for quasi-quotes

- - - - -
716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track change in API of TyCon

- - - - -
77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00
Track API changes to support empty closed type familes

- - - - -
f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00
Track the new location of setRdrNameSpace

- - - - -
ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00
ApiAnnotations : strings in warnings do not return SourceText

The strings used in a WARNING pragma are captured via

strings :: { Located ([AddAnn],[Located FastString]) }
    : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) }
..

The STRING token has a method getSTRINGs that returns the original
source text for a string.

A warning of the form

{-# WARNING Logic
          , mkSolver
          , mkSimpleSolver
          , mkSolverForLogic
          , solverSetParams
          , solverPush
          , solverPop
          , solverReset
          , solverGetNumScopes
          , solverAssertCnstr
          , solverAssertAndTrack
          , solverCheck
          , solverCheckAndGetModel
          , solverGetReasonUnknown
          "New Z3 API support is still incomplete and fragile: \
          \you may experience segmentation faults!"
  #-}

returns the concatenated warning string rather than the original source.

- - - - -
a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00
Update after wild card renaming refactoring in D613

Summary:
* Move `Post*` type instances to `Haddock.Types` as other modules than
  `Haddock.Interface.Rename` will rely on these type instances.
* Update after wild card renaming refactoring in D613.

Reviewers: simonpj, austin

Reviewed By: austin

Differential Revision: https://phabricator.haskell.org/D954

GHC Trac Issues: haskell/haddock#10098

- - - - -
25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
StrictData: print correct strictness marks

- - - - -
6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
StrictData: changes in HsBang type

- - - - -
ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00
Replace (SourceText,FastString) with WithSourceText data type

Phab:D907 introduced SourceText for a number of data types, by replacing
FastString with (SourceText,FastString). Since this has an Outputable
instance, no warnings are generated when ppr is called on it, but
unexpected output is generated. See Phab:D1096 for an example of this.

Replace the (SourceText,FastString) tuples with a new data type

data WithSourceText = WithSourceText SourceText FastString

Trac ticket: haskell/haddock#10692

- - - - -
abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00
HsBang is split into HsSrcBang and HsImplBang

With recent changes in GHC handling of strictness annotations in Haddock
is simplified.

- - - - -
3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00
Follow changes in GHC build system

- - - - -
6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00
account for changes to ipClass

- - - - -
ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00
Follow changes from haskell/haddock#6018

- - - - -
ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00
React to refactoring CoAxiom branch lists.

- - - - -
d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00
Track msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00
Create Process: removed PhaseFailed

- - - - -
3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00
s/PackageKey/UnitId/g and s/packageKey/unitId/g

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00
Roughly fix up haddock for DuplicateRecordFields changes

This compiles, but will probably need more work to produce good
documentation when the DuplicateRecordFields extension is used.

- - - - -
79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00
Track wip/spj-wildcard-refactor on main repo

- - - - -
959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00
Follow changes to HsTYpe

Not yet complete (but on a wip/ branch)

- - - - -
e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00
Work on updating Haddock to wip/spj-wildard-recactor

Still incomplete

- - - - -
aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00
More adaption to wildcard-refactor

- - - - -
8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00
Track change to PatSyn.patSynSig

- - - - -
cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00
Account for Typeable changes

The treatment of type families changed.

- - - - -
63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00
Relax upper bound on `base` to allow base-4.9

- - - - -
a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00
Matching change GHC haskell/haddock#11017 BooleanFormula located

- - - - -
2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00
Change for IEThingWith

- - - - -
593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00
Eliminate support for deprecated GADT syntax

Follows from GHC D1460.

- - - - -
b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00
Undo msHsFilePath change.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00
Update to match GHC wip/T11019

- - - - -
14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00
Wibble

- - - - -
10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00
Canonicalise Monad instances

- - - - -
ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00
Matching changes for haskell/haddock#11028

- - - - -
3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00
Placeholder for record style GADT declaration

A GADT Declaration is now presented as

    CmmCondBranch :: {..} -> CmmNode O C
        cml_pred :: CmmExpr
        cml_true, cml_false :: !Label
        cml_likely :: Maybe Bool
for

    CmmCondBranch :: {              -- conditional branch
        cml_pred :: CmmExpr,
        cml_true, cml_false :: ULabel,
        cml_likely :: Maybe Bool    -- likely result of the conditional,
                                    -- if known
    } -> CmmNode O C

- - - - -
6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00
Update for type=kinds

- - - - -
193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00
Changes to compile with 8.0

- - - - -
add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00
Warnings

- - - - -
223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00
Update for D1200

- - - - -
d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00
Types: Add Outputable[Bndr] DocName instances

- - - - -
62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00
Fix fallout from wildcards refactoring

The wildcard refactoring was introduced a new type of signature,
`ClassOpSig`, which is carried by typeclasses. The original patch
adapting Haddock for this change missed a few places where this
constructor needed to be handled, resulting in no class methods
in documentation produced by Haddock.

Additionally, this moves and renames the `isVanillaLSig` helper from
GHC's HsBinds module into GhcUtils, since it is only used by Haddock.

- - - - -
ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00
Update for D1200

- - - - -
cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00
Types: Add Outputable[Bndr] DocName instances

- - - - -
d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00
Fix fallout from wildcards refactoring

The wildcard refactoring was introduced a new type of signature,
`ClassOpSig`, which is carried by typeclasses. The original patch
adapting Haddock for this change missed a few places where this
constructor needed to be handled, resulting in no class methods
in documentation produced by Haddock.

Additionally, this moves and renames the `isVanillaLSig` helper from
GHC's HsBinds module into GhcUtils, since it is only used by Haddock.

- - - - -
ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00
Fix Hyperlinker

GHC.con_names is now GHC.getConNames

- - - - -
a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00
Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head

- - - - -
f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00
test: Compatibility with Cabal 1.23

- - - - -
88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00
Merge remote-tracking branch 'phadej/orphans' into ghc-head

- - - - -
4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00
Add html-test for orphan instances output

- - - - -
87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00
Update for GHC trac#11258

Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc

- - - - -
6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00
Merge pull request haskell/haddock#1 from haskell/ghc-head

Ghc head
- - - - -
229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00
Handle inline math with mathjax.

- - - - -
57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00
Fix the documentation for haddock itself.

Change notation and add support for inline math.

Allow newlines in display math.

Add a command line option for the mathjax url (you might want to use a
locally installed version).

Rebase tests because of extra url and version change.

Respond to (some of the) comments.

Fix warnings in InterfaceFile.hs

- - - - -
0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00
Fix-up left-over assumptions of GHC 7.12 into GHC 8.0

- - - - -
c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00
Follow removal of NamedWildCard from HsType

- - - - -
da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00
html-test/Operators: Clear up ambiguous types

For reasons that aren't entirely clear a class with ambiguous types was
accepted by GHC <8.0. I've added a functional dependency to clear up
this ambiguity.

- - - - -
541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00
hoogle-test/AssocTypes: Allow AmbiguousTypes

GHC 8.0 complains otherwise

- - - - -
25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00
OrphanInstances: Accept test output

- - - - -
841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00
Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head

- - - - -
358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00
Add missing import

- - - - -
a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00
travis: Use Travis containers

- - - - -
85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00
tweak version bounds for GHC-8.1

- - - - -
672a5f75 by randen at 2016-01-01T23:45:25-08:00
The Haddock part for fully gcc-like response files

" driver/Main.hs
  * Moved the response file handling into ResponseFile.hs,
    updating import section as appropriate.
* driver/ResponseFile.hs
  * New file. In anticipation that maybe some day this could
    be provided by another library, and to make it possible
    to unit test, this functionality is pulled out of the
    Main.hs module, and expanded to support the style/format
    of response files which gcc uses.
  * The specification for the format of response files which
    gcc generates and consumes, seems to be best derived from
    the gcc code itself (libiberty/argv.c), so that is what
    has been done here.
  * This is intended to fix haskell/haddock#379
* driver-test/Main.hs
  * New file for testing code in the driver source tree
* driver-test/ResponseFileSpec.hs
  * Tests, adapted/adopted from the same gcc code where the
    escaping/unescaping is from, in the hspec style of unit
    tests
* haddock.cabal
  * Add the driver-test test-suite.  Introduces a new library
    dependency (upon hspec) for the haddock driver target in
    the haddock.cabal file, but practically, this should not
    be a problem as the haddock-api tests already depend on
    hspec.

- - - - -
498781df by Ben Gamari at 2016-01-06T13:41:04+01:00
Version bumps and changelog

- - - - -
8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00
Merge remote-tracking branch 'randen/bug468'

- - - - -
fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00
Add ResponseFile to OtherModules

- - - - -
2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00
Merge branch 'master' into ghc-head

- - - - -
913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00
deal with un-wiring of IP class

- - - - -
c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00
Update to match wip/T11430 in GHC

- - - - -
3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00
Update to match wip/T11430 in GHC

- - - - -
c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00
Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head

- - - - -
9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00
deal with un-wiring of IP class

(cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f)

- - - - -
b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00
Make sure --mathjax affects all written HTML files

This fixes haskell/haddock#475.

- - - - -
af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00
Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473)

- - - - -
b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00
Merge pull request haskell/haddock#477 from haskell/issue-475

Make sure --mathjax affects all written HTML files
- - - - -
adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00
Merge branch 'master' into ghc-head

- - - - -
d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00
doc: Switch to Sphinx

- - - - -
acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00
Document --use-unicode flag

- - - - -
c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00
Fix GHC and haddock-library dependency bounds

- - - - -
8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00
testsuite: Rework handling of output sanitization

Previously un-cleaned artifacts were kept as reference output, making
it difficult to tell what has changed and causing spurious changes in
the version control history. Here we rework this, cleaning the output
during acceptance. To accomplish this it was necessary to move to strict
I/O to ensure the reference handle was closed before accept attempts to
open the reference file.

- - - - -
c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00
test: Compare on dump

For reasons I don't understand the Xml representations differ despite
their textual representations being identical.

- - - - -
1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00
html-test: Accept test output

- - - - -
eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00
hypsrc-test: Accept test output

And fix impredicative Polymorphism testcase.

- - - - -
d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00
Merge branch 'fix-up-testsuite'

- - - - -
206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00
Move the permalinks to "#" on the right side

Since pull request haskell/haddock#407, the identifiers have been permalinked to
themselves, but this makes it difficult to copy the identifier by
double-clicking.  To work around this usability problem, the permalinks
are now placed on the far right adjacent to "Source", indicated by "#".

Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete).

- - - - -
6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00
Update tests for previous commit

- - - - -
effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00
Merge branch 'anchors-redux'

- - - - -
9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00
Use -fprint-unicode-syntax when --use-unicode is enabled

This allows GHC to render `*` as its Unicode representation, among other
things.

- - - - -
28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00
Merge pull request haskell/haddock#480 from bgamari/sphinx

Move documentation to ReStructuredText
- - - - -
222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00
Collapse type/data family instances by default

- - - - -
a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00
Ensure expanded family instances render correctly

- - - - -
7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Various cleanups

- - - - -
79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Show kind signatures for type family variables

Addresses GHC haskell/haddock#11588.

- - - - -
b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00
Xhtml.Decl: Show 'where ...' after closed type family

Seems like we should ideally show the actual equations as well but that
seems like it would be a fair amount of work

- - - - -
cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00
Merge pull request haskell/haddock#483 from bgamari/T11588

Fix GHC haskell/haddock#11588

This fixes GHC haskell/haddock#11588:
  * Show where ... after closed type families
  * Show kind signatures on type family type variables


- - - - -
256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00
Follow-on changes to support RuntimeRep

- - - - -
2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00
Remove unused functions

- - - - -
eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00
Follow-on changes to support RuntimeRep

(cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c)

- - - - -
8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00
Changes due to fix for GHC#11648.

- - - - -
0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00
Changes due to fix for GHC#11648.

(cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1)

- - - - -
ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00
Fix printing of pattern synonym types

Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this
function will be removed from GHC. Instead, we use the function `patSynSig`
and build the `HsDecl` manually. This also fixes the printing of the two
contexts and the quantified type variables in a pattern synonym type.

Reviewers: goldfire, bgamari, mpickering

Differential Revision: https://phabricator.haskell.org/D2048

- - - - -
d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00
Fix printing of pattern synonym types

Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this
function will be removed from GHC. Instead, we use the function `patSynSig`
and build the `HsDecl` manually. This also fixes the printing of the two
contexts and the quantified type variables in a pattern synonym type.

Reviewers: goldfire, bgamari, mpickering

Differential Revision: https://phabricator.haskell.org/D2048

(cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb)

- - - - -
236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00
doc: Fix option references

(cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197)

- - - - -
692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00
doc: Only install if BUILD_SPHINX_HTML==YES

Fixes GHC haskell/haddock#11818.

- - - - -
79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00
doc: Only install if BUILD_SPHINX_HTML==YES

Fixes GHC haskell/haddock#11818.

(cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5)

- - - - -
3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00
doc: Fix option references

(cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197)

- - - - -
264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00
Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head

Collapse type/data family instances by default
- - - - -
478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00
Merge pull request haskell/haddock#489 from mpickering/unused-functions

Remove some unused functions
- - - - -
c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00
Collapse type/data family instances by default

(cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088)

- - - - -
31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00
Ensure expanded family instances render correctly

(cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103)

- - - - -
03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00
Remove unused functions

(cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0)

- - - - -
ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00
ghc: Install files for needed --hyperlinked-source

- - - - -
0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00
ghc: Install files for needed --hyperlinked-source

(cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6)

- - - - -
4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00
Track change to HsGroup

This relates to a big GHC patch for Trac haskell/haddock#11348

- - - - -
1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00
doc: At long last fix ghc.mk

The variable reference was incorrectly escaped, meaning that Sphinx
documentation was never installed.

- - - - -
0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00
doc: At long last fix ghc.mk

The variable reference was incorrectly escaped, meaning that Sphinx
documentation was never installed.

(cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9)

- - - - -
af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00
Render Haddocks for derived instances

Currently, one can document top-level instance declarations, but derived
instances (both those in `deriving` clauses and standalone `deriving`
instances) do not enjoy the same privilege. This makes the necessary
changes to the Haddock API to enable rendering Haddock comments for
derived instances.

This is part of a fix for Trac haskell/haddock#11768.

- - - - -
76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00
haddock-test: A bit of refactoring for debuggability

- - - - -
7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00
Create: Mark a comment as TODO

- - - - -
2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00
html-test: Update reference output

- - - - -
bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00
hypsrc-test: Fix reference file path in cabal file

It appears the haddock insists on prefixing --hyperlinked-sourcer output
with directory which the source appeared in.

- - - - -
c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00
doc: Update extra-source-files in Cabal file

- - - - -
41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00
Bump versions

- - - - -
ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00
Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head

- - - - -
a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00
doc: Add clean targets

- - - - -
f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00
doc: Add html as an all-target for ghc

Otherwise the html documentation won't be installed for binary-dist.

- - - - -
388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00
Update CHANGES

- - - - -
bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00
Version bump

- - - - -
c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00
Revert "Version bump"

This bump was a bit premature.

This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8.

- - - - -
7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00
doc: Fix GHC clean rule

Apparently GHC's build system doesn't permit wildcards in clean paths.

- - - - -
5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00
Version bump to 2.17.2

- - - - -
b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00
doc: Use `$(MAKE)` instead of `make`

This is necessary to ensure we use gmake.

- - - - -
8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00
Fix haskell/haddock#303. Hide footer when printing

The "Produced by Haddock" footer was overlapping the page's body when printing.
This patch hides the footer with a css media rule.

- - - - -
b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00
Fix haskell/haddock#280. Parsing of module header

The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines

- - - - -
ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00
doc: Vendorize alabaster Sphinx theme

Alabaster is now the default sphinx theme and is a significant
improvement over the previous default that it's worthproviding it when
unavailable (e.g. Sphinx <1.3).

- - - - -
c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00
Merge pull request haskell/haddock#502 from Helkafen/master

Fix haskell/haddock#303. Hide footer when printing
- - - - -
33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00
Revert "doc: Vendorize alabaster Sphinx theme"

This ended up causes far too many issues to be worthwhile. We'll just
have to live with inconsistent haddock documentation.

This reverts commit cec21957001143794e71bcd9420283df18e7de40.

- - - - -
93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00
cabal: Fix README path

- - - - -
c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00
doc: Use whichever theme sphinx deems appropriate

- - - - -
857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00
Create: Remove redundant imports

- - - - -
132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00
Create: Better debug output

For tracking down haskell/haddock#505

- - - - -
2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00
Don't consider default class ops when looking for decls

When we are looking for an operation within a class we don't care about
`default`-type declarations. This was the cause of haskell/haddock#505.

- - - - -
4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00
UnfelpfulSpan line number omitted

Kind of resolves https://github.com/haskell/haddock/issues/508

- - - - -
a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00
Change Hyperlinked lexer to know about DataKinds ticks

- - - - -
f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00
Make parser state a newtype

Previously, it was `data` wrapping a `Maybe`, which seems a bit
silly. Obviously, this can be changed back if anyone wants to add
more fields some day.

- - - - -
05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00
remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274)

Frames are a bit broken, ignored by Hackage, and considered obsolete in general.
This patch disables frames generation. The mini_*.html files are still used in the synopsis.

- - - - -
b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00
Merge pull request haskell/haddock#507 from bgamari/T505

Fix haskell/haddock#505
- - - - -
ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00
Update CHANGES

- - - - -
eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00
Merge pull request haskell/haddock#514 from Helkafen/frames

remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274)
- - - - -
0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00
Remove misplaced haddock comment

- - - - -
a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00
Merge pull request haskell/haddock#515 from alexbiehl/master

Remove misplaced haddock comment
- - - - -
9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00
Merge pull request haskell/haddock#513 from treeowl/newtype-since

Make parser state a newtype
- - - - -
74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00
Merge pull request haskell/haddock#504 from Helkafen/issue-280

Fix haskell/haddock#280. Parsing of module header
- - - - -
37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00
Matching changes for haskell/haddock#12105

- - - - -
7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00
Version bumps (2.17.3, 1.4.2)

- - - - -
85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00
Merge pull request haskell/haddock#521 from Helkafen/master

Version bumps (2.17.3, 1.4.2)
- - - - -
e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00
publish haddock-test library

- - - - -
4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00
Merge pull request haskell/haddock#512 from phadej/oleg-fixes

Fixes for haskell/haddock#508 and haskell/haddock#510
- - - - -
ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00
Documentation for LaTeX markup.

- - - - -
697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00
Fix spelling mistake.

- - - - -
246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00
Camel case MathJax.

- - - - -
4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00
Fix math typo and add link.

- - - - -
f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00
Follow changes to LHsSigWcType

- - - - -
0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00
Follow GHC re-adding FunTy

- - - - -
401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00
Merge pull request haskell/haddock#525 from idontgetoutmuch/master

Documentation for LaTeX markup.
- - - - -
92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00
Merge pull request haskell/haddock#522 from Helkafen/master

publish haddock-test library
- - - - -
0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00
Copyright holders shown on several lines. Fix haskell/haddock#279

- - - - -
65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00
ocean: Ensure that synopsis fully covers other content

Previously MathJax content was being rendered on top of the synopsis due
to ambiguous z-ordering. Here we explicitly give the synopsis block a
higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531.

- - - - -
68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00
Merge pull request haskell/haddock#534 from bgamari/T531

ocean: Ensure that synopsis fully covers other content
- - - - -
fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00
Merge pull request haskell/haddock#533 from Helkafen/master

Copyright holders shown on several lines. Fix haskell/haddock#279
- - - - -
6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00
do not create empty src directory

Fix haskell/haddock#536.

- - - - -
1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00
Merge pull request haskell/haddock#537 from Helkafen/master

do not create empty src directory
- - - - -
966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00
Add $ as a special character

If this character is not escaped, documentation built with Haddock
2.17.2 will fail.  This was not an issue with 2.16 series, which
causes builds to fail and there is nothing in the docs or error
message giving a clue about why builds that used to succeed now
don't.

- - - - -
324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00
GhcUtils: Changes for multi-pattern signatures

- - - - -
d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00
Add support for unboxed sums

- - - - -
29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00
Disable NFData instances for GHC types when GHC >= 8.2

- - - - -
702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00
Disable NFData instances for GHC types when GHC >= 8.0.2

(cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a)

- - - - -
f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00
ghc.mk: Don't attempt to install html/frames.html

The frames business has been removed.

- - - - -
9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00
Haddock.Types: More precise version guard

This allows haddock to be built with GHC 8.0.2 pre-releases.

- - - - -
f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00
Merge pull request haskell/haddock#538 from massysett/master

Add $ as a special character
- - - - -
16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00
Fix rendering of class methods for Eq and Ord

See haskell/haddock#549 and GHC issue haskell/haddock#12519

- - - - -
7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00
Fix rendering of class methods for Eq and Ord

See haskell/haddock#549 and GHC issue haskell/haddock#12519

(cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b)

- - - - -
33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00
Haddock changes for T10598

See https://ghc.haskell.org/trac/ghc/ticket/10598

- - - - -
1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00
Update for refactoring of NameCache

- - - - -
1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00
Bump upper bound on base

- - - - -
9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00
Match changes in GHC wip/T3384 branch

- - - - -
ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00
haddock-api: Don't use stdcall calling convention on 64-bit Windows

See GHC haskell/haddock#12890.

- - - - -
04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00
Matching changes for GHC wip/T12942

- - - - -
e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00
Bump base upper bound

- - - - -
3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00
HsIParamTy now has a Located name

- - - - -
7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00
Prevent GHC API from doing optimization passes.

- - - - -
d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00
Upstream changes re levity polymorphism

- - - - -
40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00
Changes to match haskell/haddock#13163 in GHC

- - - - -
504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00
Kill remaining static flags

- - - - -
49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00
Adding MDoc to exports of Documentation.Haddock

- - - - -
1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00
Also exposing toInstalledIface

- - - - -
53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00
Bump for GHC 8.3

- - - - -
c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00
Bump for GHC 8.2

- - - - -
4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00
Merge branch 'ghc-head'

- - - - -
e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00
Update Haddock w.r.t. new HsImplicitBndrs

- - - - -
6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00
Update Haddock w.r.t. new HsImplicitBndrs

- - - - -
eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00
Adapt to EnumSet

- - - - -
017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Correctly handle Backpack identity/semantic modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Add a field marking if interface is a signature or not.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Render signature module tree separately from modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Documentation.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
More docs.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00
TODO on moduleExports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Better Backpack support with signature merging.

When we merge signatures, we gain exports that don't
necessarily have a source-level declaration corresponding
to them.  This meant Haddock dropped them.

There are two big limitations:

* If there's no export list, we won't report inherited
  signatures.

* If the type has a subordinate, the current hiDecl
  implementation doesn't reconstitute them.

These are probably worth fixing eventually, but this gets
us to minimum viable functionality.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00
Fix haddock-test to work with latest version of Cabal.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00
Annotate signature docs with (signature)

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00
Render help documentation link next to (signature) in title.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00
Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD

- - - - -
0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00
haddock-api: Bump bound on GHC

- - - - -
65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00
Merge pull request haskell/haddock#581 from JustusAdam/master

Adding more exports to Documentation.Haddock
- - - - -
37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00
Merge pull request haskell/haddock#568 from awson/ghc-head

Prevent GHC API from doing optimization passes.
- - - - -
1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00
Print any user-supplied kind signatures on type parameters.

This applies to type parameters on data, newtype, type, and class
declarations, and also to forall-bound type vars in type signatures.

- - - - -
1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00
Update test suite to expect kind annotations on type parameters.

- - - - -
a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00
Include travis build indication badge
- - - - -
8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00
haddock-api: Bump bound on GHC

- - - - -
4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Correctly handle Backpack identity/semantic modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737)

- - - - -
a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Add a field marking if interface is a signature or not.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858)

- - - - -
caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Render signature module tree separately from modules.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0)

- - - - -
49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Documentation.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc)

- - - - -
4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00
More docs.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a)

- - - - -
74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
TODO on moduleExports.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e)

- - - - -
a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Better Backpack support with signature merging.

When we merge signatures, we gain exports that don't
necessarily have a source-level declaration corresponding
to them.  This meant Haddock dropped them.

There are two big limitations:

* If there's no export list, we won't report inherited
  signatures.

* If the type has a subordinate, the current hiDecl
  implementation doesn't reconstitute them.

These are probably worth fixing eventually, but this gets
us to minimum viable functionality.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3)

- - - - -
d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Fix haddock-test to work with latest version of Cabal.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267)

- - - - -
ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Annotate signature docs with (signature)

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1)

- - - - -
2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00
Render help documentation link next to (signature) in title.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe)

- - - - -
37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00
Update MathJax URL

MathJax is shutting down their CDN:
https://www.mathjax.org/cdn-shutting-down/

They recommend migrating to cdnjs.

- - - - -
e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00
Add highlight for :target to ocean.css

- - - - -
4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00
Allow base-4.10 for haddock-test

- - - - -
44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00
cabal.project for haddock-api, haddock-library and haddock-test

- - - - -
935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00
Move dist scripts to scripts/

- - - - -
128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00
Add haddock to cabal.project

- - - - -
cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00
Read files for hyperlinker eagerly

This also exposes Documentation.Haddock.Utf8

- - - - -
152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00
Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create

- - - - -
501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00
Prevent GHC API from doing optimization passes.

- - - - -
c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00
Add @alexbiehl as maintaner

- - - - -
76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00
Disable doctest with ghc-8.3

Currently doctest doesn't support ghc-head
- - - - -
46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00
Render (signature) only if it actually is a signature!

I forgot a conditional, oops!

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00
Travis: Use ghc-8.2.1 on master

- - - - -
966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00
Travis: Verbose cabal output

cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377
- - - - -
36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00
Use travis_retry for cabal invocations
- - - - -
b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00
Use new MathJax URL in html-test

18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL
but didn't update the tests.

- - - - -
ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00
Expand signatures for class declarations

- - - - -
e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00
Hoogle: Correctly print classes with associated data types

- - - - -
3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00
Render (signature) only if it actually is a signature!

I forgot a conditional, oops!

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
(cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9)

- - - - -
6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00
`html-test --accept` deltas to reference samples

- - - - -
7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00
Remove anything related to obsolete frames mode

- - - - -
b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00
Cherry-picked remaining commits from haddock-2.17.4-release (#603)

* Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3

* Set version bounds for haddock-library

NB: This allows GHC 8.2.1's base

* Set version bounds for haddock & haddock-api

The version bounds support GHC 8.2

* Merge (temporary) v2.17.3 branch into v2.17

This allows us to delete the v2.17.3 branch

* Fixup changelog

* Pin down haddock-api to a single version

as otherwise `haddock`'s package version has no proper meaning

* fix source-repo spec for haddock-api

- - - - -
4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00
Update changelog to reflect news in HEAD

- - - - -
eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00
Markdownify changelog

- - - - -
5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00
Bump to 2.18.0 (#605)


- - - - -
a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00
Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0

- - - - -
ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00
Improve error message

- - - - -
2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00
Correctly remember collapsed sections (#608)

Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed.
- - - - -
f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00
Lazily decode docMap and argMap (#610)

These are only used in case of a doc reexport so most of the time
decoding these is wasted work.
- - - - -
2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00
Fix Binary instance for InstalledInterface (#611)

(#610) introduced lazy decoding for docs from InstalledInterface but
forgot to remove the original calls to get and put_
- - - - -
6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00
Improve documenation of Haddock markup (#614)

* Improve documentation of Haddock markup.

- document that Haddock supports inferring types top-level functions
  with without type signatures, but also explain why using this
  feature is discouraged. Looks like this feature has been around
  since version 2.0.0.0 in 2008!

- rework the "Module description" section:

  - move the general discussion of field formatting to the section
    intro and add examples illustrating the prose for multiline
    fields.

  - mention that newlines are preserved in some multiline fields, but
    not in others (I also noticed that commas in the `Copyright` field
    are not preserved; I'll look into this bug later).

  - add a subsection for the module description fields documentation,
    and put the field keywords in code formatting (double back ticks)
    instead of double quotes, to be consistent with the typesetting of
    keywords in other parts of the documentation.

  - mention that "Named chunks" are not supported in the long-form
    "Module description" documentation.

- fix formatting of keywords in the "Module attributes"
  section. Perhaps these errors were left over from an automatic
  translation to ReST from some other format as part of the transition
  to using Sphinx for Haddock documentation? Also, add a missing
  reference here; it just said "See ?"!

- update footnote about special treatment for re-exporting partially
  imported modules not being implemented. In my tests it's not
  implemented at all -- I tried re-exporting both `import B
  hiding (f)` and `import B (a, b)` style partial imports, and in both
  cases got the same result as with full imports `import B`: I only
  get a module reference.

* Rework the `Controlling the documentation structure` section.

My main goal was to better explain how to use Haddock without an
export list, since that's my most common use case, but I hope I
improved the section overall:

- remove the incomplete `Omitting the export list` section and fold it
  into the other sections. In particular, summarize the differences
  between using and not using an export list -- i.e. control over what
  and in what order is documented -- in the section lead.

- add "realistic" examples that use the structure markup, both with
  and without an export list. I wanted a realistic example here to
  capture how it can be useful to explain the relationship between a
  group of functions in a section, in addition to documenting their
  individual APIs.

- make it clear that you can associate documentation chunks with
  documentation sections when you aren't using an export list, and
  that doing it in the most obvious way -- i.e. with `-- |`, as you
  can in the export list -- doesn't work without an export list. It
  took me a while to figure this out the first time, since the docs
  didn't explain it at all before.

- add a "no export list" example to the section header section.

- add more cross references.

* Add examples of gotchas for markup in `@...@`.

I'm not sure this will help anyone, since I think most people first
learn about `@...@` by reading other people's Haddocks, but I've
documented the mistakes which I've made and then gotten confused by.

* Use consistent Capitalization of Titles.

Some titles were in usual title caps, and others only had the first
word capitalized. I chose making them all use title caps because that
seems to make the cross references look better.

- - - - -
d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00
Haddock: Fix broken lazy IO in prologue reading (#615)

We previously used withFile in conjunction with hGetContents. The list returned
by the latter wasn't completely forced by the time we left the withFile block,
meaning that we would try to read from a closed handle.
- - - - -
93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00
Haddock: Fix broken lazy IO in prologue reading (#615)

We previously used withFile in conjunction with hGetContents. The list returned
by the latter wasn't completely forced by the time we left the withFile block,
meaning that we would try to read from a closed handle.
- - - - -
5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00
Consequently use inClass and notInClass in haddock-library (#617)

These allow attoparsec to do some clever lookup optimization
- - - - -
77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00
Don't enable compilation for template haskell (#624)

This is no longer necessary after
ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa
- - - - -
5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00
Improve Syb code (#621)

Specialize.hs and Ast.hs are modified to have their Syb code not recurse into
Name or Id in HsSyn types.

Specialize.hs is refactored to have fewer calls to Syb functions.

Syb.hs has some foldl calls replaced with foldl' calls.

There is still a lot of performance on the floor of Ast.hs. The RenamedSource
is traversed many times, and lookupBySpan is very inefficient. everywhereBut and
lookupBySpan dominate the runtime whenever --hyperlinked-source is passed.
- - - - -
3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00
Clear fixme comment (#625)


- - - - -
2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00
Make haddock-library and haddock-api warning free (#626)


- - - - -
bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00
Include `driver-test/*.hs` sdist (#630)

This lead to haskell/haddock#629.
- - - - -
184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00
Disable pattern match warnings (#628)

This disables the pattern match checker which can be very expensive in some
cases.

The disabled warnings include:
* Opt_WarnIncompletePatterns
* Opt_WarnIncompleteUniPatterns
* Opt_WarnIncompletePatternsRecUpd
* Opt_WarnOverlappingPatterns
- - - - -
0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00
Allow user defined signatures for pattern synonyms (#631)


- - - - -
7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00
Use NameSet for isExported check (#632)


- - - - -
d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00
Match new AST as per GHC wip/new-tree-one-param

See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow

- - - - -
da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00
Rename extension index tags

- - - - -
538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00
Haddock support for bundled pattern synonyms (#627)

* Haddock support for bundled pattern synonyms

* Add fixities to bundled pattern synonyms

* Add bundled pattern synonyms to the synopsis

* Store bundled pattern fixities in expItemFixities

* Add test for bundled pattern synonyms

* Stop threading fixities

* Include bundled pattern synonyms for re-exported data types

Sadly, fixity information isn't found for re-exported data types

* Support for pattern synonyms

* Modify tests after haskell/haddock#631

* Test some reexport variations

* Also lookup bundled pattern synonyms from `InstalledInterface`s

* Check isExported for bundled pattern synonyms

* Pattern synonym is exported check

* Always look for pattern synonyms in the current module

Another overlooked cornercase

* Account for types named twice in export lists

Also introduce a fast function for nubbing on a `Name` and use it
throughout the code base.

* correct fixities for reexported pattern synonyms

* Fuse concatMap and map

* Remove obsolete import

* Add pattern synonyms to visible exports

* Fix test

* Remove corner case

- - - - -
a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00
Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636)

There is some performance improvement.

GHC compiler:
| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 56057108648     | 41.0
| after   | 51592019560     | 35.1

base:
| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 25174011784     | 14.6
| after   | 23712637272     | 13.1

Cabal:

| version | bytes allocated | cpu_seconds
---------------------------------
| before  | 18754966920     | 12.6
| after   | 18198208864     | 11.6
- - - - -
5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00
Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639)

* Use new function getNameToInstancesIndex instead of tcRnGetInfo

There is some significant performance improvement in the ghc testsuite.

haddock.base: -23.3%
haddock.Cabal: -16.7%
haddock.compiler: -19.8%

* Remove unused imports

- - - - -
b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00
Lookup fixities for reexports without subordinates (#642)

So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-).

The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities.
- - - - -
d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00
Don't include names with empty subordinates in maps (#644)

These are unecessary anyway and just blow up interface size
- - - - -
69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00
Make per-argument docs for class methods work again (#648)

* Make per-argument docs for class methods work again

* Test case

- - - - -
c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00
Fix haddock: internal error: links: UnhelpfulSpan (#561)

* Fix haddock: internal error: links: UnhelpfulSpan

This fixes haskell/haddock#554 for me. I believe this is another fall out
of `wildcard-refactor`, like haskell/haddock#549.

* Comment to clarify why we take the methods name location

- - - - -
d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00
Document record fields when DuplicateRecordFields is enabled (#649)


- - - - -
9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00
Fix test failures on Windows (#564)

* Ignore .stack-work

* Fix for windows: use nul instead of /dev/null

* Fix for windows: canonicalize line separator

* Also normalize osx line endings

- - - - -
7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00
Avoid errors on non UTF-8 Windows (#566)

* Avoid errors on non UTF-8 Windows

Problem
====

haddock exits with errors like below:

`(1)`

```
haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character)
```

`(2)`

```
haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence)
```

`(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr.
For example, this warning contains it:

```
Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods]
    • No explicit implementation for
        ‘toEnum’
    • In the instance declaration for ‘Enum Highlight’
```

`(2)` is caused when the input file of `readFile` contains some Unicode characters.
In the case above, '⇒' is the cause.

Environment
----

OS: Windows 10
haddock: 2.17.3
GHC: 8.0.1

Solution
====

Add `hSetEncoding handle utf8` to avoid the errors.

Note
====

- I found the detailed causes by these changes for debugging:
    - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b
    - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4
- These errors happen even after executing `chcp 65001` on the console.
  According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding.

* Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows

Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1)

- - - - -
eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00
Remove redudant import warning (#651)


- - - - -
05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00
Avoid missing home module warning (#652)

* Avoid missing home module warning

* Update haddock-library.cabal

- - - - -
e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00
Fix haskell/haddock#249 (#655)


- - - - -
eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00
Fix compilation of lib:haddock-library w/ GHC < 8

- - - - -
9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00
Prepare 2.18.1 release (#657)


- - - - -
46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Tweak haddock-api.cabal for pending release

- - - - -
85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Avoid trivial use of LambdaCase

otherwise we can't test w/ e.g. GHC 7.4.2

- - - - -
3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00
Refactor .cabal to use sub-lib for vendored lib

A practical benefit is that we can control the build-depends and also
avoid some recompilation between library and test-suite.

- - - - -
e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00
haddock-api: add changelog pointing to haddock's changelog

This addresses
https://github.com/haskell/haddock/issues/638#issuecomment-309283297

- - - - -
2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00
Drop obsolete/misleading `stability: experimental`

This .cabal property has long been considered obsolete

- - - - -
9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00
Beef up haddock description (#658)

* Beef up haddock description

* Handle empty lines

- - - - -
bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00
Import @aisamanra's Haddock cheatsheet

from https://github.com/aisamanra/haddock-cheatsheet

- - - - -
0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00
Add cheatsheet to haddock.cabal

- - - - -
2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00
Mention new-build in README

- - - - -
947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00
Update README

Also improves markup and removes/fixes redundant/obsolete parts

[skip ci]

- - - - -
785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00
Bump haddock to 2.18.2, haddock-library to 1.4.5

- - - - -
e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00
Move `DocMarkup` from haddock-api to haddock-library (#659)

* Move `DocMarkup` from haddock-api to haddock-library

* Move more markup related functions

* Markup module

* CHANGELOG

- - - - -
cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00
Fixup haddock
- - - - -
583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00
Changelog for haddock-library

- - - - -
bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00
Prepare haddock-library-1.4.5 release

- - - - -
58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00
Fix renaming after instance signature specializing (#660)

* rework rename

* Add regression test for Bug 613

* update tests

* update changelog

- - - - -
b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00
Fix: Generate pattern signatures for constructors exported as patterns (#663)

* Fix pretty-printing of pattern signatures

Pattern synonyms can have up to two contexts, both having a
different semantic meaning: The first holds the constraints
required to perform the matching, the second contains the
constraints provided by a successful pattern match. When the
first context is empty but the second is not it is necessary
to render the first, empty context.

* Generate pattern synonym signatures for ctors exported as patterns

This fixes haskell/haddock#653.

* Simplify extractPatternSyn

It is not necessary to generate the simplest type signature since
it will be simplified when pretty-printed.

* Add changelog entries for PR haskell/haddock#663

* Fix extractPatternSyn error message

- - - - -
d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00
Bump haddock-library
- - - - -
99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00
Bump haddock-library in haddock-api
- - - - -
94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00
Provide --show-interface option to dump interfaces (#645)

* WIP: Provide --show-interface option to dump interfaces

Like ghcs own --show-iface this flag dumps a binary interface file to
stdout in a human (and machine) readable fashion. Currently it uses
json as output format.

* Fill all the jsonNull stubs

* Rework Bifunctor instance of DocH, update changelog and documentation

* replace changelog, bring DocMarkupH doc back

* Update CHANGES.md

* Update CHANGES.md

* Move Control.Arrow up

It would result in unused import if the Bifunctor instance is not generated.

- - - - -
c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00
Adapt to haskell/haddock#14060

- - - - -
b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00
Bifoldable and Bitraversable for DocH and MetaDoc

- - - - -
021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00
Refactoring: Make doc renaming monadic

This allows us to later throw warnings if can't find an identifier

- - - - -
39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00
Hyperlinker: Avoid linear lookup in enrichToken (#669)

* Make Span strict in Position

* Hyperlinker: Use a proper map to enrich tokens

- - - - -
e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00
Drop Avails from export list

- - - - -
86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00
Bump ghc version for haddock-api tests

- - - - -
d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00
Revert "Drop Avails from export list"

This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def.

- - - - -
c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00
IntefaceFile version

- - - - -
a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00
haddock: Add Documentation.Haddock.Markup to other-modules

- - - - -
34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00
haddock: Add Documentation.Haddock.Markup to other-modules

- - - - -
577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00
Update for haskell/haddock#14131

- - - - -
da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00
Generate an index for package content search (#662)

Generate an index for package content search
- - - - -
39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00
Content search for haddock html doc

- - - - -
91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00
Fix tests for content search

- - - - -
b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00
Add search button to #page-menu

- - - - -
25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00
Load javascript below the fold

- - - - -
8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00
Accept tests

- - - - -
c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00
Content search css

- - - - -
89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00
Removed `nowrap` for interface method sigs (#674)

with nowrap the interfaces method sigs would expand at libitum
- - - - -
a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00
Include subordinates in content index

- - - - -
4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00
QuickNav: Make docbase configurable

- - - - -
c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00
QuickNav: Also use baseUrl for doc-index.json request

- - - - -
47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00
Fix test fallout (again)

- - - - -
924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00
Write meta.json when generating html output (#676)


- - - - -
717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00
Use relative URL when no docBaseUrl given
- - - - -
e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00
Add missing js files to data-files (#677)


- - - - -
95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00
Rename "Search" tab to "Quick Jump"
- - - - -
da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00
Make trigger link configurable (#678)

QuickNav: Configurable show/hide trigger
- - - - -
de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00
Account for "Remember the AvailInfo for each IE"

As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the
AvailInfo associated with each IE. @alexbiehl has a patch making proper use of
this change, but this is just to keep things building.

- - - - -
b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00
Bump upper bound on base

- - - - -
79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00
Make compatible with Prelude.<> export in GHC 8.4/base-4.11

- - - - -
3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00
Add compile step that bundles and compresses JS files (#684)

* Add compile step that bundles and compresses JS files

Also, manage dependencies on third-party JS libraries using NPM.

* Compile JS from TypeScript

* Enable 'noImplicitAny' in TypeScript

* QuickJump: use JSX syntax

* Generate source maps from TypeScript for easier debugging

* TypeScript: more accurate type

* Separate quick jump css file from ocean theme

- - - - -
df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00
Bump base for haddock-library and haddock-test

- - - - -
62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00
Inhibit output of coverage information for hidden modules. (#687)

* Inhibit output of coverage information for hidden modules.

* Add changelog entry.

- - - - -
8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00
Don't use subMap in attachInstances

- - - - -
ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00
Revert "Don't use subMap in attachInstances"

This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9.

- - - - -
7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00
Precise Haddock: Use Avails for export resolution (#688)

* Use Avails for export resolution

* Support reexported modules

* Factor out availExportItem

* Use avails for fullModuleExports

* Don't use subMap in attachInstances

* lookupDocs without subMap

* Completely remove subMap

* Only calculate unqualified modules when explicit export list is given

* Refactor

* Refine comment

* return

* Fix

* Refactoring

* Split avail if declaration is not exported itself

* Move avail splitting

- - - - -
b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00
Fix merge fallout

- - - - -
c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00
Copy QuickJump files over

- - - - -
1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00
Use <details> element for collapsibles (#690)

* Remove unnecessary call to 'collapseSection'

The call is unnecessary since there is no corresponding toggle for hiding the
section of orphan instances.

* Use <details> for collapsibles

This makes them work even when JS is disabled. Closes haskell/haddock#560.

- - - - -
1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00
Quick Jump: Show error when loading 'doc-index.json' failed (#691)


- - - - -
910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00
Fix tiny typo in docs (#693)


- - - - -
b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00
Overhaul Haddock's rendering of kind signatures (#681)

* Overhaul Haddock's rendering of kind signatures

* Strip off kind signatures when specializing

As an added bonus, this lets us remove an ugly hack specifically for `(->)`.
Yay!

* Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67

* @alexbiehl's suggestions

* Import injectiveVarsOfBinder from GHC

- - - - -
6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00
Fix Haddock rendering of kind-indexed data family instances (#694)


- - - - -
470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00
Add QuickJump version to meta.json (#696)


- - - - -
b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00
Put Quickjump behind --quickjump flag (#697)


- - - - -
3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00
Add build command to package.json

- - - - -
f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00
Decrease threshold for fuzzy matching

- - - - -
80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00
Supported reexported-modules via --reexport flag.

Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>

- - - - -
7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00
Correct missing title in changelog

- - - - -
1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00
Copy quickjump.css for nicer error messages

- - - - -
db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00
Reexported modules: Report warnings if argument cannot be parsed or

... module cannot be found

- - - - -
eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00
More general type for nameCacheFromGhc. (#539)


- - - - -
580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00
Remote tab

- - - - -
0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00
Merge remote-tracking branch 'origin/master' into ghc-head

- - - - -
7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00
fullModuleContents traverses exports in declaration order

- - - - -
0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00
Remove excessive use of list comprehensions

- - - - -
f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00
Make better use of AvailInfo

- - - - -
f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00
Always return documentation for exported subordinates

... event if they have no documentation (e.g. noDocForDecl)

By using the information in the AvailInfo we don't need additional
export checks.

- - - - -
7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00
Match changes for Trees that Grow in GHC

- - - - -
e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00
Match Trees That Grow

- - - - -
55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00
Match Trees that Grow in GHC for HsExpr

- - - - -
2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00
Actually render infix type operators as infix (#703)

* Actually render infix type operators as infix

* Account for things like `(f :*: g) p`, too

- - - - -
c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00
Clean up use of PlaceHolder, to match TTG

- - - - -
81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00
Declare use of `Paths_haddock` module in other-modules (#705)

This was detected by `-Wmissing-home-modules`
- - - - -
f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00
Drop Paths_haddock from ghc.mk (#707)

With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more.
# Conflicts:
#	ghc.mk
- - - - -
f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00
Add autogen-modules (#706)

> Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail.
# Conflicts:
#	haddock.cabal
- - - - -
bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00
Revert "Clean up use of PlaceHolder, to match TTG"

This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049.

- - - - -
af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00
Revert "Match Trees that Grow in GHC for HsExpr"

This reverts commit 9f054dc365379c66668de6719840918190ae6e44.

- - - - -
5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00
Revert "Match Trees That Grow"

This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c.

- - - - -
99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00
Revert "Match changes for Trees that Grow in GHC"

This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547.

- - - - -
c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00
Bump GHC version

- - - - -
027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00
Bump GHC bound to 8.4.*

- - - - -
58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00
Update changelog
- - - - -
d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00
Track changes to follow Trac haskell/haddock#14529

This tracks the refactoring of HsDecl.ConDecl.

- - - - -
dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00
Pass to GHC visible modules for instance filtering

The GHC-side `getNameToInstancesIndex` filters out incorrectly some
instances because it is not aware of what modules are visible. On the
Haddock side, we need to pass in the modules we are processing.

On the GHC side, we need to check against _those_ modules when checking
if an instance is visible.

- - - - -
8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00
Constructor and pattern synonym argument docs (#709)

* Support Haddocks on constructor arguments

This is in conjunction with https://phabricator.haskell.org/D4094.
Adds support for rendering Haddock's on (non-record) constructor
arguments, both for regular and GADT constructors.

* Support haddocks on pattern synonym arguments

It appears that GHC already parsed these - we just weren't using them.
In the process of doing this, I tried to deduplicate some code around
handling patterns.

* Update the markup guide

Add some information about the new support for commenting constructor
arguments, and mention pattern synonyms and GADT-style constructors.

* Overhaul LaTeX support for data/pattern decls

This includes at least

  * fixing several bugs that resulted in invalid LaTeX
  * fixing GADT data declaration headers
  * overhaul handling of record fields
  * overhaul handling of GADT constructors
  * overhaul handling of bundled patterns
  * add support for constructor argument docs

* Support GADT record constructors

This means changes what existing HTML docs look like.

As for LaTeX, looks like GADT records were never even supported. Now they are.

* Clean up code/comments

Made code/comments consistent between the LaTeX and XHTML backend
when possible.

* Update changelog

* Patch post-rebase regressions

* Another post-rebase change

We want return values to be documentable on record GADT constructors.

- - - - -
ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00
Update the GblRdrEnv when processing modules

Without a complete environment, we will miss some instances that were
encountered during typechecking.

- - - - -
4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00
Fix haskell/haddock#732 (#733)


- - - - -
bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00
extractDecl: Extract associated types correctly (#736)


- - - - -
a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00
extractDecl: Extract associated types correctly (#736)


- - - - -
26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00
haddock-api: bump ghc to ^>= 8.4

- - - - -
f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00
Fix duplicate declarations and TypeFamilies specifics

- - - - -
0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00
Fix duplicate declarations and TypeFamilies specifics

- - - - -
cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00
Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head

- - - - -
0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00
Pass to GHC visible modules for instance filtering

The GHC-side `getNameToInstancesIndex` filters out incorrectly some
instances because it is not aware of what modules are visible. On the
Haddock side, we need to pass in the modules we are processing.

On the GHC side, we need to check against _those_ modules when checking
if an instance is visible.

- - - - -
b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00
Update the GblRdrEnv when processing modules

Without a complete environment, we will miss some instances that were
encountered during typechecking.

- - - - -
0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00
Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702)

- - - - -
8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00
Use the GHC lexer for the Hyperlinker backend (#714)

* Start changing to use GHC lexer

* better cpp

* Change SrcSpan to RealSrcSpan

* Remove error

* Try to stop too many open files

* wip

* wip

* Revert "wip"

This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1.

Conflicts:
	haddock-api/haddock-api.cabal
	haddock-api/src/Haddock/Interface.hs

* Remove pointless 'caching'

* Use dlist rather than lists when finding vars

* Use a map rather than list

* Delete bogus comment

* Rebase followup

Things now run using the GHC lexer. There are still

  - stray debug statements
  - unnecessary changes w.r.t. master

* Cleaned up differences w.r.t. current Haddock HEAD

Things are looking good. quasiquotes in particular look beautiful: the
TH ones (with Haskell source inside) colour/link their contents too!

Haven't yet begun to check for possible performance problems.

* Support CPP and top-level pragmas

The support for these is hackier - but no more hacky than the existing
support.

* Tests pass, CPP is better recognized

The tests were in some cases altered: I consider the new output to be more
correct than the old one....

* Fix shrinking of source without tabs in test

* Replace 'Position'/'Span' with GHC counterparts

Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'.

* Nits

* Forgot entry in .cabal

* Update changelog

- - - - -
95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00
Clickable anchors for headings (#716)

See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the
heading itself.
- - - - -
21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00
Quickjump: Matches on function names weight more than matches in ...

module names.

- - - - -
8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00
Treat escaped \] better in definition lists (#717)

This fixes haskell/haddock#546.
- - - - -
e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00
Remove scanner, takeWhile1_ already takes care of escaping

- - - - -
9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00
Take until line feed

- - - - -
01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00
Add simple framework for running parser fixtures (#668)

* Add simple framework for running parser fixtures

* Compatible with tree-diff-0.0.0.1

* Use parseParas to parse fixtures

This allows to test all syntactic constructs available in haddock
markup.

- - - - -
31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00
Patch flaky parser test (#720)

* Patch flaky parser test

This test was a great idea, but it doesn't port over too well to using
the GHC lexer. GHC rewrites its input a bit - nothing surprising, but
we need to guard against those cases for the test.

* Change instance head

* Change use site

- - - - -
9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00
Include secondary LICENSE file in source dist

- - - - -
51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00
Grid Tables (#718)

* Add table examples

* Add table types and adopt simple parser

Simple parser is done by Giovanni Cappellotto (@potomak)
in https://github.com/haskell/haddock/pull/577
It seems to support single fine full tables, so far from full
RST-grid tables, but it's good start.

Table type support row- and colspans, but obviously parser is lacking.

Still TODO:
- Latex backend. Should we use multirow package
  https://ctan.org/pkg/multirow?lang=en?
- Hoogle backend: ?

* Implement grid-tables

* Refactor table parser

* Add two ill-examples

* Update CHANGES.md

* Basic documentation for tables

* Fix documentation example

- - - - -
670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00
Add grid table example to cheatsheet

(pdf and svg need to be regenerated thought)
- - - - -
4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00
Fix infinite loop when specializing instance heads (#723)

* Fix infinite loop when specializing instance heads

The bug can only be triggered from TH, hence why it went un-noticed for
so long.

* Add test for haskell/haddock#679 and haskell/haddock#710

- - - - -
67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00
Filter RTS arguments from 'ghc-options' arguments (#725)

This fixes haskell/haddock#666.
- - - - -
7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00
Quickjump Scrollable overlay
- - - - -
da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Hyperlinker: Adjust parser to new PFailed constructor

- - - - -
7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00
Specialize: Add missing IdP annotations

- - - - -
78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Convert: Correct pass type

- - - - -
a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Warning free compilation

- - - - -
cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00
hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0

- - - - -
c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00
Adjust changelogs

- - - - -
1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00
haddock-library: Info about breaking changes

- - - - -
f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00
Properly color pragma contents in hyperlinker

The hyperlinker backend now classifies the content of pragmas as
'TkPragma'. That means that in something like '{-# INLINE foo #-}',
'foo' still gets classified as a pragma token.

- - - - -
c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00
Support the new 'ITcolumn_prag' token

- - - - -
4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00
QuickJump: Mitigate encoding problems on Windows

- - - - -
bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00
Use withBinaryFile

- - - - -
637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00
Try GHC 8.4.1 for Travis CI job

- - - - -
7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00
try harder to build w/ GHC 8.4.1

- - - - -
8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00
Add `SPDX-License-Identifier` as alised for "license" module header tokens

C.f. SPDX 2.1 - Appendix V
 https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b

    The tag should appear on its own line in the source file, generally as part of a comment.

    SPDX-License-Identifier: <SPDX License Expression>

Cherry-picked from haskell/haddock#743

- - - - -
267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00
Make test-suite SMP compatible

- - - - -
95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00
Hyperlink pattern synonyms and 'module' imports (#744)

Links to pattern synonyms are now generated, as well as links from
modules in import lists.

Fixes haskell/haddock#731.
- - - - -
67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00
Don't warn about missing '~' (#746)

This manually filters out '~' from the list of things to warn about. It truly
makes no sense to warn on this since '~' has nothing it could link to - it is
magical.

This fixes haskell/haddock#532.
- - - - -
ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00
Don't barf on 'HsSpliceTy' (#745)

This handles 'HsSpliceTy's by replacing them with what they expand to.
IIUC everything that is happening, 'renameHsSpliceTy' should not be
able to fail for the inputs we feed it from GHC.

This fixes haskell/haddock#574.

- - - - -
92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00
Rename: renameHsSpliceTy ttg

- - - - -
3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00
Expand SigDs

- - - - -
c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00
fullModuleContents: support named docs

- - - - -
de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00
Hyperlinker: Also link pattern synonym arguments

- - - - -
b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00
Expand SigD in a better place

In https://github.com/haskell/haddock/issues/287 we found that
haddock-2.19.0 would miss documentation on class methods with
multiples names.

This patch uses expandSigDecls in a more sensible place.

- - - - -
8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00
Add module tooltips to linked identifiers (#753)

No more clicking to figure out whether your bytestring is strict or lazy!
- - - - -
d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00
Add 'show' option to complement 'hide' (#752)

* Add 'show' option to complement 'hide'

The behaviour is for flags passed in the command line to override
flags in file headers. In the command line, later flags override
earlier ones.

Fixes haskell/haddock#751 and haskell/haddock#266.

* Add a '--show-all' option

- - - - -
6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00
QuickJump: Mitigate encoding problems on Windows

(cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231)

- - - - -
e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00
Use withBinaryFile

- - - - -
724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00
Haddock: support splitted include paths. (#689)


- - - - -
9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00
Teach the HTML backend how to render methods with multiple names

- - - - -
a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00
Hoogle/Latex: Remove use of partial function

- - - - -
66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00
Fix file handle leak (#763) (#764)

Brought back some mistakenly deleted code for handling encoding and eager
reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137.
- - - - -
bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00
Enable running test suite with stock haddock and ghc using

```
$ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc)
```

- - - - -
dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00
Make testsuite work with haddock-1.19.0 release (#766)


- - - - -
f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00
Support unicode operators, proper modules

Unicode operators are a pretty big thing in Haskell, so supporting linking them
seems like it outweighs the cost of the extra machinery to force Attoparsec to
look for unicode.

Fixes haskell/haddock#458.

- - - - -
09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00
Remove bang pattern

- - - - -
d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00
fix test

- - - - -
d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00
haddock-test: Be more explicit which packages to pass

We now pass `-hide-all-packages` to haddock when invoking the
testsuite. This ensures we don't accidentally pick up any dependencies
up through ghc.env files.

- - - - -
0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00
Revert "fix test"

This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197.

- - - - -
52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00
Fix Bug548 for real

- - - - -
89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00
Hyperlinker: Links for TyOps, class methods and associated types

- - - - -
d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00
Updates for haskell/haddock#13324

- - - - -
6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00
Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1

- - - - -
c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00
Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1

- - - - -
500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00
Update to QC 2.11

- - - - -
ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00
Restore backward-compat with base-4.5 through base-4.8

- - - - -
baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00
Bump lower bound for haddock-library

- - - - -
10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00
Haddock: Straighten out base bound

- - - - -
a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00
extractDecl: Extract constructor patterns from data family instances (#776)

* extractDecl: Allow extraction of data family instance constructors

* extractDecl: extract data family instance constructors

- - - - -
ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00
Readme: Update GHC version (#778)


- - - - -
8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for definition lists

- - - - -
425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for links

- - - - -
d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00
Add fixture test for inline links

- - - - -
f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00
fixtures: Slightly unmangle output

- - - - -
0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00
fixtures: Prevent stdout buffering

- - - - -
1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00
haddock-library.cabal: Clean up GHC options

- - - - -
066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00
Make a proper definition for the <link> parser

- - - - -
573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00
Show where instances are defined (#748)

* Indicate source module of instances

Above instance, we now also display a link to the module where the
instance was defined. This is sometimes helpful in figuring out
what to import.

* Source module for type/data families too

* Remove parens

* Accept tests

- - - - -
99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00
Prepare changelog for next release

- - - - -
482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00
Useful cost centres, timers and allocation counters (#785)

* Add some useful cost-centres for profiling

* Add withTiming for each haddock phase

Invoking haddock with `--optghc=-ddump-timings` now shows the amount
of time spent and the number of allocated bytes for each phase.

- - - - -
773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00
@since includes package name (#749)

* Metadoc stores a package name

This means that '@since' annotations can be package aware.

* Get the package name the right way

This should extract the package name for `@since` annotations the
right way. I had to move `modulePackageInfo` around to do this and,
in the process, I took the liberty to update it.

Since it appears that finding the package name is something that can
fail, I added a warning for this case.

* Silence warnings

* Hide package for local 'since' annotations

As discussed, this is still the usual case (and we should avoid being
noisy for it).

Although this commit is large, it is basically only about threading a
'Maybe Package' from 'Haddock.render' all the way to
'Haddock.Backends.Xhtml.DocMarkup.renderMeta'.

* Bump binary interface version

* Add a '--since-qual' option

This controls when to qualify since annotations with the package they
come from. The default is always, but I've left an 'external' variant
where only those annotations coming from outside of the current
package are qualified.

* Make ParserSpec work

* Make Fixtures work

* Use package name even if package version is not available

The @since stuff needs only the package name passed in, so it
makes sense to not be forced to pass in a version too.

- - - - -
e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00
haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0

- - - - -
8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00
Bump haddock and haddock-api to 2.20.0

- - - - -
5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00
Clear search string on hide for haskell/haddock#781 (#789)


- - - - -
920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00
Travis: Build with ghc-8.4.2 (#793)


- - - - -
a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00
Match changes in GHC for D4199

Removing HasSourceText and SourceTextX classes.

- - - - -
ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00
Match GHC changes for TTG

- - - - -
739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00
Match GHC for TTG implemented on HsBinds, D4581

- - - - -
2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00
Bump upper bound on base to < 4.13

See https://ghc.haskell.org/trac/ghc/ticket/15018.

- - - - -
a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00
Don't treat fixity signatures like declarations

- - - - -
d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00
Add regression test for haskell/haddock#413

Fixes haskell/haddock#413.

- - - - -
c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00
Improve the Hoogle backend's treatment of type families (#808)

Fixes parts 1 and 2 of haskell/haddock#806.
- - - - -
d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00
Replace 'attoparsec' with 'parsec' (#799)

* Remove attoparsec with parsec and start fixing failed parses

* Make tests pass

* Fix encoding issues

The Haddock parser no longer needs to worry about bytestrings. All
the internal parsing work in haddock-library happens over 'Text'.

* Remove attoparsec vendor

* Fix stuff broken in 'attoparsec' -> 'parsec'

* hyperlinks
* codeblocks
* examples

Pretty much all issues are due to attoparsec's backtracking failure
behaviour vs. parsec's non-backtracking failure behaviour.

* Fix small TODOs

* Missing quote + Haddocks

* Better handle spaces before/after paragraphs

* Address review comments

- - - - -
fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00
Match changes in GHC for TTG

- - - - -
06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00
Merge branch 'ghc-head' with 'ghc-8.4'

- - - - -
879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00
Filter out CRLFs in hyperlinker backend (#813)

This prevents spurious lines from appearing in the final output.
- - - - -
3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00
Add docs for some DocH constructors (#814)


- - - - -
0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00
Remove 'TokenGroup' from Hyperlinker (#818)

Since the hyperlinker backend now relies on the GHC tokenizer, something
like 'Bar.Baz.foo' already gets bunched together into one token (as
opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo').
- - - - -
8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00
Renamer: Warn about out of scope identifiers. (#819)


- - - - -
ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00
Remove Hoogle backend hack that butchers infix datatype names

- - - - -
03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00
Wibbles

- - - - -
b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00
Use the response file utilities defined in `base` (#821)

Summary: The response file related modules were recently copied from
`haddock` into `base`. This patch removes them from `haddock`.

GHC Trac Issues: haskell/haddock#13896
- - - - -
9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00
Account for refactoring of LitString

- - - - -
ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00
Merge pull request haskell/haddock#826 from haskell/T825

Remove Hoogle backend hack that butchers infix datatype names
- - - - -
0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00
Use `ClassOpSig` instead of `TypeSig` for class methods (#835)

* Fix minimal pragma handling

Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834.

* Accept html-test output

- - - - -
15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00
Adjust to new HsDocString internals

- - - - -
6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00
Remove ParallelArrays and Data Parallel Haskell

- - - - -
0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00
DerivingVia changes

- - - - -
0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00
Bump a few dependency bounds (#845)


- - - - -
5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00
Improve hyperlinker's 'spanToNewline' (#846)

'spanToNewline' is used to help break apart the source into lines which
can then be partioned into CPP and non-CPP chunks. It is important that
'spanToNewline' not break apart tokens, so it needs to properly handle
things like

  * block comments, possibly nested
  * string literals, possibly multi-line
  * CPP macros, possibly multi-line

String literals in particular were not being properly handled. The fix
is to to fall back in 'Text.Read.lex' to help lex things that are not
comments.

Fixes haskell/haddock#837.
- - - - -
9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00
Extract docs from strict/unpacked constructor args (#839)

This fixes haskell/haddock#836.
- - - - -
70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00
Renamer: Warn about ambiguous identifiers (#831)

* Renamer: Warn about ambiguous identifiers

Example:

    Warning: 'elem' is ambiguous. It is defined
        * in ‘Data.Foldable’
        * at /home/simon/tmp/hdk/src/Lib.hs:7:1
        You may be able to disambiguate the identifier by qualifying it or
        by hiding some imports.
        Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1

Fixes haskell/haddock#830.

* Deduplicate warnings

Fixes haskell/haddock#832.

- - - - -
495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00
Use the response file utilities defined in `base` (#821)

Summary: The response file related modules were recently copied from
`haddock` into `base`. This patch removes them from `haddock`.

GHC Trac Issues: haskell/haddock#13896
- - - - -
81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00
Account for refactoring of LitString

- - - - -
7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00
Adjust to new HsDocString internals

- - - - -
bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00
Remove ParallelArrays and Data Parallel Haskell

- - - - -
5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00
DerivingVia changes

- - - - -
73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00
Extract docs from strict/unpacked constructor args (#839)

This fixes haskell/haddock#836.
- - - - -
4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Remove `ITtildehsh` token

- - - - -
b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00
Filter out CRLFs in hyperlinker backend (#813)

This prevents spurious lines from appearing in the final output.
- - - - -
9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Add docs for some DocH constructors (#814)


- - - - -
8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00
Remove 'TokenGroup' from Hyperlinker (#818)

Since the hyperlinker backend now relies on the GHC tokenizer, something
like 'Bar.Baz.foo' already gets bunched together into one token (as
opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo').
- - - - -
29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Renamer: Warn about out of scope identifiers. (#819)


- - - - -
2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00
Remove Hoogle backend hack that butchers infix datatype names

- - - - -
a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00
Wibbles

- - - - -
a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00
Use `ClassOpSig` instead of `TypeSig` for class methods (#835)

* Fix minimal pragma handling

Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834.

* Accept html-test output

- - - - -
8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00
Bump a few dependency bounds (#845)


- - - - -
4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00
Improve hyperlinker's 'spanToNewline' (#846)

'spanToNewline' is used to help break apart the source into lines which
can then be partioned into CPP and non-CPP chunks. It is important that
'spanToNewline' not break apart tokens, so it needs to properly handle
things like

  * block comments, possibly nested
  * string literals, possibly multi-line
  * CPP macros, possibly multi-line

String literals in particular were not being properly handled. The fix
is to to fall back in 'Text.Read.lex' to help lex things that are not
comments.

Fixes haskell/haddock#837.
- - - - -
311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Renamer: Warn about ambiguous identifiers (#831)

* Renamer: Warn about ambiguous identifiers

Example:

    Warning: 'elem' is ambiguous. It is defined
        * in ‘Data.Foldable’
        * at /home/simon/tmp/hdk/src/Lib.hs:7:1
        You may be able to disambiguate the identifier by qualifying it or
        by hiding some imports.
        Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1

Fixes haskell/haddock#830.

* Deduplicate warnings

Fixes haskell/haddock#832.

- - - - -
d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Complete FixitySig and FamilyDecl pattern matches

- - - - -
055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00
Fix redundant import warnings

- - - - -
f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00
html-test: Accept output

- - - - -
04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00
Bump bounds on Cabal

- - - - -
0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00
Merge branch 'ghc-head' into ghc-head-update-3

- - - - -
c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00
Bump ghc bound for haddock-api spec test-suite

- - - - -
119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00
Travis: `--allow-newer` for all packages

- - - - -
0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00
Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3

Update ghc-head
- - - - -
5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00
Improved handling of interfaces in 'haddock-test' (#851)

This should now work with an inplace GHC where (for instance)
HTML directories may not be properly recorded in the package DB.
- - - - -
96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00
Handle -XStarIsType

- - - - -
e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00
Revert unintentional reversion of fix of haskell/haddock#548

- - - - -
01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00
Match changes in GHC for haskell/haddock#14259

- - - - -
7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00
Bump GHC version to 8.6

- - - - -
11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00
Remove HsEqTy and XEqTy

- - - - -
b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00
Revert "Bump GHC version to 8.6"

This was applied to the wrong branch; there's now a `ghc-8.6` branch;
ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version.
The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7

This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1.

- - - - -
f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00
Update Travis CI job

- - - - -
ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00
Drop GHC HEAD from CI and update GHC to 8.4.3

It's a waste of resource to even try to build this branch w/ ghc-head;
so let's not do that...

- - - - -
41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00
Bump GHC version to 8.7

- - - - -
8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00
Update CI job to use GHC 8.7.*

- - - - -
b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00
README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

- - - - -
f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00
Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.
- - - - -
a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00
Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

- - - - -
13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00
Match XFieldOcc rename in GHC

Trac haskell/haddock#15386

- - - - -
c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00
haddock-library: Bump bounds for containers

- - - - -
722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00
tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

- - - - -
f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00
Fix HEAD html-test (#860)

* Update tests for 'StarIsType'

* Accept tests

* Revert "Update tests for 'StarIsType'"

This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a.

- - - - -
394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00
haddock-library: Bump bounds for containers

- - - - -
1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00
Add HEAD.hackage overlay (#887)

* Add HEAD.hackage overlay

* Add HCPKG variable

- - - - -
c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00
Refactor handling of parens in types (#874)

* Fix type parenthesization in Hoogle backend

Ported the logic in the HTML and LaTeX backends for adding in parens
into something top-level in 'GhcUtil'. Calling that from the Hoogle
backend fixes haskell/haddock#873.

* Remove parenthesizing logic from LaTeX and XHTML backends

Now, the only times that parenthesis in types are added in any backend
is through the explicit 'HsParTy' constructor. Precedence is also
represented as its own datatype.

* List out cases explicitly vs. catch-all

* Fix printing of parens for QuantifiedConstraints

The priority of printing 'forall' types was just one too high.

Fixes haskell/haddock#877.

* Accept HTML output for quantified contexts test

- - - - -
c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00
Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

- - - - -
24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00
Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.
- - - - -
cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00
README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

(cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c)

- - - - -
133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00
Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.

(cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce)

- - - - -
11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00
Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

(cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0)

- - - - -
de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00
tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

(cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9)

- - - - -
6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00
Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

(cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4)

- - - - -
1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00
Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.

(cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05)

- - - - -
69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00
Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)
- - - - -
6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00
Misc tests (#858)

* More tests

* spliced types
* constructor/pattern argument docs
* strictness marks on fields with argument docs

* latex test cases need seperate directory

* Accept tests

- - - - -
92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00
Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)

(cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370)

- - - - -
981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00
Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

- - - - -
27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00
Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

(cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071)

- - - - -
49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00
Update the ghc-8.6 branch (#889)

* Revert "Bump GHC version to 8.6"

This was applied to the wrong branch; there's now a `ghc-8.6` branch;
ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version.
The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7

This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1.

* README updates (#856)

* README: Remove mentions of master branch

* README: Add instructions for using html-test

* README: Change command to run _all_ the testsuites

* README: Add project overview section

(cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c)

* Export more fixities for Hoogle (#871)

This exports fixities for more things, including class methods and
type-level operators.

(cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce)

* Avoid line breaks due to line length in Hoogle (#868)

* Avoid line breaks due to line length in Hoogle

Hoogle operates in a line-oriented fashion, so we should avoid ever
breaking due to long lines.

One way of doing this non-intrusively is to modify the 'DynFlags' that
are threaded through the 'Hoogle' module (note this is anyways only
passed through for use in the various 'showSDoc' functions).

* Amend test case

(cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0)

* tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880)

* tyThingToLHsDecls: Preserve type synonyms that contain a forall

Fixes haskell/haddock#879.

* Add Note [Invariant: Never expand type synonyms]

* Clarify Note [Invariant: Never expand type synonyms]

(cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9)

* Fix HEAD html-test (#860)

* Update tests for 'StarIsType'

* Accept tests

* Revert "Update tests for 'StarIsType'"

This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a.

* Refactor handling of parens in types (#874)

* Fix type parenthesization in Hoogle backend

Ported the logic in the HTML and LaTeX backends for adding in parens
into something top-level in 'GhcUtil'. Calling that from the Hoogle
backend fixes haskell/haddock#873.

* Remove parenthesizing logic from LaTeX and XHTML backends

Now, the only times that parenthesis in types are added in any backend
is through the explicit 'HsParTy' constructor. Precedence is also
represented as its own datatype.

* List out cases explicitly vs. catch-all

* Fix printing of parens for QuantifiedConstraints

The priority of printing 'forall' types was just one too high.

Fixes haskell/haddock#877.

* Accept HTML output for quantified contexts test

* Preserve docs on type family instances (#867)

* Preserve docs on type family instances

The only problem was that the instance location was slightly off
for type family instances.

* Accept output

(cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4)

* Fix broken instance source links (#869)

The problem manifests itself in instances that are defined in
modules other than the module where the class is defined. The fix
is just to thread through the 'Module' of the instance further
along.

Since orphan instances appear to already have been working, I didn't
do anything there.

(cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05)

* Add some more unicode related tests (#872)

This has been fixed for sure ever since we switched from attoparsec to
parsec. Parts of it may have been working before that, but there was a
point where this would have failed (see haskell/haddock#191).

A regression test never hurt anyone. :)

(cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370)

* Misc tests (#858)

* More tests

* spliced types
* constructor/pattern argument docs
* strictness marks on fields with argument docs

* latex test cases need seperate directory

* Accept tests

* Additional tests for the identifier parser (#816)

* Add tests for the identifier parser

* docs: Clarify how to delimit identifiers

(cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071)

- - - - -
5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00
Revert "Revert "Bump GHC version to 8.6""

That commit didn't belong onto the ghc-8.6 branch.

This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967.

- - - - -
2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00
Don't warn about ambiguous identifiers when the candidate names belong to the same type

This also changes the defaulting heuristic for ambiguous identifiers.
We now prefer local names primarily, and type constructors or class
names secondarily.

Partially fixes haskell/haddock#854.

- - - - -
fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00
outOfScope: Recommend qualifying the identifier

- - - - -
acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00
outOfScope: Recommend qualifying the identifier

(cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7)

- - - - -
1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00
Don't warn about ambiguous identifiers when the candidate names belong to the same type

This also changes the defaulting heuristic for ambiguous identifiers.
We now prefer local names primarily, and type constructors or class
names secondarily.

Partially fixes haskell/haddock#854.

(cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f)

- - - - -
48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00
Add # as a special character (#884)

'#' has special meaning used for anchors and can be escaped using backslash.
Therefore it would be nice to be listed as special characters.
- - - - -
5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00
Let `haddock-test` bypass interface version check (#890)

This means `haddock-test` might

  * crash during deserialization
  * deserialize incorrectly

Still - it means things _might_ work where they were previously sure
not to.
- - - - -
27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00
Avoid "invalid argument (invalid character)" on non-unicode Windows (#892)

Steps to reproduce and the error message
====

```
> stack haddock basement
... snip ...
    Warning: 'A' is out of scope.
    Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character)
```

Environment
====

OS: Windows 10 ver. 1709
haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD)
GHC: 8.4.3
stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2

Related pull request
====

https://github.com/haskell/haddock/pull/566
- - - - -
6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00
Accumulate explicitly which modules to load for 'attachInstances'

The old approach to fixing haskell/haddock#469, while correct, consumes a lot of
memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However,
'getNameToInstancesIndex' takes that environment and compresses it down
to a much smaller 'ModuleSet'.

Now, we compute that 'ModuleSet' explicitly as we process modules. That
way we can just tell 'getNameToInstancesIndex' what modules to load
(instead of it trying to compute that information from the interactive
context).

- - - - -
8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00
eqTyCon_RDR now lives in TysWiredIn

After GHC commit
http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071

- - - - -
1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00
Match XFieldOcc rename in GHC

Trac haskell/haddock#15386

(cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6)

- - - - -
8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00
Update against new HsImplicitBndrs

- - - - -
e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00
Latex type families (#734)

* Support for type families in LaTeX

The code is ported over from the XHTML backend.

* Refactor XHTML and LaTeX family handling

This is mostly a consolidation effort: stripping extra exports,
inlining some short definitions, and trying to make the backends
match.

The LaTeX backend now has preliminary support for data families,
although the only the data instance head is printed (not the actual constructors).

Both backends also now use "newtype" for newtype data family
instances.

* Add some tests

- - - - -
0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00
Make --package-version optional for --hoogle generation (#899)

* Make --package-version optional for --hoogle generation

* Import mkVersion

* It's makeVersion not mkVersion

- - - - -
d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00
Remove unnecessary backslashes from docs (#908)

On
https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters
the backslash and backtick special characters showed up with an extra
backslash before them – I think the escaping is not (or no longer)
needed for those characters in rst.
- - - - -
7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900
- - - - -
aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900
- - - - -
ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00
Better test output when Haddock crashes on a test (#902)

In particular: we report the tests that crashed seperately from the tests
that produced incorrect output. In order for tests to pass (and exit 0),
they must not crash and must produce the right output.
- - - - -
4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00
Fix a typo (#878)


- - - - -
4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00
Add ITcomment_line_prag token to Hyperlinker Parser

This token is necessary for parsing #line pragmas inside nested comments.

Reviewers: bgamari

Reviewed By: bgamari

Differential Revision: https://phabricator.haskell.org/D4935

- - - - -
9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00
Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances

Accumulate explicitly which modules to load for 'attachInstances'
- - - - -
d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00
Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head

- - - - -
14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00
Accumulate explicitly which modules to load for 'attachInstances'

The old approach to fixing haskell/haddock#469, while correct, consumes a lot of
memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However,
'getNameToInstancesIndex' takes that environment and compresses it down
to a much smaller 'ModuleSet'.

Now, we compute that 'ModuleSet' explicitly as we process modules. That
way we can just tell 'getNameToInstancesIndex' what modules to load
(instead of it trying to compute that information from the interactive
context).

(cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1)

- - - - -
438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00
Load plugins when starting a GHC session (#905)

Fixes haskell/haddock#900

(cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d)

- - - - -
a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00
Better rendering of unboxed sums/tuples

* adds space after/before the '#' marks
* properly reify 'HsSumTy' in 'synifyType'

- - - - -
88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00
Handle promoted tuples in 'synifyType'

When we have a fully applied promoted tuple, we can expand it out properly.

- - - - -
fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00
Accept test cases

- - - - -
6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00
Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff

Better rendering of unboxed sums, unboxed tuples, promoted tuples.
- - - - -
181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00
Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6

- - - - -
3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00
Properly synify promoted list types

We reconstruct promoted list literals whenever possible. That means
that 'synifyType' produces

   '[Int, Bool, ()]

instead of

   (Int ': (() ': (Bool ': ([] :: [Type]))))

- - - - -
b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00
Only look at visible types when synifying a 'HsListTy'

The other types are still looked at when considering whether to make
a kind signature or not.

- - - - -
a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00
Merge pull request haskell/haddock#922 from harpocrates/promoted-lists

Properly synify promoted list types
- - - - -
0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00
Update according to GHC Core changes

- - - - -
7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00
update dataFullSig to work with Co Quantification

This should have been in the previous patch, but wasn't.

- - - - -
cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00
Fix/add to various docs

* Add documentation for a bunch of previously undocumented
  options (fixes haskell/haddock#870)
* Extend the documentation of `--hoogle` considerably (see haskell/haddock#807)
* Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912)
* Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780)

- - - - -
ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00
Update Travis

- - - - -
d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00
Accept failing tests

Also silence orphan warnings.

- - - - -
f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00
Bump haddock-api-2.21.0, haddock-library-1.7.0

* Update CHANGELOGS
* Update new versions in Cabal files
* Purge references to ghc-8.4/master branches in README

- - - - -
3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00
Turn haddock-library into a minor release

Fix some version bounds in haddock-library too.

- - - - -
b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00
keep cabal.project file

- - - - -
4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00
Build on 7.4 and 7.8

- - - - -
99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00
Minor tweak to package description

- - - - -
a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00
Merge pull request haskell/haddock#945

haddock-api 2.21.0 and haddock-library 1.6.1 release
- - - - -
2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00
Bump haddock-library to 1.7.0

The 1.6.1 release should've been a major bump, since types in
the `Documentation.Haddock.Parser.Monad` module changed. This version
makes that module internal (as it morally should be).

- - - - -
ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00
Merge branch 'ghc-8.4' into ghc-8.6

- - - - -
2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00
Merge branch 'ghc-8.6' into ghc-head

- - - - -
a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00
Latex type families (#734)

* Support for type families in LaTeX

The code is ported over from the XHTML backend.

* Refactor XHTML and LaTeX family handling

This is mostly a consolidation effort: stripping extra exports,
inlining some short definitions, and trying to make the backends
match.

The LaTeX backend now has preliminary support for data families,
although the only the data instance head is printed (not the actual constructors).

Both backends also now use "newtype" for newtype data family
instances.

* Add some tests

- - - - -
63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00
Update changelog

- - - - -
099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00
Merge pull request haskell/haddock#942 from harpocrates/update-docs

Fix & add to documentation
- - - - -
0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00
Set UTF-8 encoding before writing files (#934)

This should fix haskell/haddock#929, as well as guard against future problems of this
sort in other places. Basically replaces 'writeFile' (which selects the
users default locale) with 'writeUtf8File' (which always uses utf8).
- - - - -
83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00
Output pattern synonyms in Hoogle backend (#947)

* Output pattern synonyms in Hoogle backend

We were previously weren't outputting _any_ pattern synonyms, bundled or
not. Now, we output both.

Fixes haskell/haddock#946.

* Update changelog

- - - - -
81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00
Release `haddock{,-api}-2.22.0`

This version will accompany ghc-8.6.2

- - - - -
9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00
Add NewOcean theme

And make it the default theme.

- - - - -
7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Improve appearance and readability

These changes include:

- use latest Haskell's logo colors
- decrease #content width to improve readability
- use nicer font
- improve sizes and distances

- - - - -
37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00
Include custom font in the html head

- - - - -
1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Update html test reference files

- - - - -
53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00
Make it responsive

- It makes small screens taking more space than larger ones
- fixes a few issues present in small screens currently
- make it look good across different screen sizes.

- - - - -
6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make the style consistent with hackage

Several things are addressed here:

- better responsive behaviour on the header
- better space usage
- consistent colors overall
- other nit PR comments

- - - - -
3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Place the package name before the menu links

This supports the expected responsive menu design, where the
package name appears above the menu links.

- - - - -
cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update html-test reference files

The package name element in the package-header is now a div instead of a
paragraph, and it is now above the menu ul.links instead of below.

- - - - -
2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve synopsis style and code

- Use CSS3 instead of loading pictures to show "+" and "-" symbols
- Drop redundant code

- - - - -
0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Decrease space between code blocks

There was too much space between code blocks as pointed out by
reviewers.

- - - - -
85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Add an initial-scale property to all haddock pages

This solves an issue reported about the content looking
incredibly small on mobile devices.

- - - - -
c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Address several PR comments

- Darken text color like done for hackage
- Move synopsis to left side
- Make table of contents stick to the left on wide screens
- Wrap links to avoid page overflow
- Improve expand/collapse buttons
- Fix issue with content size on mobile devices
- Fix issue with font-size on landscape mode
- Increase width of the content
- Change colors of table of contents and synopsis
- Etc

- - - - -
e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make synopsis scrollable on wide screens

When the synopsis is longer than the screen, you can’t see its end
and you can't scroll down either, making the content unreachable.

- - - - -
1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve information density

- Reduce font size
- Improve space between and within code blocks
- Improve alignments
- Improve spacing within sub-blocks

- - - - -
bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Minor adjustments

Bring in some adjustments made to hackage:
- link colors
- page header show everything when package title is too long

- - - - -
10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Fix responsive triggers overlap issue

The min and max width triggers have the same values,
which caused the style resolution to take an intersection of
both style declarations when the screen resolution had the size
of the limts (say 1280px), causing an odd behaviour and look.

- - - - -
95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00
Fix issue with menu alignment on firefox

Reported and described here:
https://github.com/haskell/haddock/pull/721#issuecomment-374668869

- - - - -
dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00
Changelog entry for NewOcean

- - - - -
27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00
html-test --accept

- - - - -
83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00
Avoid name shadowing

- - - - -
231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update font to PT Sans

Also migrate some general text related changes from hackage.

- - - - -
313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Use 'flex' to fix header alignment

- - - - -
5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Misc of tweaks

- Update link colors to hackage scheme
- Tune spacing between content elements
- Update footer style
- Fix and improve code blocks identation

- - - - -
b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update font in Xhtml.hs to PT Sans

- - - - -
78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Improve code blocks styling

- Fix and improve spacing
- Improve colors and borders

- - - - -
81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Make package-header caption backward-compatible

The current html generator of this branch wraps the package-header
caption as a div, which does not work (without style adjustments) with
the old themes. Changing it from div to span does the trick, without
needing to adjust the old stylesheets.

- - - - -
dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00
Update test-suite reference html pages

- - - - -
393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00
Accept tests

- - - - -
a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00
Fix CHANGELOG

- - - - -
8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00
Update 'data-files' to include NewOcean stuff

- - - - -
1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00
Fix typo in a warning

- - - - -
009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00
Update JS dependencies

This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with
some more serious vulnerabilities that nobody seems to have noticed.

- - - - -
051994db by Alec Theriault at 2018-10-24T17:31:09-07:00
Resurrect the style-switcher

This fixes haskell/haddock#810. Looks like things were broken during the quickjump
refactor of the JS.

For the (git) record: I do not think the style switcher is a good idea.
I'm fixing it for the same reason @mzero added it; as an answer to

  "rumblings from some that they didn't want their pixels changed on bit"

- - - - -
2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00
Fix copy-pasta error in data-files

- - - - -
ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00
Fix the synopsis button

Here's these changes are supposed to do:

  * put the synopsis back on the right side
  * properly have it on the edge of the screen on wide screens
  * adjust the background of the synopsis to match the button
    (otherwise the grey blends in with what is underneath)
  * get rid of the dotted purple line
  * the synopsis contents are now scrollable even when in wide
    screens (this has been a long-standing bug)

- - - - -
883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00
Avoid more conflicts in generated ids  (#954)

This fixes haskell/haddock#953 by passing more names into the generated ids.


- - - - -
ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00
Don't hide bullets in method docs

I think thst CSS was meant only to deal with fields and the
effect on bullets was accidental.

Fixes haskell/haddock#926.

- - - - -
9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00
Indent more things + slightly smaller font

- - - - -
b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00
Merge branch 'ghc-8.6' into wip/new-ocean

- - - - -
096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00
Accept HTML output

- - - - -
2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00
User manual + stuff for building GHC docs

- - - - -
46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00
Make 'Contents' in NewOcean scrollable

This only happens if the contents block on the left is so big that it
doesn't fit (vertically) on the page. If that happens, we want it to
be scrollable.

- - - - -
3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00
Revert "Make 'Contents' in NewOcean scrollable"

This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922.

I missed the fact this also forces the 'Contents' to always go down
to the bottom of the page.

- - - - -
ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00
Avoid some partiality

AFAICT this wasn't causing any crashes, but that's mostly because
we happen not to be forcing `pkgStr` when it would diverge. We come
dangerously close to doing that in `ppHtmlIndex`.

Fixes haskell/haddock#569.

- - - - -
6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00
Fix documentation in `haddock-api` (#957)

* Fix misplaced Haddocks in Haddock itself

Haddock should be able to generate documentation for 'haddock-api'
again.

* Make CI check that documentation can be built.

* Add back a doc that is OK

- - - - -
5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00
More explicit foralls (GHC Proposal 0007)

- - - - -
8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00
Only run MathJax on entities with "mathjax" class (#960)

Correspondingly, we wrap all inline/diplay math in

    <span class="mathjax"> ... the math .... </span>

This fixes haskell/haddock#959.
- - - - -
bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00
Deduplicate some work in 'AttachInstances'

Perf only change:

  * avoid needlessly union-ing maps
  * avoid synify-ing instances twice

Took this opportunity to add some docs too

- - - - -
cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00
Specialize some SYB functions

Perf only change:

  * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint
  * Manually specialize the needlessly general type of 'specializeTyVarBndrs'

- - - - -
4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00
Improve perf of renaming

Perf only change:

  * don't look up type variable names (they're never in the environment)
  * use a difference list for accumulating missing names
  * more efficient 'Functor'/'Applicative' instances for 'RnM'

- - - - -
4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00
Faster 'Text' driven parser combinators

Perf only change:

  * use 'getParserState'/'setParserState' to make 'Text'-optimized
    parser combinators
  * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}'

- - - - -
fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00
Support hyperlink labels with inline markup

The parser for pictures hasn't been properly adjusted yet.

- - - - -
c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00
Support (and flatten) inline markup in image links

Inline markup is supported in image links but, as per the [commonmark
recommendation][0], it is stripped back to a plain text representation.

  [0]: https://spec.commonmark.org/0.28/#example-547

- - - - -
d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00
Accept test case

- - - - -
8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00
Fix/add to haddock-library test suite

- - - - -
e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00
Bump version bounds

- - - - -
644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00
Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks

Inline markup in markdown-style links and images
- - - - -
e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00
Fix issues around plus/minus

  * swap the minimize unicode to something more intuitive
  * use new unicode expander/collapser for instance lists
  * address some alignment issues in the "index" page

- - - - -
b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00
Allow "Contents" summary to scroll in a fixed div

In the unfortunate event that the "Contents" summary doesn't fit
vertically (like in the "Prelude"), it will be scrollable.

- - - - -
ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00
Accept HTML output changes

- - - - -
82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00
overflow-y 'scroll' -> 'auto'

- - - - -
571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00
Clicking on "Contents" navigates to top of page

- - - - -
8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00
Space out functions more

Also, functions and data decls now have the same space before and after
them.

- - - - -
cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00
Merge branch 'ghc-8.6' into wip/new-ocean

- - - - -
65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00
Update changelog

- - - - -
20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00
Replace oplus/ominus expander/collapser icons with triangles

- - - - -
16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00
Merge pull request haskell/haddock#949 from haskell/wip/new-ocean

Introduce NewOcean theme.
- - - - -
357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00
Merge branch 'ghc-8.6' into ghc-head

- - - - -
de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00
Rename 'NewOcean' theme to 'Linuwial'

- - - - -
954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00
Add blockquote styling

Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server.

Fixes haskell/haddock#967.

- - - - -
d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00
Fix some broken links (#15733)

Summary:
For links in subpackages as well.
https://phabricator.haskell.org/D5257

Test Plan: Manually verify links

Reviewers: mpickering, bgamari, osa1

Reviewed By: osa1

GHC Trac Issues: haskell/haddock#15733

Differential Revision: https://phabricator.haskell.org/D5262

- - - - -
41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00
Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change

It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62.

- - - - -
c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00
Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag

Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change
- - - - -
6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00
[TTG: Handling Source Locations] Foundation and Pat
Trac Issues haskell/haddock#15495

This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A).
- the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced
- some instances of `HasSrcSpan` are introduced
- some constructors `L` are replaced with `cL`
- some patterns `L` are replaced with `dL->L` view pattern
- some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`)

- - - - -
7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00
More uniform handling of `forall`'s in HTML/LaTeX

 * don't forget to print explicit `forall`'s when there are arg docs
 * when printing an explicit `forall`, print all tyvars

Fixes haskell/haddock#973

- - - - -
d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00
Fix warnings, accept output

* remove redundant imports (only brought to light due to recent work for
  improving redundant import detection)
* fix a bug that was casuing exports to appear in reverse order
* fix something in haddock-library that prevented compilation on old GHC's

- - - - -
a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00
Output better debug infromation on internal error in extractDecl

This will make investigation of haskell/haddock#979 easier

- - - - -
2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00
Refactor names + unused functions (#982)

This commit should not introduce any change in functionality!

  * consistently use `getOccString` to convert `Name`s to strings
  * compare names directly when possible (instead of comparing strings)
  * get rid of unused utility functions
- - - - -
e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00
Load plugins when compiling each module (#983)

* WIP: Load (typechecker) plugins from language pragmas

* Revert "Load plugins when starting a GHC session (#905)"

This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193.

* Simplify plugin initialization code

- - - - -
96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00
Properly synify and render promoted type variables  (#985)

* Synify and render properly promoted type variables

Fixes haskell/haddock#923.

* Accept output

- - - - -
23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00
Remove `haddock-test`'s dep. on `syb` (#987)

The functionality is easily inlined into one short function: `gmapEverywhere`.
This doesn't warrant pulling in another package.
- - - - -
d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00
Address deprecation warnings in `haddock-test` (#988)

Fixes haskell/haddock#885.
- - - - -
4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00
Visible kind application haddock update

- - - - -
ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00
Print kinded tyvars in constructors for Hoogle (#993)

Fixes haskell/haddock#992
- - - - -
2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00
Accept new output `GHC.Maybe` -> `Data.Maybe` (#996)

Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe"
is marked as `not-home`. That changes around some test output.
- - - - -
055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00
Lone typofix
- - - - -
01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00
Keep forall on H98 existential data constructors (#1003)

The information about whether or not there is a source-level `forall`
is already available on a `ConDecl` (as `con_forall`), so we should use
it instead of always assuming `False`!

Fixes haskell/haddock#1002.
- - - - -
f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00
Fix haskell/haddock#1004 with a pinch of dropForAlls

- - - - -
5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00
Loosen 'QuickCheck' and 'hspec' bounds

It looks like the new versions don't cause any breakage
and loosening the bounds helps deps fit in one stack resolver.

- - - - -
3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00
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  haskell/haddock#998)
 * restructure temporary folder logic for `.hi`/`.hie` model
- - - - -
2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00
Update/modernise haddock-library.cabal file

- - - - -
62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00
Tentatively declare support for unreleased base-4.13/ghc-8.8

- - - - -
6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00
Normalise LICENSE text w/ cabal's BSD2 template

Also, correct the `.cabal` files to advertise `BSD2` instead
of the incorrect `BSD3` license.

- - - - -
0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00
CI: fetch GHC from validate artifact

Should help make CI be less broken

- - - - -
6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00
Fix some Hyperlinker test suite fallout

* Amend `ParserSpec` to match new Hyperlinker API
    - pass in compiler info
    - strip out null tokens

* Make `hypsrc-test` pass reliably
    - strip out `local-*` ids
    - strip out `line-*` ids from the `ClangCppBug` test
    - re-accept output

- - - - -
ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00
Update README instructions for Stack

No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock.
- - - - -
723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00
Remove `Documentation.Haddock.Utf8`

The circumstances under which this module appeared are completely gone.
The Hyperlinker backend no longer needs this module (it uses the more
efficient `Encoding` module from `ghc`).

Why no deprecation? Because this module really shouldn't exist!

  - It isn't used in `haddock-library`/`haddock-api` anymore
  - It was copy pasted directly from `utf8-string`
  - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding`

- - - - -
51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00
Miscellaneous improvements to `Convert` (#1020)

Now that Haddock is moving towards working entirely over `.hi` and `.hie` files,
all declarations and types are going to be synthesized via the `Convert` module.
In preparation for this change, here are a bunch of fixes to this module:

  * Add kind annotations to type variables in `forall`'s whose kind is not `Type`,
    unless the kind can be inferred from some later use of the variable. See
    `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this.

  * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with
    what GHC's `toIfaceTypeX` does and checking the first argument of
    `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker
    (see `isPredTy`). 

  * Beef up the logic around figuring out when an explicit `forall` is needed. This
    includes: observing if any of the type variables will need kind signatures, if the
    inferred type variable order _without_ a forall will still match the one GHC
    claims, and some other small things.

  * Add some (not yet used) functionality for default levity polymorphic type
    signatures. This functionality similar to `fprint-explicit-runtime-reps`.

Couple other smaller fixes only worth mentioning:

  * Show the family result signature only when it isn't `Type`
  * Fix rendering of implicit parameters in the LaTeX and Hoogle backends
  * Better handling of the return kind of polykinded H98 data declarations
  * Class decls produced by `tyThingToLHsDecl` now contain associated type
    defaults and default method signatures when appropriate
  * Filter out more `forall`'s in pattern synonyms
- - - - -
841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00
Make a fixture of weird parsing of lists (#997)

The second example is interesting.
If there's a list directly after the header, and that list has
deeper structure, the parser is confused: It finds two lists:

 - One with the first nested element,
 - everything after it

I'm not trying to fix this, as I'm not even sure this is a bug,
and not a feature.

- - - - -
7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00
Fix haskell/haddock#1015 with dataConUserTyVars (#1022)

The central trick in this patch is to use `dataConUserTyVars` instead of
`univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in
a way that's more faithful to how the user originally wrote it.

Fixes haskell/haddock#1015.
- - - - -
ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00
Changes from haskell/haddock#14579

We now have a top-level `tyConAppNeedsKindSig` function, which means
that we can delete lots of code in `Convert`.

- - - - -
1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00
Matching changes in GHC for haskell/haddock#16236

- - - - -
ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00
Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise

Normalise LICENSE text w/ cabal's BSD2 template
- - - - -
5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00
Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head

- - - - -
c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00
Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027)

This means that `html-test`, `latex-test`, `hoogle-test`, and
`hypsrc-test` now only depend on GHC boot libs. So we should
now be able to build and run these as part of GHC's testsuite. \o/

The reference output has changed very slightly, in three ways:

  * we don't convert quotes back into `&quot;` as the `xml` lib did
  * we don't add extra `&nbsp;` as the `xml` lib did
  * we now remove the entire footer `div` (instead of just emptying it)
- - - - -
65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00
Remove workaround for now-fixed Clang CPP bug (#1028)

Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where
lines that started with an octothorpe but turned out not
to lex like pragmas would have an extra line added after them.

Since this bug has been fixed upstream and that it doesn't have dire
consequences anyways, the workaround is not really worth it
anymore - we can just tell people to update their clang version (or re-structure
their pragma code).
- - - - -
360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00
Clean up logic for guessing `-B` and `--lib` (#1026)

Haddock built with the `in-ghc-tree` flag tries harder to find the GHC
lib folder and its own resources. This should make it possible to use
`in-ghc-tree`-built Haddock without having to specify the `-B` and
`--lib` options (just how you can use in-tree GHC without always
specifying the `-B` option).

The logic to do this relies on `getExecutablePath`, so we only get
this auto-detection on platforms where this function works.
- - - - -
d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00
Fix tests broken by GHC

Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some
of the hyperlinker output. Accepted the new output (hovering over a
`..` now shows you what that wildcard binds).

Also fixed some stray deprecation warnings.

- - - - -
da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00
Parser changes to match !380

- - - - -
ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00
Bump ghc version to 8.9

- - - - -
44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00
Match GHC changes for T16185

`FunTy` now has an `AnonArgFlag` that indicates whether the arrow is
a `t1 => t2` or `t1 -> t2`.

This commit shouldn't change any functionality in Haddock.

- - - - -
2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00
Update .travis.yml

Points to the new GHC CI artifact.
- - - - -
90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00
Support value/type namespaces on identifier links

Identifier links can be prefixed with a 'v' or 't' to indicate the value or
type namespace of the desired identifier. For example:

-- | Some link to a value: v'Data.Functor.Identity'
--
-- Some link to a type: t'Data.Functor.Identity'

The default is still the type (with a warning about the ambiguity)

- - - - -
d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00
Better identifier parsing

  * '(<|>)' and '`elem`' now get parsed and rendered properly as links
  * 'DbModule'/'DbUnitId' now properly get split apart into two links
  * tuple names now get parsed properly
  * some more small niceties...

The identifier parsing code is more precise and more efficient (although to be
fair: it is also longer and in its own module). On the rendering side, we need
to pipe through information about backticks/parens/neither all the way through
from renaming to the backends.

In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc
lib docs change. The only "regression" is things like '\0'. These should be
changed to @\\0@ (the path by which this previously worked seems accidental).

- - - - -
3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00
Fix standalone deriving docs

Docs on standalone deriving decls for classes with associated types
should be associated with the class instance, not the associated type
instance.

Fixes haskell/haddock#1033

- - - - -
d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00
Fix bogus identifier defaulting

This avoids a situation in which an identifier would get defaulted to
a completely different identifier. Prior to this commit, the 'Bug1035'
test case would hyperlink 'Foo' into 'Bar'!

Fixes haskell/haddock#1035.

- - - - -
88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00
Visible dependent quantification (#16326) changes

- - - - -
0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00
Menu item controlling which instances are expanded/collapsed (#1007)

Adds a menu item (like "Quick Jump") for options related to displaying
instances. This provides functionality for:

  * expanding/collapsing all instances on the currently opened page
  * controlling whether instances are expanded/collapsed by default
  * controlling whether the state of instances should be "remembered"

This new functionality is implemented in Typescript in `details-helper`.
The built-in-themes style switcher also got a revamp so that all three
of QuickJump, the style switcher, and instance preferences now have
the same style and implementation structure.

See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html

Fixes haskell/haddock#698.

Co-authored-by: Lysxia <lysxia at gmail.com>
Co-authored-by: Nathan Collins <conathan at galois.com>


- - - - -
3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00
`--show-interface` should output to stdout. (#1040)

Fixes haskell/haddock#864.
- - - - -
a50f4cda by gbaz at 2019-03-01T07:43:16-08:00
Increase contrast of Linuwal theme (#1037)

This is to address the concern that, on less nice and older screens,
some of the shades of grey blend in too easily with the white
background.

 * darken the font slightly
 * darken slightly the grey behind type signatures and such
 * add a border and round the corners on code blocks
 * knock the font down by one point
- - - - -
ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00
Merge branch 'ghc-8.6' into ghc-8.8

- - - - -
12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00
Remove reference to Opt_SplitObjs flag

Split-objects has been removed.

- - - - -
5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00
Update html-test output to reflect haskell/haddock#16391 changes

- - - - -
fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00
Match changes for "Stop inferring over-polymorphic kinds"

The `hsq_ext` field of `HsQTvs` is now just the implicit variables
(instead of also including information about which of these variables
are dependent).

This commit shouldn't change any functionality in Haddock.

- - - - -
6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00
Add .hi, .dyn_hi, etc files to .gitignore

Fixes haskell/haddock#1030.

- - - - -
b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00
Better support for default methods in classes

  * default methods now get rendered differently
  * default associated types get rendered
  * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend
  * LaTeX backend now renders default method signatures

NB: there is still no way to document default class members and the
NB: LaTeX backend still crashes on associated types

- - - - -
10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00
Avoid multi-line `emph` in LaTeX backend

`markupWarning` often processes inputs which span across paragraphs.
Unfortunately, LaTeX's `emph` is not made to handle this (and will
crash).

Fixes haskell/haddock#936.

- - - - -
d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00
Many LaTeX backend fixes

After this commit, we can run with `--latex` on all boot libraries
without crashing (although the generated LaTeX still fails to compile in
a handful of larger packages like `ghc` and `base`).

 * Add newlines after all block elements in LaTeX. This is important to
   prevent the final output from being more an more indented. See the
   `latext-test/src/Example` test case for a sample of this.

 * Support associated types in class declarations (but not yet defaults)

 * Several small issues for producing compiling LaTeX;
     - avoid empy `\haddockbeginargs` lists (ex: `type family Any`)
     - properly escape identifiers depending on context (ex: `Int#`)
     - add `vbox` around `itemize`/`enumerate` (so they can be in tables)

 * Several spacing fixes:
     - limit the width of `Pretty`-arranged monospaced code
     - cut out extra space characters in export lists
     - only escape spaces if there are _multiple_ spaces
     - allow type signatures to be multiline (even without docs)

 * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files
   from `latex-test` test reference output.

Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile)
Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...)

- - - - -
0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00
Remove workaround for now-fixed Clang CPP bug (#1028)

Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where
lines that started with an octothorpe but turned out not
to lex like pragmas would have an extra line added after them.

Since this bug has been fixed upstream and that it doesn't have dire
consequences anyways, the workaround is not really worth it
anymore - we can just tell people to update their clang version (or re-structure
their pragma code).

- - - - -
ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00
Matching changes in GHC for haskell/haddock#16236

(cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576)

- - - - -
d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00
Bump GHC to 8.8

- - - - -
5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00
Redo ParseModuleHeader

- - - - -
b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00
Comment C, which clarifies why e.g. ReadP is not enough

- - - - -
bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00
Remove outdated `.ghci` files and `scripts`

The `.ghci` files are actively annoying when trying to `cabal v2-repl`.
As for the `scripts`, the distribution workflow is completely different.

- - - - -
5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00
Remove obsolete arcanist files + STYLE

Now that GHC is hosted on Gitlab, the arcanist files don't make sense
anymore. The STYLE file contains nothing more than a dead link too.

- - - - -
d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00
Redo ParseModuleHeader

- - - - -
492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00
Comment C, which clarifies why e.g. ReadP is not enough

- - - - -
af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00
Changes for haskell/haddock#16110/#16356

- - - - -
6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00
Unbreak haskell/haddock#1004 test case

`fail` is no longer part of `Monad`.

- - - - -
6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00
Fix haskell/haddock#1063 with better parenthesization logic for contexts

The only other change in html/hoogle/hyperlinker output for the boot
libraries that this caused is a fix to some Hoogle output for implicit
params.

```
$ diff -r _build/docs/ old_docs
diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt
13296c13296
< assertError :: (?callStack :: CallStack) => Bool -> a -> a
---
> assertError :: ?callStack :: CallStack => Bool -> a -> a
```

- - - - -
b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00
Match changes with haskell/haddock#14332

- - - - -
c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00
Remove Haddock's dependency on `Cabal`

At this point, Haddock depended on Cabal-the-library solely for a
verbosity parser (which misleadingly accepts all sorts of verbosity
options that Haddock never uses). Now, the only dependency on Cabal
is for `haddock-test` (which uses Cabal to locate the Haddock interface
files of a couple boot libraries).

- - - - -
e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00
Regression test: promoted lists in associated types

When possible, associated types with promoted lists should use the
promoted list literal syntax (instead of repeated applications of
': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c.

Closes haskell/haddock#466,

- - - - -
cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00
Merge branch 'ghc-8.6' into ghc-8.8

- - - - -
4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00
Release haddock-2.23, haddock-library-1.8.0

Tentatively adjust bounds and changelogs for the release to be bundled
with GHC 8.8.1.

- - - - -
69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00
Update hyperlinker tests for new types in .hie files

- - - - -
29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00
update for new way to store hiefile headers

- - - - -
aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00
update for new way to store hiefile headers

- - - - -
ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00
Update test output for introduction of Safe-Inferred

- - - - -
3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00
Changes for haskell/haddock#15247

- - - - -
0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00
Fix haddockHypsrcTest

- - - - -
2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00
Fix for GHC module renaming

- - - - -
9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00
Fix Travis CI, loosen .cabal bounds (#1089)

Tentatively for the 2.23 release:

  * updated Travis CI to work again
  * tweaked bounds in the `.cabal` files
  * adjusted `extra-source-files` to properly identify test files
- - - - -
ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00
Small change in to facilitate extended typed-holes (#1090)

This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later.
- - - - -
02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00
Remove spaces around @-patterns (#1093)

This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented.
- - - - -
83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00
Fix the ignore-exports option (#1082)

The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it.
- - - - -
e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00
Fix a few haddock issues

- - - - -
3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00
Fix crash when there are no srcspans in the file due to CPP

- - - - -
339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00
Prefer un-hyperlinked sources to no sources

It is possible to fail to extract an HIE ast. This is however not a
reason to produce _no_ output - we should still make a colorized HTML
page.

- - - - -
d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00
Add a regression test for haskell/haddock#1091

Previously, this input would crash Haddock.

- - - - -
ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00
Add Hyperlinker test cases for TH-related stuff

Hopefully this will guard against regressions around quasiquotes, TH
quotes, and TH splices.

- - - - -
d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00
Refactor for withTiming changes.

- - - - -
4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00
Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor

Refactor for withTiming changes.
- - - - -
d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00
Reify oversaturated data family instances correctly (#1103)

This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see
https://gitlab.haskell.org/ghc/ghc/issues/17296 and
https://gitlab.haskell.org/ghc/ghc/merge_requests/1877).

- - - - -
331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00
Refactor for OutputableBndrId changes

- - - - -
48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00
Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable

Refactor for OutputableBndrId changes
- - - - -
f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00
Define `XRec` for location information and get rid of `HasSrcSpan`

In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a
simpler way to encode location information into the GHC and Haddock AST
while incurring no cost for e.g. TH which doesn't need location
information.

These are just changes that have to happen in lock step.

- - - - -
d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00
Changes from haskell/haddock#14579

We now have a top-level `tyConAppNeedsKindSig` function, which means
that we can delete lots of code in `Convert`.

(cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70)

- - - - -
dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00
Define `XRec` for location information and get rid of `HasSrcSpan`

In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a
simpler way to encode location information into the GHC and Haddock AST
while incurring no cost for e.g. TH which doesn't need location
information.

These are just changes that have to happen in lock step.

- - - - -
0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00
Import isRuntimeRepVar from Type rather than TyCoRep

isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441.

- - - - -
091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00
Bump to GHC 8.10

- - - - -
e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00
Merge pull request haskell/haddock#1110 from haskell/wip/T17441

Import isRuntimeRepVar from Type rather than TyCoRep
- - - - -
4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00
Version bumps for GHC 8.11

- - - - -
0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00
Bump to GHC 8.10

- - - - -
00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00
Bump ghc version to 8.11

- - - - -
dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00
Drop support for base 4.13

- - - - -
f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00
Update Hyperlinker.Parser.classify to use ITdollar

- - - - -
1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00
Remove HasSrcSpan (#17494)

- - - - -
651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00
Document error-prone conditional definition of instances

This can easily trip up people if one isn't aware of it. Usually it's
better to avoid this kind of conditionality especially for typeclasses
for which there's an compat-package as conditional instances like
these tend to fragment the ecosystem into those packages that go the
extra mile to provide backward compat via those compat-packages and
those that fail to do so.

- - - - -
b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00
Fix build-failure regression for base < 4.7

The `$>` operator definition is available only since base-4.7 which
unfortunately wasn't caught before release to Hackage (but has been
fixed up by a metadata-revision)

This commit introduces a `CompatPrelude` module which allows to reduce
the amount of CPP by ousting it to a central location, i.e. the new
`CompatPrelude` module. This pattern also tends to reduce the tricks
needed to silence unused import warnings.

Addresses haskell/haddock#1119

- - - - -
556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00
Fix after Iface modules renaming

- - - - -
bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00
hsyl20-modules-renamer

- - - - -
fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00
Changes for GHC#17608

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372

- - - - -
4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00
Changes for GHC#17566

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469

- - - - -
e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00
Rename PackageConfig into UnitInfo

- - - - -
ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00
Rename lookupPackage

- - - - -
ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00
Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two

Changes for GHC#17566
- - - - -
3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00
Merge branch 'wip-hsyl20-package-refactor' into ghc-head

- - - - -
602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00
Echo GHC's removal of PlaceHolder module

This goes with GHC's !2083.

- - - - -
ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00
Module hierarchy: runtime (cf haskell/haddock#13009)

- - - - -
554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00
Fix build of haddock in stage1

We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter.

- - - - -
5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00
Noramlize `tested-with` fields in cabal files

- - - - -
e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00
No MonadFail/Alternative for P

- - - - -
90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00
Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build

Fix build of haddock in stage1
- - - - -
93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00
Modules: Driver (#13009)

- - - - -
da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00
Use RealSrcSpan in InstMap

- - - - -
479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00
Merge remote-tracking branch 'upstream/ghc-head' into HEAD

- - - - -
55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00
Modules: Core (#13009)

- - - - -
60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00
Ignore the BufLoc/BufSpan added in GHC's !2516

- - - - -
1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00
Modules: Core (#13009)

- - - - -
6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00
Changes in GHC's !1913.

- - - - -
30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00
Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2

Modules: Core (#13009)
- - - - -
cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00
Modules: Types

- - - - -
b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00
Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types

Modules: Types
- - - - -
9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00
Replace the 'caption' class so that the collapsible sections are shown

- - - - -
5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00
Force ghc-8.8.3

- - - - -
c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00
Update test fixtures

- - - - -
5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00
Modules: Types

- - - - -
7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00
Merge branch 'ghc-8.8' into ghc-8.10

- - - - -
b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00
Update parsing to strip whitespace from table cells (#1074)

* Update parsing to strip leading & trailing whitespace from table cells

* Update fixture data to disallow whitespaces at both ends in table cells

* Add test case for whitespaces stripped from both ends of table cells

* Update table reference test data for html tests

- - - - -
b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00
Clean up warnings

  * unused imports
  * imports of `Data.List` without import lists
  * missing `CompatPrelude` file in `.cabal`

- - - - -
0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00
Fix NPM security warnings

This was done by calling `npm audit fix`. Note that the security issues
seem to have been entirely in the build dependencies, since the output
JS has not changed.

- - - - -
6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00
Tentative 2.24 release

Adjusted changelogs and versions in `.cabal` files in preparation for
the upcoming release bundled with GHC 8.10.

- - - - -
1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00
Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD

More changes from the GHC types module refactoring.

- - - - -
be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00
Update `.travis.yml` to work with GHC 8.10.1

  * Regenerated the Travis file with `haskell-ci`

  * Beef up `.cabal` files with more `tested-with` information

- - - - -
b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00
Update README

Removed some out of date links/info, added some more useful links.

  * badge to Hackage
  * update old trac link
  * `ghc-head` => `ghc-8.10`
  * `cabal new-*` is now `cabal v2-*` and it should Just Work
  * `--test-option='--accept'` is the way to accept testsuite output

- - - - -
564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00
Fix crash in `haddock-library` on unicode space

Our quickcheck tests for `haddock-library` stumbled across an edge case
input that was causing Haddock to crash: it was a unicode space
character.

The root cause of the crash is that we were implicitly assuming that
if a space character was not " \t\f\v\r", it would have to be "\n".
We fix this by instead defining horizontal space as: any space character
that is not '\n'.

Fixes haskell/haddock#1142

- - - - -
2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00
Disallow qualified uses of reserved identifiers

This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too,
but it is a relatively easy fix in Haddock. Note that the fix must live
in `haddock-api` instead of `haddock-library` because we can only really
decide if an identifier is a reserved one by asking the GHC lexer.

Fixes haskell/haddock#952

- - - - -
47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00
Remove unused `Haddock.Utils` functions

  * removed functions in `Haddock.Utils` that were not used anywhere
    (or exported from the `haddock-api` package)

  * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils`

- - - - -
c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00
Use TTG empty extensions to remove some `error`'s

None of these error cases should ever have been reachable, so this is
just a matter of leveraging the type system to assert this.

  * Use the `NoExtCon` and `noExtCon` to handle case matches for no
    extension constructors, instead of throwing an `error`.

  * Use the extension field of `HsSpliceTy` to ensure that this variant
    of `HsType` cannot exist in an `HsType DocNameI`.

- - - - -
0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00
Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL`

 * `unL` is already defined by GHC as `unLoc`
 * `reL` is already defined by GHC as `noLoc` (in a safer way too!)
 * Condense `setOutputDir` and add a about exporting from GHC

Fixes haskell/haddock#978

- - - - -
bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00
Cleanup up GHC flags in `.cabal` files

  * enable more useful warning flags in `haddock-api`, handle the new
    warnings generated

  * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in
    `-Wall` for a while now)

- - - - -
c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00
`haddock-library` document header level

Document the fact the header level is going to always be between 1 and 6
inclusive. Along the way, I also optimized the parsing code a bit.

- - - - -
71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00
Disallow links in section headers

This is quite straightforward to implement, since we already had a
function `docToHtmlNoAnchors` (which we used to generate the link in the
sidebar "Contents").

This breaks test `Bug387`, but that test case has aged badly: we now
automatically generate anchors for all headings, so manually adding an
anchor in a section makes no sense. Nested anchors are, as pointed out
in haskell/haddock#1054, disallowed by the HTML standard.

Fixes haskell/haddock#1054

- - - - -
b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00
Modules: type checker

- - - - -
cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00
Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc

Module renaming
- - - - -
5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00
Allow QuickCheck 2.14

Builds fine and all tests pass.
- - - - -
dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00
Module renaming: amend previous patch

- - - - -
eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00
Fix haskell/haddock#1050 by filtering out invisible AppTy arguments

This makes the `synifyType` case for `AppTy` more intelligent by
taking into consideration the visibilities of each `AppTy` argument
and filtering out any invisible arguments, as they aren't intended
to be displayed in the source code. (See haskell/haddock#1050 for an example of what
can happen if you fail to filter these out.)

Along the way, I noticed that a special `synifyType` case for
`AppTy t1 (CoercionTy {})` could be consolidated with the case below
it, so I took the opportunity to tidy this up.

- - - - -
23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00
Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc

Module renaming: amend previous patch
- - - - -
072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00
Make NoExtCon fields strict

These changes are a part of a fix for
[GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992).

- - - - -
d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00
Recode Doc to Json. (#1159)

* Recode Doc to Json.

* More descriptive field labels.
- - - - -
52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00
Module renaming

- - - - -
d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00
Add instance of XCollectPat for DocNameI

- - - - -
323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00
Rename XCollectPat -> CollectPass

- - - - -
2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00
Prune docstrings that are never rendered

When first creating a Haddock interface, trim `ifaceDocMap` and
`ifaceArgMap` to not include docstrings that can never appear in the
final output. Besides checking with GHC which names are exported, we
also need to keep all the docs attached to instance declarations (it is
much tougher to detect when an instance is fully private).

This change means:

  * slightly smaller interface files (7% reduction on boot libs)
  * slightly less work to do processing docstrings that aren't used
  * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070)

I've tested manually that this does not affect any of the boot library
generated docs (the only change in output was some small re-ordering in
a handful of instance lists). This should mean no docstrings have been
incorrectly dropped.

- - - - -
f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00
Don't warn about missing links in miminal sigs

When renaming the Haddock interface, never emit warnings when renaming a
minimal signature. Also added some documention around `renameInterface`.

Minimal signatures intentionally include references to potentially
un-exported methods (see the discussion in haskell/haddock#330), so it is expected
that they will not always have a link destination. On the principle
that warnings should always be resolvable, this shouldn't produce a
warning. See haskell/haddock#1070.

- - - - -
a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00
Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools

Module renaming
- - - - -
f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00
Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat

- - - - -
a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00
Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat

Trees that Grow refactor (GHC !2553)
- - - - -
6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00
Fallback to `hiDecl` when `extractDecl` fails

Sometimes, the declaration being exported is a subdecl (for instance, a
record accessor getting exported at the top-level). For these cases,
Haddock has to find a way to produce some synthetic sensible top-level
declaration. This is done with `extractDecl`.

As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a
syntactic level (for instance when the subdecl is re-exported). In these
cases, the only sensible thing to do is to try to reify a declaration
based on a GHC `TyThing` via `hiDecl`.

- - - - -
eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00
Module structure

- - - - -
50b9259c by Iñaki at 2020-04-25T18:38:11-04:00
Add support for custom section anchors (#1179)

This allows to have stable anchors for groups, even if the set of
groups in the documentation is altered.

The syntax for setting the anchor of a group is

-- * Group name #desiredAnchor#

Which will produce an html anchor of the form '#g:desiredAnchor'

Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc>
- - - - -
4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00
Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils

Module structure
- - - - -
5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00
Renamed UnitInfo fields

- - - - -
c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00
UnitId has been renamed into Unit

- - - - -
3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00
Fix for GHC.Unit.* modules

- - - - -
ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00
Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid

Refactoring of Unit code
- - - - -
b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00
add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075)

- - - - -
9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00
Atomic update of NameCache in readHieFile

- - - - -
86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00
Fix after Config module renaming

- - - - -
a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00
Explicit Specificity Support for Haddock

- - - - -
46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00
Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config

Fix after Config module renaming
- - - - -
f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00
Explicit Specificity Support for Haddock

- - - - -
55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00
Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head

- - - - -
a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00
isBootSummary now produces a result of type IsBootInterface

- - - - -
ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00
update for hiefile-typeclass-info

- - - - -
49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00
Use floor over round to calculate the percentage (#1195)

If we compile documentation where only a small fraction is undocumented,
it is misleading to see 100% coverage - 99% is more intuitive.

Fixes haskell/haddock#1194
- - - - -
c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00
Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig

isBootSummary now produces a result of type IsBootInterface
- - - - -
74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00
haddock: Bounds bumps for GHC 8.12

- - - - -
b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00
testsuite: Update expected output for simplified subsumption

- - - - -
624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00
Changes for GHC#18191

See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337.

- - - - -
fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00
Fix after unit refactoring

- - - - -
743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00
Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii

Fix after unit refactoring
- - - - -
d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00
Use HsForAllTelescope (GHC#18235)

- - - - -
389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00
haddock: Bounds bumps for GHC 8.12

- - - - -
7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00
Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12

haddock: Bounds bumps for GHC 8.12
- - - - -
9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00
Adapt Haddock to LinearTypes

See ghc/ghc!852.

- - - - -
46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30
Use functions exported from HsToCore

- - - - -
8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00
Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore

Use functions exported from GHC.HsToCore.Docs
- - - - -
22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00
Adapt Haddock for QualifiedDo

- - - - -
3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00
Handle LexicalNegation's ITprefixminus

- - - - -
03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00
Rename hsctarget into backend

- - - - -
ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00
Update for UniqFM changes.

- - - - -
9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00
Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm

Update for UniqFM changes.
- - - - -
68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00
Sync with GHC removing {-# CORE #-} pragma

See ghc ticket haskell/haddock#18048

- - - - -
eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00
Rename hscTarget into backend

- - - - -
fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00
Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg

Rename hscTarget into backend
- - - - -
1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00
Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head

- - - - -
d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30
Update for modular ping pong

- - - - -
8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00
Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong

Modular ping pong
- - - - -
a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00
Bump GHC version to 9.0

- - - - -
6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00
Fix after Outputable refactoring

- - - - -
c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00
Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception

Fix after Outputable refactoring
- - - - -
d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00
Fix after HomeUnit

- - - - -
8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00
Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit

Fix after HomeUnit
- - - - -
8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00
Remove Ord FastString instance

- - - - -
8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00
Another round of `npm audit fix` (#1228)

This should shut down the warnings on Github. Note that the security issues
seem to have been entirely in the build dependencies, since the output
JS has not changed.

Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0

Co-authored-by: Alex Biehl <alex.biehl at target.com>
- - - - -
7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00
Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord

Remove Ord FastString instance
- - - - -
ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00
Match GHC for haskell/haddock#18639, remove GENERATED pragma

- - - - -
a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00
Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma,

Match GHC for haskell/haddock#18639, remove GENERATED pragma
- - - - -
1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00
Bump GHC version to 9.1

- - - - -
6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00
Bump base upper bound to 4.16

- - - - -
a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00
Update hypsrc-test for QuickLook

This appears to be a spurious change.

- - - - -
e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00
Updates for the new linear types syntax: a %p -> b

- - - - -
30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00
Update for parser (#1234)


- - - - -
b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00
Updates for the new linear types syntax: a %p -> b

- - - - -
0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00
Adapt to GHC parser changes

- - - - -
b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00
Don't pass the HomeUnitId (#1239)


- - - - -
34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00
Changed tests due to unification of `Nat` and `Natural`

in the follwing merge request:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583

- - - - -
256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00
Add whitespace in: map ($ v)

- - - - -
4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

- - - - -
072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

(cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1)

- - - - -
9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00
Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled

(cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1)

- - - - -
636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00
GHC.Driver.Types refactoring (#1242)


- - - - -
a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00
Adapt to the removal of Hs{Boxed,Constraint}Tuple

See ghc/ghc!4097 and GHC#18723.

- - - - -
b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00
Adapt to HsConDecl{H98,GADT}Details split

Needed for GHC#18844.

- - - - -
c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00
Adapt to HsOuterTyVarBndrs

These changes accompany ghc/ghc!4107, which aims to be a fix
for haskell/haddock#16762.

- - - - -
a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00
Adapt to splitPiTysInvisible being renamed to splitInvisPiTys

This is a part of !4434, a fix for GHC#18939.

- - - - -
66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00
Fix after Plugins moved into HscEnv

- - - - -
508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00
Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv

Fix after Plugins moved into HscEnv
- - - - -
620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00
Update for changes in GHC's Pretty

- - - - -
01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00
Avoid GHC#18932.

- - - - -
8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00
Add type arguments to PrefixCon

- - - - -
414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00
DynFlags's unit fields moved to HscEnv

- - - - -
e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00
Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate

Unit fields moved from DynFlags to HscEnv
- - - - -
7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00
Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps

Update for changes in GHC's Pretty
- - - - -
fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00
Fix docs links from Darcs to GitHub in intro (#1262)


- - - - -
7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00
Use gender neutral word in docs (#1260)


- - - - -
1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00
Allow scrolling search results (#1235)

Closes https://github.com/haskell/haddock/issues/1231
- - - - -
8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00
Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255)

Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3.
- [Release notes](https://github.com/rvagg/bl/releases)
- [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3)

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00
Allow more characters in anchor following module reference (#1220)


- - - - -
14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00
Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243)

* Fix multiple typos and inconsistencies in doc/markup.rst

Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from
@parsonsmatt after creating these proposed changes - mea culpa for not
looking at the open PRs sooner.

* Fix haskell/haddock#1113 If no Signatures, no section of index.html

* Change the formatting of missing link destinations

The current formatting of the missing link destination does not really
help user to understand the reasons of the missing link.

To address this, I've changed the formatting in two ways:

- the missing link symbol name is now fully qualified. This way you
immediately know which haskell module cannot be linked. It is then easier
to understand why this module does not have documentation (hidden module
or broken documentation).
- one line per missing link, that's more readable now that symbol name
can be longer due to qualification.

For example, before haddock was listing missing symbol such as:

```
could not find link destinations for:
  Word8 Word16 mapMaybe
```

Now it is listed as:

```
could not find link destinations for:
  - Data.Word.Word8
  - Data.Word.Word16
  - Data.Maybe.mapMaybe
```

* Add `--ignore-link-symbol` command line argument

This argument can be used multiples time. A missing link to a symbol
listed by `--ignore-link-symbol` won't trigger "missing link" warning.

* Forbid spaces in anchors (#1148)

* Improve error messages with context information (#1060)

Co-authored-by: Matt Audesse <matt at mattaudesse.com>
Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com>
Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io>
Co-authored-by: Pepe Iborra <pepeiborra at gmail.com>
- - - - -
89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00
Enable two warnings (#1245)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656
- - - - -
c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00
simplify calculating percentages fixing haskell/haddock#1194 (#1236)


- - - - -
685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00
Changes for GHC#17566

See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469

- - - - -
be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00
Import intercalate

- - - - -
32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00
Adapt Haddock for QualifiedDo

- - - - -
31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00
Fix haddock-library tests

- - - - -
fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00
Move to GitHub CI (#1266)

* Initial version of ci.yml

This is a straight copy from Dmitrii Kovanikov's blog post
at https://kodimensional.dev/github-actions.

Will adapt to haddock in successive commits.

* Delete .travis.yml

* Modify to only test on ghc-8.10.{1,2}

* Use actions/setup-haskell at v1.1.4

* Relax QuickCheck bound on haddock-api

* Remove stack matrix for now

* Nail down to ghc-8.10 branch for now

* Pin index state to 2020-12-08T20:13:44Z for now

* Disable macOS and Windows tests for now for speed up
- - - - -
5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00
Enable two warnings (#1245) (#1268)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656
- - - - -
bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00
Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269)

Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7.
- [Release notes](https://github.com/isaacs/ini/releases)
- [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7)

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00
Update for boxed rep

- - - - -
a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00
Revert "Enable two warnings (#1245) (#1268)"

As this does not build on GHC `master`.

This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce.

- - - - -
a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00
Revert "Update for boxed rep"

This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d.

- - - - -
53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00
Update output for nullary TyConApp optimisation (ghc/ghc!2952)

- - - - -
4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00
Display linear/multiplicity arrows correctly (#1238)

Previously we were ignoring multiplicity and displayed
a %1 -> b as a -> b.
- - - - -
ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00
Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym

Needed for !4417, the fix for GHC#15706 and GHC#18914.

- - - - -
ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00
Enable two warnings (#1245) (#1268)

because they will be soon be added to -Wall.

See https://gitlab.haskell.org/ghc/ghc/-/issues/15656

- - - - -
d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00
Fix after binder collect changes

- - - - -
bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00
Adapt to changes to GlobalRdrElt and AvailInfo

Needed for ghc/ghc!4467

- - - - -
37736c4c by John Ericson at 2020-12-28T12:27:02-05:00
Support a new ghc --make node type for parallel backpack upsweep

- - - - -
717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00
Inline and fix getGADTConTypeG

The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782.

I noticed that getGADTConTypeG was only used in the Hoogle backend.
Interestingly, when handling H98 constructors, Hoogle converts RecCon to
PrefixCon (see Haddock.Backends.Hoogle.ppCtor).

So I changed getGADTConTypeG to handle RecConGADT in the same manner as
PrefixConGADT, and after this simplification moved it into the 'where'
clause of ppCtor, to the only place where it is used.

The practical effect of this change is as follows.
Consider this example:
	data TestH98 = T98 { bar::Int }
	data TestGADT where
	  TG :: { foo :: Int } -> TestGADT

Before this patch,  haddock --hoogle  used to produce:
	T98 :: Int -> TestH98
	[TG] :: {foo :: Int} -> TestGADT

Notice how the record syntax was discarded in T98 but not TG.
With this patch, we always produce signatures without record syntax:
	T98 :: Int -> TestH98
	[TG] :: Int -> TestGADT

I suspect this might also be a bugfix, as currently Hoogle doesn't seem
to render GADT record constructors properly.

- - - - -
cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00
Build instructions: haddock-library and -api first!

- - - - -
b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00
Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j

Changes to support -j with backpack
- - - - -
120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00
Merge pull request haskell/haddock#1282 from andreasabel/master

Build instructions: haddock-library and -api first!
- - - - -
fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00
Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0

- - - - -
b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00
Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0

- - - - -
81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00
Prepare Haddock for being a GHC Plugin

- - - - -
b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00
Make Haddock a GHC Plugin

- - - - -
cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00
Add -j[n] CLI param to Haddock executable

It translates to `--ghcopt=-j[n]`

- - - - -
84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00
Abstract Monad for interface creation

I found that when running as a plugin the lookupName function (which
runs in Ghc monad) does not work correctly from the
typeCheckResultAction hook.

Instead, we abstracted the monad used when creating interfaces, so
that access to GHC session specific parts is explicit and so that the
TcM can provide their (correct) implementation of lookupName.

- - - - -
5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00
Accept tests

- - - - -
8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00
Add missing dependency for mtl

- - - - -
3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00
Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head

- - - - -
33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00
Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows

Fix after binder collect changes
- - - - -
70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00
Make haddock more robust to changes to the `Language` data type

With the introduction of GHC2021, the `Languages` data type in GHC will
grow. In preparation of that (and to avoid changing haddock with each
new language), this change makes the code handle extensions to that data
type gracefully.

(cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5)

- - - - -
7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00
Add `NoGhcTc` instance now that it's not closed

- - - - -
e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00
Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936

Add `NoGhcTc` instance now that it's not closed
- - - - -
989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00
Add import list to Data.List

- - - - -
368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00
Adapt to "Make PatSyn immutable"

- - - - -
abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00
Rename pprLogErrMsg to new name

- - - - -
e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00
Move CI to ghc-9.0

- - - - -
dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00
Update cabal.project and README build instructions

- - - - -
31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00
Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0

Merge the late additions to ghc-8.10 into ghc-9.0
- - - - -
6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00
Cleanup: fix build warnings

- - - - -
f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00
type level characters support for haddock (required for haskell/haddock#11342)

- - - - -
d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00
Add a CONTRIBUTING.md file

- - - - -
6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00
Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette

Add a CONTRIBUTING.md file
- - - - -
955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00
Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head

- - - - -
47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00
Amend the CONTRIBUTING.md file

- - - - -
23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00
Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing

Amend the CONTRIBUTING.md file
- - - - -
69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00
Display linear/multiplicity arrows correctly (#1238)

Previously we were ignoring multiplicity and displayed
a %1 -> b as a -> b.

(cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb)

- - - - -
ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00
Add import list to Data.List

- - - - -
5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00
Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list

Add import list to Data.List
- - - - -
1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00
Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge

- - - - -
13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00
Fix partial record selector warning

- - - - -
5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00
Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge

- - - - -
b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00
Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge

- - - - -
a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00
Merge branch 'wip/ghc-head-merge' into ghc-head

- - - - -
1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00
Fix search div not scrolling

- - - - -
684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00
Add support for labeled module references

Support a markdown-style way of annotating module references. For instance

-- | [label]("Module.Name#anchor")

will create a link that points to the same place as the module
reference "Module.Name#anchor" but the text displayed on the link will
be "label".

- - - - -
bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00
Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat

Backward compat: Add support for labeled module references
- - - - -
6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00
Merge pull request haskell/haddock#1314 from tweag/show-linear-backport

Backport haskell/haddock#1238 (linear types) to ghc-9.0
- - - - -
d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00
Remove dubious parseModLink

Instead construct the ModLink value directly when parsing.

- - - - -
33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00
Merge pull request haskell/haddock#1320 from haskell/alex/fix

Remove dubious parseModLink
- - - - -
54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00
Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0

Fix search div not scrolling
- - - - -
19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00
Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge

Merge ghc-8.10 into ghc-head
- - - - -
6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00
simplify calculating percentages fixing haskell/haddock#1194 (#1236)

- - - - -
c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00
Merge pull request haskell/haddock#1322 from haskell/alex/forward-port

simplify calculating percentages fixing haskell/haddock#1194 (#1236)
- - - - -
2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00
Merge branch 'ghc-head' into ghc-9.0
- - - - -
849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00
Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0

Merge ghc-9.0 into ghc-head
- - - - -
ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00
Update for Logger

- - - - -
4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00
Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2

Logger refactoring
- - - - -
922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00
Fix to build with HEAD

- - - - -
a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00
Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2

Fix to build with HEAD
- - - - -
0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00
Add UnitId to Target record

- - - - -
d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00
Stable sort for (data/newtype) instances

- - - - -
8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00
Also make TyLit deterministic

- - - - -
f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00
Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface

Stable sort for instances
- - - - -
5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00
Add import list to Data.List in Haddock.Interface.Create

- - - - -
fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00
Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports

Add import list to Data.List in Haddock.Interface.Create
- - - - -
f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00
Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target

Add UnitId to Target record
- - - - -
674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00
html-test: Always set language

from ghc-9.2 on, the “default” langauge of GHC is expected to change
more wildly. To prepare for that (and unblock
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the
language for all the test files to `Haskell2010`. This should insolate
this test suite against changes to the default.

Cherry-picked from https://github.com/haskell/haddock/pull/1341

- - - - -
f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00
Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head

html-test: Always set language
- - - - -
caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00
Clean-up of Interface and Interface.Create's imports and pragmata

- - - - -
f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00
Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports

[ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata 
- - - - -
7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00
Explicit imports for Haddock.Interface and Haddock.Interface.Create

- - - - -
6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00
Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface

Explicit imports for Haddock.Interface and Haddock.Interface.Create
- - - - -
9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00
Context becomes a Maybe in the GHC AST

This prevents noLoc's appearing in the ParsedSource.

Match the change in GHC.

- - - - -
0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00
Fix the call-site of guessTarget in Interface.hs

Explicit the imports from GHC.HsToCore.Docs

- - - - -
b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00
Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call

Fix the call-site of guessTarget in Interface.hs
- - - - -
9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00
Fix haddockHypsrcTest output in ghc-head

- - - - -
b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00
Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head

Fix haddockHypsrcTest output in ghc-head
- - - - -
3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00
Add ITproj to parser

- - - - -
d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00
Update for boxed rep

- - - - -
6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00
Update for "FastString: Use FastMutInt instead of IORef Int"

- - - - -
e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00
Implement template-haskell's putDoc

This catches up to GHC using the new extractTHDocs function, which
returns documentation added via the putDoc function (provided it was
compiled with Opt_Haddock). Since it's already a map from names -> docs,
there's no need to do traversal etc.
It also matches the change from the argument map being made an IntMap
rather than a Map Int

- - - - -
89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00
Match changes in GHC AST for in-tree API Annotations

As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418

- - - - -
28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00
Change some type family test results.

It is not clear to me whether the original was printing
incorrectly (since we did not have the TopLevel flag before now), or
if this behaviour is expected.

For the time being I am assuming the former.

- - - - -
7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00
Fix after NameCache changes

- - - - -
addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00
NameCache doesn't store a UniqSupply anymore

- - - - -
15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00
Bump GHC version to 9.2

- - - - -
dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00
Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1

NameCache refactoring
- - - - -
2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00
Specialization of Data.List

- - - - -
32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00
Add UnitId to Target record

This way we always know to which home-unit a given target belongs to.
So far, there only exists a single home-unit at a time, but it
enables having multiple home-units at the same time.

- - - - -
54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00
Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert

Add UnitId to Target record
- - - - -
7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00
EPA : Rename ApiAnn to EpAnn

- - - - -
72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00
pprError changed name in GHC

- - - - -
4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00
EPA : Rename ApiAnn to EpAnn

- - - - -
108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00
Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD

- - - - -
1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00
Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity

Rename pprError to mkParserErr
- - - - -
d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00
Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head

- - - - -
170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00
Merge remote-tracking branch 'upstream/ghc-head' into ghc-head

- - - - -
db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00
Bump GHC version to 9.3

- - - - -
a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00
Update for EPA changes in GHC

(cherry picked from commit cafb48118f7c111020663776845897e225607b41)

- - - - -
1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00
Removal of HsVersions.h (#1388)

* Update for EPA changes in GHC

* Account for HsVersions.h removal

Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>
- - - - -
79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00
Revert "Removal of HsVersions.h (#1388)"

This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6.

- - - - -
3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00
Update for EPA changes in GHC

- - - - -
2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00
Account for HsVersions.h removal

- - - - -
00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00
Add Haddock support for the OPAQUE pragma (#1380)


- - - - -
8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00
fixup! Use GHC 9.2 in CI runner

- - - - -
27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00
EPA: match changes from GHC T19834

- - - - -
f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00
Allow hspec 2.8 (#1389)

All tests are passing.
- - - - -
df44453b by Divam Narula at 2021-05-20T15:42:42+02:00
Update ref, the variables got renamed. (#1391)

This is due to ghc/ghc!5555 which caused a change in ModDetails in case of
NoBackend. Now the initModDetails is used to recreate the ModDetails from
interface and in-memory ModDetails is not used.
- - - - -
e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00
Remove Maybe from HsQualTy

Match changes in GHC for haskell/haddock#19845

- - - - -
79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00
FieldOcc: rename extFieldOcc to foExt

- - - - -
6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00
Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head

- - - - -
f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00
New Parser diagnostics interface

- - - - -
392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00
Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages

Align Haddock to use the new Parser diagnostics interface
- - - - -
33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00
Revert "Add Haddock support for the OPAQUE pragma (#1380)"

This reverts commit a1337c599ef7720b0482a25c55f11794112496dc.

The GHC patch associated with this change is not yet ready to be merged.

- - - - -
8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00
CI configuration for ghc-head (#1395)


- - - - -
1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00
Use GHC 9.2 in CI runner (#1378)


- - - - -
e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00
Add page about common errors (#1396)

* Update index.rst

Common errors page

* Create common-errors.rst

* Update common-errors.rst

* Use GHC 9.2 in CI runner (#1378)

* [haddock-api] remove .hspec-failures

Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com>
- - - - -
abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00
Adapt Haddock to Logger and Parser changes (#1399)


- - - - -
91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00
Update haddockHypSrc tests since we now compute slighly more type info (#1397)


- - - - -
ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00
Added myself to contributors

- - - - -
49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00
Document multi component support

- - - - -
9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00
Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support

Document multi component support
- - - - -
585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00
Update CONTRIBUTING.md (#1402)


- - - - -
1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00
Update CONTRIBUTING.md (#1403)


- - - - -
58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00
Update Haddock Bug873 to account for renaming

- - - - -
c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00
HsToken in FunTy, RecConGADT

- - - - -
1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00
Update the CI badges
- - - - -
6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00
Fix mkParserOpts (#1411)


- - - - -
18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00
Rename getErrorMessages Lexer import

This commit renames the Lexer import in `Hyperlinker.Parser` from
`getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity
with the `getErrorMessages` function defined in `GHC.Types.Error`.

- - - - -
23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00
Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920

Rename getErrorMessages Lexer import
- - - - -
b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00
EPA: match changes from GHC T19834

(cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2)

- - - - -
5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00
Merge commit '2a966c8ca37' into HEAD

- - - - -
cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00
coot/multiple packages (ghc-9.2) (#1418)


- - - - -
be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00
coot/multiple package (ghc-head) (#1419)

* FromJSON class

Aeson style FromJSON class with Parsec based json parser.

* doc-index.json file for multiple packages

When creating haddock summary page for multiple packages render
doc-index.json file using contents of all found 'doc-index.json' files.

* Render doc-index.json

When rendering html, render doc-index.json file independently of
maybe_index_url option.  doc-index.json file is useful now even if
maybe_index_url is not `Nothing`.

* base url option

New `Flag_BaseURL` which configures from where static files are loaded
(--base-url).  If given and not equal "." static files are not coppied,
as this indicates that they are not read from the the directory where
we'd copy them.  The default value is ".".
- - - - -
3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00
Update GHC 9.2 to latest pre-release in CI

- - - - -
7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00
Enable Haddock tests in GHC windows CI (#1428)

* testsuite: strip windows line endings for haddock

* hyperlinker: Work around double escaping (#19236)

* deterministic SCC
- - - - -
1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00
haddock-library does not depend on bytestring or transformers (#1426)


- - - - -
a890b9aa by sheaf at 2021-10-15T22:19:42+02:00
update haddockHypsrcTest for GHC MR !6705 (#1430)


- - - - -
42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00
Fix after PkgQual refactoring (#1429)


- - - - -
91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00
Update for changes in GHC for branch

wip/az/no-srcspan-anno-instances

- - - - -
acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00
Do not use forall as an identifier

See GHC ticket haskell/haddock#20609

- - - - -
c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00
Update after NoExtCon -> DataConCantHappen rename

- - - - -
b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00
fix CI for 9.2 (#1436)


- - - - -
25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00
Update html-test for Data.List revert

- - - - -
1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00
Add hint about inline link issue (#1444)


- - - - -
791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00
Bump ghc-head (#1445)

* Update after NoExtCon -> DataConCantHappen rename

* Update html-test for Data.List revert

* Fix for new Plugins datatype

Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>
- - - - -
44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00
Fix for new Plugins datatype

- - - - -
80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00
Remove ghc-head workflow (#1446)

Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore.
- - - - -
49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00
Remove use of ExtendedModSummary

- - - - -
0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00
update URLs
- - - - -
9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00
Fix solver for GHC 9.2

- - - - -
386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00
IDoc link has bitrotted; replaced with web.archive.org cache. (#1454)


- - - - -
d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00
Fix haddock user guide  (#1456)


- - - - -
cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00
Allow text-2.0 in haddock-library (#1459)


- - - - -
7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00
Add multi-line style hint to style section (#1460)


- - - - -
c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00
Fix CollectPass instance to match TTG refactor

Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614)

- - - - -
b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00
Link to (~)

- - - - -
877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00
Add Haddock support for the OPAQUE pragma

- - - - -
0ea22721 by askeblad at 2022-03-16T09:44:27+01:00
typos (#1464)


- - - - -
a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00
Minimum changes needed for compilation with hi-haddock

With hi-haddock, of course there is a much large refactoring of haddock
which could be achieved but that is left for a future patch which can
implemented at any time independently of GHC.

- - - - -
e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00
Update test output

- - - - -
6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00
Merge branch 'wip/opaque_pragma' into 'ghc-head'

Add Haddock support for the OPAQUE pragma

See merge request ghc/haddock!2
- - - - -
42208183 by Steve Hart at 2022-03-25T20:43:50+01:00
Fix CI (#1467)

* CI: Reinstall GHC with docs

CI tests were failing because the GHC preinstalled to the CI
environment does not include documentation, which is required for
running the Haddock tests. This commit causes the CI workflow to
reinstall GHC with docs so that tests can succeed.
- - - - -
9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00
Make links in Synopsis functional again (#1458)

Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to
e.preventDefault() when handling click events that reach a toggle
element. This prevents the browser from following hyperlinks within the
Synopsis section when they are clicked by a user. This commit restores
functioning hyperlinks within the Synopsis section by removing the call
to e.preventDefault(), as it does not appear to be necessary, and
removing it increases the flexibility of the details-helper code.
- - - - -
d1edd637 by sheaf at 2022-04-01T12:02:02+02:00
Keep track of promotion ticks in HsOpTy

Keeping track of promotion ticks in HsOpTy allows us to properly
pretty-print promoted constructors such as lists.

- - - - -
9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00
Add support for \cases

See merge request ghc/ghc!7873
- - - - -
b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00
spelling errors (#1471)


- - - - -
6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00
Rename [] to List

- - - - -
2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00
HsToken ConDeclGADT con_dcolon

- - - - -
90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00
Parse Markdown links at beginning of line within a paragraph (#1470)

* Catch Markdown links at beginning of line within paragraph

Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when
they occurred at the beginning of a line other than the first line of
the paragraph. This occurred because the parser was not interpreting a
left square bracket as a special character that could delimit special
markup. A space character was considered a special character, so, if a
space occurred at the beginning of the new line, then the parser would
interpret the space by itself and then continue parsing, thereby
catching the Markdown link. '\n' was not treated as a special character,
so the parser did not catch a Markdown link that may have followed.

Note that this will allow for Markdown links that are not surrounded by
spaces. For example, the following text includes a Markdown link that
will be parsed:

  Hello, world[label](url)

This is consistent with how the parser handles other types of markup.

* Remove obsolete documentation hint

Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the
need for the workaround suggested in the documentation.
- - - - -
5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00
Force ghc-9.2 in the cabal.project

- - - - -
0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00
Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469)

Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7.
- [Release notes](https://github.com/jbgutierrez/path-parse/releases)
- [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7)

---
updated-dependencies:
- dependency-name: path-parse
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00
Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468)

Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5.
- [Release notes](https://github.com/gulpjs/copy-props/releases)
- [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md)
- [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5)

---
updated-dependencies:
- dependency-name: copy-props
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00
Update for GHC 9.4

- - - - -
9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00
Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head

- - - - -
f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00
Bump ghc version to 9.5

- - - - -
e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00
Revert "Bump ghc-head (#1445)"

This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2.

This should not have been merged.

- - - - -
a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00
Merge commit '2627a86c' into ghc-head

- - - - -
0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4

- - - - -
b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00
Revert "HsToken ConDeclGADT con_dcolon"

This reverts commit 24208496649a02d5f87373052c430ea4a97842c5.

- - - - -
15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00
Bump base upper bound

- - - - -
165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00
Update test output

- - - - -
e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00
Add hlint action .hlint.yaml with ignores & CPP. (#1475)


- - - - -
ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00
fix grammar in docs: "can the" → "can be" (#1477)


- - - - -
cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00
Allow base-4.17

- - - - -
e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00
Remove unused imports that GHC warned about. (#1480)


- - - - -
222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00
Follow hlint suggestion to remove redundant bang. (#1479)


- - - - -
058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00
Follow hlint, remove language pragmas in libs. (#1478)


- - - - -
0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00
Keep track of ordered list indexes and render them (#1407)

* Keep track of ordered list indexes and render them

* Rename some identifiers to clarify
- - - - -
f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00
update for changes in GHC API

- - - - -
3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00
Add link to the readthedocs in cabal description to show on hackage.

(cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b)

- - - - -
5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00
remove Bug873

- - - - -
968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00
Ignore "Use second" HLint suggestion. It increases laziness.

- - - - -
02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00
Fix hyperlinks to external items and modules (#1482)

Fixes haskell/haddock#1481.

There were two bugs in this:
* We were assuming that we were always getting a relative path to the
  module in question, while Nix gives us file:// URLs sometimes. This
  change checks for those and stops prepending `..` to them.
* We were not linking to the file under the module. This seems
  to have been a regression introduced by haskell/haddock#977. That is, the URLs were
  going to something like
  file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src
  which does not have the appropriate HTML file or fragment for the item
  in question at the end.

There is a remaining instance of the latter bug, but not in the
hyperlinker: the source links to items reexported from other modules are
also not including the correct file name. e.g. the reexport of Entity in
esqueleto, from persistent.

NOTE: This needs to get tested with relative-path located modules. It seems
correct for Nix based on my testing.

Testing strategy:

```
nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson
mkdir /tmp/aesonbuild && cd /tmp/aesonbuild
export out=/tmp/aesonbuild/out
genericBuild

ln -sf $HOME/co/haddock/haddock-api/resources .
./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source
```
- - - - -
b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00
fix parsing trailing quotes in backticked identifiers (#1408) (#1483)


- - - - -
80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00
Fix "Defined by not used" error

(cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a)

- - - - -
4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00
Fix the changelog and bump the version of haddock-library on ghc-9.2

- - - - -
fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00
Fix the changelog and bump the version of haddock-library on ghc-9.2

- - - - -
b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00
Hide synopsis from search when hidden (#1486)

Fix haskell/haddock#1451
- - - - -
f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00
Allow to hide interfaces when rendering multiple components (#1487)

This is useful when one wishes to `--gen-contents` when rendering
multiple components, but one does not want to render all modules.  This
is in particular useful when adding base package.
- - - - -
f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00
Check if doc-index.json exists before reading it (#1488)


- - - - -
31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00
Version bump 2.26.1 (#1489)

* Version bump 2.26.1

We extended format accepted by `--read-interface` option, which requires
updating the minor version.

* Update documentation of --read-interface option
- - - - -
7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00
Updated HaddockHypsrcTest output for record update changes (MR !7981)

- - - - -
cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00
Use visibility to decide which interfaces are included in quickjump (#1490)

This is also consistent with how html index is build.  See
haskell/cabal#7669 for rationale behind this decision.
- - - - -
00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00
Add code of conduct and hspec failure files in .gitignore

- - - - -
2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00
Add code of conduct and hspec failure files in .gitignore

- - - - -
63a5650c by romes at 2022-05-31T12:43:22+01:00
TTG: Match new GHC AST

- - - - -
dd7d1617 by romes at 2022-06-02T16:11:00+01:00
Update for IE changes in !8228

- - - - -
c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00
Fix and improve CI (#1495)

* Pin GHC version before creating the freeze file

* Use newest action versions

* Improve caching

* Avoid unnecessarily reinstalling GHC

* Use GHC 9.2.2 for CI

Co-authored-by: Cyd Wise <cwise at tripshot.com>
- - - - -
c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00
Add Mergify configuration (#1496)


- - - - -
2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00
Bump haddock's version in cabal file to 2.26.1 (#1497)


- - - - -
d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00
Render module tree per package in the content page (#1492)

* Render module tree per package in the content page

When rendering content page for multiple packages it is useful to split
the module tree per package.  Package names in this patch are inferred
from haddock's interface file names.

* Write PackageInfo into interface file

To keep interface file format backward compatible, instead of using
`Binary` instance for `InterfaceFile` we introduce functions to
serialise and deserialise, which depends on the interface file version.
- - - - -
77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00
Fix haskell/haddock#783 Don't show button if --quickjump not present

- - - - -
b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00
Merge pull request haskell/haddock#1108 from mpilgrem/fix783

Fix haskell/haddock#783 Don't show button if --quickjump not present
- - - - -
6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00
Update the contribution guide

- - - - -
e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00
Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500)

Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3.
- [Release notes](https://github.com/substack/node-shell-quote/releases)
- [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md)
- [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3)

---
updated-dependencies:
- dependency-name: shell-quote
  dependency-type: indirect
...

Signed-off-by: dependabot[bot] <support at github.com>

Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com>
- - - - -
29d0ef70 by romes at 2022-07-06T11:29:39+02:00
TTG: AST Updates for !8308

- - - - -
1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00
Match GHC changes for T21805

This brings in a newtype for FieldLabelString

- - - - -
6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00
Bump hlint version to 3.4.1, the version with counts. (#1503)

Redo the counts available with the --default option.
- - - - -
48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00
Follow hlint suggestion: unused LANGUAGE pragma. (#1504)

* Follow hlint suggestion: unused LANGUAGE pragma.

* Ignore within modules to pass linting and pass tests.
- - - - -
c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00
Follow hlint suggestion: redundant $. (#1505)

* Follow hlint suggestion: redundant $.

* Remove $ and surplus blank lines in Operators.
- - - - -
74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00
Fix hyperlinks to external items and modules (#1482)

Fixes haskell/haddock#1481.

There were two bugs in this:
* We were assuming that we were always getting a relative path to the
  module in question, while Nix gives us file:// URLs sometimes. This
  change checks for those and stops prepending `..` to them.
* We were not linking to the file under the module. This seems
  to have been a regression introduced by haskell/haddock#977. That is, the URLs were
  going to something like
  file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src
  which does not have the appropriate HTML file or fragment for the item
  in question at the end.

There is a remaining instance of the latter bug, but not in the
hyperlinker: the source links to items reexported from other modules are
also not including the correct file name. e.g. the reexport of Entity in
esqueleto, from persistent.

NOTE: This needs to get tested with relative-path located modules. It seems
correct for Nix based on my testing.

Testing strategy:

```
nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson
mkdir /tmp/aesonbuild && cd /tmp/aesonbuild
export out=/tmp/aesonbuild/out
genericBuild

ln -sf $HOME/co/haddock/haddock-api/resources .
./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source
```

(cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a)

- - - - -
faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00
Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks

Backport 9-4: Fix hyperlinks to external items and modules (#1482)
- - - - -
5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00
Merge remote-tracking branch 'origin/ghc-9.4'

- - - - -
63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00
Clean up build and testsuite for GHC 9.4

- - - - -
d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00
Bump the versions

- - - - -
505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00
Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge

Merge GHC 9.4 into `main`
- - - - -
5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00
html-test: Testsuite changes for GHC 9.4.1

- - - - -
5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00
doc: Fix a few minor ReST issues

Sphinx was complaining about too-short title underlines.

- - - - -
220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00
Merge branch 'main' into ghc-head

- - - - -
fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00
Updates for GHC 9.5

- - - - -
eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00
HsToken ConDeclGADT con_dcolon

- - - - -
c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00
Updates for GHC 9.5

- - - - -
3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00
HsToken ConDeclGADT con_dcolon

- - - - -
a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00
Merge branch 'wip/ghc-head-bump' into ghc-head

- - - - -
af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00
Disuse `mapLoc`.

- - - - -
a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00
Scrub partiality about `NewOrData`.

- - - - -
2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00
Test output changed because of change to `base`

Spooky, but I guess that is intended?

- - - - -
a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00
update tests for the move of tuples to GHC.Tuple.Prim

- - - - -
461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00
match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion)

- - - - -
f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00
Update Haddock for GHC MR !8563 (configuration of diagnostics)

- - - - -
3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00
Class layout info

- - - - -
cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00
Adapt to Constraint-vs-Type

See haskell/haddock#21623 and !8750

- - - - -
7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00
Remove outdated footnote about module re-exports

The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine.
- - - - -
206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00
Merge pull request haskell/haddock#1534 from tomsmeding/patch-1


- - - - -
a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00
Support mtl-2.3

- - - - -
e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00
Track small API change in TyCon.hs

- - - - -
eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00
Update for GhC 9.6

- - - - -
063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00
Merge remote-tracking branch 'upstream/ghc-head' into HEAD

- - - - -
4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00
Bump bounds to accomodate base-4.18

- - - - -
340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00
HsToken in HsAppKindTy

- - - - -
946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00
Bump GHC version to 9.7

- - - - -
2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00
Rename () to Unit, Rename (,,...,,) to Tuple<n>

- - - - -
eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00
Bump versions for ghc-9.6 release

- - - - -
4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00
Adapt to warning categories changes

- - - - -
642d8d60 by sheaf at 2023-03-29T13:35:56+02:00
Adapt to record field refactor

This commit adapts to the changes in GHC MR !8686, which overhauls
the treatment of record fields in the renamer, adding separate record
field namespaces and entirely removing the GreName datatype.

- - - - -
ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00
Update UniqMap API

- - - - -
7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00
update classify with new tokens

- - - - -
ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00
Remove index-state

- - - - -
05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00
`renameInterface` space leak fixes

- Change logic for accumulation of names for which link warnings
  will be generated
- Change handling of `--ignore-link-symbol` to allow qualified and
  unqualified names. Added to CHANGES.md
- Some formatting changes and comments here and there

- - - - -
e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00
Messy things

- ghc-debug dependency and instrumentation
- cabal.project custom with-compiler
- hie.yaml files
- traces and such

- - - - -
0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00
Stop retaining GRE closures

GRE closures should never be necessary to Haddock, so we never want to
keep them on the heap. Despite that, they are retained by a lot of the
data structures that Haddock makes use of.

- Attempt to fix that situation by adding strictness to various
  computations and pruning the `ifaceInstances` field of `Interface` to
  a much thinner data type.

- Removes the `ifaceFamInstances` field, as it was never used.

- Move some of the attach instances types (e.g. `SimpleType`) to the
  types module

- - - - -
8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00
Memory usage fixes

- Refactor `ifaceDeclMap` to drastically reduce memory footprint. We
  no longer store all declarations associated with a given name, since
  we only cared to determine if the only declaration associated with a
  name was a value declaration. Change the `DeclMap` type to better
  reflect this.
- Drop pre-renaming export items after the renaming step. Since the
  Hoogle backend used the pre-renamed export items, this isn't trivial.
  We now generate Hoogle output for exported declarations during the
  renaming step (if Hoogle output /should/ be generated), and store that
  with the renamed export item.
- Slightly refactor Hoogle backend to handle the above change and allow
  for early generation of Hoogle output.
- Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the
  `Interface` type, as they were never used.
- Remove some unnecessary strictness
- Remove a lot of dead code from `Syb` module

- - - - -
1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00
Unify ErrMsgM and IfM

- Delete ErrMsgM, stop accumulating warnings in a writer
- Make IfM a state monad, print warnings directly to stdout, move IfM
  type into types module
- Drop ErrMsg = String synonym
- Unset IORefs from plugin after they are read, preventing unnecessary
  retention of interfaces

- - - - -
42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00
Thunk leak fixes

The strictness introduced in this commit was motivated by observing
thunk leaks in the eventlog2html output.

- Refactor attach instances list comprehension to avoid large
  intermediate thunks
- Refactor some HTML backend list comprehensions to avoid large
  intermediate thunks
- Avoid thunks accumulating in documentation types or documentation
  parser
- A lot of orphan NFData instances to allow us to force documentation
  values

- - - - -
68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00
Remove GHC debug dep

- - - - -
10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00
Force HIE file path

Removes a potential retainer of `ModSummary`s

- - - - -
1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00
Re-add index-state, with-compiler, delete hie.yamls

- - - - -
a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00
Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes

Reduce memory usage
- - - - -
e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00
Merge branch ghc-9.6 into ghc-head

- - - - -
22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00
Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head

- - - - -
41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00
changes to the WarningTxt cases

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00
Port the remains of Hi-Haddock

- - - - -
9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00
Stdout for tests

- - - - -
36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00
Formatting, organize imports

- - - - -
a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix empty context confusion in Convert module

- - - - -
379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix associated type families in Hoogle output

- - - - -
fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00
Fix test refs

Accept several changes in Hoogle tests:

Pretty printing logic no longer prints the `(Proxy (Proxy (...))`
chain in Bug806 with parentheses. Since this test was only meant
to verify that line breaks do not occur, accept the change.

`tyThingToLHsDecl` is called for class and data declarations, which ends
up "synifying" the type variables and giving unlifted types kind
signatures. As a result, type variables of kind `Type -> Type`
are now printed with kind signatures in Hoogle output. This could
be changed by manually drop kind signatures from class variables
in the Hoogle backend if the behavior is deemed unacceptable.

Sometimes subordinate declarations are exported separate from their
parent declarations (e.g. record selectors). In this case, a type
signature is cobbled together for the export item in `extractDecl`.
Since this type signature is very manually constructed, it may lack
kind signatures of decls constructed from `tyThingToLHsDecl`. An
example of this is the `type-sigs` Hoogle test.

Change `*` to `Type` in Hoogle test refs. I don't think this will
break Hoogle behavior, since it appears to not consider type
signatures in search. I have not fully verified this.

- - - - -
e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Fix LaTeX backend test refs

Changes to GHC pretty printing code have resulted in some
differences to Haddock's LaTeX output.

- Type variables are printed explicitly quantified in the
  LinearTypes test
- Wildcard types in type family equations are now printed numbered,
  e.g. _1 _2, in the TypeFamilies3 test
- Combined signatures in DefaultSignatures test are now documented
  as separate signatures

- - - - -
41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Formatting and test source updates

- Stop using kind `*` in html test sources
- Add TypeOperators where necessary to avoid warnings and future errors
- Rename some test modules to match their module names

- - - - -
c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Fix missing deprecation warnings on record fields

`lookupOccEnv` was used to resolve `OccNames` with warnings attached, but
it doesn't look in the record field namespace. Thus, if a record field
had a warning attached, it would not resolve and the warning map would
not include it. This commit fixes by using `lookupOccEnv_WithFields`
instead.

- - - - -
fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00
Formatting and some comments

- - - - -
751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00
Accept HTML test diffs

All diffs now boil down to the expected differences resulting from
declarations being reified from TyThings in hi-haddock. Surface
syntax now has much less control over the syntax used in the
documentation.

- - - - -
d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00
Adapt to new load' type

- - - - -
dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00
Update mkWarningMap and moduleWarning

- - - - -
8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00
Revert load' changes

- - - - -
aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00
Accept change to Instances test in html-test

Link to Data.Tuple instead of GHC.Tuple.Prim

- - - - -
8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00
Reset ghc dep to ^>= 9.6

- - - - -
2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00
Update CHANGES.md, user guide, recomp avoidance

* Add --trace-args flag for tracing arguments received to standard output
* Avoid recompiling due to changes in optimization flags
* Update users guide and changes.md

- - - - -
f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00
Add "Avoiding Recompilation" section to docs

This section is a bit of a WIP due to the unstable nature of hi-haddock
and the lack of tooling supporting it, but its a good start.

- - - - -
bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00
Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345

Neither of these MRs are ready to land yet which causes issues with
other MRs which are ready to land and need haddock changes.

- - - - -
421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
atSign has no unicode variant

Prior to this change, atSign was defined as follows:

	atSign unicode = text (if unicode then "@" else "@")

Yes, this is the same symbol '\64' and not your font playing
tricks on you. Now we define:

	atSign = char '@'

Both the LaTeX and the Xhtml backend are updated accordingly.

- - - - -
3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
LaTeX: fix printing of type variable bindings

Consider this type signature:

	kindOf :: forall {k} (a :: k). Proxy a -> Proxy k

Prior to this fix, the LaTeX backend rendered it like this:

	kindOf :: forall k a. Proxy a -> Proxy k

Now we preserve explicit specificity and kind annotations.

- - - - -
0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00
Add support for invisible binders in type declarations

- - - - -
13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00
Add "Avoiding Recompilation" section to docs

This section is a bit of a WIP due to the unstable nature of hi-haddock
and the lack of tooling supporting it, but its a good start.

- - - - -
3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00
Add note about stubdir to recompilation docs

- - - - -
db7e84dc by Finley at 2023-06-08T08:11:03-06:00
Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6

hi-haddock for ghc 9.6
- - - - -
4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00
Replace SYB traversals

- - - - -
7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00
Test ref accepts, remove unused HaddockClsInst

- - - - -
df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00
Use batchMsg for progress reporting during load

With hi-haddock as is, there is an awkward silence during the load operation.
This commit makes haddock use the default `batchMsg` Messager for progress
reporting, and makes the default GHC verbosity level 1, so the user can see
what GHC is doing.

- - - - -
f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00
Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim


- - - - -
a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00
hi-haddock squashed

- - - - -
c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00
Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed

- - - - -
40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00
Changes related to MR !10283

MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase.

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00
Bump GHC version to 9.8

- - - - -
74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00
Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head

- - - - -
418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00
Remove NFData SourceText, IfaceWarnings updates

The NFData SourceText instance is now available in GHC

Handle mod_iface mi_warns now being IfaceWarnings

- - - - -
62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00
Accept Instances.hs test output

Due to ghc!10469.

- - - - -
a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00
Test fixes for "Fix associated data family doc structure items"

Associated data families were being given their own export DocStructureItems,
which resulted in them being documented separately from their classes in
haddocks. This commit fixes it.

- - - - -
cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00
Changes related to MR !10283

MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase.

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -
9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00
Bump GHC version to 9.8

- - - - -
fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00
Bump GHC version to 9.9

- - - - -
0c2a756e by sheaf at 2023-07-07T13:45:12+02:00
Avoid incomplete record update in Haddock Hoogle

This commit avoids running into an incomplete record update warning
in the Hoogle backend of Haddock.

This was only noticed now, because incomplete record updates were broken
in GHC 9.6. Now that they are fixed, we have to avoid running into them!

- - - - -
f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00
Bump base bound to <4.20

For GHC 9.8.

- - - - -
1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Check for puns (see ghc#23368)

- - - - -
457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Remove fake exports for (~), List, and Tuple<n>

The old reasoning no longer applies, nowadays those names can be
mentioned in export lists.

- - - - -
bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00
Fix pretty-printing of Solo and MkSolo

- - - - -
495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00
Fix issue with duplicate reexported definitions (T23616)

When a class method was reexported, it's default methods were also
showing up in the generated html page.

The simplest and most non-invasive fix is to not look for the default
method if we are just exporting the class method.. because the backends
are just showing default methods when the whole class is exported.

In general it would be worthwhile to rewrite this bit of code I think as
the logic and what gets included is split over `lookupDocs` and
`availExportDecl` it would be clearer to combine the two. The result of
lookupDocs is always just passed to availExportDecl so it seems simpler
and more obvious to just write the function directly.

- - - - -
6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00
Remove fake export of `FUN` from Prelude

This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes
\#23920 on GHC.

- - - - -
9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00
Match changes in wip/az/T23885-unicode-funtycon

- - - - -
69abb171 by Finley McIlwaine at 2023-10-06T14:06:28-07:00
Ensure unconstrained instance dictionaries get IPE info

In the `StgRhsCon` case of `GHC.Stg.Debug.collectStgRhs`, we were not coming up
with an initial source span based on the span of the binder, which was causing
instance dictionaries without dynamic superclass constraints to not have source
locations in their IPE info. Now they do.

Resolves #24005

- - - - -
390443b7 by Andreas Klebinger at 2023-10-07T10:00:20-04:00
rts: Split up rts/include/stg/MachRegs.h by arch

- - - - -
3685942f by Bryan Richter at 2023-10-07T10:00:56-04:00
Actually set hackage index state

Or at least, use a version of the cabal command that *claims* to set the
index state.

Time will tell.

- - - - -
46a0e5be by Bryan Richter at 2023-10-07T10:00:56-04:00
Update hackage index state

- - - - -
d4b037de by Bryan Richter at 2023-10-07T10:00:56-04:00
Ensure hadrian uses CI's hackage index state

- - - - -
e206be64 by Andrew Lelechenko at 2023-10-08T15:06:14-04:00
Do not use O_NONBLOCK on regular files or block devices

CLC proposal https://github.com/haskell/core-libraries-committee/issues/166

- - - - -
a06197c4 by David Binder at 2023-10-08T15:06:55-04:00
Update hpc-bin submodule to 0.69

- - - - -
ed6785b6 by David Binder at 2023-10-08T15:06:55-04:00
Update Hadrian with correct path to happy file for hpc-bin

- - - - -
94066d58 by Alan Zimmerman at 2023-10-09T21:35:53-04:00
EPA: Introduce HasAnnotation class

The class is defined as

    class HasAnnotation e where
      noAnnSrcSpan :: SrcSpan -> e

This generalises noAnnSrcSpan, and allows

    noLocA :: (HasAnnotation e) => a -> GenLocated e a
    noLocA = L (noAnnSrcSpan noSrcSpan)

- - - - -
8792a1bc by Ben Gamari at 2023-10-09T21:36:29-04:00
Bump unix submodule to v2.8.3.0

- - - - -
e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00
Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around.

The motivation for the flag is given in #21917.

- - - - -
3ed58cef by Matthew Pickering at 2023-10-10T19:01:22-04:00
hadrian: Add ghcToolchain to tool args list

This allows you to load ghc-toolchain and ghc-toolchain-bin into HLS.

- - - - -
476c02d4 by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Normalise triple via config.sub

We were not normalising the target triple anymore like we did with the
old make build system.

Fixes #23856

- - - - -
303dd237 by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Add missing vendor normalisation

This is copied from m4/ghc_convert_vendor.m4

Towards #23868

- - - - -
838026c9 by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Add loongarch64 to parseArch

Towards #23868

- - - - -
1a5bc0b5 by Matthew Pickering at 2023-10-10T19:01:22-04:00
Add same LD hack to ghc-toolchain

In the ./configure script, if you pass the `LD` variable then this has
the effect of stopping use searching for a linker and hence passing
`-fuse-ld=...`.

We want to emulate this logic in ghc-toolchain, if a use explicilty
specifies `LD` variable then don't add `-fuse-ld=..` with the goal of
making ./configure and ghc-toolchain agree on which flags to use when
using the C compiler as a linker.

This is quite unsavoury as we don't bake the choice of LD into the
configuration anywhere but what's important for now is making
ghc-toolchain and ./configure agree as much as possible.

See #23857 for more discussion

- - - - -
42d50b5a by Ben Gamari at 2023-10-10T19:01:22-04:00
ghc-toolchain: Check for C99 support with -std=c99

Previously we failed to try enabling C99 support with `-std=c99`, as
`autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which
don't enable C99 by default.

Fixes #23879.

- - - - -
da2961af by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro

In very old toolchains the BYTE_ORDER macro is not set but thankfully
the __BYTE_ORDER__ macro can be used instead.

- - - - -
d8da73cd by Matthew Pickering at 2023-10-10T19:01:22-04:00
configure: AC_PATH_TARGET_TOOL for LD

We want to make sure that LD is set to an absolute path in order to be
consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL
macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which
might use a relative path.

- - - - -
171f93cc by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Check whether we need -std=gnu99 for CPP as well

In ./configure the C99 flag is passed to the C compiler when used as a C
preprocessor. So we also check the same thing in ghc-toolchain.

- - - - -
89a0918d by Matthew Pickering at 2023-10-10T19:01:22-04:00
Check for --target linker flag separately to C compiler

There are situations where the C compiler doesn't accept `--target` but
when used as a linker it does (but doesn't do anything most likely)

In particular with old gcc toolchains, the C compiler doesn't support
--target but when used as a linker it does.

- - - - -
37218329 by Matthew Pickering at 2023-10-10T19:01:22-04:00
Use Cc to compile test file in nopie check

We were attempting to use the C compiler, as a linker, to compile a file
in the nopie check, but that won't work in general as the flags we pass
to the linker might not be compatible with the ones we pass when using
the C compiler.

- - - - -
9b2dfd21 by Matthew Pickering at 2023-10-10T19:01:22-04:00
configure: Error when ghc-toolchain fails to compile

This is a small QOL change as if you are working on ghc-toolchain and it
fails to compile then configure will continue and can give you outdated
results.

- - - - -
1f0de49a by Matthew Pickering at 2023-10-10T19:01:22-04:00
configure: Check whether -no-pie works when the C compiler is used as a linker

`-no-pie` is a flag we pass when using the C compiler as a linker (see
pieCCLDOpts in GHC.Driver.Session) so we should test whether the C
compiler used as a linker supports the flag, rather than just the C
compiler.

- - - - -
62cd2579 by Matthew Pickering at 2023-10-10T19:01:22-04:00
ghc-toolchain: Remove javascript special case for --target detection

emcc when used as a linker seems to ignore the --target flag, and for
consistency with configure which now tests for --target, we remove this
special case.

- - - - -
0720fde7 by Ben Gamari at 2023-10-10T19:01:22-04:00
toolchain: Don't pass --target to emscripten toolchain

As noted in `Note [Don't pass --target to emscripten toolchain]`,
emscripten's `emcc` is rather inconsistent with respect to its treatment
of the `--target` flag. Avoid this by special-casing this toolchain
in the `configure` script and `ghc-toolchain`.

Fixes on aspect of #23744.

- - - - -
6354e1da by Matthew Pickering at 2023-10-10T19:01:22-04:00
hadrian: Don't pass `--gcc-options` as a --configure-arg to cabal configure

Stop passing -gcc-options which mixed together linker flags and
non-linker flags. There's no guarantee the C compiler will accept both
of these in each mode.

- - - - -
c00a4bd6 by Ben Gamari at 2023-10-10T19:01:22-04:00
configure: Probe stage0 link flags

For consistency with later stages and CC.

- - - - -
1f11e7c4 by Sebastian Graf at 2023-10-10T19:01:58-04:00
Stricter Binary.get in GHC.Types.Unit (#23964)

I noticed some thunking while looking at Core.
This change has very modest, but throughout positive ghc/alloc effect:

```
 hard_hole_fits(normal) ghc/alloc    283,057,664    281,620,872  -0.5%

              geo. mean                                          -0.1%
              minimum                                            -0.5%
              maximum                                            +0.0%
```

Fixes #23964.

- - - - -
a4f1a181 by Bryan Richter at 2023-10-10T19:02:37-04:00
rel_eng/upload.sh cleanups

- - - - -
80705335 by doyougnu at 2023-10-10T19:03:18-04:00
ci: add javascript label rule

This adds a rule which triggers the javascript job when the "javascript"
label is assigned to an MR.

- - - - -
a2c0fff6 by Matthew Craven at 2023-10-10T19:03:54-04:00
Make 'wWarningFlagsDeps' include every WarningFlag

Fixes #24071.

- - - - -
d055f099 by Jan Hrček at 2023-10-10T19:04:33-04:00
Fix pretty printing of overlap pragmas in TH splices (fixes #24074)

- - - - -
0746b868 by Andreas Klebinger at 2023-10-10T19:05:09-04:00
Aarch64 NCG: Use encoded immediates for literals.

Try to generate

    instr x2, <imm>

instead of

    mov x1, lit
    instr x2, x1

When possible. This get's rid if quite a few redundant
mov instructions.

I believe this causes a metric decrease for LargeRecords as
we reduce register pressure.

-------------------------
Metric Decrease:
    LargeRecord
-------------------------

- - - - -
739f4e6f by Andreas Klebinger at 2023-10-10T19:05:09-04:00
AArch NCG: Refactor getRegister'

Remove some special cases which can be handled just as well by the
generic case.

This increases code re-use while also fixing #23749. Since some of the
special case wasn't upholding Note [Signed arithmetic on AArch64].

- - - - -
1b213d33 by Andreas Klebinger at 2023-10-10T19:05:09-04:00
Aarch ncg: Optimize immediate use for address calculations

When the offset doesn't fit into the immediate we now just reuse the
general getRegister' code path which is well optimized to compute the
offset into a register instead of a special case for CmmRegOff.

This means we generate a lot less code under certain conditions which is
why performance metrics for these improve.

-------------------------
Metric Decrease:
    T4801
    T5321FD
    T5321Fun
-------------------------

- - - - -
b7df0732 by John Ericson at 2023-10-11T16:02:11-04:00
RTS configure: Move over mem management checks

These are for heap allocation, a strictly RTS concern.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

The RTS configure one has a new
```
AC_CHECK_SIZEOF([void *])
```
that the top-level configure version didn't have, so that
`ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter
commits, that can go away.

Progress towards #17191

- - - - -
41130a65 by John Ericson at 2023-10-11T16:02:11-04:00
RTS configure: Move over `__thread` check

This used by (@bgamari thinks) the `GCThread` abstraction in the RTS.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
cc5ec2bd by John Ericson at 2023-10-11T16:02:11-04:00
RTS configure: Move over misc function checks

These are for general use in the RTS.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
809e7c2d by John Ericson at 2023-10-11T16:02:11-04:00
RTS configure: Move over `eventfd` check

This check is for the RTS part of the event manager and has a
corresponding part in `base`.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
58f3babf by John Ericson at 2023-10-11T16:02:48-04:00
Split `FP_CHECK_PTHREADS` and move part to RTS configure

`NEED_PTHREAD_LIB` is unused since
3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build
system), and so is no longer defined.

Progress towards #17191

- - - - -
e99cf237 by Moritz Angermann at 2023-10-11T16:03:24-04:00
nativeGen: section flags for .text$foo only

Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix
#22834 in !9810.

It does however add "xr" indiscriminatly to .text sections
even if splitSections is disabled. This leads to the assembler saying:

ghc_1.s:7849:0: error:
     Warning: Ignoring changed section attributes for .text
     |
7849 | .section .text,"xr"
     | ^

- - - - -
f383a242 by Sylvain Henry at 2023-10-11T16:04:04-04:00
Modularity: pass TempDir instead of DynFlags (#17957)

- - - - -
34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00
Test that functions from `mingwex` are available

Ryan wrote these two minimizations, but they never got added to the test
suite.

See #23309, #23378

Co-Authored-By: Ben Gamari <bgamari.foss at gmail.com>
Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com>

- - - - -
bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00
Do not check for the `mingwex` library in `/configure`

See the recent discussion in !10360 --- Cabal will itself check for the
library for the packages that need it, and while the autoconf check
additionally does some other things like define a `HAS_LIBMINGWEX` C
Preprocessor macro, those other things are also unused and unneeded.

Progress towards #17191, which aims to get rid of `/configure` entirely.

- - - - -
43e814e1 by Ben Gamari at 2023-10-12T06:49:40-04:00
base: Introduce move modules into src

The only non-move changes here are whitespace changes to pass the
`whitespace` test and a few testsuite adaptations.

- - - - -
df81536f by Moritz Angermann at 2023-10-12T06:50:16-04:00
[PEi386 linker] Bounds check and null-deref guard

We should resonably be able to expect that we won't exceed the number of
sections if we assume to be dealing with legal object files. We can however
not guarantee that we get some negative values, and while we try to
special case most, we should exclude negative indexing into the sections
array.

We also need to ensure that we do not try to derefences targetSection,
if it is NULL, due to the switch statement.

- - - - -
c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00
Move apple compat check to RTS configure

- - - - -
c80778ea by John Ericson at 2023-10-12T10:31:13-04:00
Move clock/timer fun checks to RTS configure

Actual library check (which will set the Cabal flag) is left in the
top-level configure for now.

Progress towards #17191

- - - - -
7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00
Move visibility and "musttail" annotation checks to the RTS configure

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00
Move leading underscore checks to RTS configure

`CabalLeadingUnderscore` is done via Hadrian already, so we can stop
`AC_SUBST`ing it completely.

- - - - -
25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00
Move alloca, fork, const, and big endian checks to RTS configure

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

- - - - -
5170f42a by John Ericson at 2023-10-12T10:31:13-04:00
Move libdl check to RTS configure

- - - - -
ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00
Adjust `FP_FIND_LIBFFI`

Just set vars, and `AC_SUBST` in top-level configure.

Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't
be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the
make build system).

- - - - -
f399812c by John Ericson at 2023-10-12T10:31:13-04:00
Split BFD support to RTS configure

The flag is still in the top-level configure, but the other checks
(which define various macros --- important) are in the RTS configure.

- - - - -
f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00
Split libm check between top level and RTS

- - - - -
dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00
CgUtils.fixStgRegStmt respect register width

This change ensure that the reg + offset computation is always of the
same size.  Before this we could end up with a 64bit register, and then
add a 32bit offset (on 32bit platforms).  This not only would fail type
sanity checking, but also incorrectly truncate 64bit values into 32bit
values silently on 32bit architectures.

- - - - -
9e6ef7ba by Matthew Pickering at 2023-10-12T20:35:00-04:00
hadrian: Decrease verbosity of cabal commands

In Normal, most tools do not produce output to stdout unless there are
error conditions.

Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217

- - - - -
08fc27af by John Ericson at 2023-10-12T20:35:36-04:00
Do not substitute `@...@` for stage-specific values in cabal files

`rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag
defaults; instead manual choices are passed to configure in the usual
way.

The old way was fundamentally broken, because it meant we were baking
these Cabal files for a specific stage. Now we only do stage-agnostic
@...@ substitution in cabal files (the GHC version), and so all
stage-specific configuration is properly confined to `_build` and the
right stage dir.

Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim`
(it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got
rid of it.

Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
a0ac8785 by Sebastian Graf at 2023-10-14T19:17:12-04:00
Fix restarts in .ghcid

Using the whole of `hadrian/` restarted in a loop for me.

- - - - -
fea9ecdb by Sebastian Graf at 2023-10-14T19:17:12-04:00
CorePrep: Refactor FloatingBind (#23442)

A drastically improved architecture for local floating in CorePrep
that decouples the decision of whether a float is going to be let- or case-bound
from how far it can float (out of strict contexts, out of lazy contexts, to
top-level).

There are a couple of new Notes describing the effort:

  * `Note [Floating in CorePrep]` for the overview
  * `Note [BindInfo and FloatInfo]` for the new classification of floats
  * `Note [Floats and FloatDecision]` for how FloatInfo is used to inform
    floating decisions

This is necessary ground work for proper treatment of Strict fields and
unlifted values at top-level.

Fixes #23442.

NoFib results (omitted = 0.0%):
```
--------------------------------------------------------------------------------
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
         pretty           0.0%     -1.6%
            scc           0.0%     -1.7%
--------------------------------------------------------------------------------
            Min           0.0%     -1.7%
            Max           0.0%     -0.0%
 Geometric Mean          -0.0%     -0.0%
```

- - - - -
32523713 by Matthew Pickering at 2023-10-14T19:17:49-04:00
hadrian: Move ghcBinDeps into ghcLibDeps

This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the
`ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc`
library so need to make sure they are present in the libdir even if we
are not going to build `ghc-bin`.

This also fixes things for cross compilers because the stage2
cross-compiler requires the ghc-usage.txt file, but we are using
the stage2 lib folder but not building stage3:exe:ghc-bin so
ghc-usage.txt was not being generated.

- - - - -
ec3c4488 by sheaf at 2023-10-14T19:18:29-04:00
Combine GREs when combining in mkImportOccEnv

In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import
item in favour of another, as explained in Note [Dealing with imports]
in `GHC.Rename.Names`. However, this can cause us to lose track of
important parent information.

Consider for example #24084:

  module M1 where { class C a where { type T a } }
  module M2 ( module M1 ) where { import M1 }
  module M3 where { import M2 ( C, T ); instance C () where T () = () }

When processing the import list of `M3`, we start off (for reasons that
are not relevant right now) with two `Avail`s attached to `T`, namely
`C(C, T)` and `T(T)`. We combine them in the `combine` function of
`mkImportOccEnv`; as described in Note [Dealing with imports] we discard
`C(C, T)` in favour of `T(T)`. However, in doing so, we **must not**
discard the information want that `C` is the parent of `T`. Indeed,
losing track of this information can cause errors when importing,
as we could get an error of the form

  ‘T’ is not a (visible) associated type of class ‘C’

We fix this by combining the two GREs for `T` using `plusGRE`.

Fixes #24084

- - - - -
257c2807 by Ilias Tsitsimpis at 2023-10-14T19:19:07-04:00
hadrian: Pass -DNOSMP to C compiler when needed

Hadrian passes the -DNOSMP flag to GHC when the target doesn't support
SMP, but doesn't pass it to CC as well, leading to the following
compilation error on mips64el:

| Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d
Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0
===> Command failed with error code: 1
In file included from rts/include/Stg.h:348,
                 from rts/include/Rts.h:38,
                 from rts/hooks/FlagDefaults.c:8:
rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture
  416 | #error memory barriers unimplemented on this architecture
      |  ^~~~~
rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture
  440 | #error memory barriers unimplemented on this architecture
      |  ^~~~~
rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture
  464 | #error memory barriers unimplemented on this architecture
      |  ^~~~~

The old make system correctly passed this flag to both GHC and CC [1].

Fix this error by passing -DNOSMP to CC as well.

[1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407

Closes #24082

- - - - -
13d3c613 by John Ericson at 2023-10-14T19:19:42-04:00
Users Guide: Drop dead code for Haddock refs to `parallel`

I noticed while working on !11451 that `@LIBRARY_parallel_UNIT_ID@` was
not substituted. It is dead code -- there is no `parallel-ref` usages
and it doesn't look like there ever was (going back to
3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b), so let's delete it.

- - - - -
fe067577 by Sylvain Henry at 2023-10-18T19:40:25-04:00
Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066)

bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a".

- - - - -
cc1625b1 by Sylvain Henry at 2023-10-18T19:40:25-04:00
Bignum: fix right shift of negative BigNat with native backend

- - - - -
cbe4400d by Sylvain Henry at 2023-10-18T19:40:25-04:00
Rts: expose rtsOutOfBoundsAccess symbol

- - - - -
72c7380c by Sylvain Henry at 2023-10-18T19:40:25-04:00
Hadrian: enable `-fcheck-prim-bounds` in validate flavour

This allows T24066 to fail when the bug is present.

Otherwise the out-of-bound access isn't detected as it happens in
ghc-bignum which wasn't compiled with the bounds check.

- - - - -
f9436990 by John Ericson at 2023-10-18T19:41:01-04:00
Make Hadrian solely responsible for substituting `docs/users_guide/ghc_config.py.in`

Fixes #24091
Progress on #23966

Issue #24091 reports that `@ProjectVersion@` is no longer being
substituted in the GHC user's guide. I assume this is a recent issue,
but I am not sure how it's worked since
c1a3ecde720b3bddc2c8616daaa06ee324e602ab; it looks like both Hadrian and
configure are trying to substitute the same `.in` file!

Now only Hadrian does. That is better anyways; already something that
issue #23966 requested.

It seems like we were missing some dependencies in Hadrian. (I really,
really hate that this is possible!) Hopefully it is fixed now.

- - - - -
b12df0bb by John Ericson at 2023-10-18T19:41:37-04:00
`ghcversion.h`: No need to cope with undefined `ProjectPatchLevel*`

Since 4e6c80197f1cc46dfdef0300de46847c7cfbdcb0, these are guaranteed to
be defined. (Guaranteed including a test in the testsuite.)

- - - - -
0295375a by John Ericson at 2023-10-18T19:41:37-04:00
Generate `ghcversion.h` from a `.in` file

Now that there are no conditional sections (see the previous commit), we
can just a do simple substitution rather than pasting it together line
by line.

Progress on #23966

- - - - -
740a1b85 by Krzysztof Gogolewski at 2023-10-19T11:37:20-04:00
Add a regression test for #24064

- - - - -
921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00
CLC Proposal #182: Export List from Data.List

Proposal link: https://github.com/haskell/core-libraries-committee/issues/182

- - - - -
4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00
rts: fix small argument passing on big-endian arch (fix #23387)

- - - - -
b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00
Interpreter: fix literal alignment on big-endian architectures (fix #19261)

Literals weren't correctly aligned on big-endian, despite what the
comment said.

- - - - -
a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00
Testsuite: recomp011 and recomp015 are fixed on powerpc

These tests have been fixed but not tested and re-enabled on big-endian
powerpc (see comments in #11260 and #11323)

- - - - -
fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00
CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102)
- - - - -
02efc181 by John Ericson at 2023-10-22T02:48:55-04:00
Move function checks to RTS configure

Some of these functions are used in `base` too, but we can copy the
checks over to its configure if that's an issue.

- - - - -
5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00
Move over a number of C-style checks to RTS configure

- - - - -
5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00
Move/Copy more `AC_DEFINE` to RTS config

Only exception is the LLVM version macros, which are used for GHC
itself.

- - - - -
b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00
Define `TABLES_NEXT_TO_CODE` in the RTS configure

We create a new cabal flag to facilitate this.

- - - - -
4a40271e by John Ericson at 2023-10-22T02:48:55-04:00
Configure scripts: `checkOS`: Make a bit more robust

`mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This
allows us to cope with configs/triples that we haven't normalized extra
being what GNU `config.sub` does.

- - - - -
16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00
Generate `ghcplatform.h` from RTS configure

We create a new cabal flag to facilitate this.

- - - - -
7dfcab2f by John Ericson at 2023-10-22T02:48:55-04:00
Get rid of all mention of `mk/config.h`

The RTS configure script is now solely responsible for managing its
headers; the top level configure script does not help.

- - - - -
c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00
rts: drop stale mentions of MIN_UPD_SIZE

We used to have MIN_UPD_SIZE macro that describes the minimum reserved
size for thunks, so that the thunk can be overwritten in place as
indirections or blackholes. However, this macro has not been actually
defined or used anywhere since a long time ago; StgThunkHeader already
reserves a padding word for this purpose. Hence this patch which drops
stale mentions of MIN_UPD_SIZE.

- - - - -
d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00
base changelog: move non-backported entries from 4.19 section to 4.20

Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational)
nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip)
were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section.

Also minor stylistic changes to other entries, bringing them to a uniform form.

- - - - -
de78b32a by Alan Zimmerman at 2023-10-23T09:09:41-04:00
EPA Some tweaks to annotations

- Fix span for GRHS
- Move TrailingAnns from last match to FunBind
- Fix GADT 'where' clause span
- Capture full range for a CaseAlt Match

- - - - -
d5a8780d by Simon Hengel at 2023-10-23T09:10:23-04:00
Update primitives.rst
- - - - -
4d075924 by Josh Meredith at 2023-10-24T23:04:12+11:00
JS/userguide: add explanation of writing jsbits

- - - - -
07ab5cc1 by Cheng Shao at 2023-10-24T15:40:32-04:00
testsuite: increase timeout of ghc-api tests for wasm32

ghc-api tests for wasm32 are more likely to timeout due to the large
wasm module sizes, especially when testing with wasm native tail
calls, given wasmtime's handling of tail call opcodes are suboptimal
at the moment. It makes sense to increase timeout specifically for
these tests on wasm32. This doesn't affect other targets, and for
wasm32 we don't increase timeout for all tests, so not to risk letting
major performance regressions slip through the testsuite.

- - - - -
0d6acca5 by Greg Steuck at 2023-10-26T08:44:23-04:00
Explicitly require RLIMIT_AS before use in OSMem.c

This is done elsewhere in the source tree. It also suddenly is
required on OpenBSD.

- - - - -
9408b086 by Sylvain Henry at 2023-10-26T08:45:03-04:00
Modularity: modularize external linker

Decouple runLink from DynFlags to allow calling runLink more easily.
This is preliminary work for calling Emscripten's linker (emcc) from
our JavaScript linker.

- - - - -
e0f35030 by doyougnu at 2023-10-27T08:41:12-04:00
js: add JStg IR, remove unsaturated constructor

- Major step towards #22736 and adding the optimizer in #22261

- - - - -
35587eba by Simon Peyton Jones at 2023-10-27T08:41:48-04:00
Fix a bug in tail calls with ticks

See #24078 for the diagnosis.  The change affects only
the Tick case of occurrence analysis.

It's a bit hard to test, so no regression test (yet anyway).

- - - - -
9bc5cb92 by Matthew Craven at 2023-10-28T07:06:17-04:00
Teach tag-inference about SeqOp/seq#

Fixes the STG/tag-inference analogue of #15226.

Co-Authored-By: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
34f06334 by Moritz Angermann at 2023-10-28T07:06:53-04:00
[PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra

48e391952c17ff7eab10b0b1456e3f2a2af28a9b
introduced `SYM_TYPE_DUP_DISCARD` to the bitfield.

The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value.
Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us
relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions.

- - - - -
5b51b2a2 by Mario Blažević at 2023-10-28T07:07:33-04:00
Fix and test for issue #24111, TH.Ppr output of pattern synonyms

- - - - -
723bc352 by Alan Zimmerman at 2023-10-30T20:36:41-04:00
EPA: print doc comments as normal comments

And ignore the ones allocated in haddock processing.

It does not guarantee that every original haddock-like comment appears
in the output, as it discards ones that have no legal attachment point.

closes #23459

- - - - -
21b76843 by Simon Peyton Jones at 2023-10-30T20:37:17-04:00
Fix non-termination bug in equality solver

constraint left-to-right then right to left, forever.

Easily fixed.

- - - - -
270867ac by Sebastian Graf at 2023-10-30T20:37:52-04:00
ghc-toolchain: build with `-package-env=-` (#24131)

Otherwise globally installed libraries (via `cabal install --lib`)
break the build.

Fixes #24131.

- - - - -
4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00
EPA: match changes in GHC

- EPA: Comments in AnchorOperation
- EPA: Remove EpaEofComment

- - - - -
7a90020f by Krzysztof Gogolewski at 2023-10-31T20:03:37-04:00
docs: fix ScopedTypeVariables example (#24101)

The previous example didn't compile.

Furthermore, it wasn't demonstrating the point properly.
I have changed it to an example which shows that 'a' in the signature
must be the same 'a' as in the instance head.

- - - - -
49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00
Fix pretty-printing of type family dependencies

"where" should be after the injectivity annotation.

- - - - -
73c191c0 by Ben Gamari at 2023-10-31T20:04:49-04:00
gitlab-ci: Bump LLVM bootstrap jobs to Debian 12

As the Debian 10 images have too old an LLVM.

Addresses #24056.

- - - - -
5b0392e0 by Matthew Pickering at 2023-10-31T20:04:49-04:00
ci: Run aarch64 llvm backend job with "LLVM backend" label

This brings it into line with the x86 LLVM backend job.

- - - - -
9f9c9227 by Ryan Scott at 2023-11-01T09:19:12-04:00
More robust checking for DataKinds

As observed in #22141, GHC was not doing its due diligence in catching code
that should require `DataKinds` in order to use. Most notably, it was allowing
the use of arbitrary data types in kind contexts without `DataKinds`, e.g.,

```hs
data Vector :: Nat -> Type -> Type where
```

This patch revamps how GHC tracks `DataKinds`. The full specification is
written out in the `DataKinds` section of the GHC User's Guide, and the
implementation thereof is described in `Note [Checking for DataKinds]` in
`GHC.Tc.Validity`. In brief:

* We catch _type_-level `DataKinds` violations in the renamer. See
  `checkDataKinds` in `GHC.Rename.HsType` and `check_data_kinds` in
  `GHC.Rename.Pat`.

* We catch _kind_-level `DataKinds` violations in the typechecker, as this
  allows us to catch things that appear beneath type synonyms. (We do *not*
  want to do this in type-level contexts, as it is perfectly fine for a type
  synonym to mention something that requires DataKinds while still using the
  type synonym in a module that doesn't enable DataKinds.) See `checkValidType`
  in `GHC.Tc.Validity`.

* There is now a single `TcRnDataKindsError` that classifies all manner of
  `DataKinds` violations, both in the renamer and the typechecker. The
  `NoDataKindsDC` error has been removed, as it has been subsumed by
  `TcRnDataKindsError`.

* I have added `CONSTRAINT` is `isKindTyCon`, which is what checks for illicit
  uses of data types at the kind level without `DataKinds`. Previously,
  `isKindTyCon` checked for `Constraint` but not `CONSTRAINT`. This is
  inconsistent, given that both `Type` and `TYPE` were checked by `isKindTyCon`.
  Moreover, it thwarted the implementation of the `DataKinds` check in
  `checkValidType`, since we would expand `Constraint` (which was OK without
  `DataKinds`) to `CONSTRAINT` (which was _not_ OK without `DataKinds`) and
  reject it. Now both are allowed.

* I have added a flurry of additional test cases that test various corners of
  `DataKinds` checking.

Fixes #22141.

- - - - -
575d7690 by Sylvain Henry at 2023-11-01T09:19:53-04:00
JS: fix FFI "wrapper" and "dynamic"

Fix codegen and helper functions for "wrapper" and "dynamic" foreign
imports.

Fix tests:
- ffi006
- ffi011
- T2469
- T4038

Related to #22363

- - - - -
81fb8885 by Alan Zimmerman at 2023-11-01T22:23:56-04:00
EPA: Use full range for Anchor

This change requires a series of related changes, which must all land
at the same time, otherwise all the EPA tests break.

* Use the current Anchor end as prior end

  Use the original anchor location end as the source of truth for
  calculating print deltas.

  This allows original spacing to apply in most cases, only changed
  AST items need initial delta positions.

* Add DArrow to TrailingAnn

* EPA Introduce HasTrailing in ExactPrint

   Use [TrailingAnn] in enterAnn and remove it from
   ExactPrint (LocatedN RdrName)

* In HsDo, put TrailingAnns at top of LastStmt

* EPA: do not convert comments to deltas when balancing.

* EPA: deal with fallout from getMonoBind

* EPA fix captureLineSpacing

* EPA print any comments in the span before exiting it

* EPA: Add comments to AnchorOperation

* EPA: remove AnnEofComment, it is no longer used

Updates Haddock submodule

- - - - -
03e82511 by Rodrigo Mesquita at 2023-11-01T22:24:32-04:00
Fix in docs regarding SSymbol, SNat, SChar (#24119)

- - - - -
362cc693 by Matthew Pickering at 2023-11-01T22:25:08-04:00
hadrian: Update bootstrap plans (9.4.6, 9.4.7, 9.6.2, 9.6.3, 9.8.1)

Updating the bootstrap plans with more recent GHC versions.

- - - - -
00b9b8d3 by Matthew Pickering at 2023-11-01T22:25:08-04:00
ci: Add 9.8.1 bootstrap testing job

- - - - -
ef3d20f8 by Matthew Pickering at 2023-11-01T22:25:08-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* An incorrect version guard on the stack decoding logic in ghc-heap
* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24077

- - - - -
6755d833 by Jaro Reinders at 2023-11-03T10:54:42+01:00
Add NCG support for common 64bit operations to the x86 backend.

These used to be implemented via C calls which was obviously quite bad
for performance for operations like simple addition.

Co-authored-by: Andreas Klebinger

- - - - -
0dfb1fa7 by Vladislav Zavialov at 2023-11-03T14:08:41-04:00
T2T in Expressions (#23738)

This patch implements the T2T (term-to-type) transformation in
expressions. Given a function with a required type argument
	vfun :: forall a -> ...

the user can now call it as
	vfun (Maybe Int)

instead of
	vfun (type (Maybe Int))

The Maybe Int argument is parsed and renamed as a term (HsExpr), but then
undergoes a conversion to a type (HsType).
See the new function expr_to_type in compiler/GHC/Tc/Gen/App.hs
and Note [RequiredTypeArguments and the T2T mapping]

Left as future work: checking for puns.

- - - - -
cc1c7c54 by Duncan Coutts at 2023-11-05T00:23:44-04:00
Add a test for I/O managers

It tries to cover the cases of multiple threads waiting on the same
fd for reading and multiple threads waiting for writing, including
wait cancellation by async exceptions.

It should work for any I/O manager, in-RTS or in-Haskell.
Unfortunately it will not currently work for Windows because it relies
on anonymous unix sockets. It could in principle be ported to use
Windows named pipes.

- - - - -
2e448f98 by Cheng Shao at 2023-11-05T00:23:44-04:00
Skip the IOManager test on wasm32 arch.

The test relies on the sockets API which are not (yet) available.
- - - - -
fe50eb35 by Cheng Shao at 2023-11-05T00:24:20-04:00
compiler: fix eager blackhole symbol in wasm32 NCG

- - - - -
af771148 by Cheng Shao at 2023-11-05T00:24:20-04:00
testsuite: fix optasm tests for wasm32

- - - - -
1b90735c by Matthew Pickering at 2023-11-05T00:24:20-04:00
testsuite: Add wasm32 to testsuite arches with NCG

The compiler --info reports that wasm32 compilers have a NCG, so we
should agree with that here.

- - - - -
db9a6496 by Alan Zimmerman at 2023-11-05T00:24:55-04:00
EPA: make locA a function, not a field name

And use it to generalise reLoc

The following for the windows pipeline one. 5.5%

Metric Increase:
    T5205

- - - - -
833e250c by Simon Peyton Jones at 2023-11-05T00:25:31-04:00
Update the unification count in wrapUnifierX

Omitting this caused type inference to fail in #24146.
This was an accidental omision in my refactoring of the
equality solver.

- - - - -
e451139f by Andreas Klebinger at 2023-11-05T00:26:07-04:00
Remove an accidental git conflict marker from a comment.

- - - - -
e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00
EPA: match changes in GHC, l2l cleanup

- - - - -
30baac7a by Tobias Haslop at 2023-11-06T10:50:32+00:00
Add laws relating between Foldable/Traversable with their Bi- superclasses

See https://github.com/haskell/core-libraries-committee/issues/205 for
discussion.

This commit also documents that the tuple instances only satisfy the
laws up to lazyness, similar to the documentation added in !9512.

- - - - -
df626f00 by Tobias Haslop at 2023-11-07T02:20:37-05:00
Elaborate on the quantified superclass of Bifunctor

This was requested in the comment
https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700
for when Traversable becomes a superclass of Bitraversable, but similarly
applies to Functor/Bifunctor, which already are in a superclass relationship.

- - - - -
8217acb8 by Alan Zimmerman at 2023-11-07T02:21:12-05:00
EPA: get rid of l2l and friends

Replace them with

  l2l to convert the location
  la2la to convert a GenLocated thing

Updates haddock submodule

- - - - -
dd88a260 by Luite Stegeman at 2023-11-07T02:21:53-05:00
JS: remove broken newIdents from JStg Monad

GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate
identifiers being generated in h$c1, h$c2, ... .

This change removes the broken newIdents.

- - - - -
455524a2 by Matthew Craven at 2023-11-09T08:41:59-05:00
Create specially-solved DataToTag class

Closes #20532. This implements CLC proposal 104:
  https://github.com/haskell/core-libraries-committee/issues/104

The design is explained in Note [DataToTag overview]
in GHC.Tc.Instance.Class. This replaces the existing
`dataToTag#` primop.

These metric changes are not "real"; they represent Unique-related
flukes triggering on a different set of jobs than they did previously.
See also #19414.

Metric Decrease:
    T13386
    T8095
Metric Increase:
    T13386
    T8095

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
a05f4554 by Alan Zimmerman at 2023-11-09T08:42:35-05:00
EPA: get rid of glRR and friends in GHC/Parser.y

With the HasLoc and HasAnnotation classes, we can replace a
number of type-specific helper functions in the parser with
polymorphic ones instead

Metric Decrease:
    MultiLayerModulesTH_Make

- - - - -
18498538 by Cheng Shao at 2023-11-09T16:58:12+00:00
ci: bump ci-images for wasi-sdk upgrade

- - - - -
52c0fc69 by PHO at 2023-11-09T19:16:22-05:00
Don't assume the current locale is *.UTF-8, set the encoding explicitly

primops.txt contains Unicode characters:
> LC_ALL=C ./genprimopcode --data-decl < ./primops.txt
> genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226)

Hadrian must also avoid using readFile' to read primops.txt because it
tries to decode the file with a locale-specific encoding.

- - - - -
7233b3b1 by PHO at 2023-11-09T19:17:01-05:00
Use '[' instead of '[[' because the latter is a Bash-ism

It doesn't work on platforms where /bin/sh is something other than Bash.

- - - - -
6dbab180 by Simon Peyton Jones at 2023-11-09T19:17:36-05:00
Add an extra check in kcCheckDeclHeader_sig

Fix #24083 by checking for a implicitly-scoped type variable that is not
actually bound.  See Note [Disconnected type variables] in GHC.Tc.Gen.HsType

For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler
allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures.

Metric Decrease:
    MultiLayerModulesTH_Make

- - - - -
22551364 by Sven Tennie at 2023-11-11T06:35:22-05:00
AArch64: Delete unused LDATA pseudo-instruction

Though there were consuming functions for LDATA, there were no
producers. Thus, the removed code was "dead".

- - - - -
2a0ec8eb by Alan Zimmerman at 2023-11-11T06:35:59-05:00
EPA: harmonise acsa and acsA in GHC/Parser.y

With the HasLoc class, we can remove the acsa helper function,
using acsA instead.

- - - - -
4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00
EPA: Replace Anchor with EpaLocation

Match GHC

- - - - -
7ae517a0 by Teo Camarasu at 2023-11-12T08:04:12-05:00
nofib: bump submodule

This includes changes that:
- fix building a benchmark with HEAD
- remove a Makefile-ism that causes errors in bash scripts

Resolves #24178

- - - - -
3f0036ec by Alan Zimmerman at 2023-11-12T08:04:47-05:00
EPA: Replace Anchor with EpaLocation

An Anchor has a location and an operation, which is either that it is
unchanged or that it has moved with a DeltaPos

    data Anchor = Anchor { anchor :: RealSrcSpan
                         , anchor_op :: AnchorOperation }

An EpaLocation also has either a location or a DeltaPos

    data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan)
                     | EpaDelta !DeltaPos ![LEpaComment]

Now that we do not care about always having a location in the anchor,
we remove Anchor and replace it with EpaLocation

We do this with a type alias initially, to ease the transition.
The alias will be removed in time.

We also have helpers to reconstruct the AnchorOperation from an
EpaLocation. This is also temporary.

Updates Haddock submodule

- - - - -
a7492048 by Alan Zimmerman at 2023-11-12T13:43:07+00:00
EPA: get rid of AnchorOperation

Now that the Anchor type is an alias for EpaLocation, remove
AnchorOperation.

Updates haddock submodule

- - - - -
0745c34d by Andrew Lelechenko at 2023-11-13T16:25:07-05:00
Add since annotation for showHFloat

- - - - -
e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
Suppress duplicate librares linker warning of new macOS linker

Fixes #24167

XCode 15 introduced a new linker which warns on duplicate libraries being
linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as
suggested by Brad King in CMake issue #25297.

This flag isn't necessarily available to other linkers on darwin, so we must
only configure it into the CC linker arguments if valid.

- - - - -
c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
testsuite: Encoding test witnesses recent iconv bug is fragile

A regression in the new iconv() distributed with XCode 15 and MacOS
Sonoma causes the test 'encoding004' to fail in the CP936 roundrip.

We mark this test as fragile until this is fixed upstream (rather than
broken, since previous versions of iconv pass the test)

See #24161

- - - - -
ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
testsuite: Update to LC_ALL=C no longer being ignored in darwin

MacOS seems to have fixed an issue where it used to ignore the variable
`LC_ALL` in program invocations and default to using Unicode.

Since the behaviour seems to be fixed to account for the locale
variable, we mark tests that were previously broken in spite of it as
fragile (since they now pass in recent macOS distributions)

See #24161

- - - - -
e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
darwin: Fix single_module is obsolete warning

In XCode 15's linker, -single_module is the default and otherwise
passing it as a flag results in a warning being raised:

    ld: warning: -single_module is obsolete

This patch fixes this warning by, at configure time, determining whether
the linker supports -single_module (which is likely false for all
non-darwin linkers, and true for darwin linkers in previous versions of
macOS), and using that information at runtime to decide to pass or not
the flag in the invocation.

Fixes #24168

- - - - -
929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
testsuite: Skip MultiLayerModulesTH_Make on darwin

The recent toolchain upgrade on darwin machines resulted in the
MultiLayerModulesTH_Make test metrics varying too much from the
baseline, ultimately blocking the CI pipelines.

This commit skips the test on darwin to temporarily avoid failures due
to the environment change in the runners. However, the metrics
divergence is being investigated still (tracked in #24177)

- - - - -
af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00
configure: check target (not build) understands -no_compact_unwind

Previously, we were branching on whether the build system was darwin to
shortcut this check, but we really want to branch on whether the target
system (which is what we are configuring ld_prog for) is darwin.

- - - - -
2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00
JS: Fix missing variable declarations

The JStg IR update was missing some local variable declarations
that were present earlier, causing global variables to be used
implicitly (or an error in JavaScript strict mode).

This adds the local variable declarations again.

- - - - -
99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00
Remove loopy superclass solve mechanism

Programs with a -Wloopy-superclass-solve warning will now fail with an error.

Fixes #23017

- - - - -
2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00
users-guide: Fix links to libraries from the users-guide.

The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the
package name, so we don't need to explicitly add it to the links.

Fixes #24151

- - - - -
27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00
EPA: splitLHsForAllTyInvis does not return ann

We did not use the annotations returned from splitLHsForAllTyInvis, so
do not return them.

- - - - -
a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00
Document defaulting of RuntimeReps

Fixes #24099

- - - - -
2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00
Second fix to #24083

My earlier fix turns out to be too aggressive for data/type families

See wrinkle (DTV1) in Note [Disconnected type variables]

- - - - -
cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00
Fix unusable units and module reexport interaction (#21097)

This commit fixes an issue with ModUnusable introduced in df0f148feae.

In mkUnusableModuleNameProvidersMap we traverse the list of unusable
units and generate ModUnusable origin for all the modules they contain:
exposed modules, hidden modules, and also re-exported modules. To do
this we have a two-level map:

  ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin

So for each module name "M" in broken unit "u" we have:
  "M" -> u:M -> ModUnusable reason

However in the case of module reexports we were using the *target*
module as a key. E.g. if "u:M" is a reexport for "X" from unit "o":
   "M" -> o:X -> ModUnusable reason

Case 1: suppose a reexport without module renaming (u:M -> o:M) from
unusable unit u:
   "M" -> o:M -> ModUnusable reason

Here it's claiming that the import of M is unusable because a reexport
from u is unusable. But if unit o isn't unusable we could also have in
the map:
   "M" -> o:M -> ModOrigin ...

Issue: the Semigroup instance of ModuleOrigin doesn't handle the case
(ModUnusable <> ModOrigin)

Case 2: similarly we could have 2 unusable units reexporting the same module
without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v
unusable. It gives:

  "M" -> o:M -> ModUnusable ... (for u)
  "M" -> o:M -> ModUnusable ... (for v)

Issue: the Semigroup instance of ModuleOrigin doesn't handle the case
(ModUnusable <> ModUnusable).

This led to #21097, #16996, #11050.

To fix this, in this commit we make ModUnusable track whether the module
used as key is a reexport or not (for better error messages) and we use
the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u
is unusable, we now record:

    "M" -> u:M -> ModUnusable reason reexported=True

So now, we have two cases for a reexport u:M -> o:X:
   - u unusable: "M" -> u:M -> ModUnusable ... reexported=True
   - u usable:   "M" -> o:X -> ModOrigin   ... reexportedFrom=u:M

The second case is indexed with o:X because in this case the Semigroup
instance of ModOrigin is used to combine valid expositions of a module
(directly or via reexports).

Note that module lookup functions select usable modules first (those who
have a ModOrigin value), so it doesn't matter if we add new ModUnusable
entries in the map like this:

  "M" -> {
    u:M -> ModUnusable ... reexported=True
    o:M -> ModOrigin ...
  }

The ModOrigin one will be used. Only if there is no ModOrigin or
ModHidden entry will the ModUnusable error be printed. See T21097 for an
example printing several reasons why an import is unusable.

- - - - -
3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00
Fix IPE test

A helper function was defined in a different module than used.
To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe

- - - - -
49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00
Properly compute unpacked sizes for -funpack-small-strict-fields.

Use rep size rather than rep count to compute the size.

Fixes #22309

- - - - -
b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00
Explicit methods for Alternative Compose

Explicitly define some and many in Alternative instance for
Data.Functor.Compose

Implementation of https://github.com/haskell/core-libraries-committee/issues/181

- - - - -
9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00
Add permutations for non-empty lists.

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837

- - - - -
5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00
Update changelog and since annotations for Data.List.NonEmpty.permutations

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837

- - - - -
94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00
Update doc string for traceShow

Updated doc string for traceShow.

- - - - -
faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00
JS: clean up some foreign imports

- - - - -
856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00
AArch64: Remove unused instructions

As these aren't ever emitted, we don't even know if they work or will
ever be used. If one of them is needed in future, we may easily re-add
it.

Deleted instructions are:
- CMN
- ANDS
- BIC
- BICS
- EON
- ORN
- ROR
- TST
- STP
- LDP
- DMBSY

- - - - -
615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00
EPA: Replace Monoid with NoAnn

Remove the final Monoid instances in the exact print infrastructure.

For Windows CI

Metric Decrease:
    T5205

- - - - -
5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00
Speed up stimes in instance Semigroup Endo

As discussed at
https://github.com/haskell/core-libraries-committee/issues/4

- - - - -
cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00
base: reflect latest changes in the changelog

- - - - -
48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00
EPA: Use SrcSpan in EpaSpan

This is more natural, since we already need to deal with invalid
RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for.

Updates haddock submodule.

- - - - -
97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00
Add regression test for #6070

Fixes #6070.

- - - - -
e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00
chore: Correct typo in the gitlab MR template

[skip ci]

- - - - -
f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00
Improve error message when reading invalid `.target` files

A `.target` file generated by ghc-toolchain or by configure can become
invalid if the target representation (`Toolchain.Target`) is changed
while the files are not re-generated by calling `./configure` or
`ghc-toolchain` again. There is also the issue of hadrian caching the
dependencies on `.target` files, which makes parsing fail when reading
reading the cached value if the representation has been updated.

This patch provides a better error message in both situations, moving
away from a terrible `Prelude.read: no parse` error that you would get
otherwise.

Fixes #24199

- - - - -
955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00
users guide: Note that QuantifiedConstraints implies ExplicitForAll

Fixes #24025.

- - - - -
17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00
fix: Change type signatures in NonEmpty export comments to reflect reality

This fixes several typos in the comments of
Data.List.NonEmpty export list items.

- - - - -
2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00
Fix the platform string for GNU/Hurd

As commited in Cargo
https://github.com/haskell/cabal/pull/9434
there is confusion between "gnu" and "hurd". This got fixed in Cargo, we
need the converse in Hadrian.

Fixes #24180

- - - - -
a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00
EPA: Tuple Present no longer has annotation

The Present constructor for a Tuple argument will never have an exact
print annotation. So make this impossible.

- - - - -
121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00
Unify the hpc testsuites

The hpc testsuite was split between testsuite/tests/hpc
and the submodule libraries/hpc/test. This commit unifies
the two testsuites in the GHC repository in the directory
testsuite/tests/hpc.

- - - - -
d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00
EPA: empty tup_tail has noAnn

In Parser.y, the tup_tail rule had the following option
          | {- empty -} %shift   { return [Left noAnn] }

Once this works through PostProcess.hs, it means we add an extra
Missing constructor if the last item was a comma.

Change the annotation type to a Bool to indicate this, and use the
EpAnn Anchor for the print location for the others.

- - - - -
fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00
Fix FMA primops generating broken assembly on x86.

`genFMA3Code` assumed that we had to take extra precations to avoid overwriting
the result of `getNonClobberedReg`. One of these special cases caused a bug resulting
in broken assembly.

I believe we don't need to hadle these cases specially at all, which means this MR simply
deletes the special cases to fix the bug.

Fixes #24160

- - - - -
34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00
EPA: Remove parenthesizeHsType

This is called from PostProcess.hs, and adds spurious parens.
With the looser version of exact printing we had before we could
tolerate this, as they would be swallowed by the original at the same
place.

But with the next change (remove EpAnnNotUsed) they result in
duplicates in the output.

For Darwin build:

Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -
3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00
Add name for -Wdeprecated-type-abstractions (#24154)

This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wcompat.

- - - - -
7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00
EPA: Remove EpAnnNotUsed

We no longer need the EpAnnNotUsed constructor for EpAnn, as we can
represent an unused annotation with an anchor having a EpaDelta of
zero, and empty comments and annotations.

This simplifies code handling annotations considerably.

Updates haddock submodule

Metric Increase:
    parsing001

- - - - -
471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00
Bumped the upper bound of text to <2.2

- - - - -
d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00
Term variable capture (#23740)

This patch changes type variable lookup rules (lookupTypeOccRn) and
implicit quantification rules (filterInScope) so that variables bound
in the term namespace can be captured at the type level

  {-# LANGUAGE RequiredTypeArguments #-}
  f1 x = g1 @x                -- `x` used in a type application
  f2 x = g2 (undefined :: x)  -- `x` used in a type annotation
  f3 x = g3 (type x)          -- `x` used in an embedded type
  f4 x = ...
    where g4 :: x -> x        -- `x` used in a type signature
          g4 = ...

This change alone does not allow us to accept examples shown above,
but at least it gets them past the renamer.

- - - - -
da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00
Update Note [hsScopedTvs and visible foralls]

The Note was written before GHC gained support for visible forall in
types of terms. Rewrite a few sentences and use a better example.

- - - - -
b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00
testsuite: Add mechanism to collect generic metrics

* Generalise the metric logic by adding an additional field which
  allows you to specify how to query for the actual value. Previously
  the method of querying the baseline value was abstracted (but always
  set to the same thing).

* This requires rejigging how the stat collection works slightly but now
  it's more uniform and hopefully simpler.

* Introduce some new "generic" helper functions for writing generic
  stats tests.

  - collect_size ( deviation, path )
    Record the size of the file as a metric

  - stat_from_file ( metric, deviation, path )
    Read a value from the given path, and store that as a metric

  - collect_generic_stat ( metric, deviation, get_stat)
    Provide your own `get_stat` function, `lambda way: <Int>`, which
    can be used to establish the current value of the metric.

  - collect_generic_stats ( metric_info ):
    Like collect_generic_stat but provide the whole dictionary of metric
    definitions.

    { metric: {
        deviation: <Int>
        current: lambda way: <Int>
        } }

* Introduce two new "size" metrics for keeping track of build products.
    - `size_hello_obj` - The size of `hello.o` from compiling hello.hs
    - `libdir` - The total size of the `libdir` folder.

* Track the number of modules in the AST tests
   - CountDepsAst
   - CountDepsParser

This lays the infrastructure for #24191 #22256 #17129

- - - - -
7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00
x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives

Fixes #24222

- - - - -
4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00
EPA: Remove SrcSpanAnn

Now that we only have a single constructor for EpAnn, And it uses a
SrcSpan for its location, we can do away with SrcSpanAnn completely.
It only existed to wrap the original SrcSpan in a location, and
provide a place for the exact print annotation.

For darwin only:
Metric Increase:
    MultiLayerModulesTH_OneShot

Updates haddock submodule

- - - - -
e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00
testsuite: don't initialize testdir to '.'

The test directory is removed during cleanup, if there's an interrupt
that could remove the entire repository.

Fixes #24219

- - - - -
af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00
EPA: Clean up mkScope in Ast.hs

Now that we have HasLoc we can get rid of all the custom variants of
mkScope

For deb10-numa

Metric Increase:
    libdir

- - - - -
292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00
distrib: Rediscover otool and install_name_tool on Darwin

In the bindist configure script we must rediscover the `otool` and
`install_name_tool`s since they may be different from the build
environment.

Fixes #24211.

- - - - -
dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00
llvmGen: Align objects in the data section

Objects in the data section may be referenced via tagged pointers.
Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit
platforms, respectively.  Note, this may need to be reconsidered if
objects with a greater natural alignment requirement are emitted as e.g.
128-bit atomics.

Fixes #24163.

- - - - -
f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00
metrics: Widen libdir and size_hello_obj acceptance window

af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can
fluctuate quite significantly even when the change is quite small.
Therefore we widen the acceptance window to 10%.

- - - - -
99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00
EPA: Clean up TC Monad Utils

We no longer need the alternative variant of addLocM (addLocMA)
nor wrapLocAM, wrapLocSndMA.

aarch64-darwin
Metric Increase:
    MultiLayerModulesTH_OneShot

deb10-numa-slow
Metric Decrease:
    libdir

- - - - -
94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00
Match GHC, No comments in EpaDelta for comments

- - - - -
cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00
perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414)

And additionally to T12545, link from T8095, T13386 to this new Note.

- - - - -
c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00
EPA: EpaDelta for comment has no comments

EpaLocation is used to position things. It has two constructors,
EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a
possible list of comments.  The comment list is needed because the
location in EpaDelta has no absolute information to decide which
comments should be emitted before them when printing.

But it is also used for specifying the position of a comment.  To
prevent the absurdity of a comment position having a list of comments
in it, we make EpaLocation parameterisable, using comments for the
normal case and a constant for within comments.

Updates haddock submodule.

aarch64-darwin
Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00
Kind-check body of a required forall

We now require that in 'forall a -> ty', ty has kind TYPE r for some r.
Fixes #24176

- - - - -
010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00
docs(NonEmpty/group): Remove incorrect haddock link quotes in code block

- - - - -
cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00
docs(NonEmpty/group): Remove cycle from group haddock example

- - - - -
495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00
docs(NonEmpty/group): Use repl haddock syntax in group docs

- - - - -
d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00
docs(NonEmpty/group): Use list [] notation in group haddock

- - - - -
dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00
docs(NonEmpty/group): Specify final property of group function in haddock

- - - - -
cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00
fix: Add missing property of List.group

- - - - -
bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00
testsuite: Fix T21097b test with make 4.1 (deb9)

cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which
failed on deb9 because the version of make was emitting the recipe
failure to stdout rather than stderr.

One way to fix this is to be more precise in the test about which part
of the output we care about inspecting.

- - - - -
5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00
testsuite: Track size of libdir in bytes

For consistency it's better if we track all size metrics in bytes.

Metric Increase:
  libdir

- - - - -
f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00
testsuite: Remove rogue trace in testsuite

I accidentally left a trace in the generics metric patch.

- - - - -
d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00
Only exit ghci in -e mode when :add command fails

Previously, when running `ghci -e ':add Sample.hs'` the process would
exit with exit code 1 if the file exists and could be loaded.

Fixes #24115

- - - - -
0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00
T2T in Patterns (#23739)

This patch implements the T2T (term-to-type) transformation in patterns.
Patterns that are checked against a visible forall can now be written
without the `type` keyword:

	  \(type t) (x :: t) -> ...   -- old
	  \t (x :: t) -> ...          -- new

The `t` binder is parsed and renamed as a term pattern (Pat), but
then undergoes a conversion to a type pattern (HsTyPat).
See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs

- - - - -
10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00
Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234)

Before, the source location would point at the surrounding function definition,
causing the confusion in #24234.
I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _`
to make the warning message say "irrefutable pattern" instead of "pattern
binding".

- - - - -
36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00
libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0

Updates filepath submodule
Updates unix submodule

Fixes #24240

- - - - -
91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00
Submodule linter: Allow references to tags

We modify the submodule linter so that if the bumped commit is a
specific tag then the commit is accepted.

Fixes #24241

- - - - -
86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00
hadrian: set -Wno-deprecations for directory and Win32

The filepath bump to 1.4.200.1 introduces a deprecation warning.

See https://gitlab.haskell.org/ghc/ghc/-/issues/24240
    https://github.com/haskell/filepath/pull/206

- - - - -
7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00
Zap OccInfo on case binders during StgCse #14895 #24233

StgCse can revive dead binders:

  case foo of dead { Foo x y -> Foo x y; ... }
  ===>
  case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead

So we must zap occurrence information on case binders.

Fix #14895 and #24233

- - - - -
57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00
Cpr: Turn an assertion into a check to deal with some dead code (#23862)

See the new `Note [Dead code may contain type confusions]`.

Fixes #23862.

- - - - -
c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00
testsuite: add test for #23944

- - - - -
6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00
driver: Only run a dynamic-too pipeline if object files are going to be generated

Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state
when writing simple interface" when dynamic-too is enabled

We could remove the panic and just write the interface even if the state is `DT_Dyn`,
but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already
designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled.

Fixes #23944.

- - - - -
28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00
Improve duplicate elimination in SpecConstr

This partially fixes #24229.

See the new Note [Pattern duplicate elimination] in SpecConstr

- - - - -
fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00
Make SpecConstr deal with casts better

This patch does two things, to fix #23209:

* It improves SpecConstr so that it no longer quantifies over
  coercion variables.  See Note [SpecConstr and casts]

* It improves the rule matcher to deal nicely with the case where
  the rule does not quantify over coercion variables, but the the
  template has a cast in it.  See Note [Casts in the template]

- - - - -
8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00
driver: Don't lose track of nodes when we fail to resolve cycles

The nodes that take part in a cycle should include both hs-boot and hs files,
but when we fail to resolve a cycle, we were only counting the nodes from the
graph without boot files.

Fixes #24196

- - - - -
c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00
testsuite: Skip MultiLayerModulesTH_OneShot on darwin

See #24177

- - - - -
fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00
docs(Data.Char):Add more detailed descriptions for some functions

Related changed function's docs:

-GHC.Unicode.isAlpha
-GHC.Unicode.isPrint
-GHC.Unicode.isAlphaNum

Add more details for what the function will return.

Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com>

- - - - -
ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00
Fix float parsing in GHC Cmm Lexer

Add test case for bug #24224

- - - - -
d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00
Take care when simplifying unfoldings

This MR fixes a very subtle bug exposed by #24242.

See Note [Environment for simplLetUnfolding].

I also updated a bunch of Notes on shadowing

- - - - -
03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00
Comments only in FloatIn

Relevant to #3458

- - - - -
50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00
Comments only in SpecConstr

- - - - -
9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00
Add test for #22238

- - - - -
d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00
Make forall a keyword (#23719)

Before this change, GHC used to accept `forall` as a term-level
identifier:

	-- from constraints-0.13
	forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p)
	forall d = ...

Now it is a parse error.

The -Wforall-identifier warning has served its purpose and is now
a deprecated no-op.

- - - - -
58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00
driver: Ensure we actually clear the interactive context before reloading

Previously we called discardIC, but immediately after set the session
back to an old HscEnv that still contained the IC

Partially addresses #24107
Fixes #23405

- - - - -
8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00
driver: Ensure we force the lookup of old build artifacts before returning the build plan

This prevents us from retaining all previous build artifacts in memory until a
recompile finishes, instead only retaining the exact artifacts we need.

Fixes #24118

- - - - -
105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00
testsuite: add test for #24118 and #24107

MultiLayerModulesDefsGhci was not able to catch the leak because it uses
:l which discards the previous environment.

Using :r catches both of these leaks

- - - - -
e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00
compiler: Add some strictness annotations to ImportSpec and related constructors
This prevents us from retaining entire HscEnvs.

Force these ImportSpecs when forcing the GlobalRdrEltX

Adds an NFData instance for Bag

Fixes #24107

- - - - -
522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00
compiler: Force IfGlobalRdrEnv in NFData instance.

- - - - -
188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00
LinearTypes => MonoLocalBinds

- - - - -
8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00
Linear let and where bindings

For expediency, the initial implementation of linear types in GHC
made it so that let and where binders would always be considered
unrestricted. This was rather unpleasant, and probably a big obstacle
to adoption. At any rate, this was not how the proposal was designed.

This patch fixes this infelicity. It was surprisingly difficult to
build, which explains, in part, why it took so long to materialise.

As of this patch, let or where bindings marked with %1 will be
linear (respectively %p for an arbitrary multiplicity p). Unmarked let
will infer their multiplicity.

Here is a prototypical example of program that used to be rejected and
is accepted with this patch:

```haskell
f :: A %1 -> B
g :: B %1 -> C

h :: A %1 -> C
h x = g y
  where
    y = f x
```

Exceptions:
- Recursive let are unrestricted, as there isn't a clear semantics of
  what a linear recursive binding would be.
- Destructive lets with lazy bindings are unrestricted, as their
  desugaring isn't linear (see also #23461).
- (Strict) destructive lets with inferred polymorphic type are
  unrestricted. Because the desugaring isn't linear (See #18461
  down-thread).

Closes #18461 and #18739

Co-authored-by: @jackohughes

- - - - -
effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00
Introduce `dataToTagSmall#` primop (closes #21710)

...and use it to generate slightly better code when dataToTag#
is used at a "small data type" where there is no need to mess
with "is_too_big_tag" or potentially look at an info table.

Metric Decrease:
    T18304

- - - - -
35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00
Fix formatting of Note [alg-alt heap check]

- - - - -
7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00
Allow untyped brackets in typed splices and vice versa.

Resolves #24190

Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27),
and while it does catch some mismatches, the type-checker will catch
them too. OTOH, it prevents writing completely reasonable programs.

- - - - -
32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00
EPA: Match changes to LHsToken removal

- - - - -
a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00
Drop hard Xcode dependency

XCODE_VERSION calls out to `xcodebuild`, which is only available
when having `Xcode` installed. The CommandLineTools are not
sufficient. To install Xcode, you must have an apple id to download
the Xcode.xip from apple.

We do not use xcodebuild anywhere in our build explicilty. At best
it appears to be a proxy for checking the linker or the compiler.
These should rather be done with
```
xcrun ld -version
```
or similar, and not by proxy through Xcode. The CLR should be
sufficient for building software on macOS.

- - - - -
1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00
docs: update information on RequiredTypeArguments

Update the User's Guide and Release Notes to account for the recent
progress in the implementation of RequiredTypeArguments.

- - - - -
d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00
rts/eventlog: Fix off-by-one in assertion

Previously we failed to account for the NULL terminator `postString`
asserted that there is enough room in the buffer for the string.

- - - - -
a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00
rts/eventlog: Honor result of ensureRoomForVariableEvent is

Previously we would keep plugging along, even if isn't enough room for
the event.

- - - - -
0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00
rts/eventlog: Avoid truncating event sizes

Previously ensureRoomForVariableEvent would truncate the desired size to
16-bits, resulting in #24197.

Fixes #24197.

- - - - -
64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00
Remove the "Derived Constraint" argument of TcPluginSolver, docs

- - - - -
fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00
EPA: Move tokens into GhcPs extension fields (#23447)

Summary of changes

* Remove Language.Haskell.Syntax.Concrete
* Move all tokens into GhcPs extension fields (LHsToken -> EpToken)
* Create new TTG extension fields as needed
* Drop the MultAnn wrapper

Updates the haddock submodule.

Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00
testsuite: use copy_files in T23405

This prevents the tree from being dirtied when the file is modified.

- - - - -
ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00
Document ghc package's PVP-noncompliance

This changes nothing, it just makes the status quo explicit.

- - - - -
8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00
JS: Mark spurious CI failures js_fragile(24259)

This marks the spurious test failures on the JS platform as
js_fragile(24259), so we don't hold up merge requests while
fixing the underlying issues.

See #24259

- - - - -
1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00
Late plugins

- - - - -
000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00
withTiming on LateCCs and late plugins

- - - - -
be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00
add test for late plugins

- - - - -
7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00
Document late plugins

- - - - -
9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00
Fix thunk update ordering

Previously we attempted to ensure soundness of concurrent thunk update
by synchronizing on the access of the thunk's info table pointer field.
This was believed to be sufficient since the indirectee (which may
expose a closure allocated by another core) would not be examined
until the info table pointer update is complete.

However, it turns out that this can result in data races in the presence
of multiple threads racing a update a single thunk. For instance,
consider this interleaving under the old scheme:

            Thread A                             Thread B
            ---------                            ---------
    t=0     Enter t
      1     Push update frame
      2     Begin evaluation

      4     Pause thread
      5     t.indirectee=tso
      6     Release t.info=BLACKHOLE

      7     ... (e.g. GC)

      8     Resume thread
      9     Finish evaluation
      10    Relaxed t.indirectee=x

      11                                         Load t.info
      12                                         Acquire fence
      13                                         Inspect t.indirectee

      14    Release t.info=BLACKHOLE

Here Thread A enters thunk `t` but is soon paused, resulting in `t`
being lazily blackholed at t=6. Then, at t=10 Thread A finishes
evaluation and updates `t.indirectee` with a relaxed store.

Meanwhile, Thread B enters the blackhole. Under the old scheme this
would introduce an acquire-fence but this would only synchronize with
Thread A at t=6. Consequently, the result of the evaluation, `x`, is not
visible to Thread B, introducing a data race.

We fix this by treating the `indirectee` field as we do all other
mutable fields. This means we must always access this field with
acquire-loads and release-stores.

See #23185.

- - - - -
f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00
docs: Fix link to 051-ghc-base-libraries.rst

The proposal is no longer available at the previous URL.

- - - - -
f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00
hadrian: Build all executables in bin/ folder

In the end the bindist creation logic copies them all into the bin
folder. There is no benefit to building a specific few binaries in the
lib/bin folder anymore.

This also removes the ad-hoc logic to copy the touchy and unlit
executables from stage0 into stage1. It takes <1s to build so we might
as well just build it.

- - - - -
0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00
testsuite: mark jspace as fragile on i386.

This test has been flaky for some time and has been failing consistently on
i386-linux since 8e0446df landed.

See #24261

- - - - -
dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00
Deprecate -ddump-json and introduce -fdiagnostics-as-json

Addresses #19278

This commit deprecates the underspecified -ddump-json flag and
introduces a newer, well-specified flag -fdiagnostics-as-json.

Also included is a JSON schema as part of the documentation.

The -ddump-json flag will be slated for removal shortly after this merge.

- - - - -
609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00
Deprecate -ddump-json and introduce -fdiagnostics-as-json

Addresses #19278

This commit deprecates the underspecified -ddump-json flag and
introduces a newer, well-specified flag -fdiagnostics-as-json.

Also included is a JSON schema as part of the documentation.

The -ddump-json flag will be slated for removal shortly after this merge.

- - - - -
865513b2 by Ömer Sinan Ağacan at 2023-12-24T10:11:13-05:00
Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations

- - - - -
c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00
docs: document permissibility of -XOverloadedLabels (#24249)

Document the permissibility introduced by
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst

- - - - -
e5b7eb59 by Ömer Sinan Ağacan at 2023-12-25T16:02:03-05:00
Fix a code block syntax in user manual sec. 6.8.8.6

- - - - -
2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00
genSym: Reimplement via CAS on 32-bit platforms

Previously the remaining use of the C implementation on 32-bit platforms
resulted in a subtle bug, #24261. This was due to the C object (which
used the RTS's `atomic_inc64` macro) being compiled without `-threaded`
yet later being used in a threaded compiler.

Side-step this issue by using the pure Haskell `genSym` implementation on
all platforms. This required implementing `fetchAddWord64Addr#` in terms
of CAS on 64-bit platforms.

- - - - -
19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00
Do not color the diagnostic code in error messages (#24172)

- - - - -
685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00
Enforce that bindings of implicit parameters are lifted

Fixes #24298

- - - - -
bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00
StgToCmm: Detect some no-op case-continuations

...and generate no code for them. Fixes #24264.

- - - - -
5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00
Revert "testsuite: mark jspace as fragile on i386."

This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95.

The atomicity bug should be fixed by !11802.

- - - - -
d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00
Refactor: store [[PrimRep]] rather than [Type] in STG

StgConApp stored a list of types. This list was used exclusively
during unarisation of unboxed sums (mkUbxSum).
However, this is at a wrong level of abstraction:
STG shouldn't be concerned with Haskell types, only PrimReps.
Update the code to store a [[PrimRep]]. Also, there's no point in storing
this list when we're not dealing with an unboxed sum.

- - - - -
8b340bc7 by Ömer Sinan Ağacan at 2024-01-01T12:06:29-05:00
Kind signatures docs: mention that they're allowed in newtypes

- - - - -
989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00
ci: Ensure we use the correct bindist name for the test artifact when generating
release ghcup metadata

Fixes #24268

- - - - -
89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00
Refactor: remove calls to typePrimRepArgs

The function typePrimRepArgs is just a thin wrapper around
typePrimRep, adding a VoidRep if the list is empty.
However, in StgToByteCode, we were discarding that VoidRep anyway,
so there's no point in calling it.

- - - - -
c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00
Use "-V" for alex version check for better backward compatibility
Fixes #24302.
In recent versions of alex, "-v" is used for "--verbose" instead of "-version".

- - - - -
67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00
Fix VoidRep handling in ghci debugger

'go' inside extractSubTerms was giving a bad result given a VoidRep,
attempting to round towards the next multiple of 0.
I don't understand much about the debugger but the code should be better
than it was.

Fixes #24306

- - - - -
90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00
VoidRep-related refactor

* In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep,
  bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1.
  All of them were duplicates.
* In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to
  PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out.
* In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out
  VoidRep from the result of typePrimRep. But typePrimRep never returns
  VoidRep - remove the filtering.

- - - - -
eaf72479 by brian at 2024-01-06T23:03:09-05:00
Add unaligned Addr# primops

Implements CLC proposal #154:
  https://github.com/haskell/core-libraries-committee/issues/154

* add unaligned addr primops

* add tests

* accept tests

* add documentation

* fix js primops

* uncomment in access ops

* use Word64 in tests

* apply suggestions

* remove extra file

* move docs

* remove random options

* use setByteArray# primop

* better naming

* update base-exports test

* add base-exports for other architectures

- - - - -
d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00
Remove VoidRep from PrimRep, introduce PrimOrVoidRep

This introduces

data PrimOrVoidRep = VoidRep | NVRep PrimRep

changes typePrimRep1 to return PrimOrVoidRep, and adds a new function
typePrimRepU to be used when the argument is definitely non-void.
Details in Note [VoidRep] in GHC.Types.RepType.

Fixes #19520

- - - - -
48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00
Apply Note [Sensitivity to unique increment] to LargeRecord

- - - - -
9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00
Debugging: Add diffUFM for convenient diffing between UniqFMs

- - - - -
948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00
Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal

... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures

- - - - -
4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00
Deprecate -ddump-stranal and -ddump-str-signatures

... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead

- - - - -
6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00
Move testsuite/tests/stranal to testsuite/tests/dmdanal

A separate commit so that the rename is obvious to Git(Lab)

- - - - -
c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00
CoreSubst: Stricten `substBndr` and `cloneBndr`

Doing so reduced allocations of `cloneBndr` by about 25%.

```
T9233(normal) ghc/alloc    672,488,656    663,083,216  -1.4% GOOD
T9675(optasm) ghc/alloc    423,029,256    415,812,200  -1.7%

    geo. mean                                          -0.1%
    minimum                                            -1.7%
    maximum                                            +0.1%
```

Metric Decrease:
    T9233

- - - - -
e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00
Deprecate -Wsemigroup

This warning was used to prepare for Semigroup becoming a superclass
of Monoid, and for (<>) being exported from Prelude. This happened in
GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3.

The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79.
Now the warning does nothing at all and can be deprecated.

- - - - -
08d14925 by amesgen at 2024-01-10T17:36:42-05:00
WASM metadata: use correct GHC version

- - - - -
7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00
Allow SCC declarations in TH (#24081)

- - - - -
28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00
Fix prettyprinting of SCC pragmas

- - - - -
ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00
Fix loopification in the presence of void arguments

This also removes Note [Void arguments in self-recursive tail calls],
which was just misleading.  It's important to count void args both
in the function's arity and at the call site.

Fixes #24295.

- - - - -
b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00
testsuite: Teach testsuite driver about c++ sources

- - - - -
09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00
driver: Set -DPROFILING when compiling C++ sources with profiling

Earlier, we used to pass all preprocessor flags to the c++ compiler.
This meant that -DPROFILING was passed to the c++ compiler because
it was a part of C++ flags
However, this was incorrect and the behaviour was changed in
8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291.

But that commit exposed this bug where -DPROFILING was no longer being passed
when compiling c++ sources.

The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is
enabled to ensure we pass the correct options for the way to both C and C++
compilers

Fixes #24286

- - - - -
2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00
testsuite: rename objcpp -> objcxx

To avoid confusion with C Pre Processsor

- - - - -
af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00
Make TYPE and CONSTRAINT not-apart

Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty
which is supposed to make TYPE and CONSTRAINT be not-apart.

Easily fixed.

- - - - -
4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00
ci: Fix typo in mk_ghcup_metadata.py

There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08

- - - - -
13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00
release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job

There is no reason to have this release build or distribute this variation.
This configuration is for testing purposes only.

- - - - -
afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00
Parser: Add a Note detailing why we need happy's `error` to implement layout

- - - - -
eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00
Turn -Wtype-equality-out-of-scope on by default

Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat,
since they are enabled by default. Refresh wcompat-warnings/ test
with new -Wcompat warnings.

Part of #24267

Co-authored-by: sheaf <sam.derbyshire at gmail.com>

- - - - -
42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00
Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296)

In #24296, we had a program in which we eta expanded away an error despite the
presence of `-fpedantic-bottoms`.
This was caused by turning called *at least once* lambdas into one-shot lambdas,
while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that
are called *exactly* once.
An example can be found in `Note [Combining arity type with demand info]`.

Fixes #24296.

- - - - -
7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00
Aarch64: Enable -mfma by default.

Fixes #24311

- - - - -
e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00
Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat

CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226

- - - - -
ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00
Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326)

Fixes #24326.

- - - - -
c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00
Use lookupOccRn_maybe in TH.lookupName

When looking up a value, we want to be able to find both variables
and record fields. So we should not use the lookupSameOccRn_maybe
function, as we can't know ahead of time which record field namespace
a record field with the given textual name will belong to.

Fixes #24293

- - - - -
da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00
Make the build more strict on documentation errors

* Detect undefined labels. This can be tested by adding :ref:`nonexistent`
  to a documentation rst file; attempting to build docs will fail.
  Fixed the undefined label in `9.8.1-notes.rst`.
* Detect errors. While we have plenty of warnings, we can at least enforce
  that Sphinx does not report errors.
  Fixed the error in `required_type_arguments.rst`.

Unrelated change: I have documented that the `-dlint` enables
`-fcatch-nonexhaustive-cases`, as can be verified by checking
`enableDLint`.

- - - - -
5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00
Profiling: Adds an option to not start time profiling at startup

Using the functionality provided by
d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts
flag `--no-automatic-time-samples` which disables the time profiling
when starting a program. It is then expected that the user starts it
whenever it is needed.

Fixes #24337

- - - - -
5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00
eventlog: Fix off-by-one error in postIPE

We were missing the extra_comma from the calculation of the size of the
payload of postIPE. This was causing assertion failures when the event
would overflow the buffer by one byte, as ensureRoomForVariable event
would report there was enough space for `n` bytes but then we would
write `n + 1` bytes into the buffer.

Fixes #24287

- - - - -
66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00
Improve SpecConstr (esp nofib/spectral/ansi)

This MR makes three improvements to SpecConstr: see #24282

* It fixes an outright (and recently-introduced) bug in `betterPat`, which
  was wrongly forgetting to compare the lengths of the argument lists.

* It enhances ConVal to inclue a boolean for work-free-ness, so that the
  envt can contain non-work-free constructor applications, so that we
  can do more: see Note [ConVal work-free-ness]

* It rejigs `subsumePats` so that it doesn't reverse the list.  This can
  make a difference because, when patterns overlap, we arbitrarily pick
  the first.  There is no "right" way, but this retains the old
  pre-subsumePats behaviour, thereby "fixing" the regression in #24282.

Nofib results

   +========================================
   |                 spectral/ansi  -21.14%
   | spectral/hartel/comp_lab_zift   -0.12%
   |       spectral/hartel/parstof   +0.09%
   |           spectral/last-piece   -2.32%
   |           spectral/multiplier   +6.03%
   |                 spectral/para   +0.60%
   |               spectral/simple   -0.26%
   +========================================
   |                     geom mean   -0.18%
   +----------------------------------------

The regression in `multiplier` is sad, but it simply replicates GHC's
previous behaviour (e.g. GHC 9.6).

- - - - -
65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00
hadrian: Reduce Cabal verbosity

The comment claims that `simpleUserHooks` decrease verbosity, and it
does, but only for the `postConf` phase. The other phases are too
verbose with `-V`.

At the moment > 5000 lines of the build log are devoted to output from
`cabal copy`.

So I take the simple approach and just decrease the verbosity level
again.

If the output of `postConf` is essential then it would be better to
implement our own `UserHooks` which doesn't decrease the verbosity for
`postConf`.

Fixes #24338

- - - - -
16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00
Stop retaining old ModGuts throughout subsequent simplifier phases

Each phase of the simplifier typically rewrites the majority of ModGuts,
so we want to be able to release the old ModGuts as soon as possible.

`name_ppr_ctxt` lives throught the whole optimiser phase and it was
retaining a reference to `ModGuts`, so we were failing to release the
old `ModGuts` until the end of the phase (potentially doubling peak
memory usage for that particular phase).

This was discovered using eras profiling (#24332)

Fixes #24328

- - - - -
7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00
Update nofib submodule

- - - - -
320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00
ci: bump ci-images for updated wasm image

- - - - -
2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00
base: treat all FDs as "nonblocking" on wasm

On posix platforms, when performing read/write on FDs, we check the
nonblocking flag first. For FDs without this flag (e.g. stdout), we
call fdReady() first, which in turn calls poll() to wait for I/O to be
available on that FD. This is problematic for wasm32-wasi: although
select()/poll() is supported via the poll_oneoff() wasi syscall, that
syscall is rather heavyweight and runtime behavior differs in
different wasi implementations. The issue is even worse when targeting
browsers, given there's no satisfactory way to implement async I/O as
a synchronous syscall, so existing JS polyfills for wasi often give up
and simply return ENOSYS.

Before we have a proper I/O manager that avoids poll_oneoff() for
async I/O on wasm, this patch improves the status quo a lot by merely
pretending all FDs are "nonblocking". Read/write on FDs will directly
invoke read()/write(), which are much more reliably handled in
existing wasi implementations, especially those in browsers.

Fixes #23275 and the following test cases: T7773 isEOF001 openFile009
T4808 cgrun025

Approved by CLC proposal #234:
https://github.com/haskell/core-libraries-committee/issues/234

- - - - -
83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00
base: clarify how to disable warnings about partiality of Data.List.{head,tail}

- - - - -
c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00
Fix four bug in handling of (forall cv. body_ty)

These bugs are all described in #24335

It's not easy to provoke the bug, hence no test case.

- - - - -
119586ea by Alexis King at 2024-01-19T00:08:00-05:00
Always refresh profiling CCSes after running pending initializers

Fixes #24171.

- - - - -
9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00
Set default-language: GHC2021 in ghc library

Go through compiler/ sources, and remove
all BangPatterns (and other GHC2021 enabled extensions in these files).

- - - - -
3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00
testsuite: Remove unused have_library function

Also remove the hence unused testsuite option `--test-package-db`.

Fixes #24342

- - - - -
5b7fa20c by Jade at 2024-01-19T21:55:53-05:00
Fix Spelling in the compiler

Tracking: #16591

- - - - -
09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00
testsuite: Implement `isInTreeCompiler` in a more robust way

Just a small refactoring to avoid redundantly specifying the same
strings in two different places.

- - - - -
0d12b987 by Jade at 2024-01-20T12:21:20-05:00
Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142

- - - - -
eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00
Changes for haskell/haddock#18324

- - - - -
1fa1c00c by Jade at 2024-01-23T19:17:03-05:00
Enhance Documentation of functions exported by Data.Function

This patch aims to improve the documentation of functions exported
in Data.Function

Tracking: #17929
Fixes: #10065

- - - - -
ab47a43d by Jade at 2024-01-23T19:17:39-05:00
Improve documentation of hGetLine.

- Add explanation for whether a newline is returned
- Add examples

Fixes #14804

- - - - -
dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00
Fix genapply for cross-compilation by nuking fragile CPP logic

This commit fixes incorrectly built genapply when cross compiling
(#24347) by nuking all fragile CPP logic in it from the orbit. All
target-specific info are now read from DerivedConstants.h at runtime,
see added note for details. Also removes a legacy Makefile and adds
haskell language server support for genapply.

- - - - -
0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00
rts: enable wasm32 register mapping

The wasm backend didn't properly make use of all Cmm global registers
due to #24347. Now that it is fixed, this patch re-enables full
register mapping for wasm32, and we can now generate smaller & faster
wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152.

- - - - -
0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00
Avoid utf8 in primops.txt.pp comments

They don't make it through readFile' without explicitly setting the
encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755

- - - - -
1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00
Bump hpc and hpc-bin submodule

Bump hpc to 0.7.0.1
Bump hpc-bin to commit d1780eb2

- - - - -
e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00
testsuite: Ignore stderr in T8089

Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail.
Fixes #24361.
- - - - -
a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00
Fix FMA instruction on LLVM

We were emitting the wrong instructions for fused multiply-add
operations on LLVM:

  - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd"
  - LLVM does not support other instructions such as "fmsub"; instead
    we implement these by flipping signs of some arguments
  - the instruction is an LLVM intrinsic, which requires handling it
    like a normal function call instead of a machine instruction

Fixes #24223

- - - - -
69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00
Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291)

- - - - -
0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00
compiler: remove unused GHC.Linker module

The GHC.Linker module is empty and unused, other than as a hack for
the make build system. We can remove it now that make is long gone;
the note is moved to GHC.Linker.Loader instead.

- - - - -
699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00
Clarification for newtype constructors when using `coerce`

- - - - -
b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00
Fix #24308

Add tests for semicolon separated where clauses

- - - - -
0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00
hsc2hs: Bump submodule

- - - - -
3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00
Bump containers submodule to 0.7

- - - - -
82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00
base: with{Binary}File{Blocking} only annotates own exceptions

Fixes #20886

This ensures that inner, unrelated exceptions are not misleadingly
annotated with the opened file.

- - - - -
9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00
Fix fma warning when using llvm on aarch64.

On aarch64 fma is always on so the +fma flag doesn't exist for that
target. Hence no need to try and pass +fma to llvm.

Fixes #24379

- - - - -
ced2e731 by sheaf at 2024-01-29T17:27:12-05:00
No shadowing warnings for NoFieldSelector fields

This commit ensures we don't emit shadowing warnings when a user
shadows a field defined with NoFieldSelectors.

Fixes #24381

- - - - -
8eeadfad by Patrick at 2024-01-29T17:27:51-05:00
Fix bug wrong span of nested_doc_comment #24378

close #24378
1. Update the start position of span in `nested_doc_comment` correctly.
and hence the spans of identifiers of haddoc can be computed correctly.
2. add test `HaddockSpanIssueT24378`.

- - - - -
a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00
Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value

A test *сс018* is attached (not sure about the naming convention though).
Note that without the fix, the test fails with the *dodgy-foreign-imports*
warning passed to stderr. The warning disappears after the fix.

GHC shouldn't warn on imports of natural function pointers from C by value
(which is feasible with CApiFFI), such as

```haskell
foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ())
```

where

```c
void (*f)(int);
```

See a related real-world use-case
[here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17).
There, GHC warns on import of C function pointer `pcre_free`.

- - - - -
ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00
Rename test cc018 -> T24034

- - - - -
88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00
rts/TraverseHeap.c: Ensure that PosixSource.h is included first
- - - - -
ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00
Make decomposeRuleLhs a bit more clever

This fixes #24370 by making decomposeRuleLhs undertand
dictionary /functions/ as well as plain /dictionaries/

- - - - -
94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00
doc: Add -Dn flag to user guide

Resolves #24394
- - - - -
31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00
cmm: Introduce MO_RelaxedRead

In hand-written Cmm it can sometimes be necessary to atomically load
from memory deep within an expression (e.g. see the `CHECK_GC` macro).
This MachOp provides a convenient way to do so without breaking the
expression into multiple statements.

- - - - -
0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00
codeGen: Use relaxed accesses in ticky bumping

- - - - -
be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00
base: use atomic write when updating timer manager

- - - - -
8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00
Use relaxed atomics to manipulate TSO status fields

- - - - -
d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Add necessary barriers when manipulating TSO owner

- - - - -
39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Use `switch` to branch on why_blocked

This is a semantics-preserving refactoring.

- - - - -
515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix synchronization on thread blocking state

We now use a release barrier whenever we update a thread's blocking
state. This required widening StgTSO.why_blocked as AArch64 does not
support atomic writes on 16-bit values.

- - - - -
eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in threadPaused

This only affects an assertion in the debug RTS and only needs relaxed
ordering.

- - - - -
26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in threadStatus#

- - - - -
6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00
rts: Fix data race in Interpreter's preemption check

- - - - -
9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00
rts/Messages: Fix data race

- - - - -
60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00
rts/Prof: Fix data race

- - - - -
ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Use relaxed ordering on dirty/clean info tables updates

When changing the dirty/clean state of a mutable object we needn't have
any particular ordering.

- - - - -
76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00
codeGen: Use relaxed-read in closureInfoPtr

- - - - -
a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00
STM: Use acquire loads when possible

Full sequential consistency is not needed here.

- - - - -
6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Use fence rather than redundant load

Previously we would use an atomic load to ensure acquire ordering.
However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this
more directly.

- - - - -
55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00
rts: Fix data races in profiling timer

- - - - -
856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00
Add Note [C11 memory model]

- - - - -
6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: move generic cmm optimization logic in NCG to a standalone module

This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module,
GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be
run in the wasm backend NCG code, which is defined in other modules
that's imported by GHC.CmmToAsm, causing a cyclic dependency issue.

- - - - -
87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: explicitly disable PIC in wasm32 NCG

This commit explicitly disables the ncgPIC flag for the wasm32 target.
The wasm backend doesn't support PIC for the time being.

- - - - -
c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00
compiler: enable generic cmm optimizations in wasm backend NCG

This commit enables the generic cmm optimizations in other NCGs to be
run in the wasm backend as well, followed by a late cmm control-flow
optimization pass. The added optimizations do catch some corner cases
not handled by the pre-NCG cmm pipeline and are useful in generating
smaller CFGs.

- - - - -
151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00
Namespacing for WARNING/DEPRECATED pragmas (#24396)

New syntax for WARNING and DEPRECATED pragmas was added,
namely namespace specifierss:

  namespace_spec ::= 'type' | 'data' | {- empty -}

  warning ::= warning_category namespace_spec namelist strings

  deprecation ::= namespace_spec namelist strings

A new data type was introduced to represent these namespace specifiers:

  data NamespaceSpecifier =
    NoSpecifier |
    TypeNamespaceSpecifier (EpToken "type") |
    DataNamespaceSpecifier (EpToken "data")

Extension field XWarning now contains this NamespaceSpecifier.

lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier
and checks that the namespace of the found names matches the passed flag.
With this change {-# WARNING data D "..." #-} pragma will only affect value
namespace and {-# WARNING type D "..." #-} will only affect type
namespace. The same logic is applicable to DEPRECATED pragmas.

Finding duplicated warnings inside rnSrcWarnDecls now takes into
consideration NamespaceSpecifier flag to allow warnings with the
same names that refer to different namespaces.

- - - - -
38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00
CI: Disable the test-cabal-reinstall job

Fixes #24363

- - - - -
27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00
Bump bytestring submodule to something closer to 0.12.1

...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c
(which reworks unaligned writes in Builder) and the stuff in
https://github.com/haskell/bytestring/pull/631 can see wider testing.

The less-terrible code for unaligned writes used in Builder on
hosts not known to be ulaigned-friendly also takes less effort
for GHC to compile, resulting in a metric decrease for T21839c
on some platforms.

The metric increase on T21839r is caused by the unrelated commit
750dac33465e7b59100698a330b44de7049a345c.  It perhaps warrants
further analysis and discussion (see #23822) but is not critical.

Metric Decrease:
T21839c
Metric Increase:
T21839r

- - - - -
cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00
Work around autotools setting C11 standard in CC/CXX

In autoconf >=2.70, C11 is set by default for $CC and $CXX via the
-std=...11 flag. In this patch, we split the "-std" flag out of the $CC
and $CXX variables, which we traditionally assume to be just the
executable name/path, and move it to $CFLAGS/$CXXFLAGS instead.

Fixes #24324

- - - - -
5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00
Expand `do` blocks right before typechecking using the `HsExpansion` philosophy.

- Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206

- The change is detailed in
  - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do`
  - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr`
         expains the rational of doing expansions in type checker as opposed to in the renamer

- Adds new datatypes:
  - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier
    1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`)
    2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack

  - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated
    This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam`

  - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc`

- Ensures warnings such as
  1. Pattern match checks
  2. Failable patterns
  3. non-() return in body statements are preserved

- Kill `HsMatchCtxt` in favor of `TcMatchAltChecker`

- Testcases:
  * T18324 T20020 T23147 T22788 T15598 T22086
  * T23147b (error message check),
  * DoubleMatch (match inside a match for pmc check)
  * pattern-fails (check pattern match with non-refutable pattern, eg. newtype)
  * Simple-rec (rec statements inside do statment)
  * T22788 (code snippet from #22788)
  * DoExpanion1 (Error messages for body statments)
  * DoExpansion2 (Error messages for bind statements)
  * DoExpansion3 (Error messages for let statements)

Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass

Metric Increase 'compile_time/bytes allocated':
    T9020

The testcase is a pathalogical example of a `do`-block with many statements that do nothing.
Given that we are expanding the statements into function binds, we will have to bear
a (small) 2% cost upfront in the compiler to unroll the statements.

- - - - -
0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00
Reduce parser allocations in allocateCommentsP

In the most common case, the comment queue is empty, so we can skip the
work of processing it. This reduces allocations by about 10% in the
parsing001 test.

Metric Decrease:
    MultiLayerModulesRecomp
    parsing001

- - - - -
ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00
ghc-internals fallout

- - - - -
cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00
Stop dropping a case whose binder is demanded

This MR fixes #24251.

See Note [Case-to-let for strictly-used binders]
in GHC.Core.Opt.Simplify.Iteration, plus #24251, for
lots of discussion.

Final Nofib changes over 0.1%:
+-----------------------------------------
|        imaginary/digits-of-e2    -2.16%
|                imaginary/rfib    -0.15%
|                    real/fluid    -0.10%
|                   real/gamteb    -1.47%
|                       real/gg    -0.20%
|                 real/maillist    +0.19%
|                      real/pic    -0.23%
|                      real/scs    -0.43%
|               shootout/n-body    -0.41%
|        shootout/spectral-norm    -0.12%
+========================================
|                     geom mean    -0.05%

Pleasingly, overall executable size is down by just over 1%.

Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the
geometric mean is -0.1% which seems good.

- - - - -
e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00
Add Note [Bangs in Integer functions]

...to document the bangs in the functions in GHC.Num.Integer

- - - - -
ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00
Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396)

- - - - -
e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00
Refactoring in preparation for lazy skolemisation

* Make HsMatchContext and HsStmtContext be parameterised over the
  function name itself, rather than over the pass.
  See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr
    - Replace types
        HsMatchContext GhcPs --> HsMatchContextPs
        HsMatchContext GhcRn --> HsMatchContextRn
        HsMatchContext GhcTc --> HsMatchContextRn  (sic! not Tc)
        HsStmtContext  GhcRn --> HsStmtContextRn
    - Kill off convertHsMatchCtxt

* Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing
  a complete user-supplied signature) is its own data type.
    - Split TcIdSigInfo(CompleteSig, PartialSig) into
        TcCompleteSig(CSig)
        TcPartialSig(PSig)
    - Use TcCompleteSig in tcPolyCheck, CheckGen
    - Rename types and data constructors:
        TcIdSigInfo         --> TcIdSig
        TcPatSynInfo(TPSI)  --> TcPatSynSig(PatSig)
    - Shuffle around helper functions:
        tcSigInfoName           (moved to GHC.Tc.Types.BasicTypes)
        completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes)
        tcIdSigName             (inlined and removed)
        tcIdSigLoc              (introduced)
    - Rearrange the pattern match in chooseInferredQuantifiers

* Rename functions and types:
    tcMatchesCase         --> tcCaseMatches
    tcMatchesFun          --> tcFunBindMatches
    tcMatchLambda         --> tcLambdaMatches
    tcPats                --> tcMatchPats
    matchActualFunTysRho  --> matchActualFunTys
    matchActualFunTySigma --> matchActualFunTy

* Add HasDebugCallStack constraints to:
    mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy,
    mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe

* Use `penv` from the outer context in the inner loop of
  GHC.Tc.Gen.Pat.tcMultiple

* Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file,
  factor out and export tcMkScaledFunTy.

* Move isPatSigCtxt down the file.

* Formatting and comments

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00
Lazy skolemisation for @a-binders (#17594)

This patch is a preparation for @a-binders implementation.  The main changes are:

* Skolemisation is now prepared to deal with @binders.
  See Note [Skolemisation overview] in GHC.Tc.Utils.Unify.
  Most of the action is in
    - Utils.Unify.matchExpectedFunTys
    - Gen.Pat.tcMatchPats
    - Gen.Expr.tcPolyExprCheck
    - Gen.Binds.tcPolyCheck

Some accompanying refactoring:

* I found that funTyConAppTy_maybe was doing a lot of allocation, and
  rejigged userTypeError_maybe to avoid calling it.

- - - - -
532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00
driver: Really don't lose track of nodes when we fail to resolve cycles

This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose
track of acyclic components at the start of an unresolved cycle. We now ensure we
never loose track of any of these components.

As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC:

When viewed without boot files, we have a single SCC

```
[REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
     main:T24275A [main:T24275A {-# SOURCE #-}]]
```

But with boot files this turns into

```
[NONREC main:T24275B {-# SOURCE #-} [],
 REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
    main:T24275A {-# SOURCE #-} [main:T24275B],
 NONREC main:T24275A [main:T24275A {-# SOURCE #-}]]
```

Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot.
However, we treat this entire group as a single "SCC" because it seems so when we
analyse the graph without taking boot files into account.

Indeed, we must return a single ResolvedCycle element in the BuildPlan for this
as described in Note [Upsweep].

However, since after resolving this is not a true SCC anymore, `findCycle` fails
to find a cycle and we have a sub-optimal error message as a result.

To handle this, I extended `findCycle` to not assume its input is an SCC, and to
try harder to find cycles in its input.

Fixes #24275

- - - - -
b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00
GHCi: Lookup breakpoint CCs in the correct module

We need to look up breakpoint CCs in the module that the breakpoint
points to, and not the current module.

Fixes #24327

- - - - -
b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00
testsuite: Add test for #24327

- - - - -
569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add compile_artifact, ignore_extension flag

In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the
capability to collect generic metrics. But this assumed that the test
was not linking and producing artifacts and we only wanted to track
object files, interface files, or build artifacts from the compiler
build. However, some backends, such as the JS backend, produce artifacts when
compiling, such as the jsexe directory which we want to track.

This patch:

- tweaks the testsuite to collect generic metrics on any build artifact
in the test directory.

- expands the exe_extension function to consider windows and adds the
ignore_extension flag.

- Modifies certain tests to add the ignore_extension flag. Tests such as
heaprof002 expect a .ps file, but on windows without ignore_extensions
the testsuite will look for foo.exe.ps. Hence the flag.

- adds the size_hello_artifact test

- - - - -
75a31379 by doyougnu at 2024-02-07T03:06:26-05:00
ts: add wasm_arch, heapprof002 wasm extension

- - - - -
c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00
Synchronize bindist configure for #24324

In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a
workaround for #24324 in the in-tree configure script, but forgot to
update the bindist configure script accordingly. This updates it.

- - - - -
d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00
distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable

Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we
were missing passing `--target` when invoking the linker.

Fixes #24414

- - - - -
77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00
llvmGen: Adapt to allow use of new pass manager.

We now must use `-passes` in place of `-O<n>` due to #21936.

Closes #21936.

- - - - -
3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00
testsuite: Mark length001 as fragile on javascript

Modifying the timeout multiplier is not a robust way to get this test to
reliably fail. Therefore we mark it as fragile until/if javascript ever
supports the stack limit.

- - - - -
20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00
Javascript: Don't filter out rtsDeps list

This logic appears to be incorrect as it would drop any dependency which
was not in a direct dependency of the package being linked.

In the ghc-internals split this started to cause errors because
`ghc-internal` is not a direct dependency of most packages, and hence
important symbols to keep which are hard coded into the js runtime were
getting dropped.

- - - - -
2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00
base: Cleanup whitespace in cbits

- - - - -
44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00
Move `base` to `ghc-internal`

Here we move a good deal of the implementation of `base` into a new
package, `ghc-internal` such that it can be evolved independently
from the user-visible interfaces of `base`.

While we want to isolate implementation from interfaces, naturally, we
would like to avoid turning `base` into a mere set of module re-exports.
However, this is a non-trivial undertaking for a variety of reasons:

 * `base` contains numerous known-key and wired-in things, requiring
   corresponding changes in the compiler

 * `base` contains a significant amount of C code and corresponding
   autoconf logic, which is very fragile and difficult to break apart

 * `base` has numerous import cycles, which are currently dealt with via
   carefully balanced `hs-boot` files

 * We must not break existing users

To accomplish this migration, I tried the following approaches:

* [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental
  migration of modules into ghc-internal: this knot is simply too
  intertwined to be easily pulled apart, especially given the rather
  tricky import cycles that it contains)

* [Move-Core]: Moving the "core" connected component of base (roughly
  150 modules) into ghc-internal. While the Haskell side of this seems
  tractable, the C dependencies are very subtle to break apart.

* [Move-Incrementally]:

  1. Move all of base into ghc-internal
  2. Examine the module structure and begin moving obvious modules (e.g.
     leaves of the import graph) back into base
  3. Examine the modules remaining in ghc-internal, refactor as necessary
     to facilitate further moves
  4. Go to (2) iterate until the cost/benefit of further moves is
     insufficient to justify continuing
  5. Rename the modules moved into ghc-internal to ensure that they don't
     overlap with those in base
  6. For each module moved into ghc-internal, add a shim module to base
     with the declarations which should be exposed and any requisite
     Haddocks (thus guaranteeing that base will be insulated from changes
     in the export lists of modules in ghc-internal

Here I am using the [Move-Incrementally] approach, which is empirically
the least painful of the unpleasant options above

Bumps haddock submodule.

Metric Decrease:
    haddock.Cabal
    haddock.base
Metric Increase:
    MultiComponentModulesRecomp
    T16875
    size_hello_artifact

- - - - -
e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00
Haddock comments on infix constructors (#24221)

Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for
infix constructors.

This change fixes a Haddock regression (introduced in 19e80b9af252)
that affected leading comments on infix data constructor declarations:

	-- | Docs for infix constructor
	| Int :* Bool

The comment should be associated with the data constructor (:*), not
with its left-hand side Int.

- - - - -
9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00
Add os-string as a boot package

Introduces `os-string` submodule. This will be necessary for
`filepath-1.5`.

- - - - -
9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00
gitignore: Ignore .hadrian_ghci_multi/

- - - - -
d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00
hadrian: Set -this-package-name

When constructing the GHC flags for a package Hadrian must take care to
set `-this-package-name` in addition to `-this-unit-id`. This hasn't
broken until now as we have not had any uses of qualified package
imports. However, this will change with `filepath-1.5` and the
corresponding `unix` bump, breaking `hadrian/multi-ghci`.

- - - - -
f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00
Bump filepath to 1.5.0.0

Required bumps of the following submodules:

 * `directory`
 * `filepath`
 * `haskeline`
 * `process`
 * `unix`
 * `hsc2hs`
 * `Win32`
 * `semaphore-compat`

and the addition of `os-string` as a boot package.

- - - - -
ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Use specific clang assembler when compiling with -fllvm

There are situations where LLVM will produce assembly which older gcc
toolchains can't handle. For example on Deb10, it seems that LLVM >= 13
produces assembly which the default gcc doesn't support.

A more robust solution in the long term is to require a specific LLVM
compatible assembler when using -fllvm.

Fixes #16354

- - - - -
c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0

- - - - -
5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00
Update bootstrap plans for 9.4.8 and 9.6.4

- - - - -
707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00
Add alpine 3_18 release job

This is mainly experimental and future proofing to enable a smooth
transition to newer alpine releases once 3_12 is too old.

- - - - -
c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00
Generate LLVM min/max bound policy via Hadrian

Per #23966, I want the top-level configure to only generate
configuration data for Hadrian, not do any "real" tasks on its own.
This is part of that effort --- one less file generated by it.

(It is still done with a `.in` file, so in a future world non-Hadrian
also can easily create this file.)

Split modules:

- GHC.CmmToLlvm.Config
- GHC.CmmToLlvm.Version
- GHC.CmmToLlvm.Version.Bounds
- GHC.CmmToLlvm.Version.Type

This also means we can get rid of the silly `unused.h` introduced in
!6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge.

Part of #23966

- - - - -
9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00
Enable mdo statements to use HsExpansions
Fixes: #24411
Added test T24411 for regression

- - - - -
f8429266 by Jade at 2024-02-08T14:56:50+01:00
Adjust test for ghc MR !10993

- - - - -
762b2120 by Jade at 2024-02-08T15:17:15+00:00
Improve Monad, Functor & Applicative docs

This patch aims to improve the documentation of Functor, Applicative,
Monad and related symbols. The main goal is to make it more consistent
and make accessible. See also: !10979 (closed) and !10985 (closed)

Ticket #17929

Updates haddock submodule

- - - - -
151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00
JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309)

- - - - -
2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00
ci: Allow release-hackage-lint to fail

Otherwise it blocks the ghcup metadata pipeline from running.

- - - - -
b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00
rts: eras profiling mode

The eras profiling mode is useful for tracking the life-time of
closures. When a closure is written, the current era is recorded in the
profiling header. This records the era in which the closure was created.

* Enable with -he
* User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era
* Automatically: --automatic-era-increment, increases the user era on major
  collections
* The first era is era 1
* -he<era> can be used with other profiling modes to select a specific
  era

If you just want to record the era but not to perform heap profiling you
can use `-he --no-automatic-heap-samples`.

https://well-typed.com/blog/2024/01/ghc-eras-profiling/

Fixes #24332

- - - - -
be674a2c by Jade at 2024-02-10T14:30:04-05:00
Adjust error message for trailing whitespace in as-pattern.

Fixes #22524

- - - - -
53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00
gitlab: js: add codeowners

Fixes:
- #24409

Follow on from:
- #21078 and MR !9133
- When we added the JS backend this was forgotten. This patch adds the
rightful codeowners.

- - - - -
8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00
Bump CI images so that alpine3_18 image includes clang15

The only changes here are that clang15 is now installed on the
alpine-3_18 image.

- - - - -
df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: handle stored null StablePtr

Some Haskell codes unsafely cast StablePtr into ptr to compare against
NULL. E.g. in direct-sqlite:

  if castStablePtrToPtr aggStPtr /= nullPtr then

where `aggStPtr` is read (`peek`) from zeroed memory initially.

We fix this by giving these StablePtr the same representation as other
null pointers. It's safe because StablePtr at offset 0 is unused (for
this exact reason).

- - - - -
55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: disable MergeObjsMode test

This isn't implemented for JS backend objects.

- - - - -
aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: add support for linking C sources

Support linking C sources with JS output of the JavaScript backend.
See the added documentation in the users guide.

The implementation simply extends the JS linker to use the objects (.o)
that were already produced by the emcc compiler and which were filtered
out previously. I've also added some options to control the link with C
functions (see the documentation about pragmas).

With this change I've successfully compiled the direct-sqlite package
which embeds the sqlite.c database code. Some wrappers are still
required (see the documentation about wrappers) but everything generic
enough to be reused for other libraries have been integrated into
rts/js/mem.js.

- - - - -
b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00
JS: avoid EMCC logging spurious failure

emcc would sometime output messages like:

  cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds)
  cache:INFO:  - ok

Cf https://github.com/emscripten-core/emscripten/issues/18607

This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0

- - - - -
ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00
Remove a dead comment

Just remove an out of date block of commented-out code, and tidy up
the relevant Notes.  See #8317.

- - - - -
bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00
nonmoving: Add support for heap profiling

Add support for heap profiling while using the nonmoving collector.

We greatly simply the implementation by disabling concurrent collection for
GCs when heap profiling is enabled. This entails that the marked objects on
the nonmoving heap are exactly the live objects.

Note that we match the behaviour for live bytes accounting by taking the size
of objects on the nonmoving heap to be that of the segment's block
rather than the object itself.

Resolves #22221

- - - - -
d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00
doc: Add requires prof annotation to options that require it

Resolves #24421

- - - - -
6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00
EPA: Match changes to HsParTy and HsFunTy

- - - - -
57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00
deriveConstants: add needed constants for wasm backend

This commit adds needed constants to deriveConstants. They are used by
RTS code in the wasm backend to support the JSFFI logic.

- - - - -
615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms

The pure Haskell implementation causes i386 regression in unrelated
work that can be fixed by using C-based atomic increment, see added
comment for details.

- - - - -
a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: allow JSFFI for wasm32

This commit allows the javascript calling convention to be used when
the target platform is wasm32.

- - - - -
8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: allow boxed JSVal as a foreign type

This commit allows the boxed JSVal type to be used as a foreign
argument/result type.

- - - - -
053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: ensure ctors have the right priority on wasm32

This commit fixes the priorities of ctors generated by GHC codegen on
wasm32, see the referred note for details.

- - - - -
b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: add JSFFI desugar logic for wasm32

This commit adds JSFFI desugar logic for the wasm backend.

- - - - -
2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00
compiler: add JavaScriptFFI to supported extension list on wasm32

This commit adds JavaScriptFFI as a supported extension when the
target platform is wasm32.

- - - - -
9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00
rts/ghc-internal: add JSFFI support logic for wasm32

This commit adds rts/ghc-internal logic to support the wasm backend's
JSFFI functionality.

- - - - -
e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00
ghc-internal: fix threadDelay for wasm in browsers

This commit fixes broken threadDelay for wasm when it runs in
browsers, see added note for detailed explanation.

- - - - -
f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00
utils: add JSFFI utility code

This commit adds JavaScript util code to utils to support the wasm
backend's JSFFI functionality:

- jsffi/post-link.mjs, a post-linker to process the linked wasm module
  and emit a small complement JavaScript ESM module to be used with it
  at runtime
- jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side
  of runtime logic
- jsffi/test-runner.mjs, run the jsffi test cases

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00
hadrian: distribute jsbits needed for wasm backend's JSFFI support

The post-linker.mjs/prelude.js files are now distributed in the
bindist libdir, so when using the wasm backend's JSFFI feature, the
user wouldn't need to fetch them from a ghc checkout manually.

- - - - -
c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: add opts.target_wrapper

This commit adds opts.target_wrapper which allows overriding the
target wrapper on a per test case basis when testing a cross target.
This is used when testing the wasm backend's JSFFI functionality; the
rest of the cases are tested using wasmtime, though the jsffi cases
are tested using the node.js based test runner.

- - - - -
8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: T22774 should work for wasm JSFFI

T22774 works since the wasm backend now supports the JSFFI feature.

- - - - -
1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00
testsuite: add JSFFI test cases for wasm backend

This commit adds a few test cases for the wasm backend's JSFFI
functionality, as well as a simple README to instruct future
contributors to add new test cases.

- - - - -
b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00
docs: add documentation for wasm backend JSFFI

This commit adds changelog and user facing documentation for the wasm
backend's JSFFI feature.

- - - - -
ffeb000d by David Binder at 2024-02-13T14:08:30-05:00
Add tests from libraries/process/tests and libraries/Win32/tests to GHC

These tests were previously part of the libraries, which themselves are
submodules of the GHC repository. This commit moves the tests directly
to the GHC repository.

- - - - -
5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00
Do not execute win32 tests on non-windows runners

- - - - -
500d8cb8 by Jade at 2024-02-13T14:09:07-05:00
prevent GHCi (and runghc) from suggesting other symbols when not finding main

Fixes: #23996

- - - - -
b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: update xxHash to v0.8.2

- - - - -
4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: use XXH3_64bits hash on all 64-bit platforms

This commit enables XXH3_64bits hash to be used on all 64-bit
platforms. Previously it was only enabled on x86_64, so platforms like
aarch64 silently falls back to using XXH32 which degrades the hashing
function quality.

- - - - -
ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00
rts: define XXH_INLINE_ALL

This commit cleans up how we include the xxhash.h header and only
define XXH_INLINE_ALL, which is sufficient to inline the xxHash
functions without symbol collision.

- - - - -
0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00
EPA: Move EpAnn out of extension points

Leaving a few that are too tricky, maybe some other time.

Also
 - remove some unneeded helpers from Parser.y
 - reduce allocations with strictness annotations

Updates haddock submodule

Metric Decrease:
    parsing001

- - - - -
de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00
Fix ffi callbacks with >6 args and non-64bit args.

Check for ptr/int arguments rather than 64-bit width arguments when counting
integer register arguments.
The old approach broke when we stopped using exclusively W64-sized types to represent
sub-word sized integers.

Fixes #24314

- - - - -
9c588f19 by Fendor at 2024-02-14T11:05:36+01:00
Adapt to GHC giving better Name's for linking

- - - - -
325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00
rts/EventLog: Place eliminate duplicate strlens

Previously many of the `post*` implementations would first compute the
length of the event's strings in order to determine the event length.
Later we would then end up computing the length yet again in
`postString`. Now we instead pass the string length to `postStringLen`,
avoiding the repeated work.

- - - - -
8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00
rts/eventlog: Place upper bound on IPE string field lengths

The strings in IPE events may be of unbounded length. Limit the lengths
of these fields to 64k characters to ensure that we don't exceed the
maximum event length.

- - - - -
0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00
rts: drop unused postString function

- - - - -
d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00
compiler/rts: fix wasm unreg regression

This commit fixes two wasm unreg regressions caught by a nightly
pipeline:

- Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm
- Invalid _hs_constructor(101) function name when handling ctor

- - - - -
264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00
feat: Add sortOn to Data.List.NonEmpty

Adds `sortOn` to `Data.List.NonEmpty`, and adds
comments describing when to use it, compared to
`sortWith` or `sortBy . comparing`.

The aim is to smooth out the API between
`Data.List`, and `Data.List.NonEmpty`.

This change has been discussed in the
[clc issue](https://github.com/haskell/core-libraries-committee/issues/227).

- - - - -
b57200de by Fendor at 2024-02-15T09:41:47-05:00
Prefer RdrName over OccName for looking up locations in doc renaming step

Looking up by OccName only does not take into account when functions are
only imported in a qualified way.

Fixes issue #24294

Bump haddock submodule to include regression test

- - - - -
8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00
JS: add simple optimizer

The simple optimizer reduces the size of the code generated by the
JavaScript backend without the complexity and performance penalty
of the optimizer in GHCJS.

Also see #22736

Metric Decrease:
    libdir
    size_hello_artifact

- - - - -
20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00
base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API

This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and
modifies the base API to reflect the new RTS flag.

CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243

Fixes #24337

- - - - -
778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00
Namespace specifiers for fixity signatures

- - - - -
08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00
base: export System.Mem.performBlockingMajorGC

The corresponding C function was introduced in
ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264.

Resolves #24228

The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230

Co-authored-by: Ben Gamari <bgamari.foss at gmail.com>

- - - - -
1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00
Fix C output for modern C initiative

GCC 14 on aarch64 rejects the C code written by GHC with this kind of
error:

   error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion]
         68 | *(ffi_arg*)resp = cret;
            |                 ^

Add the correct cast.

For more information on this see:
https://fedoraproject.org/wiki/Changes/PortingToModernC

Tested-by: Richard W.M. Jones <rjones at redhat.com>

- - - - -
5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00
Bump bytestring submodule to 0.12.1.0

- - - - -
902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00
Add missing BCO handling in scavenge_one.

- - - - -
97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00
Make cast between words and floats real primops (#24331)

First step towards fixing #24331. Replace foreign prim imports with real
primops.

- - - - -
a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00
Perf: add constant folding for bitcast between float and word (#24331)

- - - - -
5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00
Perf: replace stack checks with assertions in casting primops

There are RESERVED_STACK_WORDS free words (currently 21) on the stack,
so omit the checks.

Suggested by Cheng Shao.

- - - - -
401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00
Reexport primops from GHC.Float + add deprecation

- - - - -
4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00
rts/Hash: Don't iterate over chunks if we don't need to free data

When freeing a `HashTable` there is no reason to walk over the hash list
before freeing it if the user has not given us a `dataFreeFun`.

Noticed while looking at #24410.

- - - - -
bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00
compiler: add SEQ_CST fence support

In addition to existing Acquire/Release fences, this commit adds
SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a
fence that enforces total memory ordering. The following logic is
added:

- The MO_SeqCstFence callish MachOp
- The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h
- MO_SeqCstFence lowering logic in every single GHC codegen backend

- - - - -
2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00
testsuite: fix hs_try_putmvar002 for targets without pthread.h

hs_try_putmvar002 includes pthread.h and doesn't work on targets
without this header (e.g. wasm32). It doesn't need to include this
header at all. This was previously unnoticed by wasm CI, though recent
toolchain upgrade brought in upstream changes that completely removes
pthread.h in the single-threaded wasm32-wasi sysroot, therefore we
need to handle that change.

- - - - -
1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00
ci: bump ci-images to use updated wasm image

This commit bumps our ci-images revision to use updated wasm image.

- - - - -
56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00
Bump submodule text to 2.1.1

T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a.

Metric Decrease:
    T17123

- - - - -
a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00
rts: remove redundant rCCCS initialization

This commit removes the redundant logic of initializing each
Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before
initProfiling() is called during RTS startup, each Capability's rCCCS
has already been assigned CCS_SYSTEM when they're first initialized.

- - - - -
7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00
Drop dependence on `touch`

This drops GHC's dependence on the `touch` program, instead implementing
it within GHC. This eliminates an external dependency and means that we
have one fewer program to keep track of in the `configure` script

- - - - -
0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00
Parser, renamer, type checker for @a-binders (#17594)

GHC Proposal 448 introduces binders for invisible type arguments
(@a-binders) in various contexts. This patch implements @-binders
in lambda patterns and function equations:

  {-# LANGUAGE TypeAbstractions #-}

  id1 :: a -> a
  id1 @t x = x :: t      -- @t-binder on the LHS of a function equation

  higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16)
  higherRank f = (f 42, f 42)

  ex :: (Int8, Int16)
  ex = higherRank (\ @a x -> maxBound @a - x )
                         -- @a-binder in a lambda pattern in an argument
                         -- to a higher-order function

Syntax
------

To represent those @-binders in the AST, the list of patterns in Match
now uses ArgPat instead of Pat:

  data Match p body
     = Match {
         ...
-        m_pats  :: [LPat p],
+        m_pats  :: [LArgPat p],
         ...
   }

+ data ArgPat pass
+   = VisPat (XVisPat pass) (LPat pass)
+   | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass))
+   | XArgPat !(XXArgPat pass)

The VisPat constructor represents patterns for visible arguments,
which include ordinary value-level arguments and required type arguments
(neither is prefixed with a @), while InvisPat represents invisible type
arguments (prefixed with a @).

Parser
------

In the grammar (Parser.y), the lambda and lambda-cases productions of
aexp non-terminal were updated to accept argpats instead of apats:

  aexp : ...
-        | '\\' apats '->' exp
+        | '\\' argpats '->' exp
         ...
-        | '\\' 'lcases' altslist(apats)
+        | '\\' 'lcases' altslist(argpats)
         ...

+ argpat : apat
+        | PREFIX_AT atype

Function left-hand sides did not require any changes to the grammar, as
they were already parsed with productions capable of parsing @-binders.
Those binders were being rejected in post-processing (isFunLhs), and now
we accept them.

In Parser.PostProcess, patterns are constructed with the help of
PatBuilder, which is used as an intermediate data structure when
disambiguating between FunBind and PatBind. In this patch we define
ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived
data structure produced in isFunLhs and consumed in checkFunBind.

Renamer
-------

Renaming of @-binders builds upon prior work on type patterns,
implemented in 2afbddb0f24, which guarantees proper scoping and
shadowing behavior of bound type variables.

This patch merely defines rnLArgPatsAndThen to process a mix of visible
and invisible patterns:

+ rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn]
+ rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where
+   rnArgPatAndThen (VisPat x p)    = ... rnLPatAndThen ...
+   rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ...

Common logic between rnArgPats and rnPats is factored out into the
rn_pats_general helper.

Type checker
------------

Type-checking of @-binders builds upon prior work on lazy skolemisation,
implemented in f5d3e03c56f.

This patch extends tcMatchPats to handle @-binders. Now it takes and
returns a list of LArgPat rather than LPat:

  tcMatchPats ::
              ...
-             -> [LPat GhcRn]
+             -> [LArgPat GhcRn]
              ...
-             -> TcM ([LPat GhcTc], a)
+             -> TcM ([LArgPat GhcTc], a)

Invisible binders in the Match are matched up with invisible (Specified)
foralls in the type. This is done with a new clause in the `loop` worker
of tcMatchPats:

  loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a)
  loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys)
    ...
    -- NEW CLAUSE:
    | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis
    = ...

In addition to that, tcMatchPats no longer discards type patterns. This
is done by filterOutErasedPats in the desugarer instead.

x86_64-linux-deb10-validate+debug_info
Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -
486979b0 by Jade at 2024-02-19T07:12:13-05:00
Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First

Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246
Fixes: #24346

- - - - -
17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00
Fix reST in users guide

It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax.

- - - - -
35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00
Fix searching for errors in sphinx build

- - - - -
4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00
hadrian: fix wasm backend post linker script permissions

The post-link.mjs script was incorrectly copied and installed as a
regular data file without executable permission, this commit fixes it.

- - - - -
a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00
testsuite: mark T23540 as fragile on i386

See #24449 for details.

- - - - -
249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00
Add @since annotation to Data.Data.mkConstrTag

- - - - -
cdd939e7 by Jade at 2024-02-19T20:36:46-05:00
Enhance documentation of Data.Complex

- - - - -
d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

- - - - -
efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00
hadrian: Generate HSC2HS_EXTRAS variable in bindist installation

We must generate the hsc2hs wrapper at bindist installation time since
it must contain `--lflag` and `--cflag` arguments which depend upon the
installation path.

The solution here is to substitute these variables in the configure
script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in
the install rules.

Fixes #24050.

- - - - -
c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00
ci: Show --info for installed compiler

- - - - -
ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00
configure: Correctly set --target flag for linker opts

Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4
arguments, when it only takes 3 arguments. Instead we need to use the
`FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags.

Actually fixes #24414

- - - - -
9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00
configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS

- - - - -
77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00
Namespacing for fixity signatures (#14032)

Namespace specifiers were added to syntax of fixity signatures:
  - sigdecl ::= infix prec ops | ...
  + sigdecl ::= infix prec namespace_spec ops | ...

To preserve namespace during renaming MiniFixityEnv type
now has separate FastStringEnv fields for names that should be
on the term level and for name that should be on the type level.

makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way:
 - signatures without namespace specifiers fill both fields
 - signatures with 'data' specifier fill data field only
 - signatures with 'type' specifier fill type field only

Was added helper function lookupMiniFixityEnv that takes care about
looking for a name in an appropriate namespace.

Updates haddock submodule.

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00
rts: only collect live words in nonmoving census when non-concurrent

This avoids segfaults when the mutator modifies closures as we examine
them.

Resolves #24393

- - - - -
9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00
mutex wrap in refreshProfilingCCSs

- - - - -
1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00
rts: remove unused HAVE_C11_ATOMICS macro

This commit removes the unused HAVE_C11_ATOMICS macro. We used to have
a few places that have fallback paths when HAVE_C11_ATOMICS is not
defined, but that is completely redundant, since the
FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler
doesn't support C11 style atomics. There are also many places (e.g. in
unreg backend, SMP.h, library cbits, etc) where we unconditionally use
C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the
oldest distro we test in our CI, so there's no value in keeping
HAVE_C11_ATOMICS.

- - - - -
0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00
RTS: -Ds - make sure incall is non-zero before dereferencing it.

Fixes #24445

- - - - -
e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00
rts/AdjustorPool: Use ExecPage abstraction

This is just a minor cleanup I found while reviewing the implementation.

- - - - -
826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00
rename GHC.Tuple.Prim to GHC.Tuple

- - - - -
09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00
Define GHC2024 language edition (#24320)

See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also
fixes #24343 and improves the documentation of language editions.

Co-authored-by: Joachim Breitner <mail at joachim-breitner.de>

- - - - -
2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00
Bump bounds

- - - - -
f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00
Allow `@since` annotations in export lists

Here we extend Haddock to admit `@since` annotations in export lists.
These can be attached to most export list items (although not
subordinate lists). These annotations supercede the declaration's
`@since` annotation in produced Haddocks.

- - - - -
b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00
Allow package-qualified @since declarations

- - - - -
8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00
Documentation changes from ghc-internal restructuring

Previously many declarations (e.g. `Int`) were declared to have a "home"
in `Prelude`. However, now Haddock instead chooses to put these in
more specific homes (e.g. `Data.Int`). Given that the "home" decision is
driven by heuristics and in general these changes seem
quite reasonable I am accepting them:

 * `Int` moved from `Prelude` to `Data.Int`
 * `(~)` moved from `Prelude` to `Data.Type.Equality`
 * `Type` moved from `GHC.Types` to `Data.Kind`
 * `Maybe` moved from `Prelude` to `Data.Maybe`
 * `Bool` moved from `Prelude` to `Data.Bool`
 * `Ordering` moved from `Prelude` to `Data.Ord`

As well, more identifiers are now hyperlinked; it's not immediately
clear *why*, but it is an improvement nevertheless.

- - - - -
ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00
Allow docstrings after exports

Here we extend the parser and AST to preserve docstrings following
export items. We then extend Haddock to parse `@since` annotations in
such docstrings, allowing changes in export structure to be properly
documented.

Bumps haddock submodule.

- - - - -
30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00
rename GHC.Tuple.Prim to GHC.Tuple

- - - - -
0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00
Improve the synopsis and description of base

- - - - -
2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00
Error Messages: Properly align cyclic module error

Fixes: #24476

- - - - -
bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00
Allow docstrings after exports

Here we extend the parser and AST to preserve docstrings following
export items. We then extend Haddock to parse `@since` annotations in
such docstrings, allowing changes in export structure to be properly
documented.

- - - - -
d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00
ghc-internal: Move modules into GHC.Internal.* namespace

Bumps haddock submodule due to testsuite output changes.

- - - - -
a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00
ghc-internal: Rewrite `@since ` to `@since base-`

These will be incrementally moved to the export sites in `base` where
possible.

- - - - -
ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Migrate Haddock `not-home` pragmas from `ghc-internal`

This ensures that we do not use `base` stub modules as declarations'
homes when not appropriate.

- - - - -
c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Partially freeze exports of GHC.Base

Sadly there are still a few module reexports. However, at least we have
decoupled from the exports of `GHC.Internal.Base`.

- - - - -
272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00
Move Haddock named chunks

- - - - -
2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00
Drop GHC.Internal.Data.Int

- - - - -
55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler: Fix mention to `GHC....` modules in wasm desugaring

Really, these references should be via known-key names anyways. I have
fixed the proximate issue here but have opened #24472 to track the
additional needed refactoring.

- - - - -
64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00
Accept performance shifts from ghc-internal restructure

As expected, Haddock now does more work. Less expected is that some
other testcases actually get faster, presumably due to less interface
file loading. As well, the size_hello_artifact test regressed a bit when
debug information is enabled due to debug information for the new stub
symbols.

Metric Decrease:
    T12227
    T13056
Metric Increase:
    haddock.Cabal
    haddock.base
    MultiLayerModulesTH_OneShot
    size_hello_artifact

- - - - -
317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00
Expose GHC.Wasm.Prim from ghc-experimental

Previously this was only exposed from `ghc-internal` which violates our
agreement that users shall not rely on things exposed from that package.

Fixes #24479.

- - - - -
3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler/tc: Small optimisation of evCallStack

Don't lookupIds unless we actually need them.

- - - - -
3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00
compiler/tc: Use toException instead of SomeException

- - - - -
125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Factor out errorBelch

This was useful when debugging

- - - - -
3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00
base: Clean up imports of GHC.Stack.CloneStack

- - - - -
6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Move PrimMVar to GHC.Internal.MVar

- - - - -
28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Move prettyCallStack to GHC.Internal.Stack

- - - - -
4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Explicit dependency to workaround #24436

Currently `ghc -M` fails to account for `.hs-boot` files correctly,
leading to issues with cross-package one-shot builds failing. This
currently manifests in `GHC.Exception` due to the boot file for
`GHC.Internal.Stack`. Work around this by adding an explicit `import`,
ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`.

See #24436.

- - - - -
294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00
base: Use displayException in top-level exception handler

Happily this also allows us to eliminate a special case for Deadlock
exceptions.

Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198).

- - - - -
732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00
rts: Fix symbol references in Wasm RTS

- - - - -
4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00
GHCi: Improve response to unloading, loading and reloading modules

Fixes #13869

- - - - -
f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00
rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job

- - - - -
c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00
hadrian/hie-bios: pass -j to hadrian

This commit passes -j to hadrian in the hadrian/hie-bios scripts. When
the user starts HLS in a fresh clone that has just been configured, it
takes quite a while for hie-bios to pick up the ghc flags and start
actual indexing, due to the fact that the hadrian build step defaulted
to -j1, so -j speeds things up and improve HLS user experience in GHC.
Also add -j flag to .ghcid to speed up ghcid, and sets the Windows
build root to .hie-bios which also works and unifies with other
platforms, the previous build root _hie-bios was missing from
.gitignore anyway.

- - - - -
50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00
ci: enable parallelism in hadrian/ghci scripts

This commit enables parallelism when the hadrian/ghci scripts are
called in CI. The time bottleneck is in the hadrian build step, but
previously the build step wasn't parallelized.

- - - - -
61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00
m4: Correctly detect GCC version

When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here.

```
$ cc --version
cc (GCC) 13.2.1 20230801
...
```

This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler`

This patch makes it check for upper-cased "GCC" too so that it works correctly:

```
checking version of gcc... 13.2.1
```
- - - - -
001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00
Fix formatting in whereFrom docstring

Previously it used markdown syntax rather than Haddock syntax for code quotes

- - - - -
e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00
Move ClosureType type to ghc-internal

- Use ClosureType for InfoProv.ipDesc.
- Use ClosureType for CloneStack.closureType.
- Now ghc-heap re-exports this type from ghc-internal.

See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210

Resolves #22600

- - - - -
3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00
StgToJS: Simplify ExprInline constructor of ExprResult

Its payload was used only for a small optimization in genAlts,
avoiding a few assignments for programs of this form:

  case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; }

But when compiling with optimizations, this sort of code is
generally eliminated by case-of-known-constructor in Core-to-Core.
So it doesn't seem worth tracking and cleaning up again in StgToJS.

- - - - -
61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00
rts: add missing ccs_mutex guard to internal_dlopen

See added comment for details. Closes #24423.

- - - - -
dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00
cg: Remove GHC.Cmm.DataFlow.Collections

In pursuit of #15560 and #17957 and generally removing redundancy.

- - - - -
d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00
utils: remove unused lndir from tree

Ever since the removal of the make build system, the in tree lndir
hasn't been actually built, so this patch removes it.

- - - - -
86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00
Merge remote-tracking branch 'origin/ghc-head' into HEAD

- - - - -
74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00
rts: avoid checking bdescr of value outside of Haskell heap

In nonmovingTidyWeaks we want to check if the key of a weak pointer
lives in the non-moving heap. We do this by checking the flags of the
block the key lives in. But we need to be careful with values that live
outside the Haskell heap, since they will lack a block descriptor and
looking for one may lead to a segfault. In this case we should just
accept that it isn't on the non-moving heap.

Resolves #24492

- - - - -
b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00
In mkDataConRep, ensure the in-scope set is right

A small change that fixes #24489

- - - - -
3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00
testsuite: fix T23540 fragility on 32-bit platforms

T23540 is fragile on 32-bit platforms. The root cause is usage of
`getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord`
instance, which is indeterministic. The solution is adding a
deterministic `Ord` instance for `EvidenceInfo` and sorting the
evidence trees before pretty printing. Fixes #24449.

- - - - -
960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00
Reduce AtomicModifyIORef increment count

This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490

- - - - -
2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00
hadrian: Improve parallelism in binary-dist-dir rule

I noticed that the "docs" target was needed after the libraries and
executables were built. We can improve the parallelism by needing
everything at once so that documentation can be built immediately after
a library is built for example.

- - - - -
cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: Bump windows and freebsd boot compilers to 9.6.4

We have previously bumped the docker images to use 9.6.4, but neglected
to bump the windows images until now.

- - - - -
30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: darwin: Update to 9.6.2 for boot compiler

9.6.4 is currently broken due to #24050

Also update to use LLVM-15 rather than LLVM-11, which is out of date.

- - - - -
d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00
Bump minimum bootstrap version to 9.6

- - - - -
67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00
ci: Enable more documentation building

Here we enable documentation building on

1. Darwin: The sphinx toolchain was already installed so we enable html
   and manpages.
2. Rocky8: Full documentation (toolchain already installed)
3. Alpine: Full documetnation (toolchain already installed)
4. Windows: HTML and manpages (toolchain already installed)

Fixes #24465

- - - - -
39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00
ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15

- - - - -
d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00
Introduce ListTuplePuns extension

This implements Proposal 0475, introducing the `ListTuplePuns` extension
which is enabled by default.

Disabling this extension makes it invalid to refer to list, tuple and
sum type constructors by using built-in syntax like `[Int]`,
`(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`.
Instead, this syntax exclusively denotes data constructors for use with
`DataKinds`.
The conventional way of referring to these data constructors by
prefixing them with a single quote (`'(Int, Int)`) is now a parser
error.

Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo`
data constructor has been renamed to `MkSolo` (in a previous commit).
Unboxed tuples and sums now have real source declarations in `GHC.Types`.
Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo`
and `Solo#`.
Constraint tuples now have the unambiguous type constructors `CTuple<n>`
as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before.

A new parser construct has been added for the unboxed sum data
constructor declarations.

The type families `Tuple`, `Sum#` etc. that were intended to provide
nicer syntax have been omitted from this change set due to inference
problems, to be implemented at a later time.
See the MR discussion for more info.

Updates the submodule utils/haddock.
Updates the cabal submodule due to new language extension.

    Metric Increase:
        haddock.base

    Metric Decrease:
        MultiLayerModulesTH_OneShot
        size_hello_artifact

Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst

Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820

Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294

- - - - -
bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00
JS linker: filter unboxed tuples

- - - - -
dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00
Improve error messages coming from non-linear patterns

This enriched the `CtOrigin` for non-linear patterns to include data
of the pattern that created the constraint (which can be quite useful
if it occurs nested in a pattern) as well as an explanation why the
pattern is non-restricted in (at least in some cases).

- - - - -
6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00
Adjust documentation of linear lets according to committee decision

- - - - -
1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00
compiler: start deprecating cmmToRawCmmHook

cmmToRawCmmHook was added 4 years ago in
d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the
Asterius project, which has been archived and deprecated in favor of
the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by
placing a DEPRECATED pragma, and actual removal shall happen in a
future GHC major release if no issue to oppose the deprecation has
been raised in the meantime.

- - - - -
9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00
Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258

- - - - -
61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00
add -fprof-late-overloaded and -fprof-late-overloaded-calls

* Refactor late cost centre insertion for extensibility
* Add two more late cost centre insertion methods that add SCCs to overloaded
  top level bindings and call sites with dictionary arguments.
* Some tests for the basic functionality of the new insertion methods

Resolves: #24500

- - - - -
82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00
x86-ncg: Fix fma codegen when arguments are globals

Fix a bug in the x86 ncg where results would be wrong when the desired output
register and one of the input registers were the same global.

Also adds a tiny optimization to make use of the memory addressing
support when convenient.

Fixes #24496

- - - - -
18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00
rel_eng: Update hackage docs upload scripts

This adds the upload of ghc-internal and ghc-experimental to our scripts
which upload packages to hackage.

- - - - -
bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00
docs: Remove stray module comment from GHC.Profiling.Eras

- - - - -
37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00
Fix ghc-internal cabal file

The file mentioned some artifacts relating to the base library. I have
renamed these to the new ghc-internal variants.

- - - - -
23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00
Fix haddock source links and hyperlinked source

There were a few issues with the hackage links:

1. We were using the package id rather than the package name for the
   package links. This is fixed by now allowing the template to mention
   %pkg% or %pkgid% and substituing both appropiatly.
2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage`
   as the new base link works on a local or remote hackage server.
3. The "src" path including too much stuff, so cross-package source
   links were broken as the template was getting double expanded.

Fixes #24086

- - - - -
2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00
filepath: Bump submodule to 1.5.2.0

- - - - -
31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00
os-string: Bump submodule to 2.0.2

- - - - -
4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00
base: Reflect new era profiling RTS flags in GHC.RTS.Flags

* -he profiling mode
* -he profiling selector
* --automatic-era-increment

CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254

- - - - -
a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00
JS: faster implementation for some numeric primitives (#23597)

Use faster implementations for the following primitives in the JS
backend by not using JavaScript's BigInt:
- plusInt64
- minusInt64
- minusWord64
- timesWord64
- timesInt64

Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com>

- - - - -
21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00
rts: add -xr option to control two step allocator reserved space size

This patch adds a -xr RTS option to control the size of virtual memory
address space reserved by the two step allocator on a 64-bit platform,
see added documentation for explanation. Closes #24498.

- - - - -
dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00
rts: expose HeapAlloc.h as public header

This commit exposes HeapAlloc.h as a public header. The intention is
to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in
assertions in other public headers, and they may also be useful for
user code.

- - - - -
d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00
rts: assert pointer is indeed heap allocated in Bdescr()

This commit adds an assertion to Bdescr() to assert the pointer is
indeed heap allocated. This is useful to rule out RTS bugs that
attempt to access non-existent block descriptor of a static closure, #24492
being one such example.

- - - - -
9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00
ghc-experimental: Add dummy dependencies to work around #23942

This is a temporary measure to improve CI reliability until a proper
solution is developed.

Works around #23942.

- - - - -
1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00
Three compile perf improvements with deep nesting

These were changes are all triggered by #24471.

1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are
   many free variables.  See Note [Large free-variable sets].

2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument.
   This benefits the common case where the ArityType turns out to
   be nullary. See Note [Care with nested expressions]

3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested
   expressions.  See Note [Eta expansion of arguments in CorePrep]
   wrinkle (EA2).

Compile times go down by up to 4.5%, and much more in artificial
cases. (Geo mean of compiler/perf changes is -0.4%.)

Metric Decrease:
    CoOpt_Read
    T10421
    T12425

- - - - -
c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00
Use "module" instead of "library" when applicable in base haddocks

- - - - -
9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00
Rephrase error message to say "visible arguments" (#24318)

* Main change: make the error message generated by mkFunTysMsg more
  accurate by changing "value arguments" to "visible arguments".

* Refactor: define a new type synonym VisArity and use it instead of
  Arity in a few places.

It might be the case that there other places in the compiler that should
talk about visible arguments rather than value arguments, but I haven't
tried to find them all, focusing only on the error message reported in
the ticket.

- - - - -
4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00
fix haskell/haddock#24493, with module name introduced in hieAst

The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153
Two things have been done:
1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst,
2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated.

- - - - -
d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00
Bump array submodule

- - - - -
7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00
Bump stm submodule

- - - - -
32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00
Introduce exception context

Here we introduce the `ExceptionContext` type and `ExceptionAnnotation`
class, allowing dynamically-typed user-defined annotations to be
attached to exceptions.

CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199
GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330

- - - - -
39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00
testsuite/interface-stability: Update documentation

- - - - -
fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00
ghc-internal: comment formatting

- - - - -
4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00
compiler: Default and warn ExceptionContext constraints

- - - - -
3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00
base: Introduce exception backtraces

Here we introduce the `Backtraces` type and associated machinery for
attaching these via `ExceptionContext`. These has a few compile-time
regressions (`T15703` and `T9872d`) due to the additional dependencies
in the exception machinery.

As well, there is a surprisingly large regression in the
`size_hello_artifact` test. This appears to be due to various `Integer` and
`Read` bits now being reachable at link-time. I believe it should be
possible to avoid this but I have accepted the change for now to get the
feature merged.

CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199
GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330

Metric Increase:
    T15703
    T9872d
    size_hello_artifact

- - - - -
18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00
users guide: Release notes for exception backtrace work

- - - - -
f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00
compiler: Don't show ExceptionContext of GhcExceptions

Most GhcExceptions are user-facing errors and therefore the
ExceptionContext has little value. Ideally we would enable
it in the DEBUG compiler but I am leaving this for future work.

- - - - -
dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00
Disable T9930fail for the JS target (cf #19174)

- - - - -
bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00
Update showAstData to honour blanking of AnnParen

Also tweak rendering of SrcSpan to remove extra blank line.

- - - - -
50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00
ghc-internal: Eliminate GHC.Internal.Data.Kind

This was simply reexporting things from `ghc-prim`. Instead reexport
these directly from `Data.Kind`. Also add build ordering dependency to
work around #23942.

- - - - -
38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00
rts: Fix SET_HDR initialization of retainer set

This fixes a regression in retainer set profiling introduced by
b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit
the heap traversal word would be initialized by `SET_HDR` using
`LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling`
check in `LDV_RECORD_CREATE`, meaning that this initialization no longer
happened.

Given that this initialization was awkwardly indirectly anyways, I have
fixed this by explicitly initializating the heap traversal word to
`NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior,
but much more direct.

Fixes #24513.

- - - - -
635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00
Bump ghc version to 9.10

- - - - -
2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00
base: Use strerror_r instead of strerror

As noted by #24344, `strerror` is not necessarily thread-safe.
Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is
safe to use.

Fixes #24344.

CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249

- - - - -
5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00
Bump base upper bound

- - - - -
b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00
Testsuite output update

- - - - -
edb9bf77 by Jade at 2024-03-09T03:39:38-05:00
Error messages: Improve Error messages for Data constructors in type signatures.

This patch improves the error messages from invalid type signatures by
trying to guess what the user did and suggesting an appropriate fix.

Partially fixes: #17879

- - - - -
cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00
HieAst: add module name #24493

The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst.
It should fix #24493.

The following have been done:
1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))`
   To store the located module name information.
2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information.
3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests.
4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53

- - - - -
2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00
GHC.Utils.Binary: fix a couple of typos

- - - - -
5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00
rts: Drop .wasm suffix from .prof file names

This replicates the behavior on Windows, where `Hi.exe` will produce
profiling output named `Hi.prof` instead of `Hi.exe.prof`.

While in the area I also fixed the extension-stripping logic, which
incorrectly rewrote `Hi.exefoo` to `Hi.foo`.

Closes #24515.

- - - - -
259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00
testsuite: drop exe extension from .hp & .prof filenames

See #24515 for details.

- - - - -
c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00
rts/linker: Enable GOT support on all platforms

There is nothing platform-dependent about our GOT implementation and
GOT support is needed by `T24171` on i386.

- - - - -
2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00
Drop outdated comment on TcRnIllformedTypePattern

This should have been done in 0f0c53a501b but I missed it.

- - - - -
c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Bounds check array write

- - - - -
15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/CloneStack: Don't expose helper functions in header

- - - - -
e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00
base: Move internals of GHC.InfoProv into GHC.InfoProv.Types

Such that we can add new helpers into GHC.InfoProv.Types without
breakage.

- - - - -
6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00
rts: Lazily decode IPE tables

Previously we would eagerly allocate `InfoTableEnt`s for each
info table registered in the info table provenance map. However, this
costs considerable memory and initialization time. Instead we now
lazily decode these tables. This allows us to use one-third the memory
*and* opens the door to taking advantage of sharing opportunities within
a module.

This required considerable reworking since lookupIPE now must be passed
its result buffer.

- - - - -
9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Don't expose helper in header

- - - - -
308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00
rts/IPE: Share module_name within a Node

This allows us to shave a 64-bit word off of the packed IPE entry size.

- - - - -
bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00
IPE: Expose unit ID in InfoTableProv

Here we add the unit ID to the info table provenance structure.

- - - - -
6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00
rts: Refactor GHC.Stack.CloneStack.decode

Don't allocate a Ptr constructor per frame.

- - - - -
ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00
base: Do not expose whereFrom# from GHC.Exts

- - - - -
2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00
docs: Update info on TypeAbstractions

* Mention TypeAbstractions in 9.10.1-notes.rst
* Set the status to "Experimental".
* Add a "Since: GHC 9.x" comment to each section.

- - - - -
f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00
ci-images: Bump Alpine image to bootstrap with 9.8.2

- - - - -
705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark T24171 as fragile due to #24512

I will fix this but not in time for 9.10.1-alpha1

- - - - -
c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Mark linker_unload_native as fragile

In particular this fails on platforms without `dlinfo`. I plan to
address this but not before 9.10.1-alpha1.

- - - - -
f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00
configure: Bump version to 9.10

- - - - -
88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00
Bump transformers submodule to 0.6.1.1

- - - - -
8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00
testsuite: Increase ulimit for T18623

1 MByte was just too tight and failed intermittently on some platforms
(e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient
headroom.

Fixes #23139.

- - - - -
c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00
base: Bump version to 4.20.0.0

- - - - -
b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-internal: Set initial version at 9.1001.0

This provides PVP compliance while maintaining a clear correspondence
between GHC releases and `ghc-internal` versions.

- - - - -
4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00
ghc-prim: Bump version to 0.11.0

- - - - -
50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00
template-haskell: Bump version to 2.22.0.0

- - - - -
8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00
base-exports: Accommodate spurious whitespace changes in 32-bit output

It appears that this was

- - - - -
9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00
users-guide: Move exception backtrace relnotes to 9.10

This was previously mistakenly added to the GHC 9.8 release notes.

- - - - -
145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix name of Rocky8 artifact

- - - - -
39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/rel_eng: Fix path of generate_jobs_metadata

- - - - -
aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00
gitlab/upload: Rework recompression

The old `combine` approach was quite fragile due to use of filename
globbing. Moreover, it didn't parallelize well. This refactoring
makes the goal more obvious, parallelizes better, and is more robust.

- - - - -
9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00
Merge branch 'ghc-9.10' into ghc-head

- - - - -
cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00
Bump GHC version to 9.11

- - - - -
4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00
Merge remote-tracking branch 'origin/ghc-head' into ghc-head

- - - - -
dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00
configure: Bump GHC version to 9.11

Bumps haddock submodule.

- - - - -
8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload code when profiling is enabled

The heap census may contain references (e.g. `Counter.identity`) to
static data which must be available when the census is reported at the
end of execution.

Fixes #24512.

- - - - -
7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00
rts/linker: Don't unload native objects when dlinfo isn't available

To do so is unsafe as we have no way of identifying references to
symbols provided by the object.

Fixes #24513. Fixes #23993.

- - - - -
0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00
rel_eng/upload: Purge both $rel_name/ and $ver/

This is necessary for prereleases, where GHCup accesses the release via
`$ver/`

- - - - -
b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Remove duplicate code normalising slashes

- - - - -
c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00
Simplify regexes with raw strings

- - - - -
1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00
Don't normalize backslashes in characters

- - - - -
7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00
Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470)

- - - - -
39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00
Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms"

This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was
originally intended to fix #24449, but it was merely sweeping the bug
under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly
fixed the fragile test, and we no longer need the C version of genSym.
Furthermore, the C implementation causes trouble when compiling with
clang that targets i386 due to alignment warning and libatomic linking
issue, so it makes sense to revert it.

- - - - -
e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00
compiler: fix out-of-bound memory access of genSym on 32-bit

This commit fixes an unnoticed out-of-bound memory access of genSym on
32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms,
but we mistakenly treat it as a Word64 pointer in genSym, and
therefore will accidentally load 2 garbage higher bytes, or with a
small but non-zero chance, overwrite something else in the data
section depends on how the linker places the data segments. This
regression was introduced in !11802 and fixed here.

- - - - -
77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00
Note mutability of array and address access primops

Without an understanding of immutable vs. mutable memory, the index
primop family have a potentially non-intuitive type signature:

    indexOffAddr :: Addr# -> Int# -> a
    readOffAddr  :: Addr# -> Int# -> State# d -> (# State# d, a #)

indexOffAddr# might seem like a free generality improvement, which it
certainly is not!

This change adds a brief note on mutability expectations for most
index/read/write access primops.

- - - - -
7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00
EPA: Fix regression discarding comments in contexts

Closes #24533

- - - - -
73be65ab by Fendor at 2024-03-19T01:42:53-04:00
Fix sharing of 'IfaceTyConInfo' during core to iface type translation

During heap analysis, we noticed that during generation of
'mi_extra_decls' we have lots of duplicates for the instances:

* `IfaceTyConInfo NotPromoted IfaceNormalTyCon`
* `IfaceTyConInfo IsPromoted IfaceNormalTyCon`

which should be shared instead of duplicated. This duplication increased
the number of live bytes by around 200MB while loading the agda codebase
into GHCi.

These instances are created during `CoreToIface` translation, in
particular `toIfaceTyCon`.

The generated core looks like:

    toIfaceTyCon
      = \ tc_sjJw ->
          case $wtoIfaceTyCon tc_sjJw of
          { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) ->
          IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM)
          }

whichs removes causes the sharing to work propery.

Adding explicit sharing, with NOINLINE annotations, changes the core to:

    toIfaceTyCon
      = \ tc_sjJq ->
          case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) ->
          IfaceTyCon ww_sjNB ww1_sjNC
          }

which looks much more like sharing is happening.
We confirmed via ghc-debug that all duplications were eliminated and the
number of live bytes are noticeably reduced.

- - - - -
bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00
EPA: Address more 9.10.1-alpha1 regressions from recent changes

Closes #24533
Hopefully for good this time

- - - - -
31bf85ee by Fendor at 2024-03-19T14:48:08-04:00
Escape multiple arguments in the settings file

Uses responseFile syntax.

The issue arises when GHC is installed on windows into a location that
has a space, for example the user name is 'Fake User'.
The $topdir will also contain a space, consequentially.
When we resolve the top dir in the string `-I$topdir/mingw/include`,
then `words` will turn this single argument into `-I/C/Users/Fake` and
`User/.../mingw/include` which trips up the flag argument parser of
various tools such as gcc or clang.
We avoid this by escaping the $topdir before replacing it in
`initSettngs`.
Additionally, we allow to escape spaces and quotation marks for
arguments in `settings` file.

Add regression test case to count the number of options after variable
expansion and argument escaping took place.
Additionally, we check that escaped spaces and double quotation marks are
correctly parsed.

- - - - -
f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00
Read global package database from settings file

Before this patch, the global package database was always assumed to be
in libdir </> package.conf.d.

This causes issues in GHC's build system because there are sometimes
situations where the package database you need to use is not located in
the same place as the settings file.

* The stage1 compiler needs to use stage1 libraries, so we should set
  "Global Package DB" for the stage1 compiler to the stage1 package
  database.
* Stage 2 cross compilers need to use stage2 libraries, so likewise, we
  should set the package database path to `_build/stage2/lib/`

* The normal situation is where the stage2 compiler uses stage1
  libraries. Then everything lines up.

* When installing we have rearranged everything so that the settings
  file and package database line up properly, so then everything should
  continue to work as before. In this case we set the relative package
  db path to `package.conf.d`, so it resolves the same as before.

* ghc-pkg needs to be modified as well to look in the settings file fo
  the package database rather than assuming the global package database
  location relative to the lib folder.

* Cabal/cabal-install will work correctly because they query the global
  package database using `--print-global-package-db`.

A reasonable question is why not generate the "right" settings files in
the right places in GHC's build system. In order to do this you would
need to engineer wrappers for all executables to point to a specific
libdir. There are also situations where the same package db is used by
two different compilers with two different settings files (think stage2
cross compiler and stage3 compiler).

In short, this 10 line patch allows for some reasonable simplifications
in Hadrian at very little cost to anything else.

Fixes #24502

- - - - -
4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00
hadrian: Remove stage1 testsuite wrappers logic

Now instead of producing wrappers which pass the global package database
argument to ghc and ghc-pkg, we write the location of the correct
package database into the settings file so you can just use the intree
compiler directly.

- - - - -
da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00
Remove unused ghc-internal module "GHC.Internal.Constants"

- - - - -
b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00
CorePrep: Rework lowering of BigNat# literals

Don't use bigNatFromWord#, because that's terrible:
 * We shouldn't have to traverse a linked list at run-time
   to build a BigNat# literal. That's just silly!
 * The static List object we have to create is much larger
   than the actual BigNat#'s contents, bloating code size.
 * We have to read the corresponding interface file,
   which causes un-tracked implicit dependencies. (#23942)

Instead, encode them into the appropriate platform-dependent
sequence of bytes, and generate code that copies these bytes
at run-time from an Addr# literal into a new ByteArray#.
A ByteArray# literal would be the correct thing to generate,
but these are not yet supported; see also #17747.

Somewhat surprisingly, this change results in a slight
reduction in compiler allocations, averaging around 0.5%
on ghc's compiler performance tests, including when compiling
programs that contain no bignum literals to begin with.
The specific cause of this has not been investigated.

Since this lowering no longer reads the interface file for
GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer]
is obsoleted.  But the story of un-tracked built-in dependencies
remains complex, and Note [Tracking dependencies on primitives]
now exists to explain this complexity.

Additionally, many empty imports have been modified to refer to
this new note and comply with its guidance.  Several empty imports
necessary for other reasons have also been given brief explanations.

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
349ea330 by Fendor at 2024-03-19T14:50:00-04:00
Eliminate thunk in 'IfaceTyCon'

Heap analysis showed that `IfaceTyCon` retains a thunk to
`IfaceTyConInfo`, defeating the sharing of the most common instances of
`IfaceTyConInfo`.
We make sure the indirection is removed by adding bang patterns to
`IfaceTyCon`.

Experimental results on the agda code base, where the `mi_extra_decls`
were read from disk:

Before this change, we observe around 8654045 instances of:

`IfaceTyCon[Name,THUNK_1_0]`

But these thunks almost exclusively point to a shared value!

Forcing the thunk a little bit more, leads to `ghc-debug` reporting:

`IfaceTyCon[Name:Name,IfaceTyConInfo]`

and a noticeable reduction of live bytes (on agda ~10%).

- - - - -
594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00
Minor misc cleanups

- GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs;
  boxed tuples don't take RuntimeRep args
- GHC.HsToCore.Foreign.Call: avoid partial pattern matching
- GHC.Stg.Unarise: strengthen the assertion; we can assert that
  non-rubbish literals are unary rather than just non-void
- GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires
- users_guide/using-warnings.rst: remove -Wforall-identifier,
  now deprecated and does nothing
- users_guide/using.rst: fix formatting
- andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed

The rest are simple cleanups.

- - - - -
cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00
mk/relpath: Fix quoting

Previously there were two instances in this script which lacked proper
quoting. This resulted in `relpath` invocations in the binary
distribution Makefile producing incorrect results on Windows, leading to
confusing failures from `sed` and the production of empty package
registrations.

Fixes #24538.

- - - - -
5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00
testsuite: Disable T21336a on wasm

- - - - -
60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00
hadrian/bindist: Eliminate extraneous `dirname` invocation

Previously we would call `dirname` twice per installed library file.
We now instead reuse this result. This helps appreciably on Windows, where
processes are quite expensive.

- - - - -
616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00
hadrian: Package mingw toolchain in expected location

This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89.
Specifically, GHC expects to find the mingw32 toolchain in the binary distribution
root. However, after this patch it was packaged in the `lib/` directory.

- - - - -
de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00
gitlab/rel_eng: More upload.sh tweaks

- - - - -
1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00
rel_eng: Drop dead prepare_docs codepath

- - - - -
dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00
rel_env/recompress_all: unxz before recompressing

Previously we would rather compress the xz *again*, before in addition
compressing it with the desired scheme.

Fixes #24545.

- - - - -
9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00
mk-ghcup-metadata: Fix directory of testsuite tarball

As reported in #24546, the `dlTest` artifact should be extracted into
the `testsuite` directory.

- - - - -
6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00
ghcup-metadata: Don't populate dlOutput unless necessary

ghcup can apparently infer the output name of an artifact from its URL.
Consequently, we should only include the `dlOutput` field when it would
differ from the filename of `dlUri`.

Fixes #24547.

- - - - -
576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00
Revert "Apply shellcheck suggestion to SUBST_TOOLDIR"

This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392.

The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a
no-op. `set` sets positional arguments for bash, but we want to set the variable
given as the first autoconf argument.

Fixes #24542

Metric decreases because the paths in the settings file are now shorter,
so we allocate less when we read the settings file.

-------------------------
Metric Decrease:
    T12425
    T13035
    T9198
-------------------------

- - - - -
cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00
Compact serialisation of IfaceAppArgs

In #24563, we identified that IfaceAppArgs serialisation tags each
cons cell element with a discriminator byte. These bytes add up
quickly, blowing up interface files considerably when
'-fwrite-if-simplified-core' is enabled.

We compact the serialisation by writing out the length of
'IfaceAppArgs', followed by serialising the elements directly without
any discriminator byte.

This improvement can decrease the size of some interface files by up
to 35%.

- - - - -
97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00
Expand untyped splices in tcPolyExprCheck

Fixes #24559

- - - - -
5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00
EPA: Clean up Exactprint helper functions a bit

- Introduce a helper lens to compose on `EpAnn a` vs `a` versions
- Rename some prime versions of functions back to non-prime
  They were renamed during the rework

- - - - -
da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00
Type operators in promoteOccName (#24570)

Type operators differ from term operators in that they are lexically
classified as (type) constructors, not as (type) variables.

Prior to this change, promoteOccName did not account for this
difference, causing a scoping issue that affected RequiredTypeArguments.

  type (!@#) = Bool
  f = idee (!@#)      -- Not in scope: ‘!@#’  (BUG)

Now we have a special case in promoteOccName to account for this.

- - - - -
247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00
docs: Remove mention of non-existent Ord instance for Complex

The documentation for Data.Complex says that the Ord instance for Complex Float
is deficient, but there is no Ord instance for Complex a. The Eq instance for
Complex Float is similarly deficient, so we use that as an example instead.

- - - - -
6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00
Fix TH handling in `pat_to_type_pat` function (#24571)

There was missing case for `SplicePat` in `pat_to_type_at` function,
hence patterns with splicing that checked against `forall->` doesn't work
properly because they fall into the "illegal pattern" case.

Code example that is now accepted:

  g :: forall a -> ()
  g $([p| a |]) = ()

- - - - -
52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00
Type-check default declarations before deriving clauses (#24566)

See added Note and #24566. Default declarations must be type-checked
before deriving clauses.

- - - - -
7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00
Lexer: small perf changes

- Use unsafeChr because we know our values to be valid
- Remove some unnecessary use of `ord` (return Word8 values directly)

- - - - -
864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00
JS: fix some comments

- - - - -
3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00
Simplifier: Re-do dependency analysis in abstractFloats (#24551)

In #24551, we abstracted a string literal binding over a type variable,
triggering a CoreLint error when that binding floated to top-level.

The solution implemented in this patch fixes this by re-doing dependency
analysis on a simplified recursive let binding that is about to be type
abstracted, in order to find the minimal set of type variables to abstract over.
See wrinkle (AB5) of Note [Floating and type abstraction] for more details.

Fixes #24551

- - - - -
8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00
Improve toInteger @Word32 on 64-bit platforms

On 64-bit platforms, every Word32 fits in an Int, so we can
convert to Int# without having to perform the overflow check
integerFromWord# uses internally.

- - - - -
0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00
Fix for #24552 (see testcase T24552)

Fixes for a bug in desugaring pattern synonyms matches, introduced
while working on  on expanding `do`-blocks in #18324

The `matchWrapper` unecessarily (and incorrectly) filtered out the
default wild patterns in a match. Now the wild pattern alternative is
simply ignored by the pm check as its origin is `Generated`.
The current code now matches the expected semantics according to the language spec.

- - - - -
b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00
Print more info about kinds in error messages

This fixes #24553, where GHC unhelpfully said

  error: [GHC-83865]
    • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’

See Note [Showing invisible bits of types in error messages]

- - - - -
8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00
docs: remove the don't use float hint

This hint is outdated, ``Complex Float`` are now specialised,
and the heap space suggestion needs more nuance so it should
be explained in the unboxed/storable array documentation.

- - - - -
5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00
NCG: Fix a bug in jump shortcutting.

When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.

We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.

Fixes #24507

- - - - -
8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00
docs: Drop old release notes, add for 9.12.1

- - - - -
7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00
rts: fix clang compilation on aarch64

This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h
which causes "error: address argument to atomic operation must be a
pointer to _Atomic type" when compiling with clang on aarch64.

- - - - -
237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00
Lexer: fix imports for Alex 3.5.1 (#24583)

- - - - -
810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00
libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6

This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which
includes numerous upstream libffi fixes, especially
https://github.com/libffi/libffi/issues/760.

- - - - -
d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00
EPA: do not duplicate comments in signature RHS

- - - - -
32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00
configure: Use LDFLAGS when trying linkers

A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we
will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to
check for a working linker. If either of these fail, we try the next in
line.

However, we were not considering the `$LDFLAGS` when checking if these
linkers worked. So we would pick a linker that does not support the
current $LDFLAGS and fail further down the line when we used that linker
with those flags.

Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not
supported by `ld.gold` but that was being picked still.

- - - - -
bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00
bindist: Clean xattrs of bin and lib at configure time

For issue #21506, we started cleaning the extended attributes of
binaries and libraries from the bindist *after* they were installed to
workaround notarisation (#17418), as part of `make install`.

However, the `ghc-toolchain` binary that is now shipped with the bindist
must be run at `./configure` time. Since we only cleaned the xattributes
of the binaries and libs after they were installed, in some situations
users would be unable to run `ghc-toolchain` from the bindist, failing
at configure time (#24554).

In this commit we move the xattr cleaning logic to the configure script.

Fixes #24554

- - - - -
cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00
Revert "NCG: Fix a bug in jump shortcutting."

This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66.

Fixes #24586

- - - - -
13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00
JS: `h$rts_isProfiled` is removed from `profiling` and left its version at
`rts/js/config.js`

- - - - -
0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00
EPA: Do not extend declaration range for trailine zero len semi

The lexer inserts virtual semicolons having zero width.
Do not use them to extend the list span of items in a list.

- - - - -
cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00
EPA: Fix FamDecl range

The span was incorrect if opt_datafam_kind_sig was empty

- - - - -
f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00
Fix type of _get_osfhandle foreign import

Fixes #24601.

- - - - -
00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00
EPA: Extend StringLiteral range to include trailing commas

This goes slightly against the exact printing philosophy where
trailing decorations should be in an annotation, but the
practicalities of adding it to the WarningTxt environment, and the
problems caused by deviating do not make a more principles approach
worthwhile.

- - - - -
efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00
clarify Note [Preproccesing invocations]

- - - - -
c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00
rts: Fix TSAN_ENABLED CPP guard

This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`,
lest we suffer warnings.

- - - - -
e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00
rts: fix errors when compiling with TSAN

This commit fixes rts compilation errors when compiling with TSAN:

- xxx_FENCE macros are redefined and trigger CPP warnings.
- Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which
  Cmm.h doesn't include by default.

- - - - -
a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00
rts: fix clang-specific errors when compiling with TSAN

This commit fixes clang-specific rts compilation errors when compiling
with TSAN:

- clang doesn't have -Wtsan flag
- Fix prototype of ghc_tsan_* helper functions
- __tsan_atomic_* functions aren't clang built-ins and
  sanitizer/tsan_interface_atomic.h needs to be included
- On macOS, TSAN runtime library is
  libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread
  as a link-time flag will take care of linking the TSAN runtime
  library anyway so remove tsan as an rts extra library

- - - - -
865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00
compiler: fix github link to __tsan_memory_order in a comment

- - - - -
07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00
ci: improve TSAN CI jobs

- Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm
  instrumentation as well.
- Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc
  that @bgamari confirms he's using in #GHC:matrix.org. Ideally we
  should be using latest clang release for latest improvements in
  sanitizers, though that's left as future work.
- Mark TSAN jobs as manual+allow_failure in validate pipelines. The
  purpose is to demonstrate that we have indeed at least fixed
  building of TSAN mode in CI without blocking the patch to land, and
  once merged other people can begin playing with TSAN using their own
  dev setups and feature branches.

- - - - -
a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00
Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639)

This patch implements refactoring which is a prerequisite to
updating kind checking of type patterns. This is a huge simplification
of the main worker that checks kind of HsType.

It also fixes the issues caused by previous code duplication, e.g.
that we didn't add module finalizers from splices in inference mode.

- - - - -
817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00
th: Hide the Language.Haskell.TH.Lib.Internal module from haddock

Fixes #24562

- - - - -
b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00
JS: reenable h$appendToHsString optimization (#24495)

The optimization introducing h$appendToHsString wasn't kicking in
anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30).
This patch reenables the optimization by matching on case-expression, as
done in Cmm for unpackCString# standard thunks.

The test is also T24495 added in the next commits (two commits for ease
of backporting to 9.8).

- - - - -
527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00
JS: fix h$appendToHsString implementation (#24495)

h$appendToHsString needs to wrap its argument in an updatable thunk
to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is
passed, it is stored as-is in a CONS cell, making the resulting list
impossible to deepseq (forcing the thunk doesn't update the contents of
the CONS cell)!

The added test checks that the optimization kicks in and that
h$appendToHsString works as intended.

Fix #24495

- - - - -
faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00
Deal with duplicate tyvars in type declarations

GHC was outright crashing before this fix: #24604

- - - - -
e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00
Try using MCoercion in exprIsConApp_maybe

This is just a simple refactor that makes exprIsConApp_maybe
a little bit more direct, simple, and efficient.

Metrics: compile_time/bytes allocated
    geo. mean                                          -0.1%
    minimum                                            -2.0%
    maximum                                            -0.0%

Not a big gain, but worthwhile given that the code is, if anything,
easier to grok.

- - - - -
15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Initial ./configure support for selecting I/O managers

In this patch we just define new CPP vars, but don't yet use them
or replace the existing approach. That will follow.

The intention here is that every I/O manager can be enabled/disabled at
GHC build time (subject to some constraints). More than one I/O manager
can be enabled to be built. At least one I/O manager supporting the
non-threaded RTS must be enabled as well as at least one supporting the
non-threaded RTS. The I/O managers enabled here will become the choices
available at runtime at RTS startup (in later patches). The choice can
be made with RTS flags. There are separate sets of choices for the
threaded and non-threaded RTS ways, because most I/O managers are
specific to these ways. Furthermore we must establish a default I/O
manager for the threaded and non-threaded RTS.

Most I/O managers are platform-specific so there are checks to ensure
each one can be enabled on the platform. Such checks are also where (in
future) any system dependencies (e.g. libraries) can be checked.

The output is a set of CPP flags (in the mk/config.h file), with one
flag per named I/O manager:
* IOMGR_BUILD_<name>                : which ones should be built (some)
* IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one)
* IOMGR_DEFAULT_THREADED_<name>     : which one is default (exactly one)

and a set of derived flags in IOManager.h

* IOMGR_ENABLED_<name>              : enabled for the current RTS way

Note that IOMGR_BUILD_<name> just says that an I/O manager will be
built for _some_ RTS way (i.e. threaded or non-threaded). The derived
flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is
enabled in the "current" RTS way. These are the ones that can be used
for conditional compilation of the I/O manager code.

Co-authored-by: Pi Delport <pi at well-typed.com>

- - - - -
85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00
Change the handling of the RTS flag --io-manager=

Now instead of it being just used on Windows to select between the WinIO
vs the MIO or Win32-legacy I/O managers, it is now used on all platforms
for selecting the I/O manager to use.

Right now it remains the case that there is only an actual choice on
Windows, but that will change later.

Document the --io-manager flag in the user guide.

This change is also reflected in the RTS flags types in the base
library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a
message to import it from GHC.IO.Subsystem.

The way the 'IoSubSystem' is detected also changes. Instead of looking
at the RTS flag, there is now a C bool global var in the RTS which gets
set on startup when the I/O manager is selected. This bool var says
whether the selected I/O manager classifies as "native" on Windows,
which in practice means the WinIO I/O manager has been selected.

Similarly, the is_io_mng_native_p RTS helper function is re-implemented
in terms of the selected I/O manager, rather than based on the RTS
flags.

We do however remove the ./configure --native-io-manager flag because
we're bringing the WinIO/MIO/Win32-legacy choice under the new general
scheme for selecting I/O managers, and that new scheme involves no
./configure time user choices, just runtime RTS flag choices.

- - - - -
1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00
Convert {init,stop,exit}IOManager to switch style

Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS,
we use a style where we switch on the I/O manager impl, with cases for
each I/O manager impl.

- - - - -
a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Split up the CapIOManager content by I/O manager

Using the new IOMGR_ENABLED_<name> CPP defines.

- - - - -
1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00
Convert initIOManagerAfterFork and wakeupIOManager to switch style

- - - - -
c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move most of waitRead#/Write# from cmm to C

Moves it into the IOManager.c where we can follow the new pattern of
switching on the selected I/O manager.

- - - - -
457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move most of the delay# impl from cmm to C

Moves it into the IOManager.c where we can follow the new pattern of
switching on the selected I/O manager.

Uses a new IOManager API: syncDelay, following the naming convention of
sync* for thread-synchronous I/O & timer/delay operations.

As part of porting from cmm to C, we maintain the rule that the
why_blocked gets accessed using load acquire and store release atomic
memory operations. There was one exception to this rule: in the delay#
primop cmm code on posix (not win32), the why_blocked was being updated
using a store relaxed, not a store release. I've no idea why. In this
convesion I'm playing it safe here and using store release consistently.

- - - - -
e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00
insertIntoSleepingQueue is no longer public

No longer defined in IOManager.h, just a private function in
IOManager.c. Since it is no longer called from cmm code, just from
syncDelay. It ought to get moved further into the select() I/O manager
impl, rather than living in IOManager.c.

On the other hand appendToIOBlockedQueue is still called from cmm code
in the win32-legacy I/O manager primops async{Read,Write}#, and it is
also used by the select() I/O manager. Update the CPP and comments to
reflect this.

- - - - -
60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move anyPendingTimeoutsOrIO impl from .h to .c

The implementation is eventually going to need to use more private
things, which will drag in unwanted includes into IOManager.h, so it's
better to move the impl out of the header file and into the .c file, at
the slight cost of it no longer being inline.

At the same time, change to the "switch (iomgr_type)" style.

- - - - -
f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Take a simpler approach to gcc warnings in IOManager.c

We have lots of functions with conditional implementations for
different I/O managers. Some functions, for some I/O managers,
naturally have implementations that do nothing or barf. When only one
such I/O manager is enabled then the whole function implementation will
have an implementation that does nothing or barfs. This then results in
warnings from gcc that parameters are unused, or that the function
should be marked with attribute noreturn (since barf does not return).
The USED_IF_THREADS trick for fine-grained warning supression is fine
for just two cases, but an equivalent here would need
USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial
blowup. So we take a coarse grained approach and simply disable these
two warnings for the whole file.

So we use a GCC pragma, with its handy push/pop support:

 #pragma GCC diagnostic push
 #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn"
 #pragma GCC diagnostic ignored "-Wunused-parameter"

...

 #pragma GCC diagnostic pop

- - - - -
b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add a new trace class for the iomanager

It makes sense now for it to be separate from the scheduler class of
tracers.

Enabled with +RTS -Do. Document the -Do debug flag in the user guide.

- - - - -
f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Have the throwTo impl go via (new) IOManager APIs

rather than directly operating on the IO manager's data structures.

Specifically, when thowing an async exception to a thread that is
blocked waiting for I/O or waiting for a timer, then we want to cancel
that I/O waiting or cancel the timer. Currently this is done directly in
removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs
both for modularity but also to let us support multiple I/O managers.

So add sync{IO,Delay}Cancel, which is the cancellation for the
corresponding sync{IO,Delay}. The implementations of these use the usual
"switch (iomgr_type)" style.

- - - - -
4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00
Move awaitEvent into a proper IOManager API

and have the scheduler use it.

Previously the scheduler calls awaitEvent directly, and awaitEvent is
implemented directly in the RTS I/O managers (select, win32). This
relies on the old scheme where there's a single active I/O manager for
each platform and RTS way.

We want to move that to go via an API in IOManager.{h,c} which can then
call out to the active I/O manager.

Also take the opportunity to split awaitEvent into two. The existing
awaitEvent has a bool wait parameter, to say if the call should be
blocking or non-blocking. We split this into two separate functions:
pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them
for a few reasons: they have different post-conditions (specifically the
await version is supposed to guarantee that there are threads runnable
when it completes). Secondly, it is also anticipated that in future I/O
managers the implementations of the two cases will be simpler if they
are separated.

- - - - -
5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00
Rename awaitEvent in select and win32 I/O managers

These are now just called from IOManager.c and are the per-I/O manager
backend impls (whereas previously awaitEvent was the entry point).

Follow the new naming convention in the IOManager.{h,c} of
awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix:
so awaitCompletedTimeoutsOrIO{Select,Win32}.

- - - - -
d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Tidy up a couple things in Select.{h,c}

Use the standard #include {Begin,End}Private.h style rather than
RTS_PRIVATE on individual decls.

And conditionally build the code for the select I/O manager based on
the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS.

- - - - -
4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add an IOManager API for scavenging TSO blocked_info

When the GC scavenges a TSO it needs to scavenge the tso->blocked_info
but the blocked_info is a big union and what lives there depends on the
two->why_blocked, which for I/O-related reasons is something that in
principle is the responsibility of the I/O manager and not the GC. So
the right thing to do is for the GC to ask the I/O manager to sscavenge
the blocked_info if it encounters any I/O-related why_blocked reasons.

So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style.

Now as it happens, right now, there is no special scavenging to do, so
the implementation of scavengeTSOIOManager is a fancy no-op. That's
because the select I/O manager uses only the fd and target members,
which are not GC pointers, and the win32-legacy I/O manager _ought_ to
be using GC-managed heap objects for the StgAsyncIOResult but it is
actually usingthe C heap, so again no GC pointers. If the win32-legacy
were doing this more sensibly, then scavengeTSOIOManager would be the
right place to do the GC magic.

Future I/O managers will need GC heap objects in the tso->blocked_info
and will make use of this functionality.

- - - - -
94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add I/O manager API notifyIOManagerCapabilitiesChanged

Used in setNumCapabilities.

It only does anything for MIO on Posix.

Previously it always invoked Haskell code, but that code only did
anything on non-Windows (and non-JS), and only threaded. That currently
effectively means the MIO I/O manager on Posix.

So now it only invokes it for the MIO Posix case.

- - - - -
3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Select an I/O manager early in RTS startup

We need to select the I/O manager to use during startup before the
per-cap I/O manager initialisation.

- - - - -
aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Make struct CapIOManager be fully opaque

Provide an opaque (forward) definition in Capability.h (since the cap
contains a *CapIOManager) and then only provide a full definition in
a new file IOManagerInternals.h. This new file is only supposed to be
included by the IOManager implementation, not by its users. So that
means IOManager.c and individual I/O manager implementations.

The posix/Signals.c still needs direct access, but that should be
eliminated. Anything that needs direct access either needs to be clearly
part of an I/O manager (e.g. the sleect() one) or go via a proper API.

- - - - -
877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00
The select() I/O manager does have some global initialisation

It's just to make sure an exception CAF is a GC root.

- - - - -
9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00
Add tracing for the main I/O manager actions

Using the new tracer class.

Note: The unconditional definition of showIOManager should be
compatible with the debugTrace change in 7c7d1f6.

Co-authored-by: Pi Delport <pi at well-typed.com>

- - - - -
c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Include the default I/O manager in the +RTS --info output

Document the extra +RTS --info output in the user guide

- - - - -
8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00
waitRead# / waitWrite# do not work for win32-legacy I/O manager

Previously it was unclear that they did not work because the code path
was shared with other I/O managers (in particular select()).

Following the code carefully shows that what actually happens is that
the calling thread would block forever: the thread will be put into the
blocked queue, but no other action is scheduled that will ever result in
it getting unblocked.

It's better to just fail loudly in case anyone accidentally calls it,
also it's less confusing code.

- - - - -
83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Conditionally ignore some GCC warnings

Some GCC versions don't know about some warnings, and they complain
that we're ignoring unknown warnings. So we try to ignore the warning
based on the GCC version.

- - - - -
1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Accept changes to base-exports

All the changes are in fact not changes at all.

Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and
exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data
type is defined in GHC.IO.SubSystem and still exported from both
modules.

Therefore, the same exports and same instances are still available from
both modules. But the base-exports records only the defining module, and
so it looks like a change when it is fully compatible.

Related: we do add a deprecation to the export of the type via
GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem.

Also the sort order for some unrelated Show instances changed. No idea
why.

The same changes apply in the other versions, with a few more changes
due to sort order weirdness.

- - - - -
8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00
Accept metric decrease in T12227

I can't think of any good reason that anything in this MR should have
changed the number of allocations, up or down.

(Yes this is an empty commit.)

Metric Decrease:
    T12227

- - - - -
e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Several improvements to the handling of coercions

* Make `mkSymCo` and `mkInstCo` smarter
  Fixes #23642

* Fix return role of `SelCo` in the coercion optimiser.
  Fixes #23617

* Make the coercion optimiser `opt_trans_rule` work better for newtypes
  Fixes #23619

- - - - -
1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
FloatOut: improve floating for join point

See the new Note [Floating join point bindings].

* Completely get rid of the complicated join_ceiling nonsense, which
  I have never understood.

* Do not float join points at all, except perhaps to top level.

* Some refactoring around wantToFloat, to treat Rec and NonRec more
  uniformly

- - - - -
9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Improve eta-expansion through call stacks

See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity

This is a one-line change, that fixes an inconsistency
-               || isCallStackPredTy ty
+               || isCallStackPredTy ty || isCallStackTy ty

- - - - -
95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Spelling, layout, pretty-printing only

- - - - -
bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Improve exprIsConApp_maybe a little

Eliminate a redundant case at birth.  This sometimes reduces
Simplifier iterations.

See Note [Case elim in exprIsConApp_maybe].

- - - - -
609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo

When exploring compile-time regressions after meddling with the Simplifier, I
discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately
balanced.  It's a small, heavily used, overloaded function and it's important
that it inlines. By a fluke it was before, but at various times in my journey it
stopped doing so.  So I just added an INLINE pragma to it; no sense in depending
on a delicately-balanced fluke.

- - - - -
ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Slight improvement in WorkWrap

Ensure that WorkWrap preserves lambda binders, in case of join points.  Sadly I
have forgotten why I made this change (it was while I was doing a lot of
meddling in the Simplifier, but
  * it does no harm,
  * it is slightly more efficient, and
  * presumably it made something better!

Anyway I have kept it in a separate commit.

- - - - -
e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Use named record fields for the CastIt { ... } data constructor

This is a pure refactor

- - - - -
b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Remove a long-commented-out line

Pure refactoring

- - - - -
e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Simplifier improvements

This MR started as: allow the simplifer to do more in one pass,
arising from places I could see the simplifier taking two iterations
where one would do.  But it turned into a larger project, because
these changes unexpectedly made inlining blow up, especially join
points in deeply-nested cases.

The main changes are below.  There are also many new or rewritten Notes.

Avoiding simplifying repeatedly
~~~~~~~~~~~~~~~
See Note [Avoiding simplifying repeatedly]

* The SimplEnv now has a seInlineDepth field, which says how deep
  in unfoldings we are.  See Note [Inline depth] in Simplify.Env.
  Currently used only for the next point: avoiding repeatedly
  simplifying coercions.

* Avoid repeatedly simplifying coercions.
  see Note [Avoid re-simplifying coercions] in Simplify.Iteration
  As you'll see from the Note, this makes use of the seInlineDepth.

* Allow Simplify.Iteration.simplAuxBind to inline used-once things.
  This is another part of Note [Post-inline for single-use things], and
  is really good for reducing simplifier iterations in situations like
      case K e of { K x -> blah }
  wher x is used once in blah.

* Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case
  elimination.  Note [Case elim in exprIsConApp_maybe]

* Improve the case-merge transformation:
  - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts`
    and friends.  See Note [Merge Nested Cases] in GHC.Core.Utils.
  - Add a new case for `tagToEnum#`; see wrinkle (MC3).
  - Add a new case to look through join points: see wrinkle (MC4)

postInlineUnconditionally
~~~~~~~~~~~~~~~~~~~~~~~~~
* Allow Simplify.Utils.postInlineUnconditionally to inline variables
  that are used exactly once. See Note [Post-inline for single-use things].

* Do not postInlineUnconditionally join point, ever.
  Doing so does not reduce allocation, which is the main point,
  and with join points that are used a lot it can bloat code.
  See point (1) of Note [Duplicating join points] in
  GHC.Core.Opt.Simplify.Iteration.

* Do not postInlineUnconditionally a strict (demanded) binding.
  It will not allocate a thunk (it'll turn into a case instead)
  so again the main point of inlining it doesn't hold.  Better
  to check per-call-site.

* Improve occurrence analyis for bottoming function calls, to help
  postInlineUnconditionally.  See Note [Bottoming function calls]
  in GHC.Core.Opt.OccurAnal

Inlining generally
~~~~~~~~~~~~~~~~~~
* In GHC.Core.Opt.Simplify.Utils.interestingCallContext,
  use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case.
  See Note [Seq is boring]  Also, wrinkle (SB1), inline in that
  `seq` context only for INLINE functions (UnfWhen guidance).

* In GHC.Core.Opt.Simplify.Utils.interestingArg,
  - return ValueArg for OtherCon [c1,c2, ...], but
  - return NonTrivArg for OtherCon []
  This makes a function a little less likely to inline if all we
  know is that the argument is evaluated, but nothing else.

* isConLikeUnfolding is no longer true for OtherCon {}.
  This propagates to exprIsConLike.  Con-like-ness has /positive/
  information.

Join points
~~~~~~~~~~~
* Be very careful about inlining join points.
  See these two long Notes
    Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration
    Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline

* When making join points, don't do so if the join point is so small
  it will immediately be inlined; check uncondInlineJoin.

* In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining
  heuristics for join points. In general we /do not/ want to inline
  join points /even if they are small/.  See Note [Duplicating join points]
  GHC.Core.Opt.Simplify.Iteration.

  But sometimes we do: see Note [Inlining join points] in
  GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function.

* Do not add an unfolding to a join point at birth.  This is a tricky one
  and has a long Note [Do not add unfoldings to join points at birth]
  It shows up in two places
  - In `mkDupableAlt` do not add an inlining
  - (trickier) In `simplLetUnfolding` don't add an unfolding for a
    fresh join point
  I am not fully satisifed with this, but it works and is well documented.

* In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise
  having a non-inlined join point.

Performance changes
~~~~~~~~~~~~~~~~~~~
* Binary sizes fall by around 2.6%, according to nofib.

* Compile times improve slightly. Here are the figures over 1%.

  I investiate the biggest differnce in T18304. It's a very small module, just
  a few hundred nodes. The large percentage difffence is due to a single
  function that didn't quite inline before, and does now, making code size a
  bit bigger.  I decided gains outweighed the losses.

    Metrics: compile_time/bytes allocated (changes over +/- 1%)
    ------------------------------------------------
           CoOpt_Singletons(normal)   -9.2% GOOD
                LargeRecord(normal)  -23.5% GOOD
MultiComponentModulesRecomp(normal)   +1.2%
MultiLayerModulesTH_OneShot(normal)   +4.1%  BAD
                  PmSeriesS(normal)   -3.8%
                  PmSeriesV(normal)   -1.5%
                     T11195(normal)   -1.3%
                     T12227(normal)  -20.4% GOOD
                     T12545(normal)   -3.2%
                     T12707(normal)   -2.1% GOOD
                     T13253(normal)   -1.2%
                 T13253-spj(normal)   +8.1%  BAD
                     T13386(normal)   -3.1% GOOD
                     T14766(normal)   -2.6% GOOD
                     T15164(normal)   -1.4%
                     T15304(normal)   +1.2%
                     T15630(normal)   -8.2%
                    T15630a(normal)          NEW
                     T15703(normal)  -14.7% GOOD
                     T16577(normal)   -2.3% GOOD
                     T17516(normal)  -39.7% GOOD
                     T18140(normal)   +1.2%
                     T18223(normal)  -17.1% GOOD
                     T18282(normal)   -5.0% GOOD
                     T18304(normal)  +10.8%  BAD
                     T18923(normal)   -2.9% GOOD
                      T1969(normal)   +1.0%
                     T19695(normal)   -1.5%
                     T20049(normal)  -12.7% GOOD
                    T21839c(normal)   -4.1% GOOD
                      T3064(normal)   -1.5%
                      T3294(normal)   +1.2%  BAD
                      T4801(normal)   +1.2%
                      T5030(normal)  -15.2% GOOD
                   T5321Fun(normal)   -2.2% GOOD
                      T6048(optasm)  -16.8% GOOD
                       T783(normal)   -1.2%
                      T8095(normal)   -6.0% GOOD
                      T9630(normal)   -4.7% GOOD
                      T9961(normal)   +1.9%  BAD
                      WWRec(normal)   -1.4%
        info_table_map_perf(normal)   -1.3%
                 parsing001(normal)   +1.5%

                          geo. mean   -2.0%
                          minimum    -39.7%
                          maximum    +10.8%

* Runtimes generally improve. In the testsuite perf/should_run gives:
   Metrics: runtime/bytes allocated
   ------------------------------------------
             Conversions(normal)   -0.3%
                 T13536a(optasm)  -41.7% GOOD
                   T4830(normal)   -0.1%
           haddock.Cabal(normal)   -0.1%
            haddock.base(normal)   -0.1%
        haddock.compiler(normal)   -0.1%

                       geo. mean   -0.8%
                       minimum    -41.7%
                       maximum     +0.0%

* For runtime, nofib is a better test.  The news is mostly good.
  Here are the number more than +/- 0.1%:

    # bytes allocated
    ==========================++==========
       imaginary/digits-of-e1 ||  -14.40%
       imaginary/digits-of-e2 ||   -4.41%
          imaginary/paraffins ||   -0.17%
               imaginary/rfib ||   -0.15%
       imaginary/wheel-sieve2 ||   -0.10%
                real/compress ||   -0.47%
                   real/fluid ||   -0.10%
                  real/fulsom ||   +0.14%
                  real/gamteb ||   -1.47%
                      real/gg ||   -0.20%
                   real/infer ||   +0.24%
                     real/pic ||   -0.23%
                  real/prolog ||   -0.36%
                     real/scs ||   -0.46%
                 real/smallpt ||   +4.03%
        shootout/k-nucleotide ||  -20.23%
              shootout/n-body ||   -0.42%
       shootout/spectral-norm ||   -0.13%
              spectral/boyer2 ||   -3.80%
         spectral/constraints ||   -0.27%
          spectral/hartel/ida ||   -0.82%
                spectral/mate ||  -20.34%
                spectral/para ||   +0.46%
             spectral/rewrite ||   +1.30%
              spectral/sphere ||   -0.14%
    ==========================++==========
                    geom mean ||   -0.59%

    real/smallpt has a huge nest of local definitions, and I
    could not pin down a reason for a regression.  But there are
    three big wins!

Metric Decrease:
    CoOpt_Singletons
    LargeRecord
    T12227
    T12707
    T13386
    T13536a
    T14766
    T15703
    T16577
    T17516
    T18223
    T18282
    T18923
    T21839c
    T20049
    T5321Fun
    T5030
    T6048
    T8095
    T9630
    T783
Metric Increase:
    MultiLayerModulesTH_OneShot
    T13253-spj
    T18304
    T18698a
    T9961
    T3294

- - - - -
27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Testsuite message changes from simplifier improvements

- - - - -
271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00
Account for bottoming functions in OccurAnal

This fixes #24582, a small but long-standing bug

- - - - -
0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00
testsuite: Introduce template-haskell-exports test

- - - - -
0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00
Update correct counter in bumpTickyAllocd

- - - - -
5f085d3a by Fendor at 2024-04-04T14:47:33-04:00
Replace `SizedSeq` with `FlatBag` for flattened structure

LinkedLists are notoriously memory ineffiecient when all we do is
traversing a structure.
As 'UnlinkedBCO' has been identified as a data structure that impacts
the overall memory usage of GHCi sessions, we avoid linked lists and
prefer flattened structure for storing.

We introduce a new memory efficient representation of sequential
elements that has special support for the cases:

* Empty
* Singleton
* Tuple Elements

This improves sharing in the 'Empty' case and avoids the overhead of
'Array' until its constant overhead is justified.

- - - - -
82cfe10c by Fendor at 2024-04-04T14:47:33-04:00
Compact FlatBag array representation

`Array` contains three additional `Word`'s we do not need in `FlatBag`. Move
`FlatBag` to `SmallArray`.

Expand the API of SmallArray by `sizeofSmallArray` and add common
traversal functions, such as `mapSmallArray` and `foldMapSmallArray`.
Additionally, allow users to force the elements of a `SmallArray`
via `rnfSmallArray`.

- - - - -
36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00
Change how invisible patterns represented in  haskell syntax and TH AST (#24557)

Before this patch:
  data ArgPat p
    = InvisPat (LHsType p)
    | VisPat (LPat p)

With this patch:
  data Pat p
    = ...
    | InvisPat (LHsType p)
    ...

And the same transformation in the TH land. The rest of the
changes is just updating code to handle new AST and writing tests
to check if it is possible to create invalid states using TH.

Metric Increase:
    MultiLayerModulesTH_OneShot

- - - - -
28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00
Fix off by one error in seekBinNoExpand and seekBin

- - - - -
9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00
compiler: Allow more types in GHCForeignImportPrim

For many, many years `GHCForeignImportPrim` has suffered from the rather
restrictive limitation of not allowing any non-trivial types in arguments
or results. This limitation was justified by the code generator allegely
barfing in the presence of such types.

However, this restriction appears to originate well before the NCG
rewrite and the new NCG does not appear to have any trouble with such
types (see the added `T24598` test). Lift this restriction.

Fixes #24598.

- - - - -
1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00
EPA: Use EpaLocation not SrcSpan in ForeignDecls

This allows us to update them for makeDeltaAst in ghc-exactprint

- - - - -
19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00
EPA: Use EpaLocation for RecFieldsDotDot

So we can update it to a delta position in makeDeltaAst if needed.

- - - - -
e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00
Remove accidentally committed test.hs

- - - - -
88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00
Avoid UArray when indexing is not required

`UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO`
references two `UArray`'s but never indexes them. They are only needed
to encode the elements into a `ByteArray#`. The three words for
the lower bound, upper bound and number of elements are essentially
unused, thus we replace `UArray` with a wrapper around `ByteArray#`.
This saves us up to three words for each `UnlinkedBCO`.

Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat
the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances.

For example, agda's repl session has around 360_000 UnlinkedBCO's,
so avoiding these three words is already saving us around 8MB residency.

- - - - -
f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00
Never UNPACK `FastMutInt` for counting z-encoded `FastString`s

In `FastStringTable`, we count the number of z-encoded FastStrings
that exist in a GHC session.
We used to UNPACK the counters to not waste memory, but live retainer
analysis showed that we allocate a lot of `FastMutInt`s, retained by
`mkFastZString`.

We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is
forced.
The function `mkFastStringWith` calls `mkZFastString` and boxes the
`FastMutInt`, leading to the following core:

    mkFastStringWith
      = \ mk_fs _  ->
             = case stringTable of
                { FastStringTable _ n_zencs segments# _ ->
                    ...
                         case ((mk_fs (I# ...) (FastMutInt n_zencs))
                            `cast` <Co:2> :: ...)
                            ...

Marking this field as `NOUNPACK` avoids this reboxing, eliminating the
allocation of a fresh `FastMutInt` on every `FastString` allocation.

- - - - -
c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00
Force in_multi to avoid retaining entire hsc_env

- - - - -
fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00
Eliminate name thunk in declaration fingerprinting

Thunk analysis showed that we have about 100_000 thunks (in agda and
`-fwrite-simplified-core`) pointing to the name of the name decl.
Forcing this thunk fixes this issue.

The thunk created here is retained by the thunk created by forkM, it is
better to eagerly force this because the result (a `Name`) is already
retained indirectly via the `IfaceDecl`.

- - - - -
3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00
EPA: Use EpaLocation in WarningTxt

This allows us to use an EpDelta if needed when using makeDeltaAst.

- - - - -
12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00
EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc

This allows us to use a NoCommentsLocation for the possibly trailing
comma location in a StringLiteral.
This in turn allows us to correctly roundtrip via makeDeltaAst.

- - - - -
868c8a78 by Fendor at 2024-04-09T08:51:50-04:00
Prefer packed representation for CompiledByteCode

As there are many 'CompiledByteCode' objects alive during a GHCi
session, representing its element in a more packed manner improves space
behaviour at a minimal cost.

When running GHCi on the agda codebase, we find around 380 live
'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode'
can save quite some pointers.

- - - - -
be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00
EPA: Capture all comments in a ClassDecl

Hopefully the final fix needed for #24533

- - - - -
3d0806fc by Jade at 2024-04-10T05:39:53-04:00
Validate -main-is flag using parseIdentifier

Fixes #24368

- - - - -
dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
rts: free error message before returning

Fixes a memory leak in rts/linker/PEi386.c

- - - - -
e008a19a by Alexis King at 2024-04-10T05:40:29-04:00
linker: Avoid linear search when looking up Haskell symbols via dlsym

See the primary Note [Looking up symbols in the relevant objects] for a
more in-depth explanation.

When dynamically loading a Haskell symbol (typical when running a splice or
GHCi expression), before this commit we would search for the symbol in
all dynamic libraries that were loaded. However, this could be very
inefficient when too many packages are loaded (which can happen if there are
many package dependencies) because the time to lookup the would be
linear in the number of packages loaded.

This commit drastically improves symbol loading performance by
introducing a mapping from units to the handles of corresponding loaded
dlls. These handles are returned by dlopen when we load a dll, and can
then be used to look up in a specific dynamic library.

Looking up a given Name is now much more precise because we can get
lookup its unit in the mapping and lookup the symbol solely in the
handles of the dynamic libraries loaded for that unit.

In one measurement, the wait time before the expression was executed
went from +-38 seconds down to +-2s.

This commit also includes Note [Symbols may not be found in pkgs_loaded],
explaining the fallback to the old behaviour in case no dll can be found
in the unit mapping for a given Name.

Fixes #23415

Co-authored-by: Rodrigo Mesquita (@alt-romes)

- - - - -
dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
rts: Make addDLL a wrapper around loadNativeObj

Rewrite the implementation of `addDLL` as a wrapper around the more
principled `loadNativeObj` rts linker function. The latter should be
preferred while the former is preserved for backwards compatibility.

`loadNativeObj` was previously only available on ELF platforms, so this
commit further refactors the rts linker to transform loadNativeObj_ELF
into loadNativeObj_POSIX, which is available in ELF and MachO platforms.

The refactor made it possible to remove the `dl_mutex` mutex in favour
of always using `linker_mutex` (rather than a combination of both).

Lastly, we implement `loadNativeObj` for Windows too.

- - - - -
12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00
Use symbol cache in internal interpreter too

This commit makes the symbol cache that was used by the external
interpreter available for the internal interpreter too.

This follows from the analysis in #23415 that suggests the internal
interpreter could benefit from this cache too, and that there is no good
reason not to have the cache for it too. It also makes it a bit more
uniform to have the symbol cache range over both the internal and
external interpreter.

This commit also refactors the cache into a function which is used by
both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the
caching logic to `lookupSymbolInDLL` too.

- - - - -
dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00
testsuite: Add test for lookupSymbolInNativeObj

- - - - -
1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00
EPA: Remove unnecessary XRec in CompleteMatchSig

The XRec for [LIdP pass] is not needed for exact printing, remove it.

- - - - -
6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00
users-guide: Clarify language extension documentation

Over the years the users guide's language extension documentation has
gone through quite a few refactorings. In the process some of the
descriptions have been rendered non-sensical. For instance, the
description of `NoImplicitPrelude` actually describes the semantics of
`ImplicitPrelude`.

To fix this we:

 * ensure that all extensions are named in their "positive" sense (e.g.
   `ImplicitPrelude` rather than `NoImplicitPrelude`).
 * rework the documentation to avoid flag-oriented wording
   like "enable" and "disable"
 * ensure that the polarity of the documentation is consistent with
   reality.

Fixes #23895.

- - - - -
a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00
driver: Make `checkHomeUnitsClosed` faster

The implementation of `checkHomeUnitsClosed` was traversing every single path
in the unit dependency graph - this grows exponentially and quickly grows to be
infeasible on larger unit dependency graphs.

Instead we replace this with a faster implementation which follows from the
specificiation of the closure property - there is a closure error if there are
units which are both are both (transitively) depended upon by home units and
(transitively) depend on home units, but are not themselves home units.

To compute the set of units required for closure, we first compute the closure
of the unit dependency graph, then the transpose of this closure, and find all
units that are reachable from the home units in the transpose of the closure.

- - - - -
23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00
RTS: Emit warning when -M < -H

Fixes #24487

- - - - -
d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00
testsuite: Add broken test for CApiFFI with -fprefer-bytecode

See #24634.

- - - - -
a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00
base: Deprecate GHC.Pack

As proposed in #21461.

Closes #21540.

- - - - -
55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00
ghc-internal: Fix mentions of ghc-internal in deprecation warnings

Closes #24609.

- - - - -
b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00
rts: Implement set_initial_registers for AArch64

Fixes #23680.

- - - - -
14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00
ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17

Closes #24646.

- - - - -
35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00
Bump unix submodule to 2.8.5.1

Closes #24640.

- - - - -
a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00
Correct default -funfolding-use-threshold in docs

- - - - -
0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00
FastString is a __Modified__ UTF-8

- - - - -
c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00
rts: Improve tracing message when nursery is resized

It is sometimes more useful to know how much bigger or smaller the
nursery got when it is resized.

In particular I am trying to investigate situations where we end up with
fragmentation due to the nursery (#24577)

- - - - -
5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00
Don't generate wrappers for `type data` constructors with StrictData

Previously, the logic for checking if a data constructor needs a wrapper or not
would take into account whether the constructor's fields have explicit
strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into
account whether `StrictData` was enabled. This meant that something like `type
data T = MkT Int` would incorrectly generate a wrapper for `MkT` if
`StrictData` was enabled, leading to the horrible errors seen in #24620. To fix
this, we disable generating wrappers for `type data` constructors altogether.

Fixes #24620.

Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com>

- - - - -
dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00
Implements MO_S_Mul2 and MO_U_Mul2 using the  UMULH, UMULL and SMULH instructions for AArch64

Also adds a test for MO_S_Mul2

- - - - -
42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00
Make template-haskell a stage1 package

Promoting template-haskell from a stage0 to a stage1 package means that
we can much more easily refactor template-haskell.

We implement this by duplicating the in-tree `template-haskell`.
A new `template-haskell-next` library is autogenerated to mirror `template-haskell`
`stage1:ghc` to depend on the new interface of the library including the
`Binary` instances without adding an explicit dependency on `template-haskell`.

This is controlled by the `bootstrap-th` cabal flag

When building `template-haskell` modules as part of this vendoring we do
not have access to quote syntax, so we cannot use variable quote
notation (`'Just`). So we either replace these with hand-written `Name`s
or hide the code behind CPP.

We can remove the `th_hack` from hadrian, which was required when
building stage0 packages using the in-tree `template-haskell` library.

For more details see Note [Bootstrapping Template Haskell].

Resolves #23536

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>
Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00
Bump parsec submodule to 3.1.17.0

- - - - -
9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00
Clone CoVars in CorePrep

This MR addresses #24463.  It's all explained in the new

   Note [Cloning CoVars and TyVars]

- - - - -
0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00
NCG: Fix a bug where we errounously removed a required jump instruction.

Add a new method to the Instruction class to check if we can eliminate a
jump in favour of fallthrough control flow.

Fixes #24507

- - - - -
9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00
Fix documentation preview from doc-tarball job

- Include all the .html files and assets in the job artefacts
- Include all the .pdf files in the job artefacts
- Mark the artefact as an "exposed" artefact meaning it turns up in the
  UI.

Resolves #24651

- - - - -
3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00
rts: Ignore EINTR while polling in timerfd itimer implementation

While the RTS does attempt to mask signals, it may be that a foreign
library unmasks them. This previously caused benign warnings which we
now ignore.

See #24610.

- - - - -
9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00
EPA: Add additional comments field to AnnsModule

This is used in exact printing to store comments coming after the
`where` keyword but before any comments allocated to imports or decls.

It is used in ghc-exactprint, see
https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7

- - - - -
e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00
Remove unrunnable FreeBSD CI jobs

FreeBSD runner supply is inelastic. Currently there is only one, and
it's unavailable because of a hardware issue.

- - - - -
914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00
rel-eng: Fix mktemp usage in recompress-all

We need a temporary directory, not a file.

- - - - -
f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00
Fix ghc API link in docs/index.html

This was missing part of the unit ID meaning it would 404.

Resolves #24674

- - - - -
d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00
template-haskell: Declare TH.Lib.Internal as not-home

Rather than `hide`.

Closes #24659.

- - - - -
5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00
testsuite: Rename isCross() predicate to needsTargetWrapper()

isCross() was a misnamed because it assumed that all cross targets would
provide a target wrapper, but the two most common cross targets
(javascript, wasm) don't need a target wrapper.

Therefore we rename this predicate to `needsTargetWrapper()` so
situations in the testsuite where we can check whether running
executables requires a target wrapper or not.

- - - - -
55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00
Do not float HNFs out of lambdas

This MR adjusts SetLevels so that it is less eager to float a
HNF (lambda or constructor application) out of a lambda, unless
it gets to top level.

Data suggests that this change is a small net win:
 * nofib bytes-allocated falls by -0.09% (but a couple go up)
 * perf/should_compile bytes-allocated falls by -0.5%
 * perf/should_run bytes-allocated falls by -0.1%
See !12410 for more detail.

When fiddling elsewhere, I also found that this patch had a huge
positive effect on the (very delicate) test
  perf/should_run/T21839r
But that improvement doesn't show up in this MR by itself.

Metric Decrease:
    MultiLayerModulesRecomp
    T15703
    parsing001

- - - - -
f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00
EPA: Fix comments in mkListSyntaxTy0

Also extend the test to confirm.

Addresses #24669, 1 of 4

- - - - -
b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00
JS: set image `x86_64-linux-deb11-emsdk-closure` for build

- - - - -
c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00
EPA: Provide correct span for PatBind

And remove unused parameter in checkPatBind

Contributes to #24669

- - - - -
bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00
Update quantification order following GHC haskell/haddock#23764

- - - - -
2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00
hypsrc-test: Fix output of PositionPragmas.html

- - - - -
26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00
EPA: Fix span for PatBuilderAppType

Include the location of the prefix @ in the span for InVisPat.

Also removes unnecessary annotations from HsTP.

Contributes to #24669

- - - - -
dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00
testsuite: Give the pre_cmd for mhu-perf more time

- - - - -
d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00
Fix quantification order for a `op` b and a %m -> b

Fixes #23764

Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst

Updates haddock submodule.

- - - - -
385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00
Make `seq#` a magic Id and inline it in CorePrep (#24124)

We can save much code and explanation in Tag Inference and StgToCmm by making
`seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in
CorePrep. See the updated `Note [seq# magic]`.
I also implemented a new `Note [Flatten case-bind]` to get better code for
otherwise nested case scrutinees.

I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to
resolve the clash between `type CpeApp = CoreExpr` and the data constructor of
`ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`.

Fixes #24252 and #24124.

- - - - -
275e41a9 by Jade at 2024-04-20T11:10:40-04:00
Put the newline after errors instead of before them

This mainly has consequences for GHCi but also slightly alters how the
output of GHC on the commandline looks.

Fixes: #22499

- - - - -
dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00
Remove unecessary stage0 packages

Historically quite a few packages had to be stage0 as they depended on
`template-haskell` and that was stage0. In #23536 we made it so that was
no longer the case. This allows us to remove a bunch of packages from
this list.

A few still remain. A new version of `Win32` is required by
`semaphore-compat`. Including `Win32` in the stage0 set requires also
including `filepath` because otherwise Hadrian's dependency logic gets
confused. Once our boot compiler has a newer version of `Win32` all of
these will be able to be dropped.

Resolves #24652

- - - - -
2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00
EPA: Avoid duplicated comments in splice decls

Contributes to #24669

- - - - -
c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: fix typos and namings (fixes #24602)

You may noted that I've also changed term of

```
, global "h$vt_double" ||= toJExpr IntV
```

See "IntV"

and

```
  WaitReadOp  -> \[] [fd] -> pure $ PRPrimCall $ returnS (app
"h$waidRead" [fd])
```

See "h$waidRead"

- - - - -
3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: trivial checks for variable presence (fixes #24602)

- - - - -
777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped
in a closure to prevent conflict with emscripten (fixes #24602)

Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues.
At first glance we should try UMD (See https://github.com/umdjs/umd)

- - - - -
a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal
code copied from GHCJS (fixes #24602)

I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607).
Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};`

- - - - -
ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00
JS: heap and stack overflows reporting defined as js hard failure (fixes #24602)

These errors were treated as a hard failure for browser application. The fix is trivial: just throw error.

- - - - -
5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00
JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602)

These errors were fixed just by introducing stubbed functions with throw for further implementation.

- - - - -
a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Add externs to linker (fixes #24602)

After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following:

1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8).
2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle.
3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`.
4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?`

- - - - -
e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: added both tests: for size and for correctness (fixes #24602)

By some reason MacOS builds add to stderr messages like:

    Ignoring unexpected archive entry:
    __.SYMDEF
    ...

However I left stderr to `/dev/null` for compatibility with linux CI builds.

- - - - -
909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments

- - - - -
83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00
JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602)

Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators.
But now there are following compiler options: `-C` and `-CC`.
You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC).
It seems that `-CC` works better for javascript jsdoc than `-traditional`.
At least it leaves `/* ... */` comments w/o changes.

- - - - -
e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00
fix link in CODEOWNERS

It seems that our local Gitlab no longer has documentation for the
`CODEOWNERS` file, but the master documentation still does. Use
that instead.

- - - - -
a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00
Adapt to UserData split

- - - - -
1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00
Adapt to BinHandle split

- - - - -
593f4e04 by Fendor at 2024-04-23T10:19:14-04:00
Add performance regression test for '-fwrite-simplified-core'

- - - - -
1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00
Typecheck corebindings lazily during bytecode generation

This delays typechecking the corebindings until the bytecode generation
happens.

We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`.
In general, we shouldn't retain values of the hydrated `Type`, as not evaluating
the bytecode object keeps it alive.

It is better if we retain the unhydrated `IfaceType`.

See Note [Hydrating Modules]

- - - - -
e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00
EPA: Keep comments in a CaseAlt match

The comments now live in the surrounding location, not inside the
Match. Make sure we keep them.

Closes #24707

- - - - -
d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00
driver: force merge objects when building dynamic objects

This patch forces the driver to always merge objects when building
dynamic objects even when ar -L is supported. It is an oversight of
!8887: original rationale of that patch is favoring the relatively
cheap ar -L operation over object merging when ar -L is supported,
which makes sense but only if we are building static objects! Omitting
check for whether we are building dynamic objects will result in
broken .so files with undefined reference errors at executable link
time when building GHC with llvm-ar. Fixes #22210.

- - - - -
209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00
Allow non-absolute values for bootstrap GHC variable

Fixes #24682

- - - - -
3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00
Don't depend on registerPackage function in Cabal

More recent versions of Cabal modify the behaviour of libAbiHash which
breaks our usage of registerPackage.

It is simpler to inline the part of registerPackage that we need and
avoid any additional dependency and complication using the higher-level
function introduces.

- - - - -
c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00
ghc-bignum: remove obsolete ln script

This commit removes an obsolete ln script in ghc-bignum/gmp. See
060251c24ad160264ae8553efecbb8bed2f06360 for its original intention,
but it's been obsolete for a long time, especially since the removal
of the make build system. Hence the house cleaning.

- - - - -
6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00
ghc-bignum: update gmp to 6.3.0

This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0.
The tarball format is now xz, and gmpsrc.patch has been patched into
the tarball so hadrian no longer needs to deal with patching logic
when building in-tree GMP.

- - - - -
65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00
hadrian: remove obsolete Patch logic

This commit removes obsolete Patch logic from hadrian, given we no
longer need to patch the gmp tarball when building in-tree GMP.

- - - - -
71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00
autoconf: remove obsolete patch detection

This commit removes obsolete deletection logic of the patch command
from autoconf scripts, given we no longer need to patch anything in
the GHC build process.

- - - - -
daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00
JS: correctly handle RUBBISH literals (#24664)

- - - - -
8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00
Linearise ghc-internal and base build

This is achieved by requesting the final package database for
ghc-internal, which mandates it is fully built as a dependency of
configuring the `base` package. This is at the expense of cross-package
parrallelism between ghc-internal and the base package.

Fixes #24436

- - - - -
94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00
Fix tuple puns renaming (24702)

Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module.

I also fixed some hidden bugs that raised after the change was done.

- - - - -
fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00
Refactor the Binary serialisation interface

The goal is simplifiy adding deduplication tables to `ModIface`
interface serialisation.

We identify two main points of interest that make this difficult:

1. UserData hardcodes what `Binary` instances can have deduplication
   tables. Moreover, it heavily uses partial functions.
2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and
   'FastString', making it difficult to add more deduplication.

Instead of having a single `UserData` record with fields for all the
types that can have deduplication tables, we allow to provide custom
serialisers for any `Typeable`.
These are wrapped in existentials and stored in a `Map` indexed by their
respective `TypeRep`.
The `Binary` instance of the type to deduplicate still needs to
explicitly look up the decoder via `findUserDataReader` and
`findUserDataWriter`, which is no worse than the status-quo.

`Map` was chosen as microbenchmarks indicate it is the fastest for a
small number of keys (< 10).

To generalise the deduplication table serialisation mechanism, we
introduce the types `ReaderTable` and `WriterTable` which provide a
simple interface that is sufficient to implement a general purpose
deduplication mechanism for `writeBinIface` and `readBinIface`.

This allows us to provide a list of deduplication tables for
serialisation that can be extended more easily, for example for
`IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540
for more motivation.

In addition to this refactoring, we split `UserData` into `ReaderUserData`
and `WriterUserData`, to avoid partial functions and reduce overall
memory usage, as we need fewer mutable variables.

Bump haddock submodule to accomodate for `UserData` split.

-------------------------
Metric Increase:
    MultiLayerModulesTH_Make
    MultiLayerModulesRecomp
    T21839c
-------------------------

- - - - -
bac57298 by Fendor at 2024-04-26T18:03:13-04:00
Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle`

A `BinHandle` contains too much information for reading data.
For example, it needs to keep a `FastMutInt` and a `IORef BinData`,
when the non-mutable variants would suffice.

Additionally, this change has the benefit that anyone can immediately
tell whether the `BinHandle` is used for reading or writing.

Bump haddock submodule BinHandle split.

- - - - -
4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00
Fix missing escaping-kind check in tcPatSynSig

Note [Escaping kind in type signatures] explains how we deal
with escaping kinds in type signatures, e.g.
    f :: forall r (a :: TYPE r). a
where the kind of the body is (TYPE r), but `r` is not in
scope outside the forall-type.

I had missed this subtlety in tcPatSynSig, leading to #24686.
This MR fixes it; and a similar bug in tc_top_lhs_type. (The
latter is tested by T24686a.)

- - - - -
981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00
EPA: check-exact: check that the roundtrip reproduces the source

Closes #24670

- - - - -
a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00
Document that setEnv is not thread-safe

- - - - -
1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00
CI: Work around frequent Signal 9 errors

- - - - -
a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00
ghc-internal: add MonadFix instance for (,)

Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC
proposal https://github.com/haskell/core-libraries-committee/issues/238.

Adds a MonadFix instance for tuples, permitting value recursion in the
"native" writer monad and bringing consistency with the existing
instance for transformers's WriterT (and, to a lesser extent, for Solo).

- - - - -
64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00
bindist: Fix xattr cleaning

The original fix (725343aa) was incorrect because it used the shell
bracket syntax which is the quoting syntax in autoconf, making the test
for existence be incorrect and therefore `xattr` was never run.

Fixes #24554

- - - - -
e2094df3 by damhiya at 2024-04-28T23:52:00+09:00
Make read accepts binary integer formats

CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177

- - - - -
c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00
Fix tests for T22229

- - - - -
1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00
EPA: Preserve comments in Match Pats

Closes #24708
Closes #24715
Closes #24734

- - - - -
4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00
LLVM: better unreachable default destination in Switch (#24717)

See added note.

Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com>

- - - - -
a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00
ci: enable wasm jobs for MRs with wasm label

This patch enables wasm jobs for MRs with wasm label. Previously the
wasm label didn't actually have any effect on the CI pipeline, and
full-ci needed to be applied to run wasm jobs which was a waste of
runners when working on the wasm backend, hence the fix here.

- - - - -
702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00
Make interface files and object files depend on inplace .conf file

A potential fix for #24737

- - - - -
728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00
utils: remove obsolete vagrant scripts

Vagrantfile has long been removed in !5288. This commit further
removes the obsolete vagrant scripts in the tree.

- - - - -
36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00
Update autoconf scripts

Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02

- - - - -
ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00
ghcup-metadata: Drop output_name field

This is entirely redundant to the filename of the URL. There is no
compelling reason to name the downloaded file differently from its
source.

- - - - -
c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00
testsuite: Handle exceptions in framework_fail when testdir is not initialised

When `framework_fail` is called before initialising testdir, it would fail with
an exception reporting the testdir not being initialised instead of the actual failure.

Ensure we report the actual reason for the failure instead of failing in this way.

One way this can manifest is when trying to run a test that doesn't exist using `--only`

- - - - -
d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00
EPA: Fix range for GADT decl with sig only

Closes #24714

- - - - -
4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00
Fix TH dependencies (#22229)

Add a dependency between Syntax and Internal (via module reexport).

- - - - -
37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00
Bump haddock submodule

- - - - -
ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00
JS: cleanup to prepare for #24743

- - - - -
40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00
EPA: Preserve comments for PrefixCon

Preserve comments in

    fun (Con {- c1 -} a b)
        = undefined

Closes #24736

- - - - -
92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00
Correct `@since` metadata in HpcFlags

It was introduced in base-4.20, not 4.22.
Fix #24721

- - - - -
a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00
testsuite: fix req_target_smp predicate

- - - - -
ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00
STM: Remove (unused)coarse grained locking.

The STM code had a coarse grained locking mode guarded by #defines that was unused.
This commit removes the code.

- - - - -
917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00
STM: Be more optimistic when validating in-flight transactions.

* Don't lock tvars when performing non-committal validation.
* If we encounter a locked tvar don't consider it a failure.

This means in-flight validation will only fail if committing at the
moment of validation is *guaranteed* to fail.

This prevents in-flight validation from failing spuriously if it happens in
parallel on multiple threads or parallel to thread comitting.

- - - - -
167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00
EPA: fix span for empty \case(s)

In
    instance SDecide Nat where
      SZero %~ (SSucc _) = Disproved (\case)

Ensure the span for the HsLam covers the full construct.

Closes #24748

- - - - -
9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00
testsuite: expand size testing infrastructure

- closes #24191
- adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so
- path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite
- adds on_windows and req_dynamic_ghc predicate to testsuite

The design is to not make the testsuite too smart and simply offload to
ghc-pkg for locations of object files and directories.

- - - - -
b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00
GHCi: support inlining breakpoints (#24712)

When a breakpoint is inlined, its context may change (e.g. tyvars in
scope). We must take this into account and not used the breakpoint tick
index as its sole identifier. Each instance of a breakpoint (even with
the same tick index) now gets a different "info" index.

We also need to distinguish modules:
- tick module: module with the break array (tick counters, status, etc.)
- info module: module having the CgBreakInfo (info at occurrence site)

- - - - -
649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00
Expose constructors of SNat, SChar and SSymbol in ghc-internal

- - - - -
d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00
Add DCoVarSet to PluginProv (!12037)

- - - - -
ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00
JS: Enable more efficient packing of string data (fixes #24706)

- - - - -
be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Track in-scope variables in ruleCheckProgram

This small patch fixes #24726, by tracking in-scope variables
properly in -drule-check.  Not hard to do!

- - - - -
58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Add a couple more HasCallStack constraints in SimpleOpt

Just for debugging, no effect on normal code

- - - - -
70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Add comments to Prep.hs

This documentation patch fixes a TODO left over from !12364

- - - - -
e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00
Use HasDebugCallStack, rather than HasCallStack

- - - - -
631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00
driver: always merge objects when possible

This patch makes the driver always merge objects with `ld -r` when
possible, and only fall back to calling `ar -L` when merge objects
command is unavailable. This completely reverts !8887 and !12313,
given more fixes in Cabal seems to be needed to avoid breaking certain
configurations and the maintainence cost is exceeding the behefits in
this case :/

- - - - -
1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00
Bump time submodule to 1.14

As requested in #24528.

-------------------------
Metric Decrease:
    ghc_bignum_so
    rts_so
Metric Increase:
    cabal_syntax_dir
    rts_so
    time_dir
    time_so
-------------------------

- - - - -
4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00
Bump terminfo submodule to current master

- - - - -
43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00
wasm: use scheduler.postTask() for context switch when available

This patch makes use of scheduler.postTask() for JSFFI context switch
when it's available. It's a more principled approach than our
MessageChannel based setImmediate() implementation, and it's available
in latest version of Chromium based browsers.

- - - - -
08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00
testsuite: give pre_cmd for mhu-perf 5x time

- - - - -
bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00
EPA: Preserve comments for pattern synonym sig

Closes #24749

- - - - -
c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00
tests: Widen acceptance window for dir and so size tests

These are testing things which are sometimes out the control of a GHC
developer. Therefore we shouldn't fail CI if something about these
dependencies change because we can't do anything about it.

It is still useful to have these statistics for visualisation in grafana
though.

Ticket #24759

- - - - -
9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00
Disable rts_so test

It has already manifested large fluctuations and destabilising CI

Fixes #24762

- - - - -
fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00
unboxedSum{Type,Data}Name: Use GHC.Types as the module

Unboxed sum constructors are now defined in the `GHC.Types` module, so if you
manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like:

```hs
GHC.Types.Sum2#
```

The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly
believes that unboxed sum constructors are defined in `GHC.Prim`, so
`unboxedSumTypeName 2` would return an entirely different `Name`:

```hs
GHC.Prim.(#|#)
```

This is a problem for Template Haskell users, as it means that they can't be
sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.)

This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use
`GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the
`unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums
(`Sum<N>#`) as the `OccName`.

Fixes #24750.

- - - - -
7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00
EPA: Widen stmtslist to include last semicolon

Closes #24754

- - - - -
06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00
doc: Fix type error in hs_try_putmvar example
- - - - -
af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00
Fix parsing of module names in CLI arguments
  closes issue #24732

- - - - -
da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00
ghc-platform: Add Setup.hs

The Hadrian bootstrapping script relies upon `Setup.hs` to drive its
build.

Addresses #24761.

- - - - -
35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00
EPA: preserve comments in class and data decls

Fix checkTyClHdr which was discarding comments.

Closes #24755

- - - - -
03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00
Fix a float-out error

Ticket #24768 showed that the Simplifier was accidentally destroying
a join point.  It turned out to be that we were sending a bottoming
join point to the top, accidentally abstracting over /other/ join
points.

Easily fixed.

- - - - -
adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00
Substitute bindist files with Hadrian not configure

The `ghc-toolchain` overhaul will eventually replace all this stuff with
something much more cleaned up, but I think it is still worth making
this sort of cleanup in the meantime so other untanglings and dead code
cleaning can procede.

I was able to delete a fair amount of dead code doing this too.

`LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it
wasn't actually turned into a valid CPP identifier. (Original to
1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.)

Progress on #23966

Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com>

- - - - -
18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00
EPA: fix mkHsOpTyPV duplicating comments

Closes #24753

- - - - -
a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00
Add test cases for #24664

...since none are present in the original MR !12463 fixing this issue.

- - - - -
46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00
EPA: preserve comments in data decls

Closes #24771

- - - - -
3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00
Rename Solo# data constructor to MkSolo# (#24673)

- data Solo# a = (# a #)
+ data Solo# a = MkSolo# a

And `(# foo #)` syntax now becomes just a syntactic
sugar for `MkSolo# a`.

- - - - -
4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00
Add the cmm_cpp_is_gcc predicate to the testsuite

A future C-- test called T24474-cmm-override-g0 relies on the
GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it
emitting #defines past the preprocessing stage.  Clang, at least, does
not do this, so the test would fail if ran on Clang.

As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of
the workaround we apply as a fix for bug #24474, and the workaround was
for GCC-specific behaviour, the test needs to be marked as fragile on
other compilers.

- - - - -
25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00
Split out the C-- preprocessor, and make it pass -g0

Previously, C-- was processed with the C preprocessor program.  This
means that it inherited flags passed via -optc.  A flag that is somewhat
often passed through -optc is -g.  At certain -g levels (>=2), GCC
starts emitting defines *after* preprocessing, for the purposes of
debug info generation.  This is not useful for the C-- compiler, and, in
fact, causes lexer errors.  We can suppress this effect (safely, if
supported) via -g0.

As a workaround, in older versions of GCC (<=10), GCC only emitted
defines if a certain set of -g*3 flags was passed.  Newer versions check
the debug level.  For the former, we filter out those -g*3 flags and,
for the latter, we specify -g0 on top of that.

As a compatible and effective solution, this change adds a C--
preprocessor distinct from the C compiler and preprocessor, but that
keeps its flags.  The command line produced for C-- preprocessing now
looks like:

  $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP

Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474

- - - - -
9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00
-fprof-late: Only insert cost centres on functions/non-workfree cafs.

They are usually useless and doing so for data values comes with
a large compile time/code size overhead.

Fixes #24103

- - - - -
259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00
Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770)

See the adjusted `Note [DataAlt occ info]`.
This change also has a positive repercussion on
`Note [Combine case alts: awkward corner]`.

Fixes #24770.

We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all
fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675.

Metric Decrease:
    T9675

- - - - -
31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00
Kill seqRule, discard dead seq# in Prep (#24334)

Discarding seq#s in Core land via `seqRule` was problematic; see #24334.
So instead we discard certain dead, discardable seq#s in Prep now.
See the updated `Note [seq# magic]`.

This fixes the symptoms of #24334.

- - - - -
b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00
Document NcgImpl methods

Fixes #19914

- - - - -
4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00
Make renamer to be more flexible with parens in the LHS of the rules

We used to reject LHS like `(f a) b` in RULES and requires it to be written as
`f a b`. It will be handy to allow both as the expression may be more
readable with extra parens in some cases when infix operator is involved.
Espceially when TemplateHaskell is used, extra parens may be added out of
user's control and result in "valid" rules being rejected and there
are not always ways to workaround it.

Fixes #24621

- - - - -
ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00
IPE: Eliminate dependency on Read

Instead of encoding the closure type as decimal string we now simply
represent it as an integer, eliminating the need for `Read` in
`GHC.Internal.InfoProv.Types.peekInfoProv`.

Closes #24504.

-------------------------
Metric Decrease:
    T24602_perf_size
    size_hello_artifact
-------------------------

- - - - -
a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00
testsuite: fix testwsdeque with recent clang

This patch fixes compilation of testwsdeque.c with recent versions of
clang, which will fail with the error below:

```
testwsdeque.c:95:33: error:
     warning: format specifies type 'long' but the argument has type 'void *' [-Wformat]
       95 |         barf("FAIL: %ld %d %d", p, n, val);
          |                     ~~~         ^

testwsdeque.c:95:39: error:
     warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat]
       95 |         barf("FAIL: %ld %d %d", p, n, val);
          |                            ~~         ^~~
          |                            %lu

testwsdeque.c:133:42: error:
     error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types]
      133 |         createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n);
          |                                          ^~~~~

/workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error:
     note: passing argument to parameter 'startProc' here
      193 |                                     OSThreadProc *startProc, void *param);
          |                                                   ^

2 warnings and 1 error generated.
```

- - - - -
c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00
Rename pre-processor invocation args

Small clean up. Uses proper names for the various groups of arguments
that make up the pre-processor invocation.

- - - - -
2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00
ghc-heap: fix typo in ghc-heap cbits

- - - - -
fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00
Improve performance of Data.List.sort(By)

This patch improves the algorithm to sort lists in base.
It does so using two strategies:

1) Use a four-way-merge instead of the 'default' two-way-merge.
This is able to save comparisons and allocations.

2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization.
This mainly benefits types with a fast (>).

Note that this *may* break instances with a *malformed* Ord instance
where `a > b` is *not* equal to `compare a b == GT`.

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236

Fixes #24280

-------------------------
Metric Decrease:
    MultiLayerModulesTH_Make
    T10421
    T13719
    T15164
    T18698a
    T18698b
    T1969
    T9872a
    T9961
    T18730
    WWRec
    T12425
    T15703
-------------------------

- - - - -
1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00
Revert "ghcup-metadata: Drop output_name field"

This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f.

This breaks the ghcup metadata generation on the nightly jobs.

- - - - -
daff1e30 by Jannis at 2024-05-12T13:38:35-04:00
Division by constants optimization

- - - - -
413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00
Tidy: Add flag to expose unfoldings if they take dictionary arguments.

Add the flag `-fexpose-overloaded-unfoldings` to be able to control this
behaviour.

For ghc's boot libraries file size grew by less than 1% when it was
enabled. However I refrained from enabling it by default for now.

I've also added a section on specialization more broadly to the users
guide.

-------------------------
Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    T12425
    T13386
    hard_hole_fits
-------------------------

- - - - -
c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00
Don't store a GlobalRdrEnv in `mi_globals` for GHCi.

GHCi only needs the `mi_globals` field for modules imported with
:module +*SomeModule.

It uses this field to make the top level environment in `SomeModule` available
to the repl.

By default, only the first target in the command line parameters is
"star" loaded into GHCi. Other modules have to be manually "star" loaded
into the repl.

Storing the top level GlobalRdrEnv for each module is very wasteful, especially
given that we will most likely never need most of these environments.

Instead we store only the information needed to reconstruct the top level environment
in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements
as well as all top level symbols defined in the module (not taking export lists into account)

When a particular module is "star-loaded" into GHCi (as the first commandline target, or via
an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using
the `IfaceTopEnv`.

- - - - -
d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00
Add perf regression test for `-fwrite-if-simplified-core`

- - - - -
2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00
Improve pattern to type pattern transformation (23739)

`pat_to_type_pat` function now can handle more patterns:
  - TuplePat
  - ListPat
  - LitPat
  - NPat
  - ConPat

Allowing these new constructors in type patterns significantly
increases possible shapes of type patterns without `type` keyword.

This patch also changes how lookups in `lookupOccRnConstr` are
performed, because we need to fall back into
types when we didn't find a constructor on data level to perform
`ConPat` to type transformation properly.

- - - - -
be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00
hadrian: fix hadrian building with ghc-9.10.1

- - - - -
ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00
linters: fix lint-whitespace compilation with ghc-9.10.1

- - - - -
a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00
Expand the `inline` rule to look through casts/ticks.

Fixes #24808

- - - - -
b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00
testsuite: bump PartialDownSweep timeout to 5x on wasm32

- - - - -
b2227487 by Fendor at 2024-05-15T17:14:06-04:00
Add Eq and Ord instance to `IfaceType`

We add an `Ord` instance so that we can store `IfaceType` in a
`Data.Map` container.
This is required to deduplicate `IfaceType` while writing `.hi` files to
disk. Deduplication has many beneficial consequences to both file size
and memory usage, as the deduplication enables implicit sharing of
values.
See issue #24540 for more motivation.

The `Ord` instance would be unnecessary if we used a `TrieMap` instead
of `Data.Map` for the deduplication process. While in theory this is
clerarly the better option, experiments on the agda code base showed
that a `TrieMap` implementation has worse run-time performance
characteristics.

To the change itself, we mostly derive `Eq` and `Ord`. This requires us
to change occurrences of `FastString` with `LexicalFastString`, since
`FastString` has no `Ord` instance.
We change the definition of `IfLclName` to a newtype of
`LexicalFastString`, to make such changes in the future easier.

Bump haddock submodule for IfLclName changes

- - - - -
d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00
Move out LiteralMap to avoid cyclic module dependencies

- - - - -
2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00
Add deduplication table for `IfaceType`

The type `IfaceType` is a highly redundant, tree-like data structure.
While benchmarking, we realised that the high redundancy of `IfaceType`
causes high memory consumption in GHCi sessions when byte code is
embedded into the `.hi` file via `-fwrite-if-simplified-core` or
`-fbyte-code-and-object-code`.
Loading such `.hi` files from disk introduces many duplicates of
memory expensive values in `IfaceType`, such as `IfaceTyCon`,
`IfaceTyConApp`, `IA_Arg` and many more.

We improve the memory behaviour of GHCi by adding an additional
deduplication table for `IfaceType` to the serialisation of `ModIface`,
similar to how we deduplicate `Name`s and `FastString`s.
When reading the interface file back, the table allows us to automatically
share identical values of `IfaceType`.

To provide some numbers, we evaluated this patch on the agda code base.
We loaded the full library from the `.hi` files, which contained the
embedded core expressions (`-fwrite-if-simplified-core`).

Before this patch:

* Load time: 11.7 s, 2.5 GB maximum residency.

After this patch:

* Load time:  7.3 s, 1.7 GB maximum residency.

This deduplication has the beneficial side effect to additionally reduce
the size of the on-disk interface files tremendously.

For example, on agda, we reduce the size of `.hi` files (with
`-fwrite-if-simplified-core`):

* Before: 101 MB on disk
* Now:     24 MB on disk

This has even a beneficial side effect on the cabal store. We reduce the
size of the store on disk:

* Before: 341 MB on disk
* Now:    310 MB on disk

Note, none of the dependencies have been compiled with
`-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple
locations in a `ModIface`.

We also add IfaceType deduplication table to .hie serialisation and
refactor .hie file serialisation to use the same infrastrucutre as
`putWithTables`.

Bump haddock submodule to accomodate for changes to the deduplication
table layout and binary interface.

- - - - -
36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00
Add run-time configurability of `.hi` file compression

Introduce the flag `-fwrite-if-compression=<n>` which allows to
configure the compression level of writing .hi files.

The motivation is that some deduplication operations are too expensive
for the average use case. Hence, we introduce multiple compression
levels with variable impact on performance, but still reduce the
memory residency and `.hi` file size on disk considerably.

We introduce three compression levels:

* `1`: `Normal` mode. This is the least amount of compression.
    It deduplicates only `Name` and `FastString`s, and is naturally the
    fastest compression mode.
* `2`: `Safe` mode. It has a noticeable impact on .hi file size and is
  marginally slower than `Normal` mode. In general, it should be safe to
  always use `Safe` mode.
* `3`: `Full` deduplication mode. Deduplicate as much as we can,
  resulting in minimal .hi files, but at the cost of additional
  compilation time.

Reading .hi files doesn't need to know the initial compression level,
and can always deserialise a `ModIface`, as we write out a byte that
indicates the next value has been deduplicated.
This allows users to experiment with different compression levels for
packages, without recompilation of dependencies.

Note, the deduplication also has an additional side effect of reduced
memory consumption to implicit sharing of deduplicated elements.
See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where
that matters.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhciWithCore
    T16875
    T21839c
    T24471
    hard_hole_fits
    libdir
-------------------------

- - - - -
1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00
Introduce regression tests for `.hi` file sizes

Add regression tests to track how `-fwrite-if-compression` levels affect
the size of `.hi` files.

- - - - -
639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00
TTG: ApplicativeStatement exist only in Rn and Tc

Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com>

- - - - -
aa7b336b by Jade at 2024-05-15T23:06:17-04:00
Documentation: Improve documentation for symbols exported from System.IO

- - - - -
c561de8f by Jade at 2024-05-15T23:06:54-04:00
Improve suggestions for language extensions

- When suggesting Language extensions, also suggest Extensions which imply them
- Suggest ExplicitForAll and GADTSyntax instead of more specific
  extensions
- Rephrase suggestion to include the term 'Extension'
- Also moves some flag specific definitions out of Session.hs into
Flags.hs (#24478)

Fixes: #24477
Fixes: #24448
Fixes: #10893

- - - - -
4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00
Testsuite: Check if llvm assembler is available for have_llvm

- - - - -
bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00
refactor quadratic search in warnMissingHomeModules

- - - - -
7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00
add test that runs MakeDepend on thousands of modules

- - - - -
b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00
Representation-polymorphic HasField (fixes #22156)

This generalises the HasField class to support representation polymorphism,
so that instead of

    type HasField :: forall {k} . k -> Type -> Type -> Constraint

we have

    type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint

- - - - -
05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00
Bump os-string submodule to 2.0.2.2

Closes #24786

- - - - -
886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00
rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED

This commit fixes a small an oversight in !12148: the prefetch logic
in non-moving GC may trap in debug RTS because it calls Bdescr() for
mark_closure which may be a static one. It's fine in non-debug RTS
because even invalid bdescr addresses are prefetched, they will not
cause segfaults, so this commit implements the most straightforward
fix: don't prefetch mark_closure bdescr when assertions are enabled.

- - - - -
b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00
rts: Allocate non-moving segments with megablocks

Non-moving segments are 8 blocks long and need to be aligned.
Previously we serviced allocations by grabbing 15 blocks, finding
an aligned 8 block group in it and returning the rest.
This proved to lead to high levels of fragmentation as a de-allocating a segment
caused an 8 block gap to form, and this could not be reused for allocation.

This patch introduces a segment allocator based around using entire
megablocks to service segment allocations in bulk.

When there are no free segments, we grab an entire megablock and fill it
with aligned segments. As the megablock is free, we can easily guarantee
alignment. Any unused segments are placed on a free list.

It only makes sense to free segments in bulk when all of the segments in
a megablock are freeable. After sweeping, we grab the free list, sort it,
and find all groups of segments where they cover the megablock and free
them.
This introduces a period of time when free segments are not available to
the mutator, but the risk that this would lead to excessive allocation
is low. Right after sweep, we should have an abundance of partially full
segments, and this pruning step is relatively quick.

In implementing this we drop the logic that kept NONMOVING_MAX_FREE
segments on the free list.

We also introduce an eventlog event to log the amount of pruned/retained
free segments.

See Note [Segment allocation strategy]

Resolves #24150

-------------------------
Metric Decrease:
    T13253
    T19695
-------------------------

- - - - -
710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00
rts: fix I/O manager compilation errors for win32 target

This patch fixes I/O manager compilation errors for win32 target
discovered when cross-compiling to win32 using recent clang:

```
rts/win32/ThrIOManager.c:117:7: error:
     error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      117 |   if (is_io_mng_native_p ()) {
          |       ^
    |
117 |   if (is_io_mng_native_p ()) {
    |       ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/fs.c:143:28: error:
     error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes]
      143 | int setErrNoFromWin32Error () {
          |                            ^
          |                             void
    |
143 | int setErrNoFromWin32Error () {
    |                            ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/win32/ConsoleHandler.c:227:9: error:
     error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      227 |         interruptIOManagerEvent ();
          |         ^
    |
227 |         interruptIOManagerEvent ();
    |         ^

rts/win32/ConsoleHandler.c:227:9: error:
     note: did you mean 'getIOManagerEvent'?
    |
227 |         interruptIOManagerEvent ();
    |         ^

rts/include/rts/IOInterface.h:27:10: error:
     note: 'getIOManagerEvent' declared here
       27 | void *   getIOManagerEvent  (void);
          |          ^
   |
27 | void *   getIOManagerEvent  (void);
   |          ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)

rts/win32/ConsoleHandler.c:196:9: error:
     error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration]
      196 |         setThreadLabel(cap, t, "signal handler thread");
          |         ^
    |
196 |         setThreadLabel(cap, t, "signal handler thread");
    |         ^

rts/win32/ConsoleHandler.c:196:9: error:
     note: did you mean 'postThreadLabel'?
    |
196 |         setThreadLabel(cap, t, "signal handler thread");
    |         ^

rts/eventlog/EventLog.h:118:6: error:
     note: 'postThreadLabel' declared here
      118 | void postThreadLabel(Capability    *cap,
          |      ^
    |
118 | void postThreadLabel(Capability    *cap,
    |      ^

1 error generated.
`x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1)
```

- - - - -
28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00
configure: Check C99-compat for Cmm preprocessor

Fixes #24815

- - - - -
8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00
Ensure `tcHasFixedRuntimeRep (# #)` returns True.

- - - - -
04179044 by doyougnu at 2024-05-17T09:00:32-04:00
testsuite: make find_so regex less general

Closes #24759

Background. In MR !12372 we began tracking shared object files and
directories sizes for dependencies. However, this broke  release builds
because release builds alter the filenames swapping "in-place" for a
hash. This was not considered in the MR and thus broke release
pipelines. Furthermore, the rts_so test was found to be wildly varying
and was therefore disabled in !12561.

This commit fixes both of these issues:

- fix the rts_so test by making the regex less general, now the rts_so
test and all other foo.so tests must match
"libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the
rts_so test from accidentally matching different rts variants such as
rts_threaded, which was the cause of the wild swings after !12372.

- add logic to match either a hash or the string in-place. This should
make the find_so function build agnostic.

- - - - -
0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00
TagAnalysis: Treat all bottom ids as tagged during analysis.

Ticket #24806 showed that we also need to treat dead end thunks as
tagged during the analysis.

- - - - -
7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00
Remove haddock submodule

In preparation for merge into the GHC, as proposed in #23178.

- - - - -
47b14dcc by Fendor at 2024-05-17T11:28:17-04:00
Adapt to `IfLclName` newtype changes

(cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1)

- - - - -
6cc6681d by Fendor at 2024-05-17T11:28:17-04:00
Add IfaceType deduplication table to interface file serialisation

Although we do not really need it in the interface file serialisation,
as the deserialisation uses `getWithUserData`, we need to mirror the
structure `getWithUserData` expects. Thus, we write essentially an empty
`IfaceType` table at the end of the file, as the interface file doesn't
reference `IfaceType`.

(cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61)

- - - - -
b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00
ghc-tags.yaml: Initial commit

- - - - -
074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00
fourmolu: Add configuration

- - - - -
151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00
Makefile: Rework for use by haddock developers

Previously the Makefile was present only for GHC's old make-based build
system. Now since the make-based build system is gone we can use it for
more useful ends.

- - - - -
a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00
Reformat with fourmolu

Using previously-added configuration and `fourmolu -i .`
Note that we exclude the test-cases
(`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to
formatting.

- - - - -
0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00
Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660'

git-subtree-dir: utils/haddock
git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3
git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660

- - - - -
aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00
Add exceptions to the dangling notes list

- - - - -
527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00
Add haddock to the whitespace lint ignore list

- - - - -
43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00
git-blame-ignore-revs: Ignore haddock reformatting

- - - - -
0e679e37 by Fendor at 2024-05-18T00:27:24-04:00
Pass cpp options to the CC builder in hadrian

- - - - -
bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00
JS: fix allocation constant (fix #24746)

- - - - -
646d30ab by Jade at 2024-05-18T19:23:31+02:00
Add highlighting for inline-code snippets in haddock

- - - - -
64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00
haddock: Add a .readthedocs.yml file for online documentation

- - - - -
7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00
Unicode: General Category size test (related #24789)

Added trivial size performance test which involves unicode general category usage via `read`.
The `read` itself uses general category to detect spaces.

The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789.

- - - - -
8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00
EPA: Remove redundant code

Remove unused
  epAnnAnns function
  various cases for showAstData that no longer exist

- - - - -
071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00
Improve docs on closed type families in hs-boots

Fixes #24776

- - - - -
d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00
Use default deviation for large-project test

This new performance test has the purpose of detecting regressions in
complexity in relation to the number of modules in a project, so 1%
deviation is way too small to avoid false positives.

- - - - -
20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00
ghcup-metadata: Various fixes from 9.10.1

Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists
where possible.

- - - - -
6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00
Reverse arguments to stgCallocBytes (fix #24828)

- - - - -
f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00
Add log messages for Iface serialisation compression level

Fix the label of the number of 'IfaceType' entries in the log message.
Add log message for the compression level that is used to serialise a an
interface file.

Adds `Outputable` instance for 'CompressionIFace'.

- - - - -
3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00
base: Update doctests outputs

ghc-internal: Update doctests outputs

- - - - -
9317c6fb by David Binder at 2024-05-22T00:34:21-04:00
haddock: Fix the testsuites of the haddock-library

- Apply all the metadata revisions from Hackage
  to the cabal file.
- Fix the `ParserSpec.hs` file in the `spec`
  testsuite of haddock-library.
- Make `CHANGES.md` an extra-doc-file instead of
  an extra-source-file.

- - - - -
54073b02 by David Binder at 2024-05-22T00:34:21-04:00
haddock: Fix parser of @since pragma

The testsuite contained tests for annotations of
the form `@since foo-bar-0.5.0`, but the parser was
written incorrectly.

- - - - -
ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00
Fix nightly pages job

It seems likely broken by 9f99126a which moved `index.html` from the
root folder into `docs/` folder.

Fixes #24840

- - - - -
b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00
autoconf: remove unused context diff check

This patch removes redundant autoconf check for the context diff
program given it isn't actually been used anywhere, especially since
make removal.

- - - - -
ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00
haddock: Rework the contributing guide

- - - - -
0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00
haddock: Add module relationships diagrams of haddock-api and haddock-library

- - - - -
d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00
Add instructions

- - - - -
b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00
Add SVG outputs

- - - - -
6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00
rts: Fix size of StgOrigThunkInfo frames

Previously the entry code of the `stg_orig_thunk` frame failed to
account for the size of the profiling header as it hard-coded the frame
size. Fix this.

Fixes #24809.

- - - - -
c645fe40 by Fendor at 2024-05-22T13:40:05-04:00
Add regression test T24809 for stg_orig_thunk_info_frame size

- - - - -
4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00
bindists: Check for existence of share folder before trying to copy it.

This folder isn't distributed in windows bindists

A lack of doing so resulted us copying loads of files twice.

- - - - -
d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00
Remove ad-hoc installation of mingw toolchain in relocatable bindists

This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951

The choice about whether to install mingw is taken in the installation
makefile.

This is also broken on non-windows systems.

The actual issue was the EnableDistroToolchain variable wasn't declared
in mk/config.mk and therefore the check to install mingw was failing.

- - - - -
7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00
testsuite: fix T17920 for wasm backend

T17920 was marked as fragile on wasm before; it can be trivially fixed
by avoiding calling variadic printf() in cmm.

- - - - -
c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00
testsuite: bump T22744 timeout to 5x

- - - - -
c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00
testsuite: don't attempt to detect host cpu features when testing cross ghc

The testsuite driver CPU feature detection logic only detects host CPU
and only makes sense when we are not testing a cross GHC.

- - - - -
3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00
Better skolemisation

As #24810 showed, it is (a little) better to skolemise en-bloc,
so that Note [Let-bound skolems] fires more often.

See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate.

- - - - -
a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00
Add missing parenthesizePat in cvtp

We need to ensure that the output of `cvtp` is parenthesized (at precedence
`sigPrec`) so that any pattern signatures with a surrounding pattern signature
can parse correctly.

Fixes #24837.

- - - - -
4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00
[base] Document the memory overhead of ByteArray

Add a diagram that shows the constituent parts of a ByteArray and their
memory overhead.

- - - - -
8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00
Haddock: Add MR template for Haddock

- - - - -
ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00
PPC: Support ELF v2 on powerpc64 big-endian

Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF`
preprocessor macro.

Fixes #21191

- - - - -
9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00
gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock

- - - - -
28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00
haddock: Add cabal-fmt to tools for `make style`

- - - - -
00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00
haddock: fix verbosity option parsing

- - - - -
a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00
base: specify tie-breaking behavior of min, max, and related list/Foldable functions

- - - - -
bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00
cmm: add word <-> double/float bitcast

- closes: #25331

This is the last step in the project plan described in #25331. This
commit:

- adds bitcast operands for x86_64, LLVM, aarch64
- For PPC and i386 we resort to using the cmm implementations
- renames conversion MachOps from Conv to Round|Truncate

- - - - -
f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00
StgToByteCode: minor refactor

Some functions in StgToByteCode were filtering out void arguments.
However, StgToByteCode is called after unarisation: the void arguments
should have been removed earlier.
Instead of filtering out, we assert that the args are non-void.

- - - - -
03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00
StgToByteCode: minor refactor

`layoutNativeCall` was always called with a `primRepCmmType platform`
callback. Hence we can put it inside of `layoutNativeCall` rather than
repeat it.

- - - - -
27c430f3 by David Binder at 2024-05-24T07:52:38-04:00
haddock: Remove compatibility shims for GHC < 8.4 from haddock-library

- - - - -
8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00
compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs

This patch makes the STG->Cmm backend avoid saving foreign call target
to local when there are no caller-save GlobalRegs.

Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a
foreign call, we unconditionally save the foreign call target to a
temporary local first, then rely on cmmSink to clean it up later,
which only happens with -fcmm-sink (implied by -O) and not in
unoptimized code.

And this is troublesome for the wasm backend NCG, which needs to infer
a foreign call target symbol's type signature from the Cmm call site.
Previously, the NCG has been emitting incorrect type signatures for
unoptimized code, which happens to work with `wasm-ld` most of the
time, but this is never future-proof against upstream toolchain
updates, and it causes horrible breakages when LTO objects are
included in linker input. Hence this patch.

- - - - -
986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00
testsuite: add callee-no-local regression test

- - - - -
52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00
Fix HasCallStack leftovers from !12514 / #24726

- - - - -
c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00
user_guide: Fix typo in MultiWayIf chapter

Close #24829

- - - - -
bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00
base: Ensure that CHANGELOG is included in extra-source-files

This was missed in the `ghc-internal` split.

Closes #24831.

- - - - -
1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00
base: Fix changelog reference to setBacktraceMechanismState

(cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d)

- - - - -
43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00
Float/double unboxed literal support for HexFloatLiterals (fix #22155)

- - - - -
4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00
Improve test labels for binary interface file size tests

Test labels for binary interface file sizes are hard to read and overly
verbose at the same time. Extend the name for the metric title, but
shorten it in the actual comparison table.

- - - - -
14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00
Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present"

This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa.

- - - - -
f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00
Fix default hyperlinked sources pattern

Previously this didn't include the `%M` token which manifested as broken
links to the hyperlinked sources of reexports of declarations defined
in other packages.

Fixes haddock#1628.

(cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36)

- - - - -
42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00
Make DocPaths a proper data type

(cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c)

- - - - -
53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00
haddock: Bump version to 2.30

(cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602)

- - - - -
e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00
haddock-api: allow base 4.20 and ghc 9.11

- - - - -
e294f7a2 by PHO at 2024-05-24T12:17:55-04:00
Add a flag "threaded" for building haddock with the threaded RTS

GHC isn't guaranteed to have a threaded RTS. There should be a way to build
it with the vanilla one.

(cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d)

- - - - -
51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00
Update ticky counter event docs.

Add the info about the info table address and json fields.

Fixes #23200

- - - - -
98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00
Export extractPromotedList (#24866)

This can be useful in plugins.

- - - - -
228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00
template-haskell: Move wired-ins to ghc-internal

Thus we make `template-haskell` reinstallable and keep it as the public
API for Template Haskell.
All of the wired-in identifiers are moved to `ghc-internal`.
This necessitates also moving much of `ghc-boot-th` into `ghc-internal`.
These modules are then re-exported from `ghc-boot-th` and
`template-haskell`.
To avoid a dependency on `template-haskell` from `lib:ghc`, we instead
depend on the TH ASTs via `ghc-boot-th`.

As `template-haskell` no longer has special status, we can drop the
logic adding an implicit dependency on `template-haskell` when using TH.
We can also drop the `template-haskell-next` package, which was
previously used when bootstrapping.

When bootstrapping, we need to vendor the TH AST modules from
`ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap`
cabal flag as before. See Note [Bootstrapping Template Haskell].

We split out a GHC.Internal.TH.Lift module resolving #24752.
This module is only built when not bootstrapping.

Resolves #24703

-------------------------
Metric Increase:
    ghc_boot_th_dir
    ghc_boot_th_so
-------------------------

- - - - -
62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00
testsuite: mark tests broken by #24886

Now that `template-haskell` is no longer wired-in.
These tests are triggering #24886, and so need to be marked broken.

- - - - -
3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00
rts: fix missing function prototypes in ClosureMacros.h

- - - - -
e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00
UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument.

This allows representing functions like:

    int foo(void);

to be imported like this:

    foreign import ccall "a_number_c"
      c_number :: (# #) -> Int64#

Which can be useful when the imported function isn't implicitly
stateful.

- - - - -
d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00
ci: Update ci-images commit for fedora38 image

The fedora38 nightly job has been failing for quite a while because
`diff` was no longer installed. The ci-images bump explicitly installs
`diffutils` into these images so hopefully they now pass again.

- - - - -
3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00
Update exactprint docs

- - - - -
77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00
Incorporate review feedback

- - - - -
87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00
Remove no longer relevant reference to comments

- - - - -
05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00
Replace outdated code example

- - - - -
45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00
Reword error resulting from missing -XBangPatterns.

It can be the result of either a bang pattern or strict binding,
so now we say so instead of claiming it must be a bang pattern.

Fixes #21032

- - - - -
e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00
testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x

- - - - -
7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: ensure gc_thread/gen_workspace is allocated with proper alignment

gc_thread/gen_workspace are required to be aligned by 64 bytes.
However, this property has not been properly enforced before, and
numerous alignment violations at runtime has been caught by
UndefinedBehaviorSanitizer that look like:

```
rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment
0x0000027a3390: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8

rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment
0x0000027a3450: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13
```

This patch fixes the gc_thread/gen_workspace misalignment issue by
explicitly allocating them with alignment constraint.

- - - - -
c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: fix an unaligned load in nonmoving gc

This patch fixes an unaligned load in nonmoving gc by ensuring the
closure address is properly untagged first before attempting to
prefetch its header. The unaligned load is reported by
UndefinedBehaviorSanitizer:

```
rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment
0x0042005f3a71: note: pointer points here
 00 00 00  98 43 13 8e 12 7f 00 00  50 3c 5f 00 42 00 00 00  58 17 b7 92 12 7f 00 00  89 cb 5e 00 42
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9
```

This issue had previously gone unnoticed since it didn't really harm
runtime correctness, the invalid header address directly loaded from a
tagged pointer is only used as prefetch address and will not cause
segfaults. However, it still should be corrected because the prefetch
would be rendered useless by this issue, and untagging only involves a
single bitwise operation without memory access so it's cheap enough to
add.

- - - - -
05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: use __builtin_offsetof to implement STG_FIELD_OFFSET

This patch fixes the STG_FIELD_OFFSET macro definition by using
__builtin_offsetof, which is what gcc/clang uses to implement offsetof
in standard C. The previous definition that uses NULL pointer involves
subtle undefined behavior in C and thus reported by
UndefinedBehaviorSanitizer as well:

```
rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_')
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58
```

- - - - -
5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00
JS: remove useless h$CLOCK_REALTIME (#23202)

- - - - -
95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00
ghcup-metadata: Fix metadata generation

There were some syntax errors in the generation script which were
preventing it from running.

I have tested this with:

```
nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525
```

which completed successfully.

- - - - -
1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00
Add diagrams to Arrows documentation

This adds diagrams to the documentation of Arrows, similar to the ones found on
https://www.haskell.org/arrows/.

It does not add diagrams for ArrowChoice for the time being, mainly because it's
not clear to me how to visually distinguish them from the ones for Arrow. Ideally,
you might want to do something like highlight the arrows belonging to the same
tuple or same Either in common colors, but that's not really possible with unicode.

- - - - -
d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00
Make UnsafeSNat et al. into pattern synonyms

...so that they do not cause coerce to bypass the nominal
role on the corresponding singleton types when they are imported.
See Note [Preventing unsafe coercions for singleton types] and
the discussion at #23478.

This also introduces unsafeWithSNatCo (and analogues for Char
and Symbol) so that users can still access the dangerous coercions
that importing the real constructors would allow, but only in a
very localized way.

- - - - -
0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00
hadrian: build C/C++ with split sections when enabled

When split sections is enabled, ensure -fsplit-sections is passed to
GHC as well when invoking GHC to compile C/C++; and pass
-ffunction-sections -fdata-sections to gcc/clang when compiling C/C++
with the hadrian Cc builder. Fixes #23381.

- - - - -
02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00
driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled

When -fsplit-sections is passed to GHC, pass -ffunction-sections
-fdata-sections to gcc/clang when building C/C++. Previously,
-fsplit-sections was only respected by the NCG/LLVM backends, but not
the unregisterised backend; the GHC driver did not pass
-fdata-sections and -ffunction-sections to the C compiler, which
resulted in excessive executable sizes.

Fixes #23381.

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00
testsuite: mark process005 as fragile on JS

- - - - -
34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00
Add -Wderiving-typeable to -Wall

Deriving `Typeable` does nothing, and it hasn't done for a long while.

There has also been a warning for a long while which warns you about
uselessly deriving it but it wasn't enabled in -Wall.

Fixes #24784

- - - - -
75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00
docs: Fix formatting of changelog entries

- - - - -
303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00
docs: Fix link to injective type families paper

Closes #24863

- - - - -
df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00
ghc-internal: Fix package description

The previous description was inherited from `base` and was inappropriate
for `ghc-internal`. Also fix the maintainer and bug reporting fields.

Closes #24906.

- - - - -
bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00
compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans

This patch removes special consideration for ArchWasm32 in
cmmDoCmmSwitchPlans, which means the compiler will now disable
cmmImplementSwitchPlans for wasm unreg backend, just like unreg
backend of other targets. We enabled it in the past to workaround some
compile-time panic in older versions of LLVM, but those panics are no
longer present, hence no need to keep this workaround.

- - - - -
7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00
utils: add hie.yaml config file for ghc-config

Add hie.yaml to ghc-config project directory so it can be edited using
HLS.

- - - - -
1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00
hadrian: handle findExecutable "" gracefully

hadrian may invoke findExecutable "" at run-time due to a certain
program is not found by configure script. Which is fine and
findExecutable is supposed to return Nothing in this case. However, on
Windows there's a directory bug that throws an exception (see
https://github.com/haskell/directory/issues/180), so we might as well
use a wrapper for findExecutable and handle exceptions gracefully.

- - - - -
4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00
configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails

When configure fails to find LLC/OPT/LLVMAS within supported version
range, it used to set "llc"/"opt"/"clang" as fallback values. This
behavior is particularly troublesome when the user has llc/opt/clang
with other versions in their PATH and run the testsuite, since hadrian
will incorrectly assume have_llvm=True and pass that to the testsuite
driver, resulting in annoying optllvm test failures (#23186). If
configure determines llc/opt/clang wouldn't work, then we shouldn't
pretend it'll work at all, and the bindist configure will invoke
FIND_LLVM_PROG check again at install time anyway.

- - - - -
5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00
Introduce UniqueSet and use it to replace 'UniqSet Unique'

'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique',
which is wasting space (associated key/value are always the same).

Fix #23572 and #23605

- - - - -
e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00
Improve template-haskell haddocks

Closes #15822

- - - - -
ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00
Bump max LLVM version to 19 (not inclusive)

- - - - -
92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00
ci: Update CI images to test LLVM 18

The debian12 image in this commit has llvm 18 installed.

- - - - -
adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00
Unicode: make ucd2haskell build-able again

ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten.

Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures:
1. Ghc module path environment got a suffix with `src`.
2. Generated code got
2.1 `GHC.Internal` prefix for `Data.*`.
2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure.

- - - - -
ad56fd84 by Jade at 2024-06-01T09:36:29-04:00
Replace 'NB' with 'Note' in error messages

- - - - -
6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00
compiler: fix -ddump-cmm-raw when compiling .cmm

This patch fixes missing -ddump-cmm-raw output when compiling .cmm,
which is useful for debugging cmm related codegen issues.

- - - - -
1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00
Print namespace specifiers in FixitySig's Outputable instance

For whatever reason, the `Outputable` instance for `FixitySig` simply did not
print out namespace specifiers, leading to the confusing `-ddump-splices`
output seen in #24911. This patch corrects this oversight.

Fixes #24911.

- - - - -
cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00
Configure: display C++ compiler path

- - - - -
f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable PIC for in-tree GMP on wasm32

This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC
unconditionally adds undesired code size and runtime overhead for
wasm32.

- - - - -
1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable in-tree gmp fft code path for wasm32

This patch disables in-tree GMP FFT code paths for wasm32 target in
order to give up some performance of multiplying very large operands
in exchange for reduced code size.

- - - - -
06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: build in-tree GMP with malloc-notreentrant on wasm32

This patch makes hadrian build in-tree GMP with the
--enable-alloca=malloc-notreentrant configure option. We will only
need malloc-reentrant when we have threaded RTS and SMP support on
wasm32, which will take some time to happen, before which we should
use malloc-notreentrant to avoid undesired runtime overhead.

- - - - -
9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00
Set package include paths when assembling .S files

Fixes #24839.

Co-authored-by: Sylvain Henry <hsyl20 at gmail.com>

- - - - -
4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00
Improve performance of genericWordQuotRem2Op (#22966)

Implements the algorithm from compiler-rt's udiv128by64to64default. This
rewrite results in a roughly 24x improvement in runtime on AArch64 (and
likely any other arch that uses it).

- - - - -
ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00
testsuite: mark T7773 as fragile on wasm

- - - - -
c8ece0df by Fendor at 2024-06-03T19:43:22-04:00
Migrate `Finder` component to `OsPath`, fixed #24616

For each module in a GHCi session, we keep alive one `ModLocation`.
A `ModLocation` is fairly inefficiently packed, as `String`s are
expensive in memory usage.

While benchmarking the agda codebase, we concluded that we keep alive
around 11MB of `FilePath`'s, solely retained by `ModLocation`.

We provide a more densely packed encoding of `ModLocation`, by moving
from `FilePath` to `OsPath`. Further, we migrate the full `Finder`
component to `OsPath` to avoid unnecessary transformations.
As the `Finder` component is well-encapsulated, this requires only a
minimal amount of changes in other modules.

We introduce pattern synonym for 'ModLocation' which maintains backwards
compatibility and avoids breaking consumers of 'ModLocation'.

- - - - -
0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00
compiler: emit NaturallyAligned when element type & index type are the same width

This commit fixes a subtle mistake in alignmentFromTypes that used to
generate Unaligned when element type & index type are the same width.
Fixes #24930.

- - - - -
18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00
Parser: Remove unused `apats` rule

- - - - -
38757c30 by David Knothe at 2024-06-04T05:05:27-04:00
Implement Or Patterns (#22596)

This commit introduces a new language extension, `-XOrPatterns`, as described in
GHC Proposal 522.

An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ...,
`patk` succeed, in this order.

See also the summary `Note [Implmentation of OrPatterns]`.

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>

- - - - -
395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00
compiler/ghci/rts: remove stdcall support completely

We have formally dropped i386 windows support (#18487) a long time
ago. The stdcall foreign call convention is only used by i386 windows,
and the legacy logic around it is a significant maintenance burden for
future work that adds arm64 windows support (#24603). Therefore, this
patch removes stdcall support completely from the compiler as well as
the RTS (#24883):

- stdcall is still recognized as a FFI calling convention in Haskell
  syntax. GHC will now unconditionally emit a warning
  (-Wunsupported-calling-conventions) and treat it as ccall.
- Apart from minimum logic to support the parsing and warning logic,
  all other code paths related to stdcall has been completely stripped
  from the compiler.
- ghci only supports FFI_DEFAULT_ABI and ccall convention from now on.
- FFI foreign export adjustor code on all platforms no longer handles
  the stdcall case and only handles ccall from now on.
- The Win32 specific parts of RTS no longer has special code paths for
  stdcall.

This commit is the final nail on the coffin for i386 windows support.
Further commits will perform more housecleaning to strip the legacy
code paths and pave way for future arm64 windows support.

- - - - -
d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00
rts: remove legacy i386 windows code paths

This commit removes some legacy i386 windows related code paths in the
RTS, given this target is no longer supported.

- - - - -
a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00
autoconf: remove i386 windows related logic

This commit removes legacy i386 windows logic in autoconf scripts.

- - - - -
91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00
llvm-targets: remove i386 windows support

This commit removes i386 windows from llvm-targets and the script to
generate it.

- - - - -
65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00
libraries/utils: remove stdcall related legacy logic

This commit removes stdcall related legacy logic in libraries and
utils. ccall should be used uniformly for all supported windows hosts
from now on.

- - - - -
d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00
testsuite: adapt the testsuite for stdcall removal

This patch adjusts test cases to handle the stdcall removal:

- Some stdcall usages are replaced with ccall since stdcall doesn't
  make sense anymore.
- We also preserve some stdcall usages, and check in the expected
  warning messages to ensure GHC always warn about stdcall usages
  (-Wunsupported-calling-conventions) as expected.
- Error code testsuite coverage is slightly improved,
  -Wunsupported-calling-conventions is now tested.
- Obsolete code paths related to i386 windows are also removed.

- - - - -
cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: minor adjustments for stdcall removal

This commit include minor adjustments of documentation related to
stdcall removal.

- - - - -
54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: mention i386 Windows removal in 9.12 changelog

This commit mentions removal of i386 Windows support and stdcall
related change in the 9.12 changelog.

- - - - -
2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00
hadrian: improve user settings documentation

This patch adds minor improvements to hadrian user settings documentation:

- Add missing `ghc.cpp.opts` case
- Remove non-existent `cxx` case
- Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't
- Add example of passing configure argument to autoconf packages

- - - - -
71010381 by Alex Mason at 2024-06-04T12:09:07-04:00
Add AArch64 CLZ, CTZ, RBIT primop implementations.

Adds support for emitting the clz and rbit instructions, which are
used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#.

- - - - -
44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00
hadrian: add +text_simdutf flavour transformer to allow building text with simdutf

This patch adds a +text_simdutf flavour transformer to hadrian to
allow downstream packagers and users that build from source to opt-in
simdutf support for text, in order to benefit from SIMD speedup at
run-time. It's still disabled by default for the time being.

- - - - -
077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00
ci: enable +text_simdutf flavour transformer for wasm jobs

This commit enables +text_simdutf flavour transformer for wasm jobs,
so text is now built with simdutf support for wasm.

- - - - -
b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Use TemplateHaskellQuotes in instance Lift ByteArray

Resolves #24852

- - - - -
3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Mark addrToByteArray as NOINLINE

This function should never be inlined in order to keep code size small.

- - - - -
98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00
compiler: remove unused CompilerInfo/LinkerInfo types

This patch removes CompilerInfo/LinkerInfo types from the compiler
since they aren't actually used anywhere.

- - - - -
11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00
rts: remove unused PowerPC/IA64 native adjustor code

This commit removes unused PowerPC/IA64 native adjustor code which is
never actually enabled by autoconf/hadrian. Fixes #24920.

- - - - -
5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00
RTS: fix warnings with doing*Profiling (#24918)

- - - - -
accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00
hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows

- - - - -
6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00
autoconf: normalize paths of some build-time dependencies on Windows

This commit applies path normalization via cygpath -m to some
build-time dependencies on Windows. Without this logic, the
/clang64/bin prefixed msys2-style paths cause the build to fail with
--enable-distro-toolchain.

- - - - -
075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00
hadrian: remove OSDarwin mention from speedHack

This commit removes mentioning of OSDarwin from speedHack, since
speedHack is purely for i386 and we no longer support i386 darwin
(#24921).

- - - - -
83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00
compiler: remove 32-bit darwin logic

This commit removes all 32-bit darwin logic from the compiler, given
we no longer support 32-bit apple systems (#24921). Also contains a
bit more cleanup of obsolete i386 windows logic.

- - - - -
1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00
rts: remove 32-bit darwin/ios logic

This commit removes 32-bit darwin/ios related logic from the rts,
given we no longer support them (#24921).

- - - - -
24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00
llvm-targets: remove 32-bit darwin/ios targets

This commit removes 32-bit darwin/ios targets from llvm-targets given
we no longer support them (#24921).

- - - - -
ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00
testsuite: remove 32-bit darwin logic

This commit removes 32-bit darwin logic from the testsuite given it's
no longer supported (#24921). Also contains more cleanup of obsolete
i386 windows logic.

- - - - -
11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00
docs: mention 32-bit darwin/ios removal in 9.12 changelog

This commit mentions removal of 32-bit darwin/ios support (#24921) in
the 9.12 changelog.

- - - - -
7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00
Add firstA and secondA to Data.Bitraversable

Please see https://github.com/haskell/core-libraries-committee/issues/172
for related discussion

- - - - -
3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00
base: Fix name of changelog

Fixes #24899. Also place it under `extra-doc-files` to better reflect
its nature and avoid triggering unnecessary recompilation if it
changes.

- - - - -
1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00
Announce Or-patterns in the release notes for GHC 9.12 (#22596)

Leftover from !9229.

- - - - -
8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00
Improve haddocks of Language.Haskell.Syntax.Pat.Pat

- - - - -
2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00
testsuite: bump T7653 timeout for wasm

- - - - -
990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00
StgToCmm: refactor opTranslate and friends

- Change arguments order to avoid `\args -> ...` lambdas
- Fix documentation
- Rename StgToCmm options ("big" doesn't mean anything)

- - - - -
1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00
NCG x86: remove dead code (#5444)

Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead.

- - - - -
595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00
testsuite: skip objc-hi/objcxx-hi when cross compiling

objc-hi/objcxx-hi should be skipped when cross compiling. The existing
opsys('darwin') predicate only asserts the host system is darwin but
tells us nothing about the target, hence the oversight.

- - - - -
edfe6140 by qqwy at 2024-06-08T11:23:54-04:00
Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw

- - - - -
35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00
rts: cleanup inlining logic

This patch removes pre-C11 legacy code paths related to
INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE
is treated as static inline in most cases (fixes #24945), and also
corrects the comments accordingly.

- - - - -
9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00
CODEOWNERS: add @core-libraries to track base interface changes

A low-tech tactical solution for #24919

- - - - -
580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update CHANGELOG to reflect current version

- - - - -
391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update prologue.txt to reflect package description

- - - - -
3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00
compiler: Clarify comment regarding need for MOVABS

The comment wasn't clear in stating that it was only applicable to
immediate source and memory target operands.

- - - - -
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
9f3126c4 by Simon Peyton Jones at 2024-10-15T09:23:21+01:00
Be more careful about inlining top-level used-once things

Addresses #17910

- - - - -
c4b680f9 by Simon Peyton Jones at 2024-10-15T09:23:21+01:00
Work in progress...

- - - - -
aacb1fdd by Simon Peyton Jones at 2024-10-15T09:26:32+01:00
Fix for #23813

Zap one-shot info when floating a join point to top level

- - - - -
6293e6eb by Simon Peyton Jones at 2024-10-15T09:30:37+01:00
Subtle occurrence analyser point

(make sure this is documented properly before landing all this)

- - - - -
487731e0 by Simon Peyton Jones at 2024-10-15T09:31:43+01:00
Try switching off floatConstants in first FloatOut

...after all, in HEAD, they all get inlined back in!

- - - - -
03dacdc7 by Simon Peyton Jones at 2024-10-15T09:32:38+01:00
Make floatConsts affects only lvlMFE, and even then not functions

T5237 is a good example

- - - - -
0c5d72ee by Simon Peyton Jones at 2024-10-15T09:32:38+01:00
Float bottoming expressions too!

- - - - -
66e524fb by Simon Peyton Jones at 2024-10-15T09:36:28+01:00
Try not doing floatConsts

This avoid flattening, and generating lots of top level
bindings. Instead do it in late-lambda-lift.

I moved late-lambda-lift to run with -O because it is cheap
and valuable.  That's a somewhat orthogonal change, probably
should test separately.

- - - - -
661f32d4 by Simon Peyton Jones at 2024-10-15T09:36:28+01:00
Wibbles to late lambda lifting

- - - - -
020ab3f2 by Simon Peyton Jones at 2024-10-15T09:37:09+01:00
Wibbles to fix VSM

SetLevels floats out top  level things if:
bottoming (possibly lambda) and non-strict
expandable and not a con-app
The not-con-app bit is to avoid flattening big data structures
Expandable bit is because specConstr only deals with con-apps, not with fun-apps or lambdas.

- - - - -
eada7c47 by Simon Peyton Jones at 2024-10-15T09:37:09+01:00
Wibble unused variable

- - - - -
7a4edcc6 by Simon Peyton Jones at 2024-10-15T09:38:09+01:00
Another wibble

- - - - -
bf836675 by Simon Peyton Jones at 2024-10-15T09:38:09+01:00
Comments

- - - - -
2edc09d9 by Simon Peyton Jones at 2024-10-15T09:38:10+01:00
One more wibble

- - - - -
49ae4964 by Simon Peyton Jones at 2024-10-15T09:38:51+01:00
More care with floating

T5642 still floats out (from inside a lamdba)
   lvl = /\a. L1 @a (L1 @a X)
which is flattened by the next simplifer run, which takes one
extra iteration, but that's a corner case.

- - - - -
bdaa8a6c by Simon Peyton Jones at 2024-10-15T09:38:51+01:00
Wibble

Don't float so much without floatConsts

- - - - -
95c89838 by Simon Peyton Jones at 2024-10-15T09:38:51+01:00
Wibbles (comments etc)

and remove shrinking of LargeRecord

- - - - -
d61bd88f by Simon Peyton Jones at 2024-10-15T09:38:51+01:00
Inline naturally occurring top level 'build's

- - - - -
32c780c1 by Simon Peyton Jones at 2024-10-15T09:39:34+01:00
Inline data structures more aggressively again

- - - - -
b3c65d04 by Simon Peyton Jones at 2024-10-15T09:39:34+01:00
Wibble spec_constr_inhibition

- - - - -
93c2be07 by Simon Peyton Jones at 2024-10-15T15:01:52+01:00
Wibble OccurAnal

- - - - -


10 changed files:

- .ghcid
- + .git-blame-ignore-revs
- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9cd9e338456eb59590018806e43d632638d915ec...93c2be0729576cd43d20cc2fb297effbde7eaa5b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9cd9e338456eb59590018806e43d632638d915ec...93c2be0729576cd43d20cc2fb297effbde7eaa5b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 15:07:17 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 15 Oct 2024 11:07:17 -0400
Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] ttg: Using Text over
 FastString in the AST
Message-ID: <670e8525c302d_1df44043e83810254e@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC


Commits:
73a7c593 by Rodrigo Mesquita at 2024-10-15T16:07:06+01:00
ttg: Using Text over FastString in the AST

Towards the goal of making the AST independent of GHC, this commit
starts the task of replacing usages of `FastString` with `Text` in the
AST (Language.Haskell.* modules).

Even though we /do/ want to use FastStrings -- critically in Names or Ids
-- there is no particular reason for the FastStrings that occur in the
AST proper to be FastStrings. Primarily, ...

Progress towards #21592

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Utils.hs
- compiler/GHC/Data/FastString.hs
- compiler/GHC/Data/StringBuffer.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Lit.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Literal.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/ThToHs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73a7c5934ba3f78213d6c47a0ccc4c00e08b5661

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 15:45:19 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 15 Oct 2024 11:45:19 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/undeprecate-cmmtorawcmmhook
Message-ID: <670e8e0ef0b27_1df4407294301100cb@gitlab.mail>



Cheng Shao pushed new branch wip/undeprecate-cmmtorawcmmhook at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/undeprecate-cmmtorawcmmhook
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 16:15:01 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 15 Oct 2024 12:15:01 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 15 commits: Improve the synopsis and
 description of base
Message-ID: <670e95054260_1df4408c79a411531b@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
503890bb by Hécate Moonlight at 2024-10-14T09:25:29-04:00
Improve the synopsis and description of base

(cherry picked from commit 0eb2265d816f733094506034ba6285a447ebd3a5)

- - - - -
fb82ee70 by Torsten Schmits at 2024-10-14T10:11:21-04:00
finder: Add `IsBootInterface` to finder cache keys

Backport note: I have ported `uncacheModule` instead of removing it as
is done in 0d170eafacba55325dc00d0434d4462275d4376e since the necessary
type change is likely easier for possible GHC API users to accommodate
than outright removal.

(cherry picked from commit fff55592a7b9c9487c043d055f2d0d77fa549f4e)

- - - - -
c6c76e2e by Cheng Shao at 2024-10-14T10:17:28-04:00
driver: always merge objects when possible

This patch makes the driver always merge objects with `ld -r` when
possible, and only fall back to calling `ar -L` when merge objects
command is unavailable. This completely reverts !8887 and !12313,
given more fixes in Cabal seems to be needed to avoid breaking certain
configurations and the maintainence cost is exceeding the behefits in
this case :/

(cherry picked from commit 631cefec222e2db951c58db0b15a8d80ef5549cb)

- - - - -
dd93c425 by Simon Peyton Jones at 2024-10-14T10:31:21-04:00
Deal with duplicate tyvars in type declarations

GHC was outright crashing before this fix: #24604

(cherry picked from commit faa30b41a6f941627ddeeba805815b2742d312d1)

- - - - -
6101a9b5 by sheaf at 2024-10-14T10:35:26-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

(cherry picked from commit 694489edf35c35b29fbdf09a8e3fdc404469858f)

- - - - -
5ea0140c by sheaf at 2024-10-14T10:35:26-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

(cherry picked from commit 06ae85071b95376bd1eb354f7cc7901aed45b625)

- - - - -
05152a57 by Zubin Duggal at 2024-10-14T10:59:21-04:00
testsuite: use copy_files in T23405

This prevents the tree from being dirtied when the file is modified.

(cherry picked from commit 8106e695bb912e60a338908a2b6efc5b0644c9c1)

- - - - -
7326051e by Simon Peyton Jones at 2024-10-14T11:53:29-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

(cherry picked from commit 083703a12cd34369e7ed2f0efc4a5baee47aedab)

- - - - -
6b790e6c by Simon Peyton Jones at 2024-10-14T11:53:58-04:00
Wibbles

(cherry picked from commit 0dfaeb66fb8457e7339abbd44d5c53a81ad8ae3a)

- - - - -
454e2165 by Simon Peyton Jones at 2024-10-14T11:53:58-04:00
Spelling errors

(cherry picked from commit 09d24d828e48c2588a317e6dad711f8673983703)

- - - - -
a3a6da7e by Torsten Schmits at 2024-10-14T11:53:58-04:00
add test that runs MakeDepend on thousands of modules

(cherry picked from commit 7875e8cbe5d9b69a1a77354317b2bf9478172686)

- - - - -
2e6704de by Matthew Pickering at 2024-10-14T11:59:27-04:00
Compatibility with 9.8.1 as boot compiler

This fixes several compatability issues when using 9.8.1 as the boot
compiler.

* Some ghc-prim bounds need relaxing
* ghc is no longer wired in, so we have to remove the -this-unit-id ghc
  call.

Fixes #24605

(cherry picked from commit ef3d20f83499cf129b1cacac07906b8d6188fc17)

- - - - -
a5ce5c45 by Ben Gamari at 2024-10-14T12:18:06-04:00
Revert "NCG: Fix a bug in jump shortcutting."

This commit was wrong, as noted in the `master` revert cfeb70d3fed9c135295359296208bd800bab418f.
It appears to have ultimately been superceded by 0fe2b410ac0d8951f07ffcc9f3c6c97bc312df48
which is already present in `ghc-9.8`.

This reverts commit 44e119c9b7622f76b1b7e8d22548376b2591402d.

- - - - -
1f43950e by Ben Gamari at 2024-10-14T12:36:03-04:00
hadrian: Update bootstrap plans

- - - - -
8f7adb8a by Ben Gamari at 2024-10-15T08:58:56-04:00
Bump version to 9.8.3

- - - - -


22 changed files:

- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs
- configure.ac
- hadrian/bootstrap/plan-9_4_1.json
- hadrian/bootstrap/plan-9_4_2.json
- hadrian/bootstrap/plan-9_4_3.json


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/846acd2206c0eaa3056a0bee17a6951fc3033331...8f7adb8a83d3045f5f81b738bdfacef14ef9b77c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/846acd2206c0eaa3056a0bee17a6951fc3033331...8f7adb8a83d3045f5f81b738bdfacef14ef9b77c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 17:34:27 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 15 Oct 2024 13:34:27 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 4 commits: Bump semaphore-compat submodule
 back to 1.0.0
Message-ID: <670ea7a317a2_1df440bcddd812826c@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
c3dedd00 by Ben Gamari at 2024-10-15T12:51:53-04:00
Bump semaphore-compat submodule back to 1.0.0

This only drops a one-sentence change in Haddocks.

- - - - -
4a9f4d76 by Ben Gamari at 2024-10-15T13:28:36-04:00
docs: Drop Included Libraries from old release notes

- - - - -
6cc77976 by Ben Gamari at 2024-10-15T13:29:18-04:00
Update autoconf scripts

Scripts taken from autoconf 00b15927496058d23e6258a28d8996f87cf1f191

- - - - -
c332cb09 by Ben Gamari at 2024-10-15T13:32:31-04:00
gitlab-ci: Update bootstrap_matrix

- - - - -


6 changed files:

- .gitlab-ci.yml
- config.guess
- config.sub
- docs/users_guide/9.8.1-notes.rst
- docs/users_guide/9.8.2-notes.rst
- libraries/semaphore-compat


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -84,7 +84,7 @@ workflow:
   matrix:
     - GHC_VERSION: 9.4.3
       DOCKER_IMAGE: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV"
-    - GHC_VERSION: 9.6.2
+    - GHC_VERSION: 9.6.5
       DOCKER_IMAGE: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10-ghc9_6:$DOCKER_REV"
 
 # Allow linters to fail on draft MRs.


=====================================
config.guess
=====================================
@@ -1,10 +1,10 @@
 #! /bin/sh
 # Attempt to guess a canonical system name.
-#   Copyright 1992-2022 Free Software Foundation, Inc.
+#   Copyright 1992-2024 Free Software Foundation, Inc.
 
 # shellcheck disable=SC2006,SC2268 # see below for rationale
 
-timestamp='2022-05-25'
+timestamp='2024-07-27'
 
 # This file is free software; you can redistribute it and/or modify it
 # under the terms of the GNU General Public License as published by
@@ -47,7 +47,7 @@ me=`echo "$0" | sed -e 's,.*/,,'`
 usage="\
 Usage: $0 [OPTION]
 
-Output the configuration name of the system \`$me' is run on.
+Output the configuration name of the system '$me' is run on.
 
 Options:
   -h, --help         print this help, then exit
@@ -60,13 +60,13 @@ version="\
 GNU config.guess ($timestamp)
 
 Originally written by Per Bothner.
-Copyright 1992-2022 Free Software Foundation, Inc.
+Copyright 1992-2024 Free Software Foundation, Inc.
 
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE."
 
 help="
-Try \`$me --help' for more information."
+Try '$me --help' for more information."
 
 # Parse command line
 while test $# -gt 0 ; do
@@ -102,8 +102,8 @@ GUESS=
 # temporary files to be created and, as you can see below, it is a
 # headache to deal with in a portable fashion.
 
-# Historically, `CC_FOR_BUILD' used to be named `HOST_CC'. We still
-# use `HOST_CC' if defined, but it is deprecated.
+# Historically, 'CC_FOR_BUILD' used to be named 'HOST_CC'. We still
+# use 'HOST_CC' if defined, but it is deprecated.
 
 # Portable tmp directory creation inspired by the Autoconf team.
 
@@ -123,7 +123,7 @@ set_cc_for_build() {
     dummy=$tmp/dummy
     case ${CC_FOR_BUILD-},${HOST_CC-},${CC-} in
 	,,)    echo "int x;" > "$dummy.c"
-	       for driver in cc gcc c89 c99 ; do
+	       for driver in cc gcc c17 c99 c89 ; do
 		   if ($driver -c -o "$dummy.o" "$dummy.c") >/dev/null 2>&1 ; then
 		       CC_FOR_BUILD=$driver
 		       break
@@ -155,6 +155,9 @@ Linux|GNU|GNU/*)
 
 	set_cc_for_build
 	cat <<-EOF > "$dummy.c"
+	#if defined(__ANDROID__)
+	LIBC=android
+	#else
 	#include 
 	#if defined(__UCLIBC__)
 	LIBC=uclibc
@@ -162,6 +165,8 @@ Linux|GNU|GNU/*)
 	LIBC=dietlibc
 	#elif defined(__GLIBC__)
 	LIBC=gnu
+	#elif defined(__LLVM_LIBC__)
+	LIBC=llvm
 	#else
 	#include 
 	/* First heuristic to detect musl libc.  */
@@ -169,6 +174,7 @@ Linux|GNU|GNU/*)
 	LIBC=musl
 	#endif
 	#endif
+	#endif
 	EOF
 	cc_set_libc=`$CC_FOR_BUILD -E "$dummy.c" 2>/dev/null | grep '^LIBC' | sed 's, ,,g'`
 	eval "$cc_set_libc"
@@ -459,7 +465,7 @@ case $UNAME_MACHINE:$UNAME_SYSTEM:$UNAME_RELEASE:$UNAME_VERSION in
 		UNAME_RELEASE=`uname -v`
 		;;
 	esac
-	# Japanese Language versions have a version number like `4.1.3-JL'.
+	# Japanese Language versions have a version number like '4.1.3-JL'.
 	SUN_REL=`echo "$UNAME_RELEASE" | sed -e 's/-/_/'`
 	GUESS=sparc-sun-sunos$SUN_REL
 	;;
@@ -628,7 +634,8 @@ EOF
 		sed 's/^		//' << EOF > "$dummy.c"
 		#include 
 
-		main()
+		int
+		main ()
 			{
 			if (!__power_pc())
 				exit(1);
@@ -712,7 +719,8 @@ EOF
 		#include 
 		#include 
 
-		int main ()
+		int
+		main ()
 		{
 		#if defined(_SC_KERNEL_BITS)
 		    long bits = sysconf(_SC_KERNEL_BITS);
@@ -904,7 +912,7 @@ EOF
 	fi
 	;;
     *:FreeBSD:*:*)
-	UNAME_PROCESSOR=`/usr/bin/uname -p`
+	UNAME_PROCESSOR=`uname -p`
 	case $UNAME_PROCESSOR in
 	    amd64)
 		UNAME_PROCESSOR=x86_64 ;;
@@ -966,11 +974,37 @@ EOF
 	GNU_REL=`echo "$UNAME_RELEASE" | sed -e 's/[-(].*//'`
 	GUESS=$UNAME_MACHINE-unknown-$GNU_SYS$GNU_REL-$LIBC
 	;;
+    x86_64:[Mm]anagarm:*:*|i?86:[Mm]anagarm:*:*)
+	GUESS="$UNAME_MACHINE-pc-managarm-mlibc"
+	;;
+    *:[Mm]anagarm:*:*)
+	GUESS="$UNAME_MACHINE-unknown-managarm-mlibc"
+	;;
     *:Minix:*:*)
 	GUESS=$UNAME_MACHINE-unknown-minix
 	;;
     aarch64:Linux:*:*)
-	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
+	set_cc_for_build
+	CPU=$UNAME_MACHINE
+	LIBCABI=$LIBC
+	if test "$CC_FOR_BUILD" != no_compiler_found; then
+	    ABI=64
+	    sed 's/^	    //' << EOF > "$dummy.c"
+	    #ifdef __ARM_EABI__
+	    #ifdef __ARM_PCS_VFP
+	    ABI=eabihf
+	    #else
+	    ABI=eabi
+	    #endif
+	    #endif
+EOF
+	    cc_set_abi=`$CC_FOR_BUILD -E "$dummy.c" 2>/dev/null | grep '^ABI' | sed 's, ,,g'`
+	    eval "$cc_set_abi"
+	    case $ABI in
+		eabi | eabihf) CPU=armv8l; LIBCABI=$LIBC$ABI ;;
+	    esac
+	fi
+	GUESS=$CPU-unknown-linux-$LIBCABI
 	;;
     aarch64_be:Linux:*:*)
 	UNAME_MACHINE=aarch64_be
@@ -1036,7 +1070,16 @@ EOF
     k1om:Linux:*:*)
 	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
 	;;
-    loongarch32:Linux:*:* | loongarch64:Linux:*:* | loongarchx32:Linux:*:*)
+    kvx:Linux:*:*)
+	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
+	;;
+    kvx:cos:*:*)
+	GUESS=$UNAME_MACHINE-unknown-cos
+	;;
+    kvx:mbr:*:*)
+	GUESS=$UNAME_MACHINE-unknown-mbr
+	;;
+    loongarch32:Linux:*:* | loongarch64:Linux:*:*)
 	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
 	;;
     m32r*:Linux:*:*)
@@ -1191,7 +1234,7 @@ EOF
 	GUESS=$UNAME_MACHINE-pc-sysv4.2uw$UNAME_VERSION
 	;;
     i*86:OS/2:*:*)
-	# If we were able to find `uname', then EMX Unix compatibility
+	# If we were able to find 'uname', then EMX Unix compatibility
 	# is probably installed.
 	GUESS=$UNAME_MACHINE-pc-os2-emx
 	;;
@@ -1332,7 +1375,7 @@ EOF
 		GUESS=ns32k-sni-sysv
 	fi
 	;;
-    PENTIUM:*:4.0*:*)	# Unisys `ClearPath HMP IX 4000' SVR4/MP effort
+    PENTIUM:*:4.0*:*)	# Unisys 'ClearPath HMP IX 4000' SVR4/MP effort
 			# says 
 	GUESS=i586-unisys-sysv4
 	;;
@@ -1554,6 +1597,9 @@ EOF
     *:Unleashed:*:*)
 	GUESS=$UNAME_MACHINE-unknown-unleashed$UNAME_RELEASE
 	;;
+    *:Ironclad:*:*)
+	GUESS=$UNAME_MACHINE-unknown-ironclad
+	;;
 esac
 
 # Do we have a guess based on uname results?
@@ -1577,6 +1623,7 @@ cat > "$dummy.c" <."
 version="\
 GNU config.sub ($timestamp)
 
-Copyright 1992-2022 Free Software Foundation, Inc.
+Copyright 1992-2024 Free Software Foundation, Inc.
 
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE."
 
 help="
-Try \`$me --help' for more information."
+Try '$me --help' for more information."
 
 # Parse command line
 while test $# -gt 0 ; do
@@ -120,7 +120,6 @@ case $# in
 esac
 
 # Split fields of configuration type
-# shellcheck disable=SC2162
 saved_IFS=$IFS
 IFS="-" read field1 field2 field3 field4 <&2
+		echo "Invalid configuration '$1': more than four components" >&2
 		exit 1
 		;;
 	*-*-*-*)
@@ -142,10 +141,21 @@ case $1 in
 		# parts
 		maybe_os=$field2-$field3
 		case $maybe_os in
-			nto-qnx* | linux-* | uclinux-uclibc* \
-			| uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \
-			| netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \
-			| storm-chaos* | os2-emx* | rtmk-nova*)
+			  cloudabi*-eabi* \
+			| kfreebsd*-gnu* \
+			| knetbsd*-gnu* \
+			| kopensolaris*-gnu* \
+			| linux-* \
+			| managarm-* \
+			| netbsd*-eabi* \
+			| netbsd*-gnu* \
+			| nto-qnx* \
+			| os2-emx* \
+			| rtmk-nova* \
+			| storm-chaos* \
+			| uclinux-gnu* \
+			| uclinux-uclibc* \
+			| windows-* )
 				basic_machine=$field1
 				basic_os=$maybe_os
 				;;
@@ -160,8 +170,12 @@ case $1 in
 		esac
 		;;
 	*-*)
-		# A lone config we happen to match not fitting any pattern
 		case $field1-$field2 in
+			# Shorthands that happen to contain a single dash
+			convex-c[12] | convex-c3[248])
+				basic_machine=$field2-convex
+				basic_os=
+				;;
 			decstation-3100)
 				basic_machine=mips-dec
 				basic_os=
@@ -169,28 +183,88 @@ case $1 in
 			*-*)
 				# Second component is usually, but not always the OS
 				case $field2 in
-					# Prevent following clause from handling this valid os
+					# Do not treat sunos as a manufacturer
 					sun*os*)
 						basic_machine=$field1
 						basic_os=$field2
 						;;
-					zephyr*)
-						basic_machine=$field1-unknown
-						basic_os=$field2
-						;;
 					# Manufacturers
-					dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \
-					| att* | 7300* | 3300* | delta* | motorola* | sun[234]* \
-					| unicom* | ibm* | next | hp | isi* | apollo | altos* \
-					| convergent* | ncr* | news | 32* | 3600* | 3100* \
-					| hitachi* | c[123]* | convex* | sun | crds | omron* | dg \
-					| ultra | tti* | harris | dolphin | highlevel | gould \
-					| cbm | ns | masscomp | apple | axis | knuth | cray \
-					| microblaze* | sim | cisco \
-					| oki | wec | wrs | winbond)
+					  3100* \
+					| 32* \
+					| 3300* \
+					| 3600* \
+					| 7300* \
+					| acorn \
+					| altos* \
+					| apollo \
+					| apple \
+					| atari \
+					| att* \
+					| axis \
+					| be \
+					| bull \
+					| cbm \
+					| ccur \
+					| cisco \
+					| commodore \
+					| convergent* \
+					| convex* \
+					| cray \
+					| crds \
+					| dec* \
+					| delta* \
+					| dg \
+					| digital \
+					| dolphin \
+					| encore* \
+					| gould \
+					| harris \
+					| highlevel \
+					| hitachi* \
+					| hp \
+					| ibm* \
+					| intergraph \
+					| isi* \
+					| knuth \
+					| masscomp \
+					| microblaze* \
+					| mips* \
+					| motorola* \
+					| ncr* \
+					| news \
+					| next \
+					| ns \
+					| oki \
+					| omron* \
+					| pc533* \
+					| rebel \
+					| rom68k \
+					| rombug \
+					| semi \
+					| sequent* \
+					| siemens \
+					| sgi* \
+					| siemens \
+					| sim \
+					| sni \
+					| sony* \
+					| stratus \
+					| sun \
+					| sun[234]* \
+					| tektronix \
+					| tti* \
+					| ultra \
+					| unicom* \
+					| wec \
+					| winbond \
+					| wrs)
 						basic_machine=$field1-$field2
 						basic_os=
 						;;
+					zephyr*)
+						basic_machine=$field1-unknown
+						basic_os=$field2
+						;;
 					*)
 						basic_machine=$field1
 						basic_os=$field2
@@ -271,26 +345,6 @@ case $1 in
 				basic_machine=arm-unknown
 				basic_os=cegcc
 				;;
-			convex-c1)
-				basic_machine=c1-convex
-				basic_os=bsd
-				;;
-			convex-c2)
-				basic_machine=c2-convex
-				basic_os=bsd
-				;;
-			convex-c32)
-				basic_machine=c32-convex
-				basic_os=bsd
-				;;
-			convex-c34)
-				basic_machine=c34-convex
-				basic_os=bsd
-				;;
-			convex-c38)
-				basic_machine=c38-convex
-				basic_os=bsd
-				;;
 			cray)
 				basic_machine=j90-cray
 				basic_os=unicos
@@ -713,15 +767,26 @@ case $basic_machine in
 		vendor=dec
 		basic_os=tops20
 		;;
-	delta | 3300 | motorola-3300 | motorola-delta \
-	      | 3300-motorola | delta-motorola)
+	delta | 3300 | delta-motorola | 3300-motorola | motorola-delta | motorola-3300)
 		cpu=m68k
 		vendor=motorola
 		;;
-	dpx2*)
+	# This used to be dpx2*, but that gets the RS6000-based
+	# DPX/20 and the x86-based DPX/2-100 wrong.  See
+	# https://oldskool.silicium.org/stations/bull_dpx20.htm
+	# https://www.feb-patrimoine.com/english/bull_dpx2.htm
+	# https://www.feb-patrimoine.com/english/unix_and_bull.htm
+	dpx2 | dpx2[23]00 | dpx2[23]xx)
 		cpu=m68k
 		vendor=bull
-		basic_os=sysv3
+		;;
+	dpx2100 | dpx21xx)
+		cpu=i386
+		vendor=bull
+		;;
+	dpx20)
+		cpu=rs6000
+		vendor=bull
 		;;
 	encore | umax | mmax)
 		cpu=ns32k
@@ -836,18 +901,6 @@ case $basic_machine in
 	next | m*-next)
 		cpu=m68k
 		vendor=next
-		case $basic_os in
-		    openstep*)
-		        ;;
-		    nextstep*)
-			;;
-		    ns2*)
-		      basic_os=nextstep2
-			;;
-		    *)
-		      basic_os=nextstep3
-			;;
-		esac
 		;;
 	np1)
 		cpu=np1
@@ -936,14 +989,13 @@ case $basic_machine in
 		;;
 
 	*-*)
-		# shellcheck disable=SC2162
 		saved_IFS=$IFS
 		IFS="-" read cpu vendor <&2
+				echo "Invalid configuration '$1': machine '$cpu-$vendor' not recognized" 1>&2
 				exit 1
 				;;
 		esac
@@ -1306,11 +1491,12 @@ esac
 
 # Decode manufacturer-specific aliases for certain operating systems.
 
-if test x$basic_os != x
+if test x"$basic_os" != x
 then
 
 # First recognize some ad-hoc cases, or perhaps split kernel-os, or else just
 # set os.
+obj=
 case $basic_os in
 	gnu/linux*)
 		kernel=linux
@@ -1325,7 +1511,6 @@ case $basic_os in
 		os=`echo "$basic_os" | sed -e 's|nto-qnx|qnx|'`
 		;;
 	*-*)
-		# shellcheck disable=SC2162
 		saved_IFS=$IFS
 		IFS="-" read kernel os <&2
+		fi
+		;;
+	*)
+		echo "Invalid configuration '$1': OS '$os' not recognized" 1>&2
+		exit 1
+		;;
+esac
+
+case $obj in
+	aout* | coff* | elf* | pe*)
+		;;
+	'')
+		# empty is fine
+		;;
 	*)
-		echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2
+		echo "Invalid configuration '$1': Machine code format '$obj' not recognized" 1>&2
+		exit 1
+		;;
+esac
+
+# Here we handle the constraint that a (synthetic) cpu and os are
+# valid only in combination with each other and nowhere else.
+case $cpu-$os in
+	# The "javascript-unknown-ghcjs" triple is used by GHC; we
+	# accept it here in order to tolerate that, but reject any
+	# variations.
+	javascript-ghcjs)
+		;;
+	javascript-* | *-ghcjs)
+		echo "Invalid configuration '$1': cpu '$cpu' is not valid with os '$os$obj'" 1>&2
 		exit 1
 		;;
 esac
 
 # As a final step for OS-related things, validate the OS-kernel combination
 # (given a valid OS), if there is a kernel.
-case $kernel-$os in
-	linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* \
-		   | linux-musl* | linux-relibc* | linux-uclibc* )
+case $kernel-$os-$obj in
+	linux-gnu*- | linux-android*- | linux-dietlibc*- | linux-llvm*- \
+		    | linux-mlibc*- | linux-musl*- | linux-newlib*- \
+		    | linux-relibc*- | linux-uclibc*- | linux-ohos*- )
+		;;
+	uclinux-uclibc*- | uclinux-gnu*- )
+		;;
+	managarm-mlibc*- | managarm-kernel*- )
 		;;
-	uclinux-uclibc* )
+	windows*-msvc*-)
 		;;
-	-dietlibc* | -newlib* | -musl* | -relibc* | -uclibc* )
+	-dietlibc*- | -llvm*- | -mlibc*- | -musl*- | -newlib*- | -relibc*- \
+		    | -uclibc*- )
 		# These are just libc implementations, not actual OSes, and thus
 		# require a kernel.
-		echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2
+		echo "Invalid configuration '$1': libc '$os' needs explicit kernel." 1>&2
 		exit 1
 		;;
-	kfreebsd*-gnu* | kopensolaris*-gnu*)
+	-kernel*- )
+		echo "Invalid configuration '$1': '$os' needs explicit kernel." 1>&2
+		exit 1
 		;;
-	vxworks-simlinux | vxworks-simwindows | vxworks-spe)
+	*-kernel*- )
+		echo "Invalid configuration '$1': '$kernel' does not support '$os'." 1>&2
+		exit 1
 		;;
-	nto-qnx*)
+	*-msvc*- )
+		echo "Invalid configuration '$1': '$os' needs 'windows'." 1>&2
+		exit 1
 		;;
-	os2-emx)
+	kfreebsd*-gnu*- | knetbsd*-gnu*- | netbsd*-gnu*- | kopensolaris*-gnu*-)
+		;;
+	vxworks-simlinux- | vxworks-simwindows- | vxworks-spe-)
+		;;
+	nto-qnx*-)
 		;;
-	*-eabi* | *-gnueabi*)
+	os2-emx-)
 		;;
-	-*)
+	rtmk-nova-)
+		;;
+	*-eabi*- | *-gnueabi*-)
+		;;
+	none--*)
+		# None (no kernel, i.e. freestanding / bare metal),
+		# can be paired with an machine code file format
+		;;
+	-*-)
 		# Blank kernel with real OS is always fine.
 		;;
-	*-*)
-		echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2
+	--*)
+		# Blank kernel and OS with real machine code file format is always fine.
+		;;
+	*-*-*)
+		echo "Invalid configuration '$1': Kernel '$kernel' not known to work with OS '$os'." 1>&2
 		exit 1
 		;;
 esac
@@ -1813,7 +2273,7 @@ case $vendor in
 			*-riscix*)
 				vendor=acorn
 				;;
-			*-sunos*)
+			*-sunos* | *-solaris*)
 				vendor=sun
 				;;
 			*-cnk* | *-aix*)
@@ -1883,7 +2343,7 @@ case $vendor in
 		;;
 esac
 
-echo "$cpu-$vendor-${kernel:+$kernel-}$os"
+echo "$cpu-$vendor${kernel:+-$kernel}${os:+-$os}${obj:+-$obj}"
 exit
 
 # Local variables:


=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -334,48 +334,3 @@ will need to avoid using a bundled import (e.g. by qualification): ::
 
     import Data.Text.Array as A
 
-
-Included libraries
-~~~~~~~~~~~~~~~~~~
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/semaphore-compat/semaphore-compat.cabal: Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable


=====================================
docs/users_guide/9.8.2-notes.rst
=====================================
@@ -121,48 +121,3 @@ Core libraries
 - Bump ``unix`` to 2.8.4.0
 - Bump ``bytestring`` to 0.12.1.0
 - Bump ``text`` to 2.1.1
-
-Included libraries
-------------------
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/semaphore-compat/semaphore-compat.cabal: Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable


=====================================
libraries/semaphore-compat
=====================================
@@ -1 +1 @@
-Subproject commit c8fc7b1757b4eecbd10239038fbc6602340105b1
+Subproject commit ec34791e402e9e6d01623eba90284e8129eb8dba



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8f7adb8a83d3045f5f81b738bdfacef14ef9b77c...c332cb09f1bc767536bd2afd12c9ccbcf0a34289

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8f7adb8a83d3045f5f81b738bdfacef14ef9b77c...c332cb09f1bc767536bd2afd12c9ccbcf0a34289
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 18:01:14 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Tue, 15 Oct 2024 14:01:14 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-4
Message-ID: <670eadea18c71_6594513ab28780c4@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 18:54:29 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 15 Oct 2024 14:54:29 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Changed
 import from Ghc.  module to L.H.S module
Message-ID: <670eba651c652_11005616a3f010555b@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
1b9f398a by Simon Peyton Jones at 2024-10-15T14:54:18-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -


3 changed files:

- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- docs/users_guide/9.14.1-notes.rst


Changes:

=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -31,10 +31,9 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat
 
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
+import Language.Haskell.Syntax.Basic ( Fixity )
 
-import GHC.Types.Fixity (Fixity)
 import GHC.Types.Basic (InlinePragma)
-
 import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -94,13 +94,12 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
 import Language.Haskell.Syntax.Binds
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
-import Language.Haskell.Syntax.Basic (Role)
+import Language.Haskell.Syntax.Basic (Role, LexicalFixity)
 import Language.Haskell.Syntax.Specificity (Specificity)
 
 import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation
                        ,TyConFlavour(..), TypeOrData(..))
 import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
-import GHC.Types.Fixity (LexicalFixity)
 
 import GHC.Unit.Module.Warnings (WarningTxt)
 


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -11,6 +11,15 @@ for specific guidance on migrating programs to this release.
 Language
 ~~~~~~~~
 
+* ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
+  by `GHC Proposal 516: add warning for incomplete record selectors _`.
+  Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
+  Workaround: add ``-Werror=no-incomplete-record-selectors``.
+
+  Note that this warning is at least
+  as serious as a warning about missing patterns from a function definition, perhaps even
+  more so, since it is invisible in the source program.
+
 Compiler
 ~~~~~~~~
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d045238bf74edfb4fabd2ca4f8086f56e44ffd8a...1b9f398ae94206d0cda2e644729a88e835db1ef7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d045238bf74edfb4fabd2ca4f8086f56e44ffd8a...1b9f398ae94206d0cda2e644729a88e835db1ef7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 19:13:17 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 15 Oct 2024 15:13:17 -0400
Subject: [Git][ghc/ghc][wip/ubsan] 534 commits: template-haskell: Move
 wired-ins to ghc-internal
Message-ID: <670ebecd6032b_1100562fd8d41089c@gitlab.mail>



Cheng Shao pushed to branch wip/ubsan at Glasgow Haskell Compiler / GHC


Commits:
228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00
template-haskell: Move wired-ins to ghc-internal

Thus we make `template-haskell` reinstallable and keep it as the public
API for Template Haskell.
All of the wired-in identifiers are moved to `ghc-internal`.
This necessitates also moving much of `ghc-boot-th` into `ghc-internal`.
These modules are then re-exported from `ghc-boot-th` and
`template-haskell`.
To avoid a dependency on `template-haskell` from `lib:ghc`, we instead
depend on the TH ASTs via `ghc-boot-th`.

As `template-haskell` no longer has special status, we can drop the
logic adding an implicit dependency on `template-haskell` when using TH.
We can also drop the `template-haskell-next` package, which was
previously used when bootstrapping.

When bootstrapping, we need to vendor the TH AST modules from
`ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap`
cabal flag as before. See Note [Bootstrapping Template Haskell].

We split out a GHC.Internal.TH.Lift module resolving #24752.
This module is only built when not bootstrapping.

Resolves #24703

-------------------------
Metric Increase:
    ghc_boot_th_dir
    ghc_boot_th_so
-------------------------

- - - - -
62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00
testsuite: mark tests broken by #24886

Now that `template-haskell` is no longer wired-in.
These tests are triggering #24886, and so need to be marked broken.

- - - - -
3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00
rts: fix missing function prototypes in ClosureMacros.h

- - - - -
e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00
UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument.

This allows representing functions like:

    int foo(void);

to be imported like this:

    foreign import ccall "a_number_c"
      c_number :: (# #) -> Int64#

Which can be useful when the imported function isn't implicitly
stateful.

- - - - -
d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00
ci: Update ci-images commit for fedora38 image

The fedora38 nightly job has been failing for quite a while because
`diff` was no longer installed. The ci-images bump explicitly installs
`diffutils` into these images so hopefully they now pass again.

- - - - -
3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00
Update exactprint docs

- - - - -
77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00
Incorporate review feedback

- - - - -
87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00
Remove no longer relevant reference to comments

- - - - -
05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00
Replace outdated code example

- - - - -
45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00
Reword error resulting from missing -XBangPatterns.

It can be the result of either a bang pattern or strict binding,
so now we say so instead of claiming it must be a bang pattern.

Fixes #21032

- - - - -
e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00
testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x

- - - - -
7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: ensure gc_thread/gen_workspace is allocated with proper alignment

gc_thread/gen_workspace are required to be aligned by 64 bytes.
However, this property has not been properly enforced before, and
numerous alignment violations at runtime has been caught by
UndefinedBehaviorSanitizer that look like:

```
rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment
0x0000027a3390: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8

rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment
0x0000027a3450: note: pointer points here
 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00 00 00 00 00  00 00 00 00
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13
```

This patch fixes the gc_thread/gen_workspace misalignment issue by
explicitly allocating them with alignment constraint.

- - - - -
c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: fix an unaligned load in nonmoving gc

This patch fixes an unaligned load in nonmoving gc by ensuring the
closure address is properly untagged first before attempting to
prefetch its header. The unaligned load is reported by
UndefinedBehaviorSanitizer:

```
rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment
0x0042005f3a71: note: pointer points here
 00 00 00  98 43 13 8e 12 7f 00 00  50 3c 5f 00 42 00 00 00  58 17 b7 92 12 7f 00 00  89 cb 5e 00 42
              ^
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9
```

This issue had previously gone unnoticed since it didn't really harm
runtime correctness, the invalid header address directly loaded from a
tagged pointer is only used as prefetch address and will not cause
segfaults. However, it still should be corrected because the prefetch
would be rendered useless by this issue, and untagging only involves a
single bitwise operation without memory access so it's cheap enough to
add.

- - - - -
05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00
rts: use __builtin_offsetof to implement STG_FIELD_OFFSET

This patch fixes the STG_FIELD_OFFSET macro definition by using
__builtin_offsetof, which is what gcc/clang uses to implement offsetof
in standard C. The previous definition that uses NULL pointer involves
subtle undefined behavior in C and thus reported by
UndefinedBehaviorSanitizer as well:

```
rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_')
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58
```

- - - - -
5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00
JS: remove useless h$CLOCK_REALTIME (#23202)

- - - - -
95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00
ghcup-metadata: Fix metadata generation

There were some syntax errors in the generation script which were
preventing it from running.

I have tested this with:

```
nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525
```

which completed successfully.

- - - - -
1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00
Add diagrams to Arrows documentation

This adds diagrams to the documentation of Arrows, similar to the ones found on
https://www.haskell.org/arrows/.

It does not add diagrams for ArrowChoice for the time being, mainly because it's
not clear to me how to visually distinguish them from the ones for Arrow. Ideally,
you might want to do something like highlight the arrows belonging to the same
tuple or same Either in common colors, but that's not really possible with unicode.

- - - - -
d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00
Make UnsafeSNat et al. into pattern synonyms

...so that they do not cause coerce to bypass the nominal
role on the corresponding singleton types when they are imported.
See Note [Preventing unsafe coercions for singleton types] and
the discussion at #23478.

This also introduces unsafeWithSNatCo (and analogues for Char
and Symbol) so that users can still access the dangerous coercions
that importing the real constructors would allow, but only in a
very localized way.

- - - - -
0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00
hadrian: build C/C++ with split sections when enabled

When split sections is enabled, ensure -fsplit-sections is passed to
GHC as well when invoking GHC to compile C/C++; and pass
-ffunction-sections -fdata-sections to gcc/clang when compiling C/C++
with the hadrian Cc builder. Fixes #23381.

- - - - -
02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00
driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled

When -fsplit-sections is passed to GHC, pass -ffunction-sections
-fdata-sections to gcc/clang when building C/C++. Previously,
-fsplit-sections was only respected by the NCG/LLVM backends, but not
the unregisterised backend; the GHC driver did not pass
-fdata-sections and -ffunction-sections to the C compiler, which
resulted in excessive executable sizes.

Fixes #23381.

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00
testsuite: mark process005 as fragile on JS

- - - - -
34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00
Add -Wderiving-typeable to -Wall

Deriving `Typeable` does nothing, and it hasn't done for a long while.

There has also been a warning for a long while which warns you about
uselessly deriving it but it wasn't enabled in -Wall.

Fixes #24784

- - - - -
75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00
docs: Fix formatting of changelog entries

- - - - -
303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00
docs: Fix link to injective type families paper

Closes #24863

- - - - -
df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00
ghc-internal: Fix package description

The previous description was inherited from `base` and was inappropriate
for `ghc-internal`. Also fix the maintainer and bug reporting fields.

Closes #24906.

- - - - -
bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00
compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans

This patch removes special consideration for ArchWasm32 in
cmmDoCmmSwitchPlans, which means the compiler will now disable
cmmImplementSwitchPlans for wasm unreg backend, just like unreg
backend of other targets. We enabled it in the past to workaround some
compile-time panic in older versions of LLVM, but those panics are no
longer present, hence no need to keep this workaround.

- - - - -
7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00
utils: add hie.yaml config file for ghc-config

Add hie.yaml to ghc-config project directory so it can be edited using
HLS.

- - - - -
1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00
hadrian: handle findExecutable "" gracefully

hadrian may invoke findExecutable "" at run-time due to a certain
program is not found by configure script. Which is fine and
findExecutable is supposed to return Nothing in this case. However, on
Windows there's a directory bug that throws an exception (see
https://github.com/haskell/directory/issues/180), so we might as well
use a wrapper for findExecutable and handle exceptions gracefully.

- - - - -
4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00
configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails

When configure fails to find LLC/OPT/LLVMAS within supported version
range, it used to set "llc"/"opt"/"clang" as fallback values. This
behavior is particularly troublesome when the user has llc/opt/clang
with other versions in their PATH and run the testsuite, since hadrian
will incorrectly assume have_llvm=True and pass that to the testsuite
driver, resulting in annoying optllvm test failures (#23186). If
configure determines llc/opt/clang wouldn't work, then we shouldn't
pretend it'll work at all, and the bindist configure will invoke
FIND_LLVM_PROG check again at install time anyway.

- - - - -
5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00
Introduce UniqueSet and use it to replace 'UniqSet Unique'

'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique',
which is wasting space (associated key/value are always the same).

Fix #23572 and #23605

- - - - -
e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00
Improve template-haskell haddocks

Closes #15822

- - - - -
ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00
Bump max LLVM version to 19 (not inclusive)

- - - - -
92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00
ci: Update CI images to test LLVM 18

The debian12 image in this commit has llvm 18 installed.

- - - - -
adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00
Unicode: make ucd2haskell build-able again

ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten.

Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures:
1. Ghc module path environment got a suffix with `src`.
2. Generated code got
2.1 `GHC.Internal` prefix for `Data.*`.
2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure.

- - - - -
ad56fd84 by Jade at 2024-06-01T09:36:29-04:00
Replace 'NB' with 'Note' in error messages

- - - - -
6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00
compiler: fix -ddump-cmm-raw when compiling .cmm

This patch fixes missing -ddump-cmm-raw output when compiling .cmm,
which is useful for debugging cmm related codegen issues.

- - - - -
1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00
Print namespace specifiers in FixitySig's Outputable instance

For whatever reason, the `Outputable` instance for `FixitySig` simply did not
print out namespace specifiers, leading to the confusing `-ddump-splices`
output seen in #24911. This patch corrects this oversight.

Fixes #24911.

- - - - -
cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00
Configure: display C++ compiler path

- - - - -
f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable PIC for in-tree GMP on wasm32

This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC
unconditionally adds undesired code size and runtime overhead for
wasm32.

- - - - -
1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: disable in-tree gmp fft code path for wasm32

This patch disables in-tree GMP FFT code paths for wasm32 target in
order to give up some performance of multiplying very large operands
in exchange for reduced code size.

- - - - -
06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00
hadrian: build in-tree GMP with malloc-notreentrant on wasm32

This patch makes hadrian build in-tree GMP with the
--enable-alloca=malloc-notreentrant configure option. We will only
need malloc-reentrant when we have threaded RTS and SMP support on
wasm32, which will take some time to happen, before which we should
use malloc-notreentrant to avoid undesired runtime overhead.

- - - - -
9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00
Set package include paths when assembling .S files

Fixes #24839.

Co-authored-by: Sylvain Henry <hsyl20 at gmail.com>

- - - - -
4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00
Improve performance of genericWordQuotRem2Op (#22966)

Implements the algorithm from compiler-rt's udiv128by64to64default. This
rewrite results in a roughly 24x improvement in runtime on AArch64 (and
likely any other arch that uses it).

- - - - -
ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00
testsuite: mark T7773 as fragile on wasm

- - - - -
c8ece0df by Fendor at 2024-06-03T19:43:22-04:00
Migrate `Finder` component to `OsPath`, fixed #24616

For each module in a GHCi session, we keep alive one `ModLocation`.
A `ModLocation` is fairly inefficiently packed, as `String`s are
expensive in memory usage.

While benchmarking the agda codebase, we concluded that we keep alive
around 11MB of `FilePath`'s, solely retained by `ModLocation`.

We provide a more densely packed encoding of `ModLocation`, by moving
from `FilePath` to `OsPath`. Further, we migrate the full `Finder`
component to `OsPath` to avoid unnecessary transformations.
As the `Finder` component is well-encapsulated, this requires only a
minimal amount of changes in other modules.

We introduce pattern synonym for 'ModLocation' which maintains backwards
compatibility and avoids breaking consumers of 'ModLocation'.

- - - - -
0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00
compiler: emit NaturallyAligned when element type & index type are the same width

This commit fixes a subtle mistake in alignmentFromTypes that used to
generate Unaligned when element type & index type are the same width.
Fixes #24930.

- - - - -
18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00
Parser: Remove unused `apats` rule

- - - - -
38757c30 by David Knothe at 2024-06-04T05:05:27-04:00
Implement Or Patterns (#22596)

This commit introduces a new language extension, `-XOrPatterns`, as described in
GHC Proposal 522.

An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ...,
`patk` succeed, in this order.

See also the summary `Note [Implmentation of OrPatterns]`.

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>

- - - - -
395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00
compiler/ghci/rts: remove stdcall support completely

We have formally dropped i386 windows support (#18487) a long time
ago. The stdcall foreign call convention is only used by i386 windows,
and the legacy logic around it is a significant maintenance burden for
future work that adds arm64 windows support (#24603). Therefore, this
patch removes stdcall support completely from the compiler as well as
the RTS (#24883):

- stdcall is still recognized as a FFI calling convention in Haskell
  syntax. GHC will now unconditionally emit a warning
  (-Wunsupported-calling-conventions) and treat it as ccall.
- Apart from minimum logic to support the parsing and warning logic,
  all other code paths related to stdcall has been completely stripped
  from the compiler.
- ghci only supports FFI_DEFAULT_ABI and ccall convention from now on.
- FFI foreign export adjustor code on all platforms no longer handles
  the stdcall case and only handles ccall from now on.
- The Win32 specific parts of RTS no longer has special code paths for
  stdcall.

This commit is the final nail on the coffin for i386 windows support.
Further commits will perform more housecleaning to strip the legacy
code paths and pave way for future arm64 windows support.

- - - - -
d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00
rts: remove legacy i386 windows code paths

This commit removes some legacy i386 windows related code paths in the
RTS, given this target is no longer supported.

- - - - -
a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00
autoconf: remove i386 windows related logic

This commit removes legacy i386 windows logic in autoconf scripts.

- - - - -
91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00
llvm-targets: remove i386 windows support

This commit removes i386 windows from llvm-targets and the script to
generate it.

- - - - -
65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00
libraries/utils: remove stdcall related legacy logic

This commit removes stdcall related legacy logic in libraries and
utils. ccall should be used uniformly for all supported windows hosts
from now on.

- - - - -
d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00
testsuite: adapt the testsuite for stdcall removal

This patch adjusts test cases to handle the stdcall removal:

- Some stdcall usages are replaced with ccall since stdcall doesn't
  make sense anymore.
- We also preserve some stdcall usages, and check in the expected
  warning messages to ensure GHC always warn about stdcall usages
  (-Wunsupported-calling-conventions) as expected.
- Error code testsuite coverage is slightly improved,
  -Wunsupported-calling-conventions is now tested.
- Obsolete code paths related to i386 windows are also removed.

- - - - -
cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: minor adjustments for stdcall removal

This commit include minor adjustments of documentation related to
stdcall removal.

- - - - -
54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00
docs: mention i386 Windows removal in 9.12 changelog

This commit mentions removal of i386 Windows support and stdcall
related change in the 9.12 changelog.

- - - - -
2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00
hadrian: improve user settings documentation

This patch adds minor improvements to hadrian user settings documentation:

- Add missing `ghc.cpp.opts` case
- Remove non-existent `cxx` case
- Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't
- Add example of passing configure argument to autoconf packages

- - - - -
71010381 by Alex Mason at 2024-06-04T12:09:07-04:00
Add AArch64 CLZ, CTZ, RBIT primop implementations.

Adds support for emitting the clz and rbit instructions, which are
used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#.

- - - - -
44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00
hadrian: add +text_simdutf flavour transformer to allow building text with simdutf

This patch adds a +text_simdutf flavour transformer to hadrian to
allow downstream packagers and users that build from source to opt-in
simdutf support for text, in order to benefit from SIMD speedup at
run-time. It's still disabled by default for the time being.

- - - - -
077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00
ci: enable +text_simdutf flavour transformer for wasm jobs

This commit enables +text_simdutf flavour transformer for wasm jobs,
so text is now built with simdutf support for wasm.

- - - - -
b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Use TemplateHaskellQuotes in instance Lift ByteArray

Resolves #24852

- - - - -
3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00
base: Mark addrToByteArray as NOINLINE

This function should never be inlined in order to keep code size small.

- - - - -
98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00
compiler: remove unused CompilerInfo/LinkerInfo types

This patch removes CompilerInfo/LinkerInfo types from the compiler
since they aren't actually used anywhere.

- - - - -
11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00
rts: remove unused PowerPC/IA64 native adjustor code

This commit removes unused PowerPC/IA64 native adjustor code which is
never actually enabled by autoconf/hadrian. Fixes #24920.

- - - - -
5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00
RTS: fix warnings with doing*Profiling (#24918)

- - - - -
accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00
hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows

- - - - -
6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00
autoconf: normalize paths of some build-time dependencies on Windows

This commit applies path normalization via cygpath -m to some
build-time dependencies on Windows. Without this logic, the
/clang64/bin prefixed msys2-style paths cause the build to fail with
--enable-distro-toolchain.

- - - - -
075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00
hadrian: remove OSDarwin mention from speedHack

This commit removes mentioning of OSDarwin from speedHack, since
speedHack is purely for i386 and we no longer support i386 darwin
(#24921).

- - - - -
83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00
compiler: remove 32-bit darwin logic

This commit removes all 32-bit darwin logic from the compiler, given
we no longer support 32-bit apple systems (#24921). Also contains a
bit more cleanup of obsolete i386 windows logic.

- - - - -
1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00
rts: remove 32-bit darwin/ios logic

This commit removes 32-bit darwin/ios related logic from the rts,
given we no longer support them (#24921).

- - - - -
24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00
llvm-targets: remove 32-bit darwin/ios targets

This commit removes 32-bit darwin/ios targets from llvm-targets given
we no longer support them (#24921).

- - - - -
ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00
testsuite: remove 32-bit darwin logic

This commit removes 32-bit darwin logic from the testsuite given it's
no longer supported (#24921). Also contains more cleanup of obsolete
i386 windows logic.

- - - - -
11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00
docs: mention 32-bit darwin/ios removal in 9.12 changelog

This commit mentions removal of 32-bit darwin/ios support (#24921) in
the 9.12 changelog.

- - - - -
7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00
Add firstA and secondA to Data.Bitraversable

Please see https://github.com/haskell/core-libraries-committee/issues/172
for related discussion

- - - - -
3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00
base: Fix name of changelog

Fixes #24899. Also place it under `extra-doc-files` to better reflect
its nature and avoid triggering unnecessary recompilation if it
changes.

- - - - -
1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00
Announce Or-patterns in the release notes for GHC 9.12 (#22596)

Leftover from !9229.

- - - - -
8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00
Improve haddocks of Language.Haskell.Syntax.Pat.Pat

- - - - -
2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00
testsuite: bump T7653 timeout for wasm

- - - - -
990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00
StgToCmm: refactor opTranslate and friends

- Change arguments order to avoid `\args -> ...` lambdas
- Fix documentation
- Rename StgToCmm options ("big" doesn't mean anything)

- - - - -
1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00
NCG x86: remove dead code (#5444)

Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead.

- - - - -
595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00
testsuite: skip objc-hi/objcxx-hi when cross compiling

objc-hi/objcxx-hi should be skipped when cross compiling. The existing
opsys('darwin') predicate only asserts the host system is darwin but
tells us nothing about the target, hence the oversight.

- - - - -
edfe6140 by qqwy at 2024-06-08T11:23:54-04:00
Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw

- - - - -
35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00
rts: cleanup inlining logic

This patch removes pre-C11 legacy code paths related to
INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE
is treated as static inline in most cases (fixes #24945), and also
corrects the comments accordingly.

- - - - -
9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00
CODEOWNERS: add @core-libraries to track base interface changes

A low-tech tactical solution for #24919

- - - - -
580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update CHANGELOG to reflect current version

- - - - -
391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00
ghc-internal: Update prologue.txt to reflect package description

- - - - -
3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00
compiler: Clarify comment regarding need for MOVABS

The comment wasn't clear in stating that it was only applicable to
immediate source and memory target operands.

- - - - -
6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00
JS: establish single source of truth for symbols

In pursuit of: #22736.

This MR moves ad-hoc symbols used throughout the js backend into a
single symbols file. Why? First, this cleans up the code by removing
ad-hoc strings created on the fly and therefore makes the code more
maintainable. Second, it makes it much easier to eventually type these
identifiers.

- - - - -
f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00
rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS

This patch replaces the ad-hoc `MYTASK_USE_TLV` with the
`CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then
we should use that for managing `myTask` in the threaded RTS.

- - - - -
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes

- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:

baling -> bailing

- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems

- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs

- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.

This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.

Fixes #24967

- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message

- - - - -
2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00
Fix a QuickLook bug

This MR fixes the bug exposed by #24676.  The problem was that
quickLookArg was trying to avoid calling tcInstFun unnecessarily; but
it was in fact necessary.  But that in turn forced me into a
significant refactoring, putting more fields into EValArgQL.

Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App

* Instantiation variables are now distinguishable from ordinary
  unification variables, by level number = QLInstVar. This is
  treated like "level infinity".  See Note [The QLInstVar TcLevel]
  in GHC.Tc.Utils.TcType.

* In `tcApp`, we don't track the instantiation variables in a set Delta
  any more; instead, we just tell them apart by their level number.

* EValArgQL now much more clearly captures the "half-done" state
  of typechecking an argument, ready for later resumption.
  See Note [Quick Look at value arguments] in GHC.Tc.Gen.App

* Elminated a bogus (never used) fast-path in
  GHC.Tc.Utils.Instantiate.instCallConstraints
  See Note [Possible fast path for equality constraints]

Many other small refactorings.

- - - - -
1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00
Fix non-compiling extensible record `HasField` example
- - - - -
97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Fix hyperlinker source urls (#24907)

This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to
external modules in the hyperlinker are uniformly generated using splicing the
template given to us instead of attempting to construct the url in an ad-hoc manner.

- - - - -
954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00
haddock: Add name anchor to external source urls from documentation page

URLs for external source links from documentation pages were missing a splice
location for the name.

Fixes #24912

- - - - -
b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00
Prioritise nominal equalities

The main payload of this patch is

* Prioritise nominal equalities in the constraint solver. This
  ameliorates the incompleteness of solving for representational
  constraints over newtypes: see #24887.

   See (EX2) in Note [Decomposing newtype equalities] in
   GHC.Tc.Solver.Equality

In doing this patch I tripped over some other things that I refactored:

* Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate`
  where it seems more at home.

* Clarify the "rewrite role" of a constraint.  I was very puzzled
  about what the role of, say `(Eq a)` might be, but see the new
  Note [The rewrite-role of a constraint].

  In doing so I made predTypeEqRel crash when given a non-equality.
  Usually it expects an equality; but it was being mis-used for
  the above rewrite-role stuff.

- - - - -
cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00
compiler: missing-deriving-strategies suggested fix

Extends the missing-deriving-strategies warning with a suggested fix
that includes which deriving strategies were assumed.

For info about the warning, see comments for
`TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, &
`TcRnNoStandaloneDerivingStrategySpecified`.

For info about the suggested fix, see
`SuggestExplicitDerivingClauseStrategies` &
`SuggestExplicitStandalanoDerivingStrategy`.

docs: Rewords missing-deriving-strategies to mention the suggested fix.

Resolves #24955

- - - - -
4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00
Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat

- - - - -
558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00
rts: use page sized mblocks on wasm

This patch changes mblock size to page size on wasm. It allows us to
simplify our wasi-libc fork, makes it much easier to test third party
libc allocators like emmalloc/mimalloc, as well as experimenting with
threaded RTS in wasm.

- - - - -
b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00
compiler: Make ghc-experimental not wired in

If you need to wire in definitions, then place them in ghc-internal and
reexport them from ghc-experimental.

Ticket #24903

- - - - -
700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00
base: Use a more appropriate unicode arrow for the ByteArray diagram

This commit rectifies the usage of a unicode arrow in favour of one that
doesn't provoke mis-alignment.

- - - - -
cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00
ghcup-metadata: Fix debian version ranges

This was caught by `ghcup-ci` failing and attempting to install a deb12
bindist on deb11.

```
configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got  in ArSupportsDashL_STAGE0. Defaulting to False.
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so)
```

Fixes #24974

- - - - -
7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00
ucd2haskell: remove Streamly dependency + misc

- Remove dead code.
- Remove `streamly` dependency.
- Process files with `bytestring`.
- Replace Unicode files parsers with the corresponding ones from the
  package `unicode-data-parser`.
- Simplify cabal file and rename module
- Regenerate `ghc-internal` Unicode files with new header

- - - - -
4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00
Document how to run haddocks tests (#24976)

Also remove ghc 9.7 requirement

- - - - -
fb629e24 by amesgen at 2024-06-14T00:28:20-04:00
compiler: refactor lower_CmmExpr_Ptr

- - - - -
def46c8c by amesgen at 2024-06-14T00:28:20-04:00
compiler: handle CmmRegOff in lower_CmmExpr_Ptr

- - - - -
ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00
Small documentation update in Quick Look

- - - - -
19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Add hack for #24623

..Th bug in #24623 is randomly triggered by this MR!..

- - - - -
7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Various fixes to type-tidying

This MR was triggered by #24868, but I found a number of bugs
and infelicities in type-tidying as I went along.  Highlights:

* Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid
  using the OccNames of /bound/ variables when tidying /free/
  variables; see the call to `tidyAvoiding`.  That avoid the
  gratuitous renaming which was the cause of #24868. See
     Note [tidyAvoiding] in GHC.Core.TyCo.Tidy

* Refactor and document the tidying of open types.
  See GHC.Core.TyCo.Tidy
     Note [Tidying open types]
     Note [Tidying is idempotent]

* Tidy the coercion variable in HoleCo. That's important so
  that tidied types have tidied kinds.

* Some small renaming to make things consistent.  In particular
  the "X" forms return a new TidyEnv.  E.g.
     tidyOpenType  :: TidyEnv -> Type -> Type
     tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type)

- - - - -
2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00
Wibble

- - - - -
e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00
Wibbles

- - - - -
246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00
Localise a case-binder in SpecConstr.mkSeqs

This small change fixes #24944

See (SCF1) in Note [SpecConstr and strict fields]

- - - - -
a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00
PPC: display foreign label in panic message (cf #23969)

- - - - -
bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00
cmm: Parse MO_BSwap primitive operation

Parsing this operation allows it to be tested using `test-primops` in a
subsequent MR.

- - - - -
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -
118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00
EPA: Add location to Match Pats list

So we can freely modify the pats and the following item spacing will
still be valid when exact printing.

Closes #24862

- - - - -
db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00
compiler: Rejects RULES whose LHS immediately fails to type-check

Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.

Fixes #24026

- - - - -
e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00
Add hscTypecheckRenameWithDiagnostics, for HLS (#24996)

Use runHsc' in runHsc so that both functions can't fall out of sync

We're currently copying parts of GHC code to get structured warnings
in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics`
locally. Once we get this function into GHC we can drop the copied code
in future versions of HLS.

- - - - -
d70abb49 by sheaf at 2024-06-18T18:47:20-04:00
Clarify -XGADTs enables existential quantification

Even though -XGADTs does not turn on -XExistentialQuantification,
it does allow the user of existential quantification syntax, without
needing to use GADT-style syntax.

Fixes #20865

- - - - -
13fdf788 by David Binder at 2024-06-18T18:48:02-04:00
Add RTS flag --read-tix-file (GHC Proposal 612)

This commit introduces the RTS flag `--read-tix-file=<yes|no>` which
controls whether a preexisting .tix file is read in at the beginning
of a program run. The default is currently `--read-tix-file=yes` but
will change to `--read-tix-file=no` in a future release of GHC. For
this reason, whenever a .tix file is read in a warning is emitted to
stderr. This warning can be silenced by explicitly passing the
`--read-tix-file=yes` option. Details can be found in the GHC proposal
cited below.

Users can query whether this flag has been used with the help of the
module `GHC.RTS.Flags`. A new field `readTixFile` was added to the
record `HpcFlags`.

These changes have been discussed and approved in
- GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612
- CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276

- - - - -
f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00
Improve sharing of duplicated values in `ModIface`, fixes #24723

As a `ModIface` often contains duplicated values that are not
necessarily shared, we improve sharing by serialising the `ModIface`
to an in-memory byte array. Serialisation uses deduplication tables, and
deserialisation implicitly shares duplicated values.

This helps reducing the peak memory usage while compiling in
`--make` mode. The peak memory usage is especially smaller when
generating interface files with core expressions
(`-fwrite-if-simplified-core`).

On agda, this reduces the peak memory usage:

* `2.2 GB` to `1.9 GB` for a ghci session.

On `lib:Cabal`, we report:

* `570 MB` to `500 MB` for a ghci session
* `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc

There is a small impact on execution time, around 2% on the agda code
base.

- - - - -
1bab7dde by Fendor at 2024-06-18T18:48:38-04:00
Avoid unneccessarily re-serialising the `ModIface`

To reduce memory usage of `ModIface`, we serialise `ModIface` to an
in-memory byte array, which implicitly shares duplicated values.

This serialised byte array can be reused to avoid work when we actually
write the `ModIface` to disk.
We introduce a new field to `ModIface` which allows us to save the byte
array, and write it direclty to disk if the `ModIface` wasn't changed
after the initial serialisation.

This requires us to change absolute offsets, for example to jump to the
deduplication table for `Name` or `FastString` with relative offsets, as
the deduplication byte array doesn't contain header information, such as
fingerprints.
To allow us to dump the binary blob to disk, we need to replace all
absolute offsets with relative ones.

We introduce additional helpers for `ModIface` binary serialisation, which
construct relocatable binary blobs. We say the binary blob is relocatable,
if the binary representation can be moved and does not contain any
absolute offsets.

Further, we introduce new primitives for `Binary` that allow to create
relocatable binaries, such as `forwardGetRel` and `forwardPutRel`.

-------------------------
Metric Decrease:
    MultiLayerModulesDefsGhcWithCore
Metric Increase:
    MultiComponentModules
    MultiLayerModules
    T10421
    T12150
    T12234
    T12425
    T13035
    T13253-spj
    T13701
    T13719
    T14697
    T15703
    T16875
    T18698b
    T18140
    T18304
    T18698a
    T18730
    T18923
    T20049
    T24582
    T5837
    T6048
    T9198
    T9961
    mhu-perf
-------------------------

These metric increases may look bad, but they are all completely benign,
we simply allocate 1 MB per module for `shareIface`. As this allocation
is quite quick, it has a negligible impact on run-time performance.
In fact, the performance difference wasn't measurable on my local
machine. Reducing the size of the pre-allocated 1 MB buffer avoids these
test failures, but also requires us to reallocate the buffer if the
interface file is too big. These reallocations *did* have an impact on
performance, which is why I have opted to accept all these metric
increases, as the number of allocated bytes is merely a guidance.

This 1MB allocation increase causes a lot of tests to fail that
generally have a low allocation number. E.g., increasing from 40MB to
41MB is a 2.5% increase.
In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a,
T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin
job, where the number of allocated bytes seems to be lower than in other
jobs.
The tests T16875 and T18698b fail on i386-linux for the same reason.

- - - - -
099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00
Improve documentation of @Any@ type.

In particular mention possible uses for non-lifted types.

Fixes #23100.

- - - - -
5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00
Update user guide to indicate support for 64-tuples

- - - - -
4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00
lint notes: Add more info to notes.stdout

When fixing a note reference CI fails with a somewhat confusing diff.
See #21123. This commit adds a line to the output file being compared
which hopefully makes it clear this is the list of broken refs, not all
refs.

Fixes #21123

- - - - -
1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00
docs: Update mention of ($) type in user guide

Fixes #24909

- - - - -
1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00
Remove duplicate Anno instances

- - - - -
8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00
AArch64: Delete unused RegNos

This has the additional benefit of getting rid of the -1 encoding (real
registers start at 0.)

- - - - -
325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00
Bump stm submodule to current master

- - - - -
64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00
testsuite: bump T17572 timeout on wasm32

- - - - -
eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00
AArch64: Simplify BL instruction

The BL constructor carried unused data in its third argument.

- - - - -
b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00
TTG: Move SourceText from `Fixity` to `FixitySig`

It is only used there, simplifies the use of `Fixity` in the rest of
the code, and is moved into a TTG extension point.

Precedes !12842, to simplify it

- - - - -
842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00
base: Deprecate some .Internal modules

Deprecates the following modules according to clc-proposal #217:
https://github.com/haskell/core-libraries-committee/issues/217

* GHC.TypeNats.Internal
* GHC.TypeLits.Internal
* GHC.ExecutionStack.Internal

Closes #24998

- - - - -
24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00
ttg: Use List instead of Bag in AST for LHsBindsLR

Considering that the parser used to create a Bag of binds using a
cons-based approach, it can be also done using lists. The operations in
the compiler don't really require Bag.

By using lists, there is no dependency on GHC.Data.Bag anymore from the
AST.

Progress towards #21592

- - - - -
04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00
Fix untouchability test

This MR fixes #24938.  The underlying problem was tha the test for
"does this implication bring in scope any equalities" was plain wrong.

See
  Note [Tracking Given equalities] and
  Note [Let-bound skolems]
both in GHC.Tc.Solver.InertSet.

Then
* Test LocalGivenEqs succeeds for a different reason than before;
  see (LBS2) in Note [Let-bound skolems]

* New test T24938a succeeds because of (LBS2), whereas it failed
  before.

* Test LocalGivenEqs2 now fails, as it should.

* Test T224938, the repro from the ticket, fails, as it should.

- - - - -
9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00
Fix demand signatures for join points

This MR tackles #24623 and #23113

The main change is to give a clearer notion of "worker/wrapper arity", esp
for join points. See GHC.Core.Opt.DmdAnal
     Note [Worker/wrapper arity and join points]
This Note is a good summary of what this MR does:

(1) The "worker/wrapper arity" of an Id is
    * For non-join-points: idArity
    * The join points: the join arity (Id part only of course)
    This is the number of args we will use in worker/wrapper.
    See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`.

(2) A join point's demand-signature arity may exceed the Id's worker/wrapper
    arity.  See the `arity_ok` assertion in `mkWwBodies`.

(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond
    the worker/wrapper arity.

(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper
    arity (re)-computed by workWrapArity.

- - - - -
5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00
Update haddocks of Import/Export AST types

- - - - -
cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00
haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project

- - - - -
8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00
cmm: Don't parse MO_BSwap for W8

Don't support parsing bswap8, since bswap8 is not really an operation
and would have to be implemented as a no-op (and currently is not
implemented at all).

Fixes #25002

- - - - -
5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00
Delete unused testsuite files

These files were committed by mistake in !11902.
This commit simply removes them.

- - - - -
7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00
Remove left over debugging pragma from 2016

This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147

The top-level cost centres lead to a lack of optimisation when compiling
with profiling.

- - - - -
c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default

This commit enables some extensions and GHC flags in the cabal file in a way
that allows us to reduce the amount of prologuing on top of each file.

We also prefix the usage of some List functions that removes ambiguity
when they are also exported from the Prelude, like foldl'.
In general, this has the effect of pointing out more explicitly
that a linked list is used.

Metric Increase:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
Add test case for #23586

- - - - -
568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00
When matching functions in rewrite rules: ignore multiplicity

When matching a template variable to an expression, we check that it
has the same type as the matched expression. But if the variable `f` has
type `A -> B` while the expression `e` has type `A %1 -> B`, the match was
previously rejected.

A principled solution would have `f` substituted by `\(%Many x) -> e
x` or some other appropriate coercion. But since linearity is not
properly checked in Core, we can be cheeky and simply ignore
multiplicity while matching. Much easier.

This has forced a change in the linter which, when `-dlinear-core-lint`
is off, must consider that `a -> b` and `a %1 -> b` are equal. This is
achieved by adding an argument to configure the behaviour of
`nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour
which ignores multiplicities when comparing two `FunTy`.

Fixes #24725.

- - - - -
c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00
Faster type equality

This MR speeds up type equality, triggered by perf regressions that
showed up when fixing #24725 by parameterising type equality over
whether to ignore multiplicity.

The changes are:

* Do not use `nonDetCmpType` for type /equality/. Instead use a specialised
  type-equality function, which we have always had!

  `nonDetCmpType` remains, but I did not invest effort in refactoring
  or optimising it.

* Type equality is parameterised by
    - whether to expand synonyms
    - whether to respect multiplicities
    - whether it has a RnEnv2 environment
  In this MR I systematically specialise it for static values of these
  parameters.  Much more direct and predictable than before.  See
  Note [Specialising type equality]

* We want to avoid comparing kinds if possible.  I refactored how this
  happens, at least for `eqType`.
  See Note [Casts and coercions in type comparison]

* To make Lint fast, we want to avoid allocating a thunk for <msg> in
      ensureEqTypes ty1 ty2 <msg>
  because the test almost always succeeds, and <msg> isn't needed.
  See Note [INLINE ensureEqTys]

Metric Decrease:
    T13386
    T5030

- - - - -
21fc180b by Ryan Hendrickson at 2024-06-22T10:40:55-04:00
base: Add inits1 and tails1 to Data.List

- - - - -
d640a3b6 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Derive previously hand-written `Lift` instances (#14030)

This is possible now that #22229 is fixed.

- - - - -
33fee6a2 by Sebastian Graf at 2024-06-22T10:41:32-04:00
Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030)

After #22229 had been fixed, we can finally derive the `Lift` instance for the
TH AST, as proposed by Ryan Scott in
https://mail.haskell.org/pipermail/libraries/2015-September/026117.html.

Fixes #14030, #14296, #21759 and #24560.

The residency of T24471 increases by 13% because we now load `AnnLookup`
from its interface file, which transitively loads the whole TH AST.
Unavoidable and not terrible, I think.

Metric Increase:
    T24471

- - - - -
383c01a8 by Matthew Pickering at 2024-06-22T10:42:08-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

- - - - -
5759133f by Hécate Kleidukos at 2024-06-22T10:42:49-04:00
haddock: Use the more precise SDocContext instead of DynFlags

The pervasive usage of DynFlags (the parsed command-line options passed
to ghc) blurs the border between different components of Haddock, and
especially those that focus solely on printing text on the screen.

In order to improve the understanding of the real dependencies of a
function, the pretty-printer options are made concrete earlier in the
pipeline instead of late when pretty-printing happens.

This also has the advantage of clarifying which functions actually
require DynFlags for purposes other than pretty-printing, thus making
the interactions between Haddock and GHC more understandable when
exploring the code base.

See Henry, Ericson, Young. "Modularizing GHC".
https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022

- - - - -
749e089b by Alexander McKenna at 2024-06-22T10:43:24-04:00
Add INLINE [1] pragma to compareInt / compareWord

To allow rules to be written on the concrete implementation of
`compare` for `Int` and `Word`, we need to have an `INLINE [1]`
pragma on these functions, following the
`matching_overloaded_methods_in_rules` note in `GHC.Classes`.

CLC proposal https://github.com/haskell/core-libraries-committee/issues/179

Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/22643

- - - - -
db033639 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ci: Enable strict ghc-toolchain setting for bindists

- - - - -
14308a8f by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Improve parse failure error

Improves the error message for when `ghc-toolchain` fails to read a
valid `Target` value from a file (in doFormat mode).

- - - - -
6e7cfff1 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: ghc-toolchain related options in configure

- - - - -
958d6931 by Matthew Pickering at 2024-06-24T17:21:15-04:00
ci: Fail when bindist configure fails when installing bindist

It is better to fail earlier if the configure step fails rather than
carrying on for a more obscure error message.

- - - - -
f48d157d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
ghc-toolchain: Fix error logging indentation

- - - - -
f1397104 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
bindist: Correct default.target substitution

The substitution on `default.target.in` must be done after
`PREP_TARGET_FILE` is called -- that macro is responsible for
setting the variables that will be effectively substituted in the target
file. Otherwise, the target file is invalid.

Fixes #24792 #24574

- - - - -
665e653e by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
configure: Prefer tool name over tool path

It is non-obvious whether the toolchain configuration should use
full-paths to tools or simply their names. In addressing #24574, we've
decided to prefer executable names over paths, ultimately, because the
bindist configure script already does this, thus is the default in ghcs
out there.

Updates the in-tree configure script to prefer tool names
(`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to
ignore the full-path-result of `findExecutable`, which it previously
used over the program name.

This change doesn't undo the fix in bd92182cd56140ffb2f68ec01492e5aa6333a8fc
because `AC_CHECK_TOOL` still takes into account the target triples,
unlike `AC_CHECK_PROG/AC_PATH_PROG`.

- - - - -
463716c2 by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
dist: Don't forget to configure JavascriptCPP

We introduced a configuration step for the javascript preprocessor, but
only did so for the in-tree configure script.

This commit makes it so that we also configure the javascript
preprocessor in the configure shipped in the compiler bindist.

- - - - -
e99cd73d by Rodrigo Mesquita at 2024-06-24T17:21:15-04:00
distrib: LlvmTarget in distrib/configure

LlvmTarget was being set and substituted in the in-tree configure, but
not in the configure shipped in the bindist.

We want to set the LlvmTarget to the canonical LLVM name of the platform
that GHC is targetting.

Currently, that is going to be the boostrapped llvm target (hence the
code which sets LlvmTarget=bootstrap_llvm_target).

- - - - -
4199aafe by Matthew Pickering at 2024-06-24T17:21:51-04:00
Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10)

- - - - -
f599d816 by Matthew Pickering at 2024-06-24T17:21:51-04:00
ci: Add 9_10 bootstrap testing job

- - - - -
8f4b799d by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags

Follow up to !12931

- - - - -
210cf1cd by Hécate Kleidukos at 2024-06-24T17:22:30-04:00
haddock: Remove cabal file linting rule

This will be reintroduced with a properly ignored commit
when the cabal files are themselves formatted for good.

- - - - -
7fe85b13 by Peter Trommler at 2024-06-24T22:03:41-04:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -
949a0e0b by Andrew Lelechenko at 2024-06-24T22:04:17-04:00
base: fix missing changelog entries

- - - - -
1bfa9111 by Andreas Klebinger at 2024-06-26T21:49:53-04:00
GHCi interpreter: Tag constructor closures when possible.

When evaluating PUSH_G try to tag the reference we are pushing if it's a
constructor. This is potentially helpful for performance and required to
fix #24870.

- - - - -
caf44a2d by Andrew Lelechenko at 2024-06-26T21:50:30-04:00
Implement Data.List.compareLength and Data.List.NonEmpty.compareLength

`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`.
The latter would force and traverse the entire spine (potentially diverging),
while the former traverses as few elements as possible.

The implementation is carefully designed to maintain as much laziness as possible.

As per https://github.com/haskell/core-libraries-committee/issues/257

- - - - -
f4606ae0 by Serge S. Gulin at 2024-06-26T21:51:05-04:00
Unicode: adding compact version of GeneralCategory (resolves #24789)

The following features are applied:
1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20)
2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20)

-------------------------
Metric Decrease:
    size_hello_artifact
    size_hello_unicode
-------------------------

- - - - -
0e424304 by Hécate Kleidukos at 2024-06-26T21:51:44-04:00
haddock: Restructure import statements

This commit removes idiosyncrasies that have accumulated with the years
in how import statements were laid out, and defines clear but simple
guidelines in the CONTRIBUTING.md file.

- - - - -
9b8ddaaf by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Rename test for #24725

I must have fumbled my tabs when I copy/pasted the issue number in
8c87d4e1136ae6d28e92b8af31d78ed66224ee16.

- - - - -
b0944623 by Arnaud Spiwack at 2024-06-26T21:52:23-04:00
Add original reproducer for #24725

- - - - -
77ce65a5 by Matthew Pickering at 2024-06-27T07:57:14-04:00
Expand LLVM version matching regex for compability with bsd systems

sed on BSD systems (such as darwin) does not support the + operation.

Therefore we take the simple minded approach of manually expanding
group+ to groupgroup*.

Fixes #24999

- - - - -
bdfe4a9e by Matthew Pickering at 2024-06-27T07:57:14-04:00
ci: On darwin configure LLVMAS linker to match LLC and OPT toolchain

The version check was previously broken so the toolchain was not
detected at all.

- - - - -
07e03a69 by Matthew Pickering at 2024-06-27T07:57:15-04:00
Update nixpkgs commit for darwin toolchain

One dependency (c-ares) changed where it hosted the releases which
breaks the build with the old nixpkgs commit.

- - - - -
144afed7 by Rodrigo Mesquita at 2024-06-27T07:57:50-04:00
base: Add changelog entry for #24998

- - - - -
eebe1658 by Sylvain Henry at 2024-06-28T07:13:26-04:00
X86/DWARF: support no tables-next-to-code and asm-shortcutting (#22792)

- Without TNTC (tables-next-to-code), we must be careful to not
  duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is
  identified by the label of its entry block (and not of its info
  table), we can't reuse the same label to delimit the block end and the
  proc end.

- We generate debug infos from Cmm blocks. However, when
  asm-shortcutting is enabled, some blocks are dropped at the asm
  codegen stage and some labels in the DebugBlocks become missing.
  We fix this by filtering the generated debug-info after the asm
  codegen to only keep valid infos.

Also add some related documentation.

- - - - -
6e86d82b by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: handle JMP to ForeignLabels (#23969)

- - - - -
9e4b4b0a by Sylvain Henry at 2024-06-28T07:14:06-04:00
PPC NCG: support loading 64-bit value on 32-bit arch (#23969)

- - - - -
50caef3e by Sylvain Henry at 2024-06-28T07:14:46-04:00
Fix warnings in genapply

- - - - -
37139b17 by Matthew Pickering at 2024-06-28T07:15:21-04:00
libraries: Update os-string to 2.0.4

This updates the os-string submodule to 2.0.4 which removes the usage of
`TemplateHaskell` pragma.

- - - - -
0f3d3bd6 by Sylvain Henry at 2024-06-30T00:47:40-04:00
Bump array submodule

- - - - -
354c350c by Sylvain Henry at 2024-06-30T00:47:40-04:00
GHCi: Don't use deprecated sizeofMutableByteArray#

- - - - -
35d65098 by Ben Gamari at 2024-06-30T00:47:40-04:00
primops: Undeprecate addr2Int# and int2Addr#

addr2Int# and int2Addr# were marked as deprecated with the introduction
of the OCaml code generator (1dfaee318171836b32f6b33a14231c69adfdef2f)
due to its use of tagged integers. However, this backend has long
vanished and `base` has all along been using `addr2Int#` in the Show
instance for Ptr.

While it's unlikely that we will have another backend which has tagged
integers, we may indeed support platforms which have tagged pointers.
Consequently we undeprecate the operations but warn the user that the
operations may not be portable.

- - - - -
3157d817 by Sylvain Henry at 2024-06-30T00:47:41-04:00
primops: Undeprecate par#

par# is still used in base and it's not clear how to replace it with
spark# (see #24825)

- - - - -
c8d5b959 by Ben Gamari at 2024-06-30T00:47:41-04:00
Primops: Make documentation generation more efficient

Previously we would do a linear search through all primop names, doing a
String comparison on the name of each when preparing the HsDocStringMap.
Fix this.

- - - - -
65165fe4 by Ben Gamari at 2024-06-30T00:47:41-04:00
primops: Ensure that deprecations are properly tracked

We previously failed to insert DEPRECATION pragmas into GHC.Prim's
ModIface, meaning that they would appear in the Haddock documentation
but not issue warnings. Fix this.

See #19629. Haddock also needs to be fixed: https://github.com/haskell/haddock/issues/223

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
bc1d435e by Mario Blažević at 2024-06-30T00:48:20-04:00
Improved pretty-printing of unboxed TH sums and tuples, fixes #24997

- - - - -
0d170eaf by Zubin Duggal at 2024-07-04T11:08:41-04:00
compiler: Turn `FinderCache` into a record of operations so that GHC API clients can
have full control over how its state is managed by overriding `hsc_FC`.

Also removes the `uncacheModule` function as this wasn't being used by anything
since 1893ba12fe1fa2ade35a62c336594afcd569736e

Fixes #23604

- - - - -
4664997d by Teo Camarasu at 2024-07-04T11:09:18-04:00
Add HasCallStack to T23221

This makes the test a bit easier to debug

- - - - -
66919dcc by Teo Camarasu at 2024-07-04T11:09:18-04:00
rts: use live words to estimate heap size

We use live words rather than live blocks to determine the size of the
heap for determining memory retention.

Most of the time these two metrics align, but they can come apart in
normal usage when using the nonmoving collector.

The nonmoving collector leads to a lot of partially occupied blocks. So,
using live words is more accurate.

They can also come apart when the heap is suffering from high levels
fragmentation caused by small pinned objects, but in this case, the
block size is the more accurate metric. Since this case is best avoided
anyway. It is ok to accept the trade-off that we might try (and
probably) fail to return more memory in this case.

See also the Note [Statistics for retaining memory]

Resolves #23397

- - - - -
8dfca66a by Oleg Grenrus at 2024-07-04T11:09:55-04:00
Add reflections of GHC.TypeLits/Nats type families

-------------------------
Metric Increase:
    ghc_experimental_dir
    ghc_experimental_so
-------------------------

- - - - -
6c469bd2 by Adam Gundry at 2024-07-04T11:10:33-04:00
Correct -Wpartial-fields warning to say "Definition" rather than "Use"

Fixes #24710.  The message and documentation for `-Wpartial-fields` were
misleading as (a) the warning occurs at definition sites rather than use
sites, and (b) the warning relates to the definition of a field independently
of the selector function (e.g. because record updates are also partial).

- - - - -
977b6b64 by Max Ulidtko at 2024-07-04T11:11:11-04:00
GHCi: Support local Prelude

Fixes #10920, an issue where GHCi bails out when started alongside a
file named Prelude.hs or Prelude.lhs (even empty file suffices).

The in-source Note [GHCi and local Preludes] documents core reasoning.

Supplementary changes:

 * add debug traces for module lookups under -ddump-if-trace;
 * drop stale comment in GHC.Iface.Load;
 * reduce noise in -v3 traces from GHC.Utils.TmpFs;
 * new test, which also exercizes HomeModError.

- - - - -
87cf4111 by Ryan Scott at 2024-07-04T11:11:47-04:00
Add missing gParPat in cvtp's ViewP case

When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern
is parenthesized so that the resulting code will parse correctly when
roundtripped back through GHC's parser.

Fixes #24894.

- - - - -
b05613c5 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation for module cycle errors (see #18516)

This removes the re-export of cyclicModuleErr from the top-level GHC module.

- - - - -
70389749 by Adam Gundry at 2024-07-04T11:12:23-04:00
Use structured error representation when reloading a nonexistent module

- - - - -
680ade3d by sheaf at 2024-07-04T11:12:23-04:00
Use structured errors for a Backpack instantiation error

- - - - -
97c6d6de by sheaf at 2024-07-04T11:12:23-04:00
Move mkFileSrcSpan to GHC.Unit.Module.Location

- - - - -
f9e7bd9b by Adriaan Leijnse at 2024-07-04T11:12:59-04:00
ttg: Remove SourceText from OverloadedLabel

Progress towards #21592

- - - - -
00d63245 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: GHC.Prelude -> Prelude

Refactor occurrences to GHC.Prelude with Prelude within
Language/Haskell.

Progress towards #21592

- - - - -
cc846ea5 by Alexander Foremny at 2024-07-04T11:12:59-04:00
AST: remove occurrences of GHC.Unit.Module.ModuleName

`GHC.Unit.Module` re-exports `ModuleName` from
`Language.Haskell.Syntax.Module.Name`.

Progress towards #21592

- - - - -
24c7d287 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move Data instance definition for ModuleName to GHC.Unit.Types

To remove the dependency on GHC.Utils.Misc inside
Language.Haskell.Syntax.Module.Name, the instance definition is moved
from there into GHC.Unit.Types.

Progress towards #21592

- - - - -
6cbba381 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move negateOverLitVal into GHC.Hs.Lit

The function negateOverLitVal is not used within Language.Haskell and
therefore can be moved to the respective module inside GHC.Hs.

Progress towards #21592

- - - - -
611aa7c6 by Fabian Kirchner at 2024-07-04T11:12:59-04:00
AST: move conDetailsArity into GHC.Rename.Module

The function conDetailsArity is only used inside GHC.Rename.Module.  We
therefore move it there from Language.Haskell.Syntax.Lit.

Progress towards #21592

- - - - -
1b968d16 by Mauricio at 2024-07-04T11:12:59-04:00
AST: Remove GHC.Utils.Assert from GHC

Simple cleanup.

Progress towards #21592

- - - - -
3d192e5d by Fabian Kirchner at 2024-07-04T11:12:59-04:00
ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var

Progress towards #21592

Specificity, ForAllTyFlag and its' helper functions are extracted from
GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity.

Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on
GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls.
At this point, this would cause cyclic dependencies.

- - - - -
257d1adc by Adowrath at 2024-07-04T11:12:59-04:00
ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type

Progress towards #21592

This splits HsSrcBang up, creating the new HsBang within
`Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness
and strictness information, while `HsSrcBang` only adds the SourceText
for usage within the compiler directly.

Inside the AST, to preserve the SourceText, it is hidden behind the
pre-existing extension point `XBindTy`. All other occurrences of
`HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when
interacting with the `BindTy` constructor, the hidden `SourceText` is
extracted/inserted into the `XBindTy` extension point.

`GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for
convenience. A constructor function `mkHsSrcBang` that takes all
individual components has been added.

Two exceptions has been made though:
- The `Outputable HsSrcBang` instance is replaced by
  `Outputable HsBang`. While being only GHC-internal, the only place
  it's used is in outputting `HsBangTy` constructors -- which already
  have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just
  to ignore the `SourceText` anyway.
- The error `TcRnUnexpectedAnnotation` did not use the `SourceText`,
  so it too now only holds a `HsBang`.

- - - - -
24757fec by Mauricio at 2024-07-04T11:12:59-04:00
AST: Moved definitions that use GHC.Utils.Panic to GHC namespace

Progress towards #21592

- - - - -
9be49379 by Mike Pilgrem at 2024-07-04T11:13:41-04:00
Fix #25032 Refer to Cabal's `includes` field, not `include-files`

- - - - -
9e2ecf14 by Andrew Lelechenko at 2024-07-04T11:14:17-04:00
base: fix more missing changelog entries

- - - - -
a82121b3 by Peter Trommler at 2024-07-04T11:14:53-04:00
X86 NCG: Fix argument promotion in foreign C calls

Promote 8 bit and 16 bit signed arguments by sign extension.

Fixes #25018

- - - - -
fab13100 by Bryan Richter at 2024-07-04T11:15:29-04:00
Add .gitlab/README.md with creds instructions

- - - - -
564981bd by Matthew Pickering at 2024-07-05T07:35:29-04:00
configure: Set LD_STAGE0 appropiately when 9.10.1 is used as a boot compiler

In 9.10.1 the "ld command" has been removed, so we fall back to using
the more precise "merge objects command" when it's available as
LD_STAGE0 is only used to set the object merging command in hadrian.

Fixes #24949

- - - - -
a949c792 by Matthew Pickering at 2024-07-05T07:35:29-04:00
hadrian: Don't build ghci object files for ./hadrian/ghci target

There is some convoluted logic which determines whether we build ghci
object files are not. In any case, if you set `ghcDynPrograms = pure
False` then it forces them to be built.

Given we aren't ever building executables with this flavour it's fine
to leave `ghcDynPrograms` as the default and it should be a bit faster
to build less.

Also fixes #24949

- - - - -
48bd8f8e by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Remove STG dump from ticky_ghc flavour transformer

This adds 10-15 minutes to build time, it is a better strategy to
precisely enable dumps for the modules which show up prominently in a
ticky profile.

Given I am one of the only people regularly building ticky compilers I
think it's worthwhile to remove these.

Fixes #23635

- - - - -
5b1aefb7 by Matthew Pickering at 2024-07-05T07:36:06-04:00
hadrian: Add dump_stg flavour transformer

This allows you to write `--flavour=default+ticky_ghc+dump_stg` if you
really want STG for all modules.

- - - - -
ab2b60b6 by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtToInstrs type

There's no need to hand `Nothing`s around... (there was no case with a
`BlockId`.)

- - - - -
71a7fa8c by Sven Tennie at 2024-07-08T15:03:41-04:00
AArch64: Simplify stmtsToInstrs type

The `BlockId` parameter (`bid`) is never used, only handed around.
Deleting it simplifies the surrounding code.

- - - - -
8bf6fd68 by Simon Peyton Jones at 2024-07-08T15:04:17-04:00
Fix eta-expansion in Prep

As #25033 showed, we were eta-expanding in a way that broke a join point,
which messed up Note [CorePrep invariants].

The fix is rather easy.  See Wrinkle (EA1) of
Note [Eta expansion of arguments in CorePrep]

- - - - -
96acf823 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
One-shot Haddock

- - - - -
74ec4c06 by Sjoerd Visscher at 2024-07-09T06:16:14-04:00
Remove haddock-stdout test option

Superseded by output handling of Hadrian

- - - - -
ed8a8f0b by Rodrigo Mesquita at 2024-07-09T06:16:51-04:00
ghc-boot: Relax Cabal bound

Fixes #25013

- - - - -
3f9548fe by Matthew Pickering at 2024-07-09T06:17:36-04:00
ci: Unset ALEX/HAPPY variables when testing bootstrap jobs

Ticket #24826 reports a regression in 9.10.1 when building from a source
distribution. This patch is an attempt to reproduce the issue on CI by
more aggressively removing `alex` and `happy` from the environment.

- - - - -
aba2c9d4 by Andrea Bedini at 2024-07-09T06:17:36-04:00
hadrian: Ignore build-tool-depends fields in cabal files

hadrian does not utilise the build-tool-depends fields in cabal files
and their presence can cause issues when building source distribution
(see #24826)

Ideally Cabal would support building "full" source distributions which
would remove the need for workarounds in hadrian but for now we can
patch the build-tool-depends out of the cabal files.

Fixes #24826

- - - - -
12bb9e7b by Matthew Pickering at 2024-07-09T06:18:12-04:00
testsuite: Don't attempt to link when checking whether a way is supported

It is sufficient to check that the simple test file compiles as it will
fail if there are not the relevant library files for the requested way.

If you break a way so badly that even a simple executable fails to link
(as I did for profiled dynamic way), it will just mean the tests for
that way are skipped on CI rather than displayed.

- - - - -
46ec0a8e by Torsten Schmits at 2024-07-09T13:37:02+02:00
Improve docs for NondecreasingIndentation

The text stated that this affects indentation of layouts nested in do
expressions, while it actually affects that of do layouts nested in any
other.

- - - - -
dddc9dff by Zubin Duggal at 2024-07-12T11:41:24-04:00
compiler: Fingerprint -fwrite-if-simplified-core

We need to recompile if this flag is changed because later modules might depend on the
simplified core for this module if -fprefer-bytecode is enabled.

Fixes #24656

- - - - -
145a6477 by Matthew Pickering at 2024-07-12T11:42:00-04:00
Add support for building profiled dynamic way

The main payload of this change is to hadrian.

* Default settings will produced dynamic profiled objects
* `-fexternal-interpreter` is turned on in some situations when there is
  an incompatibility between host GHC and the way attempting to be
  built.
* Very few changes actually needed to GHC

There are also necessary changes to the bootstrap plans to work with the
vendored Cabal dependency. These changes should ideally be reverted by
the next GHC release.

In hadrian support is added for building profiled dynamic libraries
(nothing too exciting to see there)

Updates hadrian to use a vendored Cabal submodule, it is important that
we replace this usage with a released version of Cabal library before
the 9.12 release.

Fixes #21594

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
414a6950 by Matthew Pickering at 2024-07-12T11:42:00-04:00
testsuite: Make find_so regex more precise

The hash contains lowercase [a-z0-9] and crucially not _p which meant we
sometimes matched on `libHS.._p` profiled shared libraries rather than
the normal shared library.

- - - - -
dee035bf by Alex Mason at 2024-07-12T11:42:41-04:00
ncg(aarch64): Add fsqrt instruction, byteSwap primitives [#24956]

Implements the FSQRT machop using native assembly rather than a C call.

Implements MO_BSwap by producing assembly to do the byte swapping
instead of producing a foreign call a C function.

In `tar`, the hot loop for `deserialise` got almost 4x faster by
avoiding the foreign call which caused spilling live variables to the
stack -- this means the loop did 4x more memory read/writing than
necessary in that particular case!

- - - - -
5104ee61 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: use m32 allocator for sections when NEED_PLT (#24432)

Use M32 allocator to avoid fragmentation when allocating ELF sections.
We already did this when NEED_PLT was undefined. Failing to do this led
to relocations impossible to fulfil (#24432).

- - - - -
52d66984 by Sylvain Henry at 2024-07-12T11:43:23-04:00
RTS: allow M32 allocation outside of 4GB range when assuming -fPIC

- - - - -
c34fef56 by Sylvain Henry at 2024-07-12T11:43:23-04:00
Linker: fix stub offset

Remove unjustified +8 offset that leads to memory corruption (cf
discussion in #24432).

- - - - -
280e4bf5 by Simon Peyton Jones at 2024-07-12T11:43:59-04:00
Make type-equality on synonyms a bit faster

This MR make equality fast for (S tys1 `eqType` S tys2),
where S is a non-forgetful type synonym.

It doesn't affect compile-time allocation much, but then comparison doesn't
allocate anyway.  But it seems like a Good Thing anyway.

See Note [Comparing type synonyms] in GHC.Core.TyCo.Compare
and Note [Forgetful type synonyms] in GHC.Core.TyCon

Addresses #25009.

- - - - -
cb83c347 by Alan Zimmerman at 2024-07-12T11:44:35-04:00
EPA: Bring back SrcSpan in EpaDelta

When processing files in ghc-exactprint, the usual workflow is to
first normalise it with makeDeltaAst, and then operate on it.

But we need the original locations to operate on it, in terms of
finding things.

So restore the original SrcSpan for reference in EpaDelta

- - - - -
7bcda869 by Matthew Pickering at 2024-07-12T11:45:11-04:00
Update alpine release job to 3.20

alpine 3.20 was recently released and uses a new python and sphinx
toolchain which could be useful to test.

- - - - -
43aa99b8 by Matthew Pickering at 2024-07-12T11:45:11-04:00
testsuite: workaround bug in python-3.12

There is some unexplained change to binding behaviour in python-3.12
which requires moving this import from the top-level into the scope of
the function.

I didn't feel any particular desire to do a deep investigation as to why
this changed as the code works when modified like this. No one in the
python IRC channel seemed to know what the problem was.

- - - - -
e3914028 by Adam Sandberg Ericsson at 2024-07-12T11:45:47-04:00
initialise mmap_32bit_base during RTS startup #24847
- - - - -
86b8ecee by Hécate Kleidukos at 2024-07-12T11:46:27-04:00
haddock: Only fetch supported languages and extensions once per Interface list

This reduces the number of operations done on each Interface, because
supported languages and extensions are determined from architecture and
operating system of the build host. This information remains stable
across Interfaces, and as such doesn not need to be recovered for each
Interface.

- - - - -
4f85366f by sheaf at 2024-07-13T05:58:14-04:00
Testsuite: use py-cpuinfo to compute CPU features

This replaces the rather hacky logic we had in place for checking
CPU features. In particular, this means that feature availability now
works properly on Windows.

- - - - -
41f1354d by Matthew Pickering at 2024-07-13T05:58:51-04:00
testsuite: Replace $CC with $TEST_CC

The TEST_CC variable should be set based on the test compiler, which may
be different to the compiler which is set to CC on your system (for
example when cross compiling).

Fixes #24946

- - - - -
572fbc44 by sheaf at 2024-07-15T08:30:32-04:00
isIrrefutableHsPat: consider COMPLETE pragmas

This patch ensures we taken into account COMPLETE pragmas when we
compute whether a pattern is irrefutable. In particular, if a pattern
synonym is the sole member of a COMPLETE pragma (without a result TyCon),
then we consider a pattern match on that pattern synonym to be irrefutable.

This affects the desugaring of do blocks, as it ensures we don't use
a "fail" operation.

Fixes #15681 #16618 #22004

- - - - -
84dadea9 by Zubin Duggal at 2024-07-15T08:31:09-04:00
haddock: Handle non-hs files, so that haddock can generate documentation for modules with
foreign imports and template haskell.

Fixes #24964

- - - - -
0b4ff9fa by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of warnings/deprecations from dependent packages in `InstalledInterface`
and use this to propagate these on items re-exported from dependent packages.

Fixes #25037

- - - - -
b8b4b212 by Zubin Duggal at 2024-07-15T12:12:30-04:00
haddock: Keep track of instance source locations in `InstalledInterface` and use this to add
source locations on out of package instances

Fixes #24929

- - - - -
559a7a7c by Matthew Pickering at 2024-07-15T12:13:05-04:00
ci: Refactor job_groups definition, split up by platform

The groups are now split up so it's easier to see which jobs are
generated for each platform

No change in behaviour, just refactoring.

- - - - -
20383006 by Matthew Pickering at 2024-07-16T11:48:25+01:00
ci: Replace debian 10 with debian 12 on validation jobs

Since debian 10 is now EOL we migrate onwards to debian 12 as the basis
for most platform independent validation jobs.

- - - - -
12d3b66c by Matthew Pickering at 2024-07-17T13:22:37-04:00
ghcup-metadata: Fix use of arch argument

The arch argument was ignored when making the jobname, which lead to
failures when generating metadata for the alpine_3_18-aarch64 bindist.

Fixes #25089

- - - - -
bace981e by Matthew Pickering at 2024-07-19T10:14:02-04:00
testsuite: Delay querying ghc-pkg to find .so dirs until test is run

The tests which relied on find_so would fail when `test` was run
before the tree was built. This was because `find_so` was evaluated too
eagerly.

We can fix this by waiting to query the location of the libraries until
after the compiler has built them.

- - - - -
478de1ab by Torsten Schmits at 2024-07-19T10:14:37-04:00
Add `complete` pragmas for backwards compat patsyns `ModLocation` and `ModIface`

!12347 and !12582 introduced breaking changes to these two constructors
and mitigated that with pattern synonyms.

- - - - -
b57792a8 by Matthew Pickering at 2024-07-19T10:15:13-04:00
ci: Fix ghcup-metadata generation (again)

I made some mistakes in 203830065b81fe29003c1640a354f11661ffc604

* Syntax error
* The aarch-deb11 bindist doesn't exist

I tested against the latest nightly pipeline locally:

```
nix run .gitlab/generate-ci#generate-job-metadata
nix shell -f .gitlab/rel_eng/ -c ghcup-metadata --pipeline-id 98286 --version 9.11.20240715 --fragment --date 2024-07-17 --metadata=/tmp/meta
```

- - - - -
1fa35b64 by Andreas Klebinger at 2024-07-19T17:35:20+02:00
Revert "Allow non-absolute values for bootstrap GHC variable"

This broke configure in subtle ways resulting in #25076 where hadrian
didn't end up the boot compiler it was configured to use.

This reverts commit 209d09f52363b261b900cf042934ae1e81e2caa7.

- - - - -
55117e13 by Simon Peyton Jones at 2024-07-24T02:41:12-04:00
Fix bad bug in mkSynonymTyCon, re forgetfulness

As #25094 showed, the previous tests for forgetfulness was
plain wrong, when there was a forgetful synonym in the RHS
of a synonym.

- - - - -
a8362630 by Sergey Vinokurov at 2024-07-24T12:22:45-04:00
Define Eq1, Ord1, Show1 and Read1 instances for basic Generic representation types

This way the Generically1 newtype could be used to derive Eq1 and Ord1
for user types with DerivingVia.

The CLC proposal is https://github.com/haskell/core-libraries-committee/issues/273.

The GHC issue is https://gitlab.haskell.org/ghc/ghc/-/issues/24312.

- - - - -
de5d9852 by Simon Peyton Jones at 2024-07-24T12:23:22-04:00
Address #25055, by disabling case-of-runRW# in Gentle phase

See Note [Case-of-case and full laziness]
in GHC.Driver.Config.Core.Opt.Simplify

- - - - -
3f89ab92 by Andreas Klebinger at 2024-07-25T14:12:54+02:00
Fix -freg-graphs for FP and AARch64 NCG (#24941).

It seems we reserve 8 registers instead of four for global regs
based on the layout in Note [AArch64 Register assignments].

I'm not sure it's neccesary, but for now we just accept this state of
affairs and simple update -fregs-graph to account for this.

- - - - -
f6b4c1c9 by Simon Peyton Jones at 2024-07-27T09:45:44-04:00
Fix nasty bug in occurrence analyser

As #25096 showed, the occurrence analyser was getting one-shot info
flat out wrong.

This commit does two things:

* It fixes the bug and actually makes the code a bit tidier too.
  The work is done in the new function
     GHC.Core.Opt.OccurAnal.mkRhsOccEnv,
  especially the bit that prepares the `occ_one_shots` for the RHS.

  See Note [The OccEnv for a right hand side]

* When floating out a binding we must be conservative about one-shot
  info.  But we were zapping the entire demand info, whereas we only
  really need zap the /top level/ cardinality.

  See Note [Floatifying demand info when floating]
  in GHC.Core.Opt.SetLevels

For some reason there is a 2.2% improvement in compile-time allocation
for CoOpt_Read.  Otherwise nickels and dimes.

Metric Decrease:
    CoOpt_Read

- - - - -
646ee207 by Torsten Schmits at 2024-07-27T09:46:20-04:00
add missing cell in flavours table

- - - - -
ec2eafdb by Ben Gamari at 2024-07-28T20:51:12+02:00
users-guide: Drop mention of dead __PARALLEL_HASKELL__ macro

This has not existed for over a decade.

- - - - -
e2f2a56e by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Add tests for 25081

- - - - -
23f50640 by Arnaud Spiwack at 2024-07-28T22:21:07-04:00
Scale multiplicity in list comprehension

Fixes #25081

- - - - -
d2648289 by romes at 2024-07-30T01:38:12-04:00
TTG HsCmdArrForm: use Fixity via extension point

Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax
since it no longer uses any GHC-specific data types.

Fixed arrow desugaring bug. (This was dead code before.)
Remove mkOpFormRn, it is also dead code, only used in the arrow
desugaring now removed.

Co-authored-by: Fabian Kirchner <kirchner at posteo.de>
Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com>

- - - - -
e258ad54 by Matthew Pickering at 2024-07-30T01:38:48-04:00
ghcup-metadata: More metadata fixes

* Incorrect version range on the alpine bindists
* Missing underscore in "unknown_versioning"

Fixes #25119

- - - - -
72b54c07 by Rodrigo Mesquita at 2024-08-01T00:47:29-04:00
Deriving-via one-shot strict state Monad instances

A small refactor to use deriving via GHC.Utils.Monad.State.Strict
Monad instances for state Monads with unboxed/strict results which all
re-implemented the one-shot trick in the instance and used unboxed
tuples:

* CmmOptM in GHC.Cmm.GenericOpt
* RegM in GHC.CmmToAsm.Reg.Linear.State
* UniqSM in GHC.Types.Unique.Supply

- - - - -
bfe4b3d3 by doyougnu at 2024-08-01T00:48:06-04:00
Rts linker: add case for pc-rel 64 relocation

part of the upstream haskell.nix patches

- - - - -
5843c7e3 by doyougnu at 2024-08-01T00:48:42-04:00
RTS linker: aarch64: better debug information

Dump better debugging information when a symbol address is null.

Part of the haskell.nix patches upstream project

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
c2e9c581 by Rodrigo Mesquita at 2024-08-01T00:49:18-04:00
base: Add haddocks to HasExceptionContext

Fixes #25091

- - - - -
f954f428 by Sylvain Henry at 2024-08-01T00:49:59-04:00
Only lookup ghcversion.h file in the RTS include-dirs by default.

The code was introduced in 3549c952b535803270872adaf87262f2df0295a4.
It used `getPackageIncludePath` which name doesn't convey that it looks
into all include paths of the preload units too. So this behavior is
probably unintentional and it should be ok to change it.

Fix #25106

- - - - -
951ce3d5 by Matthew Pickering at 2024-08-01T00:50:35-04:00
driver: Fix -Wmissing-home-modules when multiple units have the same module name

It was assumed that module names were unique but that isn't true with
multiple units.

The fix is quite simple, maintain a set of `(ModuleName, UnitId)` and
query that to see whether the module has been specified.

Fixes #25122

- - - - -
bae1fea4 by sheaf at 2024-08-01T00:51:15-04:00
PMC: suggest in-scope COMPLETE sets when possible

This commit modifies GHC.HsToCore.Pmc.Solver.generateInhabitingPatterns
to prioritise reporting COMPLETE sets in which all of the ConLikes
are in scope. This avoids suggesting out of scope constructors
when displaying an incomplete pattern match warning, e.g. in

  baz :: Ordering -> Int
  baz = \case
    EQ -> 5

we prefer:

  Patterns of type 'Ordering' not matched:
      LT
      GT

over:

  Patterns of type 'Ordering' not matched:
      OutOfScope

Fixes #25115

- - - - -
ff158fcd by Tommy Bidne at 2024-08-02T01:14:32+12:00
Print exception metadata in default handler

CLC proposals 231 and 261:

- Add exception type metadata to SomeException's displayException.
- Add "Exception" header to default exception handler.

See:

https://github.com/haskell/core-libraries-committee/issues/231
https://github.com/haskell/core-libraries-committee/issues/261

Update stm submodule for test fixes.

- - - - -
8b2f70a2 by Andrei Borzenkov at 2024-08-01T23:00:46-04:00
Type syntax in expressions (#24159, #24572, #24226)

This patch extends the grammar of expressions with syntax that is
typically found only in types:
  * function types (a -> b), (a ->. b), (a %m -> b)
  * constrained types (ctx => t)
  * forall-quantification (forall tvs. t)

The new forms are guarded behind the RequiredTypeArguments extension,
as specified in GHC Proposal #281. Examples:

  {-# LANGUAGE RequiredTypeArguments #-}
  e1 = f (Int    -> String)          -- function type
  e2 = f (Int %1 -> String)          -- linear function type
  e3 = f (forall a. Bounded a => a)  -- forall type, constraint

The GHC AST and the TH AST have been extended as follows:

   syntax        | HsExpr   | TH.Exp
  ---------------+----------+--------------
   a -> b        | HsFunArr | ConE (->)
   a %m -> b     | HsFunArr | ConE FUN
   ctx => t      | HsQual   | ConstrainedE
   forall a. t   | HsForAll | ForallE
   forall a -> t | HsForAll | ForallVisE

Additionally, a new warning flag -Wview-pattern-signatures has been
introduced to aid with migration to the new precedence of (e -> p :: t).

Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com>

- - - - -
66e7f57d by Brandon Chinn at 2024-08-01T21:50:58-07:00
Implement MultilineStrings (#24390)

This commit adds support for multiline strings, proposed at
https://github.com/ghc-proposals/ghc-proposals/pull/569.
Multiline strings can now be written as:

    myString =
      """
      this is a
      multiline string
      """

The multiline string will have leading indentation stripped away.
Full details of this post-processing may be found at the new
GHC.Parser.String module.

In order to cleanly implement this and maximize reusability, I
broke out the lexing logic for strings out of Lexer.x into a
new GHC.Parser.String module, which lexes strings with any
provided "get next character" function. This also gave us the
opportunity to clean up this logic, and even optimize it a bit.
With this change, parsing string literals now takes 25% less
time and 25% less space.

- - - - -
cf47b96f by Rodrigo Mesquita at 2024-08-03T05:59:40-04:00
hi: Stable sort avails

Sorting the Avails in DocStructures is required to produce fully
deterministic interface files in presence of re-exported modules.

Fixes #25104

- - - - -
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.

- - - - -
d94410f8 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: @since for backtraceDesired

Fixes point 1 in #25052

- - - - -
bfe600f5 by Rodrigo Mesquita at 2024-08-07T11:49:19-04:00
ghc-internal: No trailing whitespace in exceptions

Fixes #25052

- - - - -
62650d9f by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Add since annotation for -fkeep-auto-rules.

This partially addresses #25082.

- - - - -
5f0e23fd by Andreas Klebinger at 2024-08-07T11:49:54-04:00
Mention `-fkeep-auto-rules` in release notes.

It was added earlier but hadn't appeared in any release notes yet.
Partially addresses #25082.

- - - - -
7446a09a by Sylvain Henry at 2024-08-07T11:50:35-04:00
Cmm: don't perform unsound optimizations on 32-bit compiler hosts

- beef61351b240967b49169d27a9a19565cf3c4af enabled the use of
  MO_Add/MO_Sub for 64-bit operations in the C and LLVM backends
- 6755d833af8c21bbad6585144b10e20ac4a0a1ab did the same for the x86 NCG
  backend

However we store some literal values as `Int` in the compiler. As a
result, some Cmm optimizations transformed target 64-bit literals into
compiler `Int`. If the compiler is 32-bit, this leads to computing with
wrong literals (see #24893 and #24700).

This patch disables these Cmm optimizations for 32-bit compilers. This
is unsatisfying (optimizations shouldn't be compiler-word-size
dependent) but it fixes the bug and it makes the patch easy to backport.
A proper fix would be much more invasive but it shall be implemented in
the future.

Co-authored-by: amesgen <amesgen at amesgen.de>

- - - - -
d59faaf2 by Vladislav Zavialov at 2024-08-07T11:51:11-04:00
docs: Update info on RequiredTypeArguments

Add a section on "types in terms" that were implemented in 8b2f70a202
and remove the now outdated suggestion of using `type` for them.

- - - - -
39fd6714 by Sylvain Henry at 2024-08-07T11:51:52-04:00
JS: fix minor typo in base's jsbits

- - - - -
e7764575 by Sylvain Henry at 2024-08-07T11:51:52-04:00
RTS: remove hack to force old cabal to build a library with only JS sources

Need to extend JSC externs with Emscripten RTS definitions to avoid
JSC_UNDEFINED_VARIABLE errors when linking without the emcc rts.

Fix #25138

Some recompilation avoidance tests now fail. This is tracked with the
other instances of this failure in #23013. My hunch is that they were
working by chance when we used the emcc linker.

Metric Decrease:
    T24602_perf_size

- - - - -
d1a40233 by Brandon Chinn at 2024-08-07T11:53:08-04:00
Support multiline strings in type literals (#25132)

- - - - -
610840eb by Sylvain Henry at 2024-08-07T11:53:50-04:00
JS: fix callback documentation (#24377)

Fix #24377

- - - - -
6ae4b76a by Zubin Duggal at 2024-08-13T13:36:57-04:00
haddock: Build haddock-api and haddock-library using hadrian

We build these two packages as regular boot library dependencies rather
than using the `in-ghc-tree` flag to include the source files into the haddock
executable.

The `in-ghc-tree` flag is moved into haddock-api to ensure that haddock built
from hackage can still find the location of the GHC bindist using `ghc-paths`.

Addresses #24834

This causes a metric decrease under non-release flavours because under these
flavours libraries are compiled with optimisation but executables are not.

Since we move the bulk of the code from the haddock executable to the
haddock-api library, we see a metric decrease on the validate flavours.

Metric Decrease:
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
51ffba5d by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add an extension field to HsRecFields

This is the Right Thing to Do™. And it prepares for storing a
multiplicity coercion there.

First step of the plan outlined here and below
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12947#note_573091

- - - - -
4d2faeeb by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Add test for #24961

- - - - -
623b4337 by Arnaud Spiwack at 2024-08-13T13:37:50-04:00
Ensures that omitted record fields in pattern have multiplicity Many

Omitted fields were simply ignored in the type checker and produced
incorrect Core code.

Fixes #24961

Metric Increase:
    RecordUpdPerf

- - - - -
c749bdfd by Sylvain Henry at 2024-08-13T13:38:41-04:00
AARCH64 linker: skip NONE relocations

This patch is part of the patches upstreamed from haskell.nix.
See https://github.com/input-output-hk/haskell.nix/pull/1960 for the
original report/patch.

- - - - -
682a6a41 by Brandon Chinn at 2024-08-13T13:39:17-04:00
Support multiline strings in TH

- - - - -
ee0a9c18 by Matthew Pickering at 2024-08-14T14:27:39-04:00
Extend -reexported-module flag to support module renaming

The -reexported-module flag now supports renaming -rexported-modules.

```
-rexported-module "A as B"
```

This feature is only relevant to multi-component sessions.

Fixes #25139

- - - - -
e9496000 by Arnaud Spiwack at 2024-08-14T14:28:20-04:00
Don't restrict eta-reduction of linear functions

This commit simply removes code. All the supporting implementation has
been done as part of !12883.

Closes #25129

- - - - -
2bb4156e by sheaf at 2024-08-14T14:28:56-04:00
Allow @ character in C labels

Generated symbol names can include the '@' character, for example when using
`__attribute__((vectorcall))`.
- - - - -
7602ca23 by Sylvain Henry at 2024-08-14T14:29:36-04:00
Linker: replace blind tuple with a datatype + docs

- - - - -
bdd77b9e by sheaf at 2024-08-16T12:47:11-04:00
isIrrefutableHsPat: look up ConLikes in the HscEnv

At GhcRn stage, in isIrrefutableHsPat we only looked up data constructors
in the RdrEnv, which meant that we lacked fallibility information for
out-of-scope constructors (which can arise from Template Haskell splices).

Instead, we use 'lookupGREInfo', which looks up the information in
the type environment. This was the correct function to call all along,
but was not used in 572fbc44 due to import cycle reasons. The appropriate
functions, 'irrefutableConLike{Rn,Tc}' have been moved to 'GHC.Rename.Env',
which avoids import cycles.

Fixes #25164

- - - - -
4bee377c by Sylvain Henry at 2024-08-16T12:47:53-04:00
Linker: some refactoring to prepare for #24886

- Rename LoadedBCOs into LazyBCOs
- Bundle SptEntries with CompiledByteCode and removed [SptEntry] field
  from the BCOs constructor
- Rename Linkable's LM constructor into Linkable: in the past we had LM
  and LP for Module and Package, now we only have the former.
- Rename Unlinked into LinkablePart (and linkableUnlinked into
  linkableParts)
- Use NonEmpty to encode invariant in Linkable's linkableParts type
- Add helpers: linkableLibs, linkableBCOs, etc.
- Add documentation
- Remove partial nameOfObject
- Rename nameOfObject_maybe into linkablePartPath
- Rename byteCodeOfObject into linkablePartAllBCOs.
- Refactor linkablePartAllBCOs to avoid a panic if a LazyBCO has a C
  stub. Document the fact that LazyBCOs are returned in this case
  (contrary to linkableBCOs which only returns non-lazy ones)

Refactoring done while trying to understand how to adapt the linker code
to support the JS backend too (cf #24886).

- - - - -
fa0dbaca by Mario Blažević at 2024-08-17T03:31:32+00:00
Implements the Exportable Named Default proposal (#24305)

This squashed commit adds support for exportable named defaults, the accepted
GHC proposal at https://github.com/ghc-proposals/ghc-proposals/pull/409

The proposal extends the Haskell '98 declarations

    default (Int, Double)

which were implicitly always applying to Num class alone, to allow specifying
an arbitrary single-parameter class:

    default IsString (Text, String)

The effect of this declaration would be to eliminate the ambiguous type errors
around string literals when OverloadedStrings extension is active. The
declaration by itself has effect only in its module, so the proposal also adds
the ability to export class defaults:

    module MyModule (default IsIstring)

Once the language extension is published and established, we can consider using
it in base and other libraries.

See Note [Named default declarations] in GHC.Tc.Gen.Default
for implementation details.

- - - - -
1deba6b2 by Simon Peyton Jones at 2024-08-17T13:58:13-04:00
Make kick-out more selective

This MR revised the crucial kick-out criteria in the constraint solver.

Ticket #24984 showed an example in which
 * We were kicking out unnecessarily
 * That gave rise to extra work, of course
 * But it /also/ led to exponentially-sized coercions due to lack
   of sharing in coercions (something we want to fix separately #20264)

This MR sharpens up the kick-out criteria; specifially in (KK2) we look
only under type family applications if (fs>=fw).

This forced me to understand the existing kick-out story, and I ended
up rewriting many of the careful Notes in GHC.Tc.Solver.InertSet.
Especially look at the new `Note [The KickOut Criteria]`

The proof of termination is not air-tight, but it is better than before,
and both Richard and I think it's correct :-).

- - - - -
88488847 by Cheng Shao at 2024-08-18T04:44:01+02:00
testsuite: remove undesired -fasm flag from test ways

This patch removes the -fasm flag from test ways, except ways like
optasm that explicitly state they are meant to be compiled with NCG
backend. Most test ways should use the default codegen backend, and
the precense of -fasm can cause stderr mismatches like this when GHC
is configured with the unregisterised backend:

```
--- /dev/null
+++ /tmp/ghctest-3hydwldj/test   spaces/testsuite/tests/profiling/should_compile/prof-late-cc.run/prof-late-cc.comp.stderr.normalised
@@ -0,0 +1,2 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+    Target platform uses unregisterised ABI, so compiling via C
*** unexpected failure for prof-late-cc(prof_no_auto)
```

This has been breaking the wasm unreg nightly job since !12595 landed.

- - - - -
3a145315 by Cheng Shao at 2024-08-18T13:05:45-04:00
ghci: fix isMinTTY.h casing for Windows targets

This commit fixes isMinTTY.h casing in isMinTTY.c that's compiled for
Windows targets. While this looks harmless given Windows filesystems
are case-insensitive by default, it does cause a compilation warning
with recent versions of clang, so we might as well fix the casing:

```
driver\ghci\isMinTTY.c:10:10: error:
     warning: non-portable path to file '"isMinTTY.h"'; specified path differs in case from file name on disk [-Wnonportable-include-path]
   |
10 | #include "isMINTTY.h"
   |          ^

 #include "isMINTTY.h"
         ^~~~~~~~~~~~
         "isMinTTY.h"
1 warning generated.
```

- - - - -
5f972bfb by Zubin Duggal at 2024-08-21T03:18:15-04:00
compiler: Fix pretty printing of ticked prefix constructors (#24237)

- - - - -
ef0a08e7 by Mike Pilgrem at 2024-08-21T03:18:57-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs

- - - - -
05a4be58 by Sebastian Graf at 2024-08-21T03:19:33-04:00
Improve efficiency of `assertError` (#24625)

... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.

- - - - -
c29b2b5a by sheaf at 2024-08-21T13:11:30-04:00
GHCi debugger: drop record name spaces for Ids

When binding new local variables at a breakpoint, we should create
Ids with variable namespace, and not record field namespace. Otherwise
the rest of the compiler falls over because the IdDetails are wrong.

Fixes #25109

- - - - -
bd82ac9f by Hécate Kleidukos at 2024-08-21T13:12:12-04:00
base: Final deprecation of GHC.Pack

The timeline mandated by #21461 has come to its term and after two years
and four minor releases, we are finally removing GHC.Pack from base.

Closes #21536

- - - - -
5092dbff by Sylvain Henry at 2024-08-21T13:12:54-04:00
JS: support rubbish static literals (#25177)

Support for rubbish dynamic literals was added in #24664. This patch
does the same for static literals.

Fix #25177

- - - - -
b5a2c061 by Phil de Joux at 2024-08-21T13:13:33-04:00
haddock docs: prefix comes before, postfix comes after

- - - - -
6fde3685 by Marcin Szamotulski at 2024-08-21T23:15:39-04:00
haddock: include package info with --show-interface

- - - - -
7e02111b by Andreas Klebinger at 2024-08-21T23:16:15-04:00
Document the (x86) SIMD macros.

Fixes #25021.

- - - - -
05116c83 by Rodrigo Mesquita at 2024-08-22T10:37:44-04:00
ghc-internal: Derive version from ghc's version

Fixes #25005

- - - - -
73f5897d by Ben Gamari at 2024-08-22T10:37:44-04:00
base: Deprecate GHC.Desugar

See https://github.com/haskell/core-libraries-committee/issues/216.

This will be removed in GHC 9.14.

- - - - -
821d0a9a by Cheng Shao at 2024-08-22T10:38:22-04:00
compiler: Store ForeignStubs and foreign C files in interfaces

This data is used alongside Core bindings to reconstruct intermediate
build products when linking Template Haskell splices with bytecode.

Since foreign stubs and files are generated in the pipeline, they were
lost with only Core bindings stored in interfaces.

The interface codec type `IfaceForeign` contains a simplified
representation of `ForeignStubs` and the set of foreign sources that
were manually added by the user.

When the backend phase writes an interface, `mkFullIface` calls
`encodeIfaceForeign` to read foreign source file contents and assemble
`IfaceForeign`.

After the recompilation status check of an upstream module,
`initWholeCoreBindings` calls `decodeIfaceForeign` to restore
`ForeignStubs` and write the contents of foreign sources to the file
system as temporary files.
The restored foreign inputs are then processed by `hscInteractive` in
the same manner as in a regular pipeline.

When linking the stub objects for splices, they are excluded from suffix
adjustment for the interpreter way through a new flag in `Unlinked`.

For details about these processes, please consult Note [Foreign stubs
and TH bytecode linking].

Metric Decrease:
    T13701

- - - - -
f0408eeb by Cheng Shao at 2024-08-23T10:37:10-04:00
git: remove a.out and include it in .gitignore

a.out is a configure script byproduct. It was mistakenly checked into
the tree in !13118. This patch removes it, and include it in
.gitignore to prevent a similar error in the future.

- - - - -
1f95c5e4 by Matthew Pickering at 2024-08-23T10:37:46-04:00
docs: Fix code-block syntax on old sphinx version

This code-block directive breaks the deb9 sphinx build.

Fixes #25201

- - - - -
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
975badc5 by Cheng Shao at 2024-10-15T21:12:59+02:00
hadrian/rts: add support for building with UndefinedBehaviorSanitizer

- - - - -


15 changed files:

- .gitignore
- .gitlab-ci.yml
- + .gitlab/README.md
- .gitlab/ci.sh
- .gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5a42a4c3614e299cde641bc254920878ec7de077...975badc59711a4980973a9cecb2a1bbb675b976b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5a42a4c3614e299cde641bc254920878ec7de077...975badc59711a4980973a9cecb2a1bbb675b976b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 19:19:41 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Tue, 15 Oct 2024 15:19:41 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-4] 43 commits: Handle
 exceptions from IO manager backend
Message-ID: <670ec04dcc4cd_1100564795f0109117@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC


Commits:
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
f181a258 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsDocTy

- - - - -
ec054db4 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsBangTy

- - - - -
49e2c393 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsExplicitListTy

- - - - -
07416f3d by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsExplicitTupleTy

- - - - -
ccbbbf7a by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsTypedBracket

- - - - -
6bf58da1 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from HsUntypedBracket

- - - - -
3ad371f8 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
Remove [AddEpAnn] from PatBuilderOpApp

- - - - -
13704726 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: break out 'EpToken "|"' from ClassDecl anns

- - - - -
7a6ddfa4 by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from ClassDecl

- - - - -
67a5a8cc by Alan Zimmerman at 2024-10-15T19:32:07+01:00
EPA: Remove [AddEpAnn] from SynDecl

- - - - -
f4c2b3bd by Alan Zimmerman at 2024-10-15T20:18:13+01:00
EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

This has a knock-on to everything that uses HsDataDefn

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- + compiler/GHC/Hs/Doc.hs-boot


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1a9382906d17b8d4335414e8cee54d30a8ad178...f4c2b3bd6a7ffe280a31fac7d0eef34c9934f9ba

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1a9382906d17b8d4335414e8cee54d30a8ad178...f4c2b3bd6a7ffe280a31fac7d0eef34c9934f9ba
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 21:07:41 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 15 Oct 2024 17:07:41 -0400
Subject: [Git][ghc/ghc][wip/ubsan] hadrian/rts: add support for building with
 UndefinedBehaviorSanitizer
Message-ID: <670ed99d29d24_1100568bbfa0117223@gitlab.mail>



Cheng Shao pushed to branch wip/ubsan at Glasgow Haskell Compiler / GHC


Commits:
73db80fd by Cheng Shao at 2024-10-15T23:05:46+02:00
hadrian/rts: add support for building with UndefinedBehaviorSanitizer

- - - - -


3 changed files:

- hadrian/src/Flavour.hs
- rts/Interpreter.c
- rts/rts.cabal


Changes:

=====================================
hadrian/src/Flavour.hs
=====================================
@@ -8,6 +8,7 @@ module Flavour
   , splitSections
   , enableThreadSanitizer
   , enableLateCCS
+  , enableUBSan
   , enableDebugInfo, enableTickyGhc
   , viaLlvmBackend
   , enableProfiledGhc
@@ -50,6 +51,7 @@ flavourTransformers = M.fromList
     , "no_split_sections" =: noSplitSections
     , "thread_sanitizer" =: enableThreadSanitizer False
     , "thread_sanitizer_cmm" =: enableThreadSanitizer True
+    , "ubsan"            =: enableUBSan
     , "llvm"             =: viaLlvmBackend
     , "profiled_ghc"     =: enableProfiledGhc
     , "no_dynamic_ghc"   =: disableDynamicGhcPrograms
@@ -239,6 +241,23 @@ enableThreadSanitizer instrumentCmm = addArgs $ notStage0 ? mconcat
         ]
     ]
 
+enableUBSan :: Flavour -> Flavour
+enableUBSan =
+  addArgs $
+    notStage0
+      ? mconcat
+        [ package rts ? builder (Cabal Flags) ? arg "ubsan",
+          builder (Ghc CompileHs) ? arg "-optc-fsanitize=undefined",
+          builder (Ghc CompileCWithGhc) ? arg "-optc-fsanitize=undefined",
+          builder (Ghc CompileCppWithGhc) ? arg "optcxx-fsanitize=undefined",
+          builder (Ghc LinkHs) ? arg "-optc-fsanitize=undefined"
+            <> arg "-optl-fsanitize=undefined"
+            <> arg "-optl-shared-libsan"
+            <> arg "-optl-Wl,-rpath,/usr/lib/llvm-19/lib/clang/19/lib/linux"
+            <> arg "-optl--rtlib=compiler-rt",
+          builder (Cc CompileC) ? arg "-fsanitize=undefined"
+        ]
+
 -- | Use the LLVM backend in stages 1 and later.
 viaLlvmBackend :: Flavour -> Flavour
 viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"


=====================================
rts/Interpreter.c
=====================================
@@ -326,6 +326,7 @@ static StgWord app_ptrs_itbl[] = {
 HsStablePtr rts_breakpoint_io_action; // points to the IO action which is executed on a breakpoint
                                       // it is set in ghci/GHCi/Run.hs:withBreakAction
 
+__attribute__((no_sanitize("undefined")))
 Capability *
 interpretBCO (Capability* cap)
 {


=====================================
rts/rts.cabal
=====================================
@@ -81,6 +81,8 @@ flag thread-sanitizer
     mechanism supported by GCC and Clang. See Note [ThreadSanitizer]
     in @rts/include/rts/TSANUtils.h at .
   default: False
+flag ubsan
+  default: False
 
 library
     -- rts is a wired in package and
@@ -190,6 +192,9 @@ library
         cc-options: -fsanitize=thread
         ld-options: -fsanitize=thread
 
+      if flag(ubsan)
+        ld-options: -fsanitize=undefined -shared-libsan -Wl,-rpath,/usr/lib/llvm-19/lib/clang/19/lib/linux --rtlib=compiler-rt
+
       if os(linux)
          -- the RTS depends upon libc. while this dependency is generally
          -- implicitly added by `cc`, we must explicitly add it here to ensure



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/73db80fd9f263797019583324f49d1f4eb7d5ce7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 21:30:32 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 15 Oct 2024 17:30:32 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 2 commits: Revert "finder: Add
 `IsBootInterface` to finder cache keys"
Message-ID: <670edef8b54e_11005699fb381196c6@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
bb8f9dc0 by Ben Gamari at 2024-10-15T13:46:09-04:00
Revert "finder: Add `IsBootInterface` to finder cache keys"

There are objections raised on the MR (!13237) and the interface change
makes me rather uncomfortable.

This reverts commit fb82ee70d9f7fe43cd1cd2aa7263e9aef6cf9238.

- - - - -
036044df by Ben Gamari at 2024-10-15T17:30:09-04:00
Revert "gitlab-ci: Update bootstrap_matrix"

This reverts commit c332cb09f1bc767536bd2afd12c9ccbcf0a34289.

- - - - -


13 changed files:

- .gitlab-ci.yml
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs
- − testsuite/tests/driver/boot-target/A.hs
- − testsuite/tests/driver/boot-target/A.hs-boot
- − testsuite/tests/driver/boot-target/B.hs
- − testsuite/tests/driver/boot-target/Makefile
- − testsuite/tests/driver/boot-target/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -84,7 +84,7 @@ workflow:
   matrix:
     - GHC_VERSION: 9.4.3
       DOCKER_IMAGE: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV"
-    - GHC_VERSION: 9.6.5
+    - GHC_VERSION: 9.6.2
       DOCKER_IMAGE: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10-ghc9_6:$DOCKER_REV"
 
 # Allow linters to fail on draft MRs.


=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -893,7 +893,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2055,43 +2055,25 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = src_fn
-
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+
+        -- Make a ModLocation for this file
+        let location = mkHomeModLocation fopts pi_mod_name src_fn
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
             , nms_src_hash = src_hash
-            , nms_hsc_src = hsc_src
+            , nms_is_boot = NotBoot
+            , nms_hsc_src =
+                if isHaskellSigFilename src_fn
+                   then HsigFile
+                   else HsSrcFile
             , nms_location = location
             , nms_mod = mod
             , nms_preimps = preimps
@@ -2119,10 +2101,9 @@ checkSummaryHash
            -- Also, only add to finder cache for non-boot modules as the finder cache
            -- makes sure to add a boot suffix for boot files.
            _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
+              let fc        = hsc_FC hsc_env
               case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
+                HsSrcFile -> addModuleToFinder fc (ms_mod old_summary) location
                 _ -> return ()
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
@@ -2260,6 +2241,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
             , nms_src_hash = src_hash
+            , nms_is_boot = is_boot
             , nms_hsc_src = hsc_src
             , nms_location = location
             , nms_mod = mod
@@ -2272,6 +2254,7 @@ data MakeNewModSummary
   = MakeNewModSummary
       { nms_src_fn :: FilePath
       , nms_src_hash :: Fingerprint
+      , nms_is_boot :: IsBootInterface
       , nms_hsc_src :: HscSource
       , nms_location :: ModLocation
       , nms_mod :: Module


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -743,7 +743,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location
 
   -- Make the ModSummary to hand to hscMain
   let


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -89,7 +89,7 @@ type BaseName = String  -- Basename of file
 
 
 initFinderCache :: IO FinderCache
-initFinderCache = FinderCache <$> newIORef emptyInstalledModuleWithIsBootEnv
+initFinderCache = FinderCache <$> newIORef emptyInstalledModuleEnv
                               <*> newIORef M.empty
 
 -- remove all the home modules from the cache; package modules are
@@ -97,23 +97,23 @@ initFinderCache = FinderCache <$> newIORef emptyInstalledModuleWithIsBootEnv
 -- cache
 flushFinderCaches :: FinderCache -> UnitEnv -> IO ()
 flushFinderCaches (FinderCache ref file_ref) ue = do
-  atomicModifyIORef' ref $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+  atomicModifyIORef' ref $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
   atomicModifyIORef' file_ref $ \_ -> (M.empty, ())
  where
-  is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+  is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-addToFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+addToFinderCache :: FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
 addToFinderCache (FinderCache ref _) key val =
-  atomicModifyIORef' ref $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+  atomicModifyIORef' ref $ \c -> (extendInstalledModuleEnv c key val, ())
 
-removeFromFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> IO ()
+removeFromFinderCache :: FinderCache -> InstalledModule -> IO ()
 removeFromFinderCache (FinderCache ref _) key =
-  atomicModifyIORef' ref $ \c -> (delInstalledModuleWithIsBootEnv c key, ())
+  atomicModifyIORef' ref $ \c -> (delInstalledModuleEnv c key, ())
 
-lookupFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+lookupFinderCache :: FinderCache -> InstalledModule -> IO (Maybe InstalledFindResult)
 lookupFinderCache (FinderCache ref _) key = do
    c <- readIORef ref
-   return $! lookupInstalledModuleWithIsBootEnv c key
+   return $! lookupInstalledModuleEnv c key
 
 lookupFileCache :: FinderCache -> FilePath -> IO Fingerprint
 lookupFileCache (FinderCache _ ref) key = do
@@ -262,7 +262,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -319,7 +319,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -329,23 +329,22 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  let imod = toUnitId <$> mod
+  addToFinderCache fc imod (InstalledFound loc imod)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+  let mod = mkHomeInstalledModule home_unit mod_name
+  addToFinderCache fc mod (InstalledFound loc mod)
+  return (mkHomeModule home_unit mod_name)
 
-uncacheModule :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> IO ()
+uncacheModule :: FinderCache -> HomeUnit -> ModuleName -> IO ()
 uncacheModule fc home_unit mod_name = do
-  let mod = mkHomeInstalledModule home_unit (gwib_mod mod_name)
-  removeFromFinderCache fc (GWIB mod (gwib_isBoot mod_name))
-
+  let mod = mkHomeInstalledModule home_unit mod_name
+  removeFromFinderCache fc mod
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -478,7 +477,7 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -22,7 +22,7 @@ import qualified Data.Set as Set
 -- modules along the search path. On @:load@, we flush the entire
 -- contents of this cache.
 --
-type FinderCacheState = InstalledModuleWithIsBootEnv InstalledFindResult
+type FinderCacheState = InstalledModuleEnv InstalledFindResult
 type FileCacheState   = M.Map FilePath Fingerprint
 data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState)
                                , fcFileCache   :: (IORef FileCacheState)


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -86,8 +86,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -715,8 +713,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -730,6 +726,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}


=====================================
testsuite/tests/driver/boot-target/A.hs deleted
=====================================
@@ -1,5 +0,0 @@
-module A where
-
-import B
-
-data A = A B


=====================================
testsuite/tests/driver/boot-target/A.hs-boot deleted
=====================================
@@ -1,3 +0,0 @@
-module A where
-
-data A


=====================================
testsuite/tests/driver/boot-target/B.hs deleted
=====================================
@@ -1,5 +0,0 @@
-module B where
-
-import {-# source #-} A
-
-data B = B A


=====================================
testsuite/tests/driver/boot-target/Makefile deleted
=====================================
@@ -1,8 +0,0 @@
-boot1:
-	$(TEST_HC) -c A.hs-boot B.hs
-
-boot2:
-	$(TEST_HC) A.hs-boot A.hs B.hs -v0
-
-boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/all.T deleted
=====================================
@@ -1,10 +0,0 @@
-def test_boot(name):
-    return test(name,
-     [extra_files(['A.hs', 'A.hs-boot', 'B.hs']),
-      ],
-     makefile_test,
-     [])
-
-test_boot('boot1')
-test_boot('boot2')
-test_boot('boot3')



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c332cb09f1bc767536bd2afd12c9ccbcf0a34289...036044dffaa555f217fdd696d425dc877e21d9b9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c332cb09f1bc767536bd2afd12c9ccbcf0a34289...036044dffaa555f217fdd696d425dc877e21d9b9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 22:46:08 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 15 Oct 2024 18:46:08 -0400
Subject: [Git][ghc/ghc][wip/ubsan] hadrian/rts: add support for building with
 UndefinedBehaviorSanitizer
Message-ID: <670ef0b0fb35_38cb40bcf34925e0@gitlab.mail>



Cheng Shao pushed to branch wip/ubsan at Glasgow Haskell Compiler / GHC


Commits:
0ff36bbb by Cheng Shao at 2024-10-16T00:44:23+02:00
hadrian/rts: add support for building with UndefinedBehaviorSanitizer

- - - - -


2 changed files:

- hadrian/src/Flavour.hs
- rts/rts.cabal


Changes:

=====================================
hadrian/src/Flavour.hs
=====================================
@@ -8,6 +8,7 @@ module Flavour
   , splitSections
   , enableThreadSanitizer
   , enableLateCCS
+  , enableUBSan
   , enableDebugInfo, enableTickyGhc
   , viaLlvmBackend
   , enableProfiledGhc
@@ -50,6 +51,7 @@ flavourTransformers = M.fromList
     , "no_split_sections" =: noSplitSections
     , "thread_sanitizer" =: enableThreadSanitizer False
     , "thread_sanitizer_cmm" =: enableThreadSanitizer True
+    , "ubsan"            =: enableUBSan
     , "llvm"             =: viaLlvmBackend
     , "profiled_ghc"     =: enableProfiledGhc
     , "no_dynamic_ghc"   =: disableDynamicGhcPrograms
@@ -239,6 +241,23 @@ enableThreadSanitizer instrumentCmm = addArgs $ notStage0 ? mconcat
         ]
     ]
 
+enableUBSan :: Flavour -> Flavour
+enableUBSan =
+  addArgs $
+    notStage0
+      ? mconcat
+        [ package rts ? builder (Cabal Flags) ? arg "ubsan",
+          builder (Ghc CompileHs) ? arg "-optc-fsanitize=undefined",
+          builder (Ghc CompileCWithGhc) ? arg "-optc-fsanitize=undefined",
+          builder (Ghc CompileCppWithGhc) ? arg "optcxx-fsanitize=undefined",
+          builder (Ghc LinkHs) ? arg "-optc-fsanitize=undefined"
+            <> arg "-optl-fsanitize=undefined"
+            <> arg "-optl-shared-libsan"
+            <> arg "-optl-Wl,-rpath,/usr/lib/llvm-19/lib/clang/19/lib/linux"
+            <> arg "-optl--rtlib=compiler-rt",
+          builder (Cc CompileC) ? arg "-fsanitize=undefined"
+        ]
+
 -- | Use the LLVM backend in stages 1 and later.
 viaLlvmBackend :: Flavour -> Flavour
 viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"


=====================================
rts/rts.cabal
=====================================
@@ -81,6 +81,8 @@ flag thread-sanitizer
     mechanism supported by GCC and Clang. See Note [ThreadSanitizer]
     in @rts/include/rts/TSANUtils.h at .
   default: False
+flag ubsan
+  default: False
 
 library
     -- rts is a wired in package and
@@ -190,6 +192,9 @@ library
         cc-options: -fsanitize=thread
         ld-options: -fsanitize=thread
 
+      if flag(ubsan)
+        ld-options: -fsanitize=undefined -shared-libsan -Wl,-rpath,/usr/lib/llvm-19/lib/clang/19/lib/linux --rtlib=compiler-rt
+
       if os(linux)
          -- the RTS depends upon libc. while this dependency is generally
          -- implicitly added by `cc`, we must explicitly add it here to ensure



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ff36bbbbefb7e1184fb0a453cd4e38bdb8b61ec

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 15 23:47:40 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 15 Oct 2024 19:47:40 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-interpreter-pointer-overflow
Message-ID: <670eff1c92c3b_38cb402d2418963fc@gitlab.mail>



Cheng Shao pushed new branch wip/fix-interpreter-pointer-overflow at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-interpreter-pointer-overflow
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 01:42:11 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 15 Oct 2024 21:42:11 -0400
Subject: [Git][ghc/ghc][wip/T25374] 2 commits: rts/Disassembler: Fix encoding
 of BRK_FUN instruction
Message-ID: <670f19f373116_38cb4082d1741086e@gitlab.mail>



Ben Gamari pushed to branch wip/T25374 at Glasgow Haskell Compiler / GHC


Commits:
4e1d8e80 by Ben Gamari at 2024-10-15T20:17:36-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -
d7e80814 by Ben Gamari at 2024-10-15T21:25:43-04:00
testsuite: Add test for #25374

- - - - -


5 changed files:

- rts/Disassembler.c
- + testsuite/tests/codeGen/should_run/T25374/T25374.hs
- + testsuite/tests/codeGen/should_run/T25374/T25374.script
- + testsuite/tests/codeGen/should_run/T25374/T25374A.hs
- + testsuite/tests/codeGen/should_run/T25374/all.T


Changes:

=====================================
rts/Disassembler.c
=====================================
@@ -67,12 +67,12 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }
          debugBelch("\n");
-         pc += 4;
+         pc += 6;
          break;
       case bci_SWIZZLE: {
          W_     stkoff = BCO_GET_LARGE_ARG;


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.hs
=====================================
@@ -0,0 +1,8 @@
+import T25374A
+
+fieldsSam :: NP xs -> NP xs -> Bool
+fieldsSam UNil UNil = True
+
+x :: Bool
+x = fieldsSam UNil UNil
+


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.script
=====================================
@@ -0,0 +1,2 @@
+:load T25374
+x


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374A.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+module T25374A where
+
+import GHC.Exts
+
+type NP :: [UnliftedType] -> UnliftedType
+data NP xs where
+  UNil :: NP '[]
+  (::*) :: x -> NP xs -> NP (x ': xs)
+


=====================================
testsuite/tests/codeGen/should_run/T25374/all.T
=====================================
@@ -0,0 +1,3 @@
+# This shouldn't crash the disassembler
+test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, unless(debug_rts, skip)], ghci_script, [''])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a69c8d6698549ec3007d934e7e4817c1983b00b8...d7e80814967923b97f4acc1322dce69c66e60a76

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a69c8d6698549ec3007d934e7e4817c1983b00b8...d7e80814967923b97f4acc1322dce69c66e60a76
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 03:44:49 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 15 Oct 2024 23:44:49 -0400
Subject: [Git][ghc/ghc][master] Changed import from Ghc.  module to L.H.S
 module
Message-ID: <670f36b178352_38cb40d7721012712b@gitlab.mail>



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


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -


2 changed files:

- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs


Changes:

=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -31,10 +31,9 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat
 
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
+import Language.Haskell.Syntax.Basic ( Fixity )
 
-import GHC.Types.Fixity (Fixity)
 import GHC.Types.Basic (InlinePragma)
-
 import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -94,13 +94,12 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
 import Language.Haskell.Syntax.Binds
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
-import Language.Haskell.Syntax.Basic (Role)
+import Language.Haskell.Syntax.Basic (Role, LexicalFixity)
 import Language.Haskell.Syntax.Specificity (Specificity)
 
 import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation
                        ,TyConFlavour(..), TypeOrData(..))
 import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
-import GHC.Types.Fixity (LexicalFixity)
 
 import GHC.Unit.Module.Warnings (WarningTxt)
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 03:45:37 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 15 Oct 2024 23:45:37 -0400
Subject: [Git][ghc/ghc][master] Add a release-notes entry for
 -Wincomplete-record-selectors
Message-ID: <670f36e1e23d_38cb40d771c01299dc@gitlab.mail>



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


Commits:
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -


1 changed file:

- docs/users_guide/9.14.1-notes.rst


Changes:

=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -11,6 +11,15 @@ for specific guidance on migrating programs to this release.
 Language
 ~~~~~~~~
 
+* ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
+  by `GHC Proposal 516: add warning for incomplete record selectors _`.
+  Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
+  Workaround: add ``-Werror=no-incomplete-record-selectors``.
+
+  Note that this warning is at least
+  as serious as a warning about missing patterns from a function definition, perhaps even
+  more so, since it is invisible in the source program.
+
 Compiler
 ~~~~~~~~
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 04:13:59 2024
From: gitlab at gitlab.haskell.org (Brandon Chinn (@brandonchinn178))
Date: Wed, 16 Oct 2024 00:13:59 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25375
Message-ID: <670f3d87891b8_38cb40121ce8c130123@gitlab.mail>



Brandon Chinn pushed new branch wip/T25375 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25375
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 04:17:02 2024
From: gitlab at gitlab.haskell.org (Brandon Chinn (@brandonchinn178))
Date: Wed, 16 Oct 2024 00:17:02 -0400
Subject: [Git][ghc/ghc][wip/T25375] Fix CRLF in multiline strings (#25375)
Message-ID: <670f3e3eb784_38cb4012305cc1359f5@gitlab.mail>



Brandon Chinn pushed to branch wip/T25375 at Glasgow Haskell Compiler / GHC


Commits:
838b5c67 by Brandon Chinn at 2024-10-15T21:15:50-07:00
Fix CRLF in multiline strings (#25375)

- - - - -


6 changed files:

- .gitattributes
- compiler/GHC/Parser/String.hs
- docs/users_guide/exts/multiline_strings.rst
- + testsuite/tests/parser/should_run/T25375.hs
- + testsuite/tests/parser/should_run/T25375.stdout
- testsuite/tests/parser/should_run/all.T


Changes:

=====================================
.gitattributes
=====================================
@@ -2,3 +2,4 @@
 # don't convert anything on checkout
 * text=auto eol=lf
 mk/win32-tarballs.md5sum text=auto eol=LF
+testsuite/tests/parser/should_run/T25375.hs text=auto eol=crlf


=====================================
compiler/GHC/Parser/String.hs
=====================================
@@ -262,6 +262,7 @@ lexMultilineString = lexStringWith processChars processChars
     processChars =
           collapseGaps             -- Step 1
       >>> expandLeadingTabs        -- Step 3
+      >>> normalizeEOL
       >>> rmCommonWhitespacePrefix -- Step 4
       >>> collapseOnlyWsLines      -- Step 5
       >>> rmFirstNewline           -- Step 7a
@@ -280,6 +281,18 @@ lexMultilineString = lexStringWith processChars processChars
             [] -> []
        in go 0
 
+    -- Normalize line endings to LF. The spec dictates that lines should be
+    -- split on EOL and rejoined with LF always, even if originally CRLF. But
+    -- because we aren't actually splitting/rejoining, we'll manually convert
+    -- CRLF here
+    normalizeEOL :: HasChar c => [c] -> [c]
+    normalizeEOL =
+      let go = \case
+            Char '\r' : c@(Char '\n') : cs -> c : go cs
+            c : cs -> c : go cs
+            [] -> []
+       in go
+
     rmCommonWhitespacePrefix :: HasChar c => [c] -> [c]
     rmCommonWhitespacePrefix cs0 =
       let commonWSPrefix = getCommonWsPrefix (map getChar cs0)
@@ -354,14 +367,14 @@ the same behavior as HsString, which contains the normalized string
 
 The canonical steps for post processing a multiline string are:
 1. Collapse string gaps
-2. Split the string by newlines
+2. Split the string by EOL
 3. Convert leading tabs into spaces
     * In each line, any tabs preceding non-whitespace characters are replaced with spaces up to the next tab stop
 4. Remove common whitespace prefix in every line except the first (see below)
 5. If a line contains only whitespace, remove all of the whitespace
 6. Join the string back with `\n` delimiters
-7a. If the first character of the string is a newline, remove it
-7b. If the last character of the string is a newline, remove it
+7a. If the first character of the string is an EOL, remove it
+7b. If the last character of the string is an EOL, remove it
 8. Interpret escaped characters
 
 The common whitespace prefix can be informally defined as "The longest
@@ -372,7 +385,7 @@ It's more precisely defined with the following algorithm:
 
 1. Take a list representing the lines in the string
 2. Ignore the following elements in the list:
-    * The first line (we want to ignore everything before the first newline)
+    * The first line (we want to ignore everything before the first EOL)
     * Empty lines
     * Lines with only whitespace characters
 3. Calculate the longest prefix of whitespace shared by all lines in the remaining list


=====================================
docs/users_guide/exts/multiline_strings.rst
=====================================
@@ -14,7 +14,7 @@ With this extension, GHC now recognizes multiline string literals with ``"""`` d
 
 Normal string literals are lexed, then string gaps are collapsed, then escape characters are resolved. Multiline string literals add the following post-processing steps between collapsing string gaps and resolving escape characters:
 
-#. Split the string by newlines
+#. Split the string by EOL
 
 #. Replace leading tabs with spaces up to the next tab stop
 
@@ -22,9 +22,11 @@ Normal string literals are lexed, then string gaps are collapsed, then escape ch
 
 #. If a line only contains whitespace, remove all of the whitespace
 
-#. Join the string back with ``\n`` delimiters
+#. Join the string back with ``\n`` delimiters -- even if file uses CRLF
 
-#. If the first character of the string is a newline, remove it
+#. If the first character of the string is an EOL, remove it
+
+#. If the last character of the string is an EOL, remove it
 
 Examples
 ~~~~~~~~


=====================================
testsuite/tests/parser/should_run/T25375.hs
=====================================
@@ -0,0 +1,38 @@
+{-# LANGUAGE MultilineStrings #-}
+
+str1 = unlines
+  [ "aaa"
+  , "bbb"
+  , "ccc"
+  ]
+
+str2 = "aaa\n\
+       \bbb\n\
+       \ccc\n"
+
+str3 = """
+       aaa
+       bbb
+       ccc
+       """
+
+str4 = """
+
+       aaa
+       bbb
+       ccc
+
+       """
+
+str5 = """
+       aaa
+       bbb
+       ccc\n
+       """
+
+main = do
+  print str1
+  print str2
+  print str3
+  print str4
+  print str5


=====================================
testsuite/tests/parser/should_run/T25375.stdout
=====================================
@@ -0,0 +1,5 @@
+"aaa\nbbb\nccc\n"
+"aaa\nbbb\nccc\n"
+"aaa\nbbb\nccc"
+"\naaa\nbbb\nccc\n"
+"aaa\nbbb\nccc\n"


=====================================
testsuite/tests/parser/should_run/all.T
=====================================
@@ -23,3 +23,4 @@ test('RecordDotSyntax5', normal, compile_and_run, [''])
 test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
 test('MultilineStrings', normal, compile_and_run, [''])
 test('MultilineStringsOverloaded', normal, compile_and_run, [''])
+test('T25375', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/838b5c679d02ed26e2fbca69c1b1b7b0274ebf84

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 11:51:10 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 16 Oct 2024 07:51:10 -0400
Subject: [Git][ghc/ghc] Pushed new tag ghc-9.12.1-alpha1
Message-ID: <670fa8aeb0543_94ff3880a54113342@gitlab.mail>



Zubin pushed new tag ghc-9.12.1-alpha1 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/ghc-9.12.1-alpha1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 12:39:09 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 16 Oct 2024 08:39:09 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] More boot-file awareness in Finder
Message-ID: <670fb3ed4452d_3c117e1ecc1082835@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
97d48ad4 by Sjoerd Visscher at 2024-10-16T14:38:41+02:00
More boot-file awareness in Finder

Finishes work started in fff55592

Adds findImportedModuleWithIsBoot and findHomeModuleWithIsBoot so that callers don't have to call addBootSuffix on the result.

Removes InstalledModule field from InstalledFound constructor since it's already part of the key that was searched for.

- - - - -


13 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Location.hs
- + testsuite/tests/driver/boot-target/C.hs
- + testsuite/tests/driver/boot-target/D.hs
- testsuite/tests/driver/boot-target/Makefile
- testsuite/tests/driver/boot-target/all.T
- + testsuite/tests/driver/boot-target/boot4.stderr


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -771,7 +771,7 @@ summariseRequirement pn mod_name = do
     let fopts = initFinderOpts dflags
 
     let PackageName pn_fs = pn
-    let location = mkHomeModLocation2 fopts mod_name
+    let location = mkHomeModLocation2 fopts (notBoot mod_name)
                     (unsafeEncodeUtf $ unpackFS pn_fs  moduleNameSlashes mod_name) (os "hsig")
 
     env <- getBkpEnv
@@ -848,23 +848,20 @@ hsModuleToModSummary home_keys pn hsc_src modname
     let PackageName unit_fs = pn
         dflags = hsc_dflags hsc_env
         fopts = initFinderOpts dflags
+        modWithIsBoot = GWIB modname (hscSourceToIsBoot hsc_src)
     -- Unfortunately, we have to define a "fake" location in
     -- order to appease the various code which uses the file
     -- name to figure out where to put, e.g. object files.
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation2 fopts modWithIsBoot
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
                               (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
@@ -893,7 +890,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modWithIsBoot location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2126,31 +2126,21 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
               ".lhs-boot" -> IsBoot
               _ -> NotBoot
 
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            modWithIsBoot = GWIB pi_mod_name is_boot
+
+            hsc_src
+              | IsBoot <- is_boot = HsBootFile
+              | isHaskellSigFilename src_fn = HsigFile
+              | otherwise = HsSrcFile
+
+            location = mkHomeModLocation fopts modWithIsBoot src_path
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit modWithIsBoot location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2180,14 +2170,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
            _ <- do
               let fc = hsc_FC hsc_env
                   gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+              addModuleToFinder fc gwib location
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
@@ -2239,7 +2225,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env (GWIB wanted_mod is_boot) mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2243,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2253,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env (GWIB imp is_boot) pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,19 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+        modWithIsBoot = GWIB mod_name (hscSourceToIsBoot src_flavour)
+    let location1 = mkHomeModLocation2 fopts modWithIsBoot (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -804,15 +799,15 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     -- above
     let expl_o_file = outputFile_ dflags
         expl_dyn_o_file  = dynOutputFile_ dflags
-        location5 | Just ofile <- expl_o_file
+        location4 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
-    return location5
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
+    return location4
     where
       fopts = initFinderOpts dflags
 


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -317,7 +317,7 @@ loadSrcInterface_maybe doc mod want_boot maybe_pkg
   -- interface; it will call the Finder again, but the ModLocation will be
   -- cached from the first search.
   = do hsc_env <- getTopEnv
-       res <- liftIO $ findImportedModule hsc_env mod maybe_pkg
+       res <- liftIO $ findImportedModuleWithIsBoot hsc_env (GWIB mod want_boot) maybe_pkg
        case res of
            Found _ mod -> initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
            -- TODO: Make sure this error message is good
@@ -895,9 +895,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit (GWIB mod hi_boot_file))
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,9 +15,11 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
+    findHomeModuleWithIsBoot,
     findExposedPackageModule,
     mkHomeModLocation,
     mkHomeModLocation2,
@@ -148,7 +150,10 @@ initFinderCache = do
 -- that package is searched for the module.
 
 findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult
-findImportedModule hsc_env mod pkg_qual =
+findImportedModule hsc_env = findImportedModuleWithIsBoot hsc_env . notBoot
+
+findImportedModuleWithIsBoot :: HscEnv -> ModuleNameWithIsBoot -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod pkg_qual =
   let fc        = hsc_FC hsc_env
       mhome_unit = hsc_home_unit_maybe hsc_env
       dflags    = hsc_dflags hsc_env
@@ -161,10 +166,10 @@ findImportedModuleNoHsc
   -> FinderOpts
   -> UnitEnv
   -> Maybe HomeUnit
-  -> ModuleName
+  -> ModuleNameWithIsBoot
   -> PkgQual
   -> IO FindResult
-findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
+findImportedModuleNoHsc fc fopts ue mhome_unit gwib at GWIB { gwib_mod = mod_name } mb_pkg =
   case mb_pkg of
     NoPkgQual  -> unqual_import
     ThisPkg uid | (homeUnitId <$> mhome_unit) == Just uid -> home_import
@@ -178,7 +183,7 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
 
 
     home_import = case mhome_unit of
-                   Just home_unit -> findHomeModule fc fopts home_unit mod_name
+                   Just home_unit -> findHomeModuleWithIsBoot fc fopts home_unit gwib
                    Nothing -> pure $ NoPackage (panic "findImportedModule: no home-unit")
 
 
@@ -186,11 +191,11 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
       -- If the module is reexported, then look for it as if it was from the perspective
       -- of that package which reexports it.
       | Just real_mod_name <- mod_name `M.lookup` finder_reexportedModules opts =
-        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) real_mod_name NoPkgQual
+        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) gwib{ gwib_mod = real_mod_name } NoPkgQual
       | mod_name `Set.member` finder_hiddenModules opts =
         return (mkHomeHidden uid)
       | otherwise =
-        findHomePackageModule fc opts uid mod_name
+        findHomePackageModule fc opts uid gwib
 
     -- Do not be smart and change this to `foldr orIfNotFound home_import hs` as
     -- that is not the same!! home_import is first because we need to look within ourselves
@@ -228,15 +233,15 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModuleWithIsBoot -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit gwib at GWIB { gwib_mod = mod } = do
   case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
-        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
+        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName <$> gwib)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
-        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
-    _ -> findPackageModule fc unit_state fopts mod
+        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName <$> gwib)
+    _ -> findPackageModule fc unit_state fopts gwib
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -271,10 +276,10 @@ orIfNotFound this or_this = do
 -- been done.  Otherwise, do the lookup (with the IO action) and save
 -- the result in the finder cache and the module location cache (if it
 -- was successful.)
-homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
+homeSearchCache :: FinderCache -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
-  let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  let mod = mkModule home_unit <$> mod_name
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -290,13 +295,13 @@ findLookupResult :: FinderCache -> FinderOpts -> LookupResult -> IO FindResult
 findLookupResult fc fopts r = case r of
      LookupFound m pkg_conf -> do
        let im = fst (getModuleInstantiation m)
-       r' <- findPackageModule_ fc fopts im (fst pkg_conf)
+       r' <- findPackageModule_ fc fopts (notBoot im) (fst pkg_conf)
        case r' of
         -- TODO: ghc -M is unlikely to do the right thing
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -344,24 +349,27 @@ modLocationCache fc mod do_this = do
 addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
   let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
 addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
   let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
+  addToFinderCache fc mod (InstalledFound loc)
   return (mkHomeModule home_unit (gwib_mod mod_name))
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
 
 findHomeModule :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
-findHomeModule fc fopts  home_unit mod_name = do
+findHomeModule fc fopts home_unit = findHomeModuleWithIsBoot fc fopts home_unit . notBoot
+
+findHomeModuleWithIsBoot :: FinderCache -> FinderOpts -> HomeUnit -> ModuleNameWithIsBoot -> IO FindResult
+findHomeModuleWithIsBoot fc fopts home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -381,12 +389,12 @@ mkHomeHidden uid =
            , fr_unusables = []
            , fr_suggestions = []}
 
-findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO FindResult
+findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO FindResult
 findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -414,35 +422,33 @@ findHomePackageModule fc fopts  home_unit mod_name = do
 --
 --  4. Some special-case code in GHCi (ToDo: Figure out why that needs to
 --  call this.)
-findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO InstalledFindResult
-findInstalledHomeModule fc fopts home_unit mod_name = do
-  homeSearchCache fc home_unit mod_name $
+findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult
+findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib_isBoot = is_boot } = do
+  homeSearchCache fc home_unit gwib $
    let
      maybe_working_dir = finder_workingDirectory fopts
      home_path = case maybe_working_dir of
                   Nothing -> finder_importPaths fopts
                   Just fp -> augmentImports fp (finder_importPaths fopts)
+     mod = mkModule home_unit mod_name
      hi_dir_path =
       case finder_hiDir fopts of
         Just hiDir -> case maybe_working_dir of
           Nothing -> [hiDir]
           Just fp -> [fp  hiDir]
         Nothing -> home_path
-     hisuf = finder_hiSuf fopts
-     mod = mkModule home_unit mod_name
 
-     source_exts =
-      [ (os "hs",    mkHomeModLocationSearched fopts mod_name $ os "hs")
-      , (os "lhs",   mkHomeModLocationSearched fopts mod_name $ os "lhs")
-      , (os "hsig",  mkHomeModLocationSearched fopts mod_name $ os "hsig")
-      , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig")
-      ]
+     sufs = case is_boot of
+       NotBoot -> ["hs", "lhs", "hsig", "lhsig"]
+       IsBoot -> ["hs-boot", "lhs-boot"]
+     source_exts = [ (ext, mkHomeModLocationSearched fopts gwib ext) | ext <- map os sufs ]
 
+     hisuf = case is_boot of
+       NotBoot -> finder_hiSuf fopts
+       IsBoot -> addBootSuffix $ finder_hiSuf fopts
      -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that
      -- when hiDir field is set in dflags, we know to look there (see #16500)
-     hi_exts = [ (hisuf,                mkHomeModHiOnlyLocation fopts mod_name)
-               , (addBootSuffix hisuf,  mkHomeModHiOnlyLocation fopts mod_name)
-               ]
+     hi_exts = [ (hisuf, mkHomeModHiOnlyLocation fopts gwib) ]
 
         -- In compilation manager modes, we look for source files in the home
         -- package because we can compile these automatically.  In one-shot
@@ -456,7 +462,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -467,9 +473,9 @@ augmentImports work_dir (fp:fps)
   | otherwise            = (work_dir  fp) : augmentImports work_dir fps
 
 -- | Search for a module in external packages only.
-findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult
+findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModuleWithIsBoot -> IO InstalledFindResult
 findPackageModule fc unit_state fopts mod = do
-  let pkg_id = moduleUnit mod
+  let pkg_id = moduleUnit (gwib_mod mod)
   case lookupUnitId unit_state pkg_id of
      Nothing -> return (InstalledNoPackage pkg_id)
      Just u  -> findPackageModule_ fc fopts mod u
@@ -481,15 +487,15 @@ findPackageModule fc unit_state fopts mod = do
 -- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
 -- The redundancy is to avoid an extra lookup in the package state
 -- for the appropriate config.
-findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ fc fopts mod pkg_conf = do
+findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModuleWithIsBoot -> UnitInfo -> IO InstalledFindResult
+findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc gwib $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +519,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,10 +553,10 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
-mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt
+mkHomeModLocationSearched :: FinderOpts -> ModuleNameWithIsBoot -> FileExt
                           -> OsPath -> BaseName -> ModLocation
 mkHomeModLocationSearched fopts mod suff path basename =
   mkHomeModLocation2 fopts mod (path  basename) suff
@@ -589,34 +595,35 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
+mkHomeModLocation :: FinderOpts -> ModuleNameWithIsBoot -> OsPath -> ModLocation
 mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
+   let (basename, extension) = OsPath.splitExtension src_filename
    in mkHomeModLocation2 dflags mod basename extension
 
 mkHomeModLocation2 :: FinderOpts
-                   -> ModuleName
+                   -> ModuleNameWithIsBoot
                    -> OsPath  -- Of source module, without suffix
                    -> FileExt    -- Suffix
                    -> ModLocation
-mkHomeModLocation2 fopts mod src_basename ext =
+mkHomeModLocation2 fopts (GWIB mod is_boot) src_basename ext =
    let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod
-
-       obj_fn = mkObjPath  fopts src_basename mod_basename
-       dyn_obj_fn = mkDynObjPath  fopts src_basename mod_basename
-       hi_fn  = mkHiPath   fopts src_basename mod_basename
-       dyn_hi_fn  = mkDynHiPath   fopts src_basename mod_basename
-       hie_fn = mkHiePath  fopts src_basename mod_basename
-
-   in (OsPathModLocation{ ml_hs_file_ospath   = Just (src_basename <.> ext),
-                          ml_hi_file_ospath   = hi_fn,
-                          ml_dyn_hi_file_ospath = dyn_hi_fn,
-                          ml_obj_file_ospath  = obj_fn,
+       bootify = if is_boot == IsBoot then addBootSuffix else id
+
+       obj_fn     = bootify $ mkObjPath    fopts src_basename mod_basename
+       dyn_obj_fn = bootify $ mkDynObjPath fopts src_basename mod_basename
+       hi_fn      = bootify $ mkHiPath     fopts src_basename mod_basename
+       dyn_hi_fn  = bootify $ mkDynHiPath  fopts src_basename mod_basename
+       hie_fn     = bootify $ mkHiePath    fopts src_basename mod_basename
+
+   in (OsPathModLocation{ ml_hs_file_ospath      = Just (src_basename <.> ext),
+                          ml_hi_file_ospath      = hi_fn,
+                          ml_dyn_hi_file_ospath  = dyn_hi_fn,
+                          ml_obj_file_ospath     = obj_fn,
                           ml_dyn_obj_file_ospath = dyn_obj_fn,
-                          ml_hie_file_ospath  = hie_fn })
+                          ml_hie_file_ospath     = hie_fn })
 
 mkHomeModHiOnlyLocation :: FinderOpts
-                        -> ModuleName
+                        -> ModuleNameWithIsBoot
                         -> OsPath
                         -> BaseName
                         -> ModLocation


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,10 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
-   , addBootSuffixLocn
-   , addBootSuffixLocnOut
    , removeBootSuffix
    , mkFileSrcSpan
    )
@@ -99,38 +95,6 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
--- | Add the @-boot@ suffix to all file paths associated with the module
-addBootSuffixLocn :: ModLocation -> ModLocation
-addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
-
--- | Add the @-boot@ suffix to all output file paths associated with the
--- module, not including the input file itself
-addBootSuffixLocnOut :: ModLocation -> ModLocation
-addBootSuffixLocnOut locn
-  = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn)
-         }
-
 -- | Compute a 'SrcSpan' from a 'ModLocation'.
 mkFileSrcSpan :: ModLocation -> SrcSpan
 mkFileSrcSpan mod_loc


=====================================
testsuite/tests/driver/boot-target/C.hs
=====================================
@@ -0,0 +1,5 @@
+module C where
+
+import {-# source #-} D
+
+data C = C D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/D.hs
=====================================
@@ -0,0 +1,3 @@
+module D where
+
+data D = D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/Makefile
=====================================
@@ -5,4 +5,7 @@ boot2:
 	$(TEST_HC) A.hs-boot A.hs B.hs -v0
 
 boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file
+	$(TEST_HC) A.hs-boot B.hs -v0
+
+boot4:
+	$(TEST_HC) C.hs -v0
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/all.T
=====================================
@@ -8,3 +8,9 @@ def test_boot(name):
 test_boot('boot1')
 test_boot('boot2')
 test_boot('boot3')
+
+test('boot4',
+     [extra_files(['C.hs', 'D.hs']),
+      exit_code(2)],
+     makefile_test,
+     [])


=====================================
testsuite/tests/driver/boot-target/boot4.stderr
=====================================
@@ -0,0 +1,8 @@
+C.hs:3:1: [GHC-87110]
+    Could not find module ‘D’.
+    Use -v to see a list of the files searched for.
+  |
+3 | import {-# source #-} D
+  | ^^^^^^^^^^^^^^^^^^^^^^^
+
+make: *** [Makefile:11: boot4] Error 1
\ No newline at end of file



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/97d48ad490b948ae3b16307b65f8d8e7bbe8d4e8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 13:00:38 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 16 Oct 2024 09:00:38 -0400
Subject: [Git][ghc/ghc][wip/T25266] 21 commits: Changed import from Ghc. 
 module to L.H.S module
Message-ID: <670fb8f681ab6_3c117e4e07c893717@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
adddcc3a by Simon Peyton Jones at 2024-10-16T14:00:24+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
8dce1394 by Simon Peyton Jones at 2024-10-16T14:00:24+01:00
Work in progress on #25266

- - - - -
662bba40 by Simon Peyton Jones at 2024-10-16T14:00:24+01:00
Better generalisation

- - - - -
673a0493 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibbles to short cuts

- - - - -
b332b8a9 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Iterating in decideAndPromote

- - - - -
c4ec20a2 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble

- - - - -
dc6cd5cf by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble Solver

- - - - -
6b2f0555 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble

- - - - -
48c80305 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Keep variables in correct order

- - - - -
e146bc22 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble solver

- - - - -
ccae457e by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibbles related to the MR

- - - - -
c93b219e by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Respond to rae review

- - - - -
8918f37f by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibbles

- - - - -
e4f71335 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Add type sig

Acked-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
afbdcea1 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble assert in approximateWC

- - - - -
52d35f09 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibbles to solver and MR

- - - - -
2b50a6a3 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Fix build

- - - - -
76ba8527 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibble error messages

- - - - -
458764e1 by Simon Peyton Jones at 2024-10-16T14:00:25+01:00
Wibbles

- - - - -


8 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/edd61fdc5463aff3fdea91ffbdf659c48b1d02d3...458764e15adce1436c6877deaa657b8cfaaa9825

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/edd61fdc5463aff3fdea91ffbdf659c48b1d02d3...458764e15adce1436c6877deaa657b8cfaaa9825
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 14:26:36 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 16 Oct 2024 10:26:36 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] 50 commits: javascript: Read fields
 of ObjectBlock lazily
Message-ID: <670fcd1ced0e_28dde33192f0492b9@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
9151799f by Sjoerd Visscher at 2024-10-16T15:42:41+02:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Errors/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/786cbfb558d3d9aa2469a04035eabad4ea1b0f74...9151799fbc754b204ddaff5f228d3f3fb19e8b3a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/786cbfb558d3d9aa2469a04035eabad4ea1b0f74...9151799fbc754b204ddaff5f228d3f3fb19e8b3a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 14:28:28 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 16 Oct 2024 10:28:28 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] More boot-file awareness in Finder
Message-ID: <670fcd8c4c4db_28dde32b6290498c9@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
6d6785f2 by Sjoerd Visscher at 2024-10-16T16:28:15+02:00
More boot-file awareness in Finder

Finishes work started in fff55592

Adds findImportedModuleWithIsBoot and findHomeModuleWithIsBoot so that callers don't have to call addBootSuffix on the result.

Removes InstalledModule field from InstalledFound constructor since it's already part of the key that was searched for.

- - - - -


13 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Location.hs
- + testsuite/tests/driver/boot-target/C.hs
- + testsuite/tests/driver/boot-target/D.hs
- testsuite/tests/driver/boot-target/Makefile
- testsuite/tests/driver/boot-target/all.T
- + testsuite/tests/driver/boot-target/boot4.stderr


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -771,7 +771,7 @@ summariseRequirement pn mod_name = do
     let fopts = initFinderOpts dflags
 
     let PackageName pn_fs = pn
-    let location = mkHomeModLocation2 fopts mod_name
+    let location = mkHomeModLocation2 fopts (notBoot mod_name)
                     (unsafeEncodeUtf $ unpackFS pn_fs  moduleNameSlashes mod_name) (os "hsig")
 
     env <- getBkpEnv
@@ -848,23 +848,20 @@ hsModuleToModSummary home_keys pn hsc_src modname
     let PackageName unit_fs = pn
         dflags = hsc_dflags hsc_env
         fopts = initFinderOpts dflags
+        modWithIsBoot = GWIB modname (hscSourceToIsBoot hsc_src)
     -- Unfortunately, we have to define a "fake" location in
     -- order to appease the various code which uses the file
     -- name to figure out where to put, e.g. object files.
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation2 fopts modWithIsBoot
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
                               (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
@@ -893,7 +890,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modWithIsBoot location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2126,31 +2126,21 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
               ".lhs-boot" -> IsBoot
               _ -> NotBoot
 
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            modWithIsBoot = GWIB pi_mod_name is_boot
+
+            hsc_src
+              | IsBoot <- is_boot = HsBootFile
+              | isHaskellSigFilename src_fn = HsigFile
+              | otherwise = HsSrcFile
+
+            location = mkHomeModLocation fopts modWithIsBoot src_path
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit modWithIsBoot location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2180,14 +2170,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
            _ <- do
               let fc = hsc_FC hsc_env
                   gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+              addModuleToFinder fc gwib location
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
@@ -2239,7 +2225,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env (GWIB wanted_mod is_boot) mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2243,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2253,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env (GWIB imp is_boot) pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,19 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+        modWithIsBoot = GWIB mod_name (hscSourceToIsBoot src_flavour)
+    let location1 = mkHomeModLocation2 fopts modWithIsBoot (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -804,15 +799,15 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     -- above
     let expl_o_file = outputFile_ dflags
         expl_dyn_o_file  = dynOutputFile_ dflags
-        location5 | Just ofile <- expl_o_file
+        location4 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
-    return location5
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
+    return location4
     where
       fopts = initFinderOpts dflags
 


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -317,7 +317,7 @@ loadSrcInterface_maybe doc mod want_boot maybe_pkg
   -- interface; it will call the Finder again, but the ModLocation will be
   -- cached from the first search.
   = do hsc_env <- getTopEnv
-       res <- liftIO $ findImportedModule hsc_env mod maybe_pkg
+       res <- liftIO $ findImportedModuleWithIsBoot hsc_env (GWIB mod want_boot) maybe_pkg
        case res of
            Found _ mod -> initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
            -- TODO: Make sure this error message is good
@@ -895,9 +895,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit (GWIB mod hi_boot_file))
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,9 +15,11 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
+    findHomeModuleWithIsBoot,
     findExposedPackageModule,
     mkHomeModLocation,
     mkHomeModLocation2,
@@ -148,7 +150,10 @@ initFinderCache = do
 -- that package is searched for the module.
 
 findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult
-findImportedModule hsc_env mod pkg_qual =
+findImportedModule hsc_env = findImportedModuleWithIsBoot hsc_env . notBoot
+
+findImportedModuleWithIsBoot :: HscEnv -> ModuleNameWithIsBoot -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod pkg_qual =
   let fc        = hsc_FC hsc_env
       mhome_unit = hsc_home_unit_maybe hsc_env
       dflags    = hsc_dflags hsc_env
@@ -161,10 +166,10 @@ findImportedModuleNoHsc
   -> FinderOpts
   -> UnitEnv
   -> Maybe HomeUnit
-  -> ModuleName
+  -> ModuleNameWithIsBoot
   -> PkgQual
   -> IO FindResult
-findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
+findImportedModuleNoHsc fc fopts ue mhome_unit gwib at GWIB { gwib_mod = mod_name } mb_pkg =
   case mb_pkg of
     NoPkgQual  -> unqual_import
     ThisPkg uid | (homeUnitId <$> mhome_unit) == Just uid -> home_import
@@ -178,7 +183,7 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
 
 
     home_import = case mhome_unit of
-                   Just home_unit -> findHomeModule fc fopts home_unit mod_name
+                   Just home_unit -> findHomeModuleWithIsBoot fc fopts home_unit gwib
                    Nothing -> pure $ NoPackage (panic "findImportedModule: no home-unit")
 
 
@@ -186,11 +191,11 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
       -- If the module is reexported, then look for it as if it was from the perspective
       -- of that package which reexports it.
       | Just real_mod_name <- mod_name `M.lookup` finder_reexportedModules opts =
-        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) real_mod_name NoPkgQual
+        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) gwib{ gwib_mod = real_mod_name } NoPkgQual
       | mod_name `Set.member` finder_hiddenModules opts =
         return (mkHomeHidden uid)
       | otherwise =
-        findHomePackageModule fc opts uid mod_name
+        findHomePackageModule fc opts uid gwib
 
     -- Do not be smart and change this to `foldr orIfNotFound home_import hs` as
     -- that is not the same!! home_import is first because we need to look within ourselves
@@ -228,15 +233,15 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModuleWithIsBoot -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit gwib at GWIB { gwib_mod = mod } = do
   case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
-        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
+        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName <$> gwib)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
-        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
-    _ -> findPackageModule fc unit_state fopts mod
+        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName <$> gwib)
+    _ -> findPackageModule fc unit_state fopts gwib
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -271,10 +276,10 @@ orIfNotFound this or_this = do
 -- been done.  Otherwise, do the lookup (with the IO action) and save
 -- the result in the finder cache and the module location cache (if it
 -- was successful.)
-homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
+homeSearchCache :: FinderCache -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
-  let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  let mod = mkModule home_unit <$> mod_name
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -290,13 +295,13 @@ findLookupResult :: FinderCache -> FinderOpts -> LookupResult -> IO FindResult
 findLookupResult fc fopts r = case r of
      LookupFound m pkg_conf -> do
        let im = fst (getModuleInstantiation m)
-       r' <- findPackageModule_ fc fopts im (fst pkg_conf)
+       r' <- findPackageModule_ fc fopts (notBoot im) (fst pkg_conf)
        case r' of
         -- TODO: ghc -M is unlikely to do the right thing
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -344,24 +349,27 @@ modLocationCache fc mod do_this = do
 addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
   let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
 addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
   let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
+  addToFinderCache fc mod (InstalledFound loc)
   return (mkHomeModule home_unit (gwib_mod mod_name))
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
 
 findHomeModule :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
-findHomeModule fc fopts  home_unit mod_name = do
+findHomeModule fc fopts home_unit = findHomeModuleWithIsBoot fc fopts home_unit . notBoot
+
+findHomeModuleWithIsBoot :: FinderCache -> FinderOpts -> HomeUnit -> ModuleNameWithIsBoot -> IO FindResult
+findHomeModuleWithIsBoot fc fopts home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -381,12 +389,12 @@ mkHomeHidden uid =
            , fr_unusables = []
            , fr_suggestions = []}
 
-findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO FindResult
+findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO FindResult
 findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -414,35 +422,33 @@ findHomePackageModule fc fopts  home_unit mod_name = do
 --
 --  4. Some special-case code in GHCi (ToDo: Figure out why that needs to
 --  call this.)
-findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO InstalledFindResult
-findInstalledHomeModule fc fopts home_unit mod_name = do
-  homeSearchCache fc home_unit mod_name $
+findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult
+findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib_isBoot = is_boot } = do
+  homeSearchCache fc home_unit gwib $
    let
      maybe_working_dir = finder_workingDirectory fopts
      home_path = case maybe_working_dir of
                   Nothing -> finder_importPaths fopts
                   Just fp -> augmentImports fp (finder_importPaths fopts)
+     mod = mkModule home_unit mod_name
      hi_dir_path =
       case finder_hiDir fopts of
         Just hiDir -> case maybe_working_dir of
           Nothing -> [hiDir]
           Just fp -> [fp  hiDir]
         Nothing -> home_path
-     hisuf = finder_hiSuf fopts
-     mod = mkModule home_unit mod_name
 
-     source_exts =
-      [ (os "hs",    mkHomeModLocationSearched fopts mod_name $ os "hs")
-      , (os "lhs",   mkHomeModLocationSearched fopts mod_name $ os "lhs")
-      , (os "hsig",  mkHomeModLocationSearched fopts mod_name $ os "hsig")
-      , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig")
-      ]
+     sufs = case is_boot of
+       NotBoot -> ["hs", "lhs", "hsig", "lhsig"]
+       IsBoot -> ["hs-boot", "lhs-boot"]
+     source_exts = [ (ext, mkHomeModLocationSearched fopts gwib ext) | ext <- map os sufs ]
 
+     hisuf = case is_boot of
+       NotBoot -> finder_hiSuf fopts
+       IsBoot -> addBootSuffix $ finder_hiSuf fopts
      -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that
      -- when hiDir field is set in dflags, we know to look there (see #16500)
-     hi_exts = [ (hisuf,                mkHomeModHiOnlyLocation fopts mod_name)
-               , (addBootSuffix hisuf,  mkHomeModHiOnlyLocation fopts mod_name)
-               ]
+     hi_exts = [ (hisuf, mkHomeModHiOnlyLocation fopts gwib) ]
 
         -- In compilation manager modes, we look for source files in the home
         -- package because we can compile these automatically.  In one-shot
@@ -456,7 +462,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -467,9 +473,9 @@ augmentImports work_dir (fp:fps)
   | otherwise            = (work_dir  fp) : augmentImports work_dir fps
 
 -- | Search for a module in external packages only.
-findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult
+findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModuleWithIsBoot -> IO InstalledFindResult
 findPackageModule fc unit_state fopts mod = do
-  let pkg_id = moduleUnit mod
+  let pkg_id = moduleUnit (gwib_mod mod)
   case lookupUnitId unit_state pkg_id of
      Nothing -> return (InstalledNoPackage pkg_id)
      Just u  -> findPackageModule_ fc fopts mod u
@@ -481,15 +487,15 @@ findPackageModule fc unit_state fopts mod = do
 -- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
 -- The redundancy is to avoid an extra lookup in the package state
 -- for the appropriate config.
-findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ fc fopts mod pkg_conf = do
+findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModuleWithIsBoot -> UnitInfo -> IO InstalledFindResult
+findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc gwib $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +519,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,10 +553,10 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
-mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt
+mkHomeModLocationSearched :: FinderOpts -> ModuleNameWithIsBoot -> FileExt
                           -> OsPath -> BaseName -> ModLocation
 mkHomeModLocationSearched fopts mod suff path basename =
   mkHomeModLocation2 fopts mod (path  basename) suff
@@ -589,34 +595,35 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
+mkHomeModLocation :: FinderOpts -> ModuleNameWithIsBoot -> OsPath -> ModLocation
 mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
+   let (basename, extension) = OsPath.splitExtension src_filename
    in mkHomeModLocation2 dflags mod basename extension
 
 mkHomeModLocation2 :: FinderOpts
-                   -> ModuleName
+                   -> ModuleNameWithIsBoot
                    -> OsPath  -- Of source module, without suffix
                    -> FileExt    -- Suffix
                    -> ModLocation
-mkHomeModLocation2 fopts mod src_basename ext =
+mkHomeModLocation2 fopts (GWIB mod is_boot) src_basename ext =
    let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod
-
-       obj_fn = mkObjPath  fopts src_basename mod_basename
-       dyn_obj_fn = mkDynObjPath  fopts src_basename mod_basename
-       hi_fn  = mkHiPath   fopts src_basename mod_basename
-       dyn_hi_fn  = mkDynHiPath   fopts src_basename mod_basename
-       hie_fn = mkHiePath  fopts src_basename mod_basename
-
-   in (OsPathModLocation{ ml_hs_file_ospath   = Just (src_basename <.> ext),
-                          ml_hi_file_ospath   = hi_fn,
-                          ml_dyn_hi_file_ospath = dyn_hi_fn,
-                          ml_obj_file_ospath  = obj_fn,
+       bootify = if is_boot == IsBoot then addBootSuffix else id
+
+       obj_fn     = bootify $ mkObjPath    fopts src_basename mod_basename
+       dyn_obj_fn = bootify $ mkDynObjPath fopts src_basename mod_basename
+       hi_fn      = bootify $ mkHiPath     fopts src_basename mod_basename
+       dyn_hi_fn  = bootify $ mkDynHiPath  fopts src_basename mod_basename
+       hie_fn     = bootify $ mkHiePath    fopts src_basename mod_basename
+
+   in (OsPathModLocation{ ml_hs_file_ospath      = Just (src_basename <.> ext),
+                          ml_hi_file_ospath      = hi_fn,
+                          ml_dyn_hi_file_ospath  = dyn_hi_fn,
+                          ml_obj_file_ospath     = obj_fn,
                           ml_dyn_obj_file_ospath = dyn_obj_fn,
-                          ml_hie_file_ospath  = hie_fn })
+                          ml_hie_file_ospath     = hie_fn })
 
 mkHomeModHiOnlyLocation :: FinderOpts
-                        -> ModuleName
+                        -> ModuleNameWithIsBoot
                         -> OsPath
                         -> BaseName
                         -> ModLocation


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,10 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
-   , addBootSuffixLocn
-   , addBootSuffixLocnOut
    , removeBootSuffix
    , mkFileSrcSpan
    )
@@ -25,7 +21,6 @@ where
 import GHC.Prelude
 
 import GHC.Data.OsPath
-import GHC.Unit.Types
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Data.FastString (mkFastString)
@@ -99,38 +94,6 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
--- | Add the @-boot@ suffix to all file paths associated with the module
-addBootSuffixLocn :: ModLocation -> ModLocation
-addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
-
--- | Add the @-boot@ suffix to all output file paths associated with the
--- module, not including the input file itself
-addBootSuffixLocnOut :: ModLocation -> ModLocation
-addBootSuffixLocnOut locn
-  = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn)
-         }
-
 -- | Compute a 'SrcSpan' from a 'ModLocation'.
 mkFileSrcSpan :: ModLocation -> SrcSpan
 mkFileSrcSpan mod_loc


=====================================
testsuite/tests/driver/boot-target/C.hs
=====================================
@@ -0,0 +1,5 @@
+module C where
+
+import {-# source #-} D
+
+data C = C D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/D.hs
=====================================
@@ -0,0 +1,3 @@
+module D where
+
+data D = D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/Makefile
=====================================
@@ -5,4 +5,7 @@ boot2:
 	$(TEST_HC) A.hs-boot A.hs B.hs -v0
 
 boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file
+	$(TEST_HC) A.hs-boot B.hs -v0
+
+boot4:
+	$(TEST_HC) C.hs -v0
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/all.T
=====================================
@@ -8,3 +8,9 @@ def test_boot(name):
 test_boot('boot1')
 test_boot('boot2')
 test_boot('boot3')
+
+test('boot4',
+     [extra_files(['C.hs', 'D.hs']),
+      exit_code(2)],
+     makefile_test,
+     [])


=====================================
testsuite/tests/driver/boot-target/boot4.stderr
=====================================
@@ -0,0 +1,8 @@
+C.hs:3:1: [GHC-87110]
+    Could not find module ‘D’.
+    Use -v to see a list of the files searched for.
+  |
+3 | import {-# source #-} D
+  | ^^^^^^^^^^^^^^^^^^^^^^^
+
+make: *** [Makefile:11: boot4] Error 1
\ No newline at end of file



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d6785f2bdc6d9d420ef69964bed9a674bb80005

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 14:51:30 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 16 Oct 2024 10:51:30 -0400
Subject: [Git][ghc/ghc][ghc-9.12] 47 commits: SpecConstr: Introduce a separate
 argument limit for forced specs.
Message-ID: <670fd2f2d25ef_28dde362af48583e4@gitlab.mail>



Zubin pushed to branch ghc-9.12 at Glasgow Haskell Compiler / GHC


Commits:
18860aa6 by Andreas Klebinger at 2024-10-13T21:07:34+05:30
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

(cherry picked from commit da20cac16d0982c982f9d6779dc8174e5184fe15)

- - - - -
0904d0c1 by Andreas Klebinger at 2024-10-13T21:08:23+05:30
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

(cherry picked from commit 39497eeda74fc7f1e7ea89292de395b16f69cee2)

- - - - -
187b2d5d by Sylvain Henry at 2024-10-13T21:08:36+05:30
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

(cherry picked from commit e9dc26907e13eeb73514ff3f70323b40b40ef8ac)

- - - - -
b9b6807e by Matthew Pickering at 2024-10-13T21:08:51+05:30
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

(cherry picked from commit 36bbb167f354a2fbc6c4842755f2b1e374e3580e)

- - - - -
d6b8a4fb by ARATA Mizuki at 2024-10-13T21:09:19+05:30
Use bundled llc/opt on Windows (#22438)

(cherry picked from commit 92976985625ffba551f1e1422f5e3a0cbf7beb89)

- - - - -
f9a0dc6d by Andreas Klebinger at 2024-10-13T21:09:36+05:30
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

(cherry picked from commit 2293c0b7d709df7be04f596e72c97fd2435c4134)

- - - - -
a85c33c4 by Rodrigo Mesquita at 2024-10-13T21:09:47+05:30
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

(cherry picked from commit 64e876bc0a5dd5d59b47ee3969b52a3bcecb37e6)

- - - - -
623a2534 by Cheng Shao at 2024-10-13T21:09:56+05:30
testsuite: remove accidentally checked in debug print logic

(cherry picked from commit bcb293f216e56c8dfd199f990e8eaa48071ef845)

- - - - -
6bbb7588 by Daniel Díaz at 2024-10-13T21:10:06+05:30
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

(cherry picked from commit 535a2117239f0d0e4588c6616fcd8deed725cfc0)

- - - - -
b78e8c5b by Krzysztof Gogolewski at 2024-10-13T21:10:14+05:30
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

(cherry picked from commit 92f8939a5fa689dc0143501cfeac0b3b2cd7abd6)

- - - - -
a4328a4c by Teo Camarasu at 2024-10-13T21:11:42+05:30
Add changelog entries for !12479

(cherry picked from commit c9590ba0703d65ecb9d71ac8390c1ae1144bd9d0)

- - - - -
616dfef0 by Matthew Pickering at 2024-10-13T21:12:05+05:30
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

(cherry picked from commit af59749abb723283fa42b51f62a8ac8b345a7f8f)

- - - - -
76549660 by Matthew Pickering at 2024-10-13T21:12:20+05:30
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

(cherry picked from commit a49e66fcf26632b31991384193e9fc0f7d051adc)

- - - - -
30e85658 by Andreas Klebinger at 2024-10-13T21:12:35+05:30
Add support for fp min/max to riscv

Fixes #25313

(cherry picked from commit 115a30e9142b4481de3ba735396e9d0417d46445)

- - - - -
a4b9b1a2 by Sven Tennie at 2024-10-13T21:12:45+05:30
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

(cherry picked from commit 5fd320da57bb52458bb1e8c14c5311129d88a3a7)

- - - - -
328dedef by sheaf at 2024-10-13T21:12:56+05:30
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

(cherry picked from commit 9c9c790dbca89722080f47158001ac3920f11606)

- - - - -
7b07c101 by Matthew Pickering at 2024-10-13T21:13:04+05:30
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

(cherry picked from commit 504900755e3297c000a3bcf4f20eaae1f10298f4)

- - - - -
86f3005b by Cheng Shao at 2024-10-13T21:13:52+05:30
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>
(cherry picked from commit 2338a971ce45ce7bc6ba2711e40966ec5ff12359)

- - - - -
abd0d124 by Simon Peyton Jones at 2024-10-13T21:16:19+05:30
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

(cherry picked from commit 083703a12cd34369e7ed2f0efc4a5baee47aedab)

- - - - -
fbbba0f1 by Simon Peyton Jones at 2024-10-13T21:16:27+05:30
Wibbles

(cherry picked from commit 0dfaeb66fb8457e7339abbd44d5c53a81ad8ae3a)

- - - - -
7164dbca by Simon Peyton Jones at 2024-10-13T21:16:33+05:30
Spelling errors

(cherry picked from commit 09d24d828e48c2588a317e6dad711f8673983703)

- - - - -
aa5026c7 by sheaf at 2024-10-13T21:16:57+05:30
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

(cherry picked from commit 694489edf35c35b29fbdf09a8e3fdc404469858f)

- - - - -
0b323326 by sheaf at 2024-10-13T21:17:15+05:30
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

(cherry picked from commit 06ae85071b95376bd1eb354f7cc7901aed45b625)

- - - - -
b1f40130 by Ben Gamari at 2024-10-13T21:17:26+05:30
base: Improve documentation of Control.Exception.Backtrace

(cherry picked from commit 0060ece762d7a936daf28195676b6162c30dc845)

- - - - -
95880157 by Ben Gamari at 2024-10-13T21:17:55+05:30
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

(cherry picked from commit d029f1700effa626ff622700b198ed49ee8b6c19)

- - - - -
f92a8a84 by Ben Gamari at 2024-10-13T21:18:09+05:30
base: Add test for #25066

(cherry picked from commit da5d7d0d8bde06a1c29612fd17b6a579fc523036)

- - - - -
3d0fe159 by Ben Gamari at 2024-10-13T21:22:40+05:30
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

(cherry picked from commit eb7ddae1a2b3fb1be1cd635849516a6398327b29)

- - - - -
772b4f59 by Artem Pelenitsyn at 2024-10-13T21:22:40+05:30
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>
(cherry picked from commit 4dd30cba51c7936dc53f0c1d331f88a590f93013)

- - - - -
1418869f by Ben Gamari at 2024-10-13T21:22:40+05:30
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

(cherry picked from commit 876d6e0e807c074d5c71370aa3c3451bbcb28342)

- - - - -
b5ad81c7 by Matthew Pickering at 2024-10-13T21:22:40+05:30
Fix toException method for ExceptionWithContext

Fixes #25235

(cherry picked from commit 9bfd9fd0730359b4e88e97b08d3654d966a9a11d)

- - - - -
35f20223 by Matthew Pickering at 2024-10-13T21:22:40+05:30
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

(cherry picked from commit ac0040286a8962b728a7cdb3c1be4691db635366)

- - - - -
a2ec22e7 by Rodrigo Mesquita at 2024-10-13T21:26:21+05:30
Add test for #25300

(cherry picked from commit 0e5cff6676426d614739c74bf6a953ef6e9659e6)

- - - - -
d92aa23a by Rodrigo Mesquita at 2024-10-13T21:26:30+05:30
Backport !13302 docs to users guide

(cherry picked from commit e44e448ea8745a04724420edfa6ab4d24252a53f)

- - - - -
d2f2a3b2 by Alan Zimmerman at 2024-10-13T21:26:50+05:30
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

(cherry picked from commit 4a2f0f1302f5919dfc9c8cbc410fceb19e7309ba)

- - - - -
b2c53e75 by Alan Zimmerman at 2024-10-13T21:29:24+05:30
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr
(cherry picked from commit ef481813719c5f6d9d97b60ffef4617307d24c80)

- - - - -
7564b6a7 by Zubin Duggal at 2024-10-13T21:30:30+05:30
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

(cherry picked from commit 8b402da2738ef6bbc17409f1daac7448e064503a)

- - - - -
39e19e26 by Zubin Duggal at 2024-10-13T21:30:37+05:30
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

(cherry picked from commit 16f97667a859337e8c82636aca7dd7102aa94b55)

- - - - -
c6dd5542 by Zubin Duggal at 2024-10-13T21:30:44+05:30
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

(cherry picked from commit f1a2c9fc140baa0aaeda00c02648aa75deb59723)

- - - - -
e78c7ef9 by Zubin Duggal at 2024-10-14T14:20:59+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

- - - - -
f230e29f by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: normalise some versions in callstacks

- - - - -
b19de476 by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

- - - - -
fbf0889e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

- - - - -
473a201c by Zubin Duggal at 2024-10-15T04:26:11+05:30
Bump base bound to 4.21 for GHC 9.12

- - - - -
a79a587e by Zubin Duggal at 2024-10-15T04:26:11+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

- - - - -
f858875e by Zubin Duggal at 2024-10-15T04:41:35+05:30
testsuite: normalise windows file seperators

- - - - -
24e5761e by Zubin Duggal at 2024-10-15T04:55:36+05:30
testsuite: Mark 25300A as broken on windows

- - - - -
ca2b21c3 by Zubin Duggal at 2024-10-15T04:55:41+05:30
Prepare 9.12.1 alpha

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/362afd632032ee8f174690c3ffe0015076b83ce6...ca2b21c3429a5ff780cb6c58c33c171a3c0af82b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/362afd632032ee8f174690c3ffe0015076b83ce6...ca2b21c3429a5ff780cb6c58c33c171a3c0af82b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 15:19:22 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 16 Oct 2024 11:19:22 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25377
Message-ID: <670fd97a23dd1_28dde380b2f462129@gitlab.mail>



Ben Gamari pushed new branch wip/T25377 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25377
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 15:26:19 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 16 Oct 2024 11:26:19 -0400
Subject: [Git][ghc/ghc][wip/T25377] rts: Add assertions surrounding tracking
 of StgAsyncIOResult
Message-ID: <670fdb1b73a84_28dde398e4dc685be@gitlab.mail>



Ben Gamari pushed to branch wip/T25377 at Glasgow Haskell Compiler / GHC


Commits:
182b2a99 by Ben Gamari at 2024-10-16T11:26:00-04:00
rts: Add assertions surrounding tracking of StgAsyncIOResult

We were previously pretty cavalier in handling StgAsyncIOResults which
has proven in #25377 to be problematic. We now initialize the
AsyncResult field of the `stg_block_async_void` frame to NULL when
pushing, assert that it is NULL in `awaitRequest` and that it is not
NULL in `stg_block_async_void`.

- - - - -


2 changed files:

- rts/HeapStackCheck.cmm
- rts/win32/AsyncMIO.c


Changes:

=====================================
rts/HeapStackCheck.cmm
=====================================
@@ -730,6 +730,7 @@ stg_block_async
 INFO_TABLE_RET ( stg_block_async_void, RET_SMALL, W_ info_ptr, W_ ares )
     return ()
 {
+    ASSERT(ares != 0);
     ccall free(ares "ptr");
     return ();
 }
@@ -738,6 +739,7 @@ stg_block_async_void
 {
     Sp_adj(-2);
     Sp(0) = stg_block_async_void_info;
+    Sp(1) = 0;  // this is the StgAsyncIOResult, which will be filled in by awaitRequests.
     BLOCK_GENERIC;
 }
 


=====================================
rts/win32/AsyncMIO.c
=====================================
@@ -326,6 +326,8 @@ start:
                         // stg_block_async_info stack frame, because
                         // the block_info field will be overwritten by
                         // pushOnRunQueue().
+                        ASSERT(tso->stackobj->sp[0] == (StgWord) &stg_block_async_void_info);
+                        ASSERT(tso->stackobj->sp[1] == 0);
                         tso->stackobj->sp[1] = (W_)tso->block_info.async_result;
                         pushOnRunQueue(&MainCapability, tso);
                         break;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/182b2a99c1f79c98c928e63eec536b6c9ab15cae

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 16:04:44 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 16 Oct 2024 12:04:44 -0400
Subject: [Git][ghc/ghc][wip/T25377] rts: Add assertions surrounding tracking
 of StgAsyncIOResult
Message-ID: <670fe41c8bf17_28dde3d16dfc760ec@gitlab.mail>



Ben Gamari pushed to branch wip/T25377 at Glasgow Haskell Compiler / GHC


Commits:
a540601c by Ben Gamari at 2024-10-16T12:04:32-04:00
rts: Add assertions surrounding tracking of StgAsyncIOResult

We were previously pretty cavalier in handling StgAsyncIOResults which
has proven in #25377 to be problematic. We now initialize the
AsyncResult field of the `stg_block_async_void` frame to NULL when
pushing, assert that it is NULL in `awaitRequest` and that it is not
NULL in `stg_block_async_void`.

- - - - -


2 changed files:

- rts/HeapStackCheck.cmm
- rts/win32/AsyncMIO.c


Changes:

=====================================
rts/HeapStackCheck.cmm
=====================================
@@ -730,6 +730,7 @@ stg_block_async
 INFO_TABLE_RET ( stg_block_async_void, RET_SMALL, W_ info_ptr, W_ ares )
     return ()
 {
+    ASSERT(ares != 0);
     ccall free(ares "ptr");
     return ();
 }
@@ -738,6 +739,7 @@ stg_block_async_void
 {
     Sp_adj(-2);
     Sp(0) = stg_block_async_void_info;
+    Sp(1) = 0;  // this is the StgAsyncIOResult, which will be filled in by awaitRequests.
     BLOCK_GENERIC;
 }
 


=====================================
rts/win32/AsyncMIO.c
=====================================
@@ -203,6 +203,22 @@ shutdownAsyncIO(bool wait_threads)
     OS_CLOSE_LOCK(&queue_lock);
 }
 
+static void
+assertValidAsyncFrame(StgPtr sp) {
+#if defined(DEBUG)
+    StgPtr info = sp[0];
+    if (info != (StgWord) &stg_block_async_void_info &&
+        info != (StgWord) &stg_block_async_info) {
+        barf("assertValidAsyncFrame: invalid frame type");
+    }
+    if (sp[1] != 0) {
+        barf("assertValidAsyncFrame: non-null StgAsyncIOResult");
+    }
+#else
+    (void) sp;
+#endif
+}
+
 /*
  * Function: awaitRequests(wait)
  *
@@ -326,6 +342,7 @@ start:
                         // stg_block_async_info stack frame, because
                         // the block_info field will be overwritten by
                         // pushOnRunQueue().
+                        assertValidBlockAsyncFrame(tso->stackobj->sp);
                         tso->stackobj->sp[1] = (W_)tso->block_info.async_result;
                         pushOnRunQueue(&MainCapability, tso);
                         break;



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 16:07:09 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 16 Oct 2024 12:07:09 -0400
Subject: [Git][ghc/ghc][wip/T25377] rts: Add assertions surrounding tracking
 of StgAsyncIOResult
Message-ID: <670fe4ad8d76c_28dde3cbb3947642c@gitlab.mail>



Ben Gamari pushed to branch wip/T25377 at Glasgow Haskell Compiler / GHC


Commits:
916fd675 by Ben Gamari at 2024-10-16T12:06:49-04:00
rts: Add assertions surrounding tracking of StgAsyncIOResult

We were previously pretty cavalier in handling StgAsyncIOResults which
has proven in #25377 to be problematic. We now initialize the
AsyncResult field of the `stg_block_async_void` frame to NULL when
pushing, assert that it is NULL in `awaitRequest` and that it is not
NULL in `stg_block_async_void`.

- - - - -


2 changed files:

- rts/HeapStackCheck.cmm
- rts/win32/AsyncMIO.c


Changes:

=====================================
rts/HeapStackCheck.cmm
=====================================
@@ -730,6 +730,7 @@ stg_block_async
 INFO_TABLE_RET ( stg_block_async_void, RET_SMALL, W_ info_ptr, W_ ares )
     return ()
 {
+    ASSERT(ares != 0);
     ccall free(ares "ptr");
     return ();
 }
@@ -738,6 +739,7 @@ stg_block_async_void
 {
     Sp_adj(-2);
     Sp(0) = stg_block_async_void_info;
+    Sp(1) = 0;  // this is the StgAsyncIOResult, which will be filled in by awaitRequests.
     BLOCK_GENERIC;
 }
 


=====================================
rts/win32/AsyncMIO.c
=====================================
@@ -203,6 +203,22 @@ shutdownAsyncIO(bool wait_threads)
     OS_CLOSE_LOCK(&queue_lock);
 }
 
+static void
+assertValidBlockAsyncFrame(StgPtr sp) {
+#if defined(DEBUG)
+    StgPtr info = sp[0];
+    if (info != (StgWord) &stg_block_async_void_info &&
+        info != (StgWord) &stg_block_async_info) {
+        barf("assertValidAsyncFrame: invalid frame type");
+    }
+    if (sp[1] != 0) {
+        barf("assertValidAsyncFrame: non-null StgAsyncIOResult");
+    }
+#else
+    (void) sp;
+#endif
+}
+
 /*
  * Function: awaitRequests(wait)
  *
@@ -326,6 +342,7 @@ start:
                         // stg_block_async_info stack frame, because
                         // the block_info field will be overwritten by
                         // pushOnRunQueue().
+                        assertValidBlockAsyncFrame(tso->stackobj->sp);
                         tso->stackobj->sp[1] = (W_)tso->block_info.async_result;
                         pushOnRunQueue(&MainCapability, tso);
                         break;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/916fd6755ccd01cb4c85db0a12f00c789100c5dd

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 17:13:48 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Wed, 16 Oct 2024 13:13:48 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] Don't push
 breakpoints because they are urkh
Message-ID: <670ff44c9868b_3c6e601d6f146880@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
d17c1c55 by Andreas Klebinger at 2024-10-16T18:54:24+02:00
Don't push breakpoints because they are urkh

- - - - -


1 changed file:

- compiler/GHC/Core/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -321,6 +321,8 @@ mkTick t orig_expr = mkTick' id id orig_expr
     -- Float ticks into unsafe coerce.
     Case scrut bndr ty alts@[Alt ac abs _rhs]
       | Just rhs <- isUnsafeEqualityCase scrut bndr alts
+      -- Breakpoints contain free variables which causes issues.
+      , Breakpoint{} <- t
       -> mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
 
     -- Cost centre ticks should never be reordered relative to each



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 18:20:47 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 16 Oct 2024 14:20:47 -0400
Subject: [Git][ghc/ghc][wip/T25377] 2 commits: rts: Add assertions surrounding
 tracking of StgAsyncIOResult
Message-ID: <671003ff4d1c7_3c6e6055690091372@gitlab.mail>



Ben Gamari pushed to branch wip/T25377 at Glasgow Haskell Compiler / GHC


Commits:
13c20249 by Ben Gamari at 2024-10-16T12:10:25-04:00
rts: Add assertions surrounding tracking of StgAsyncIOResult

We were previously pretty cavalier in handling StgAsyncIOResults which
has proven in #25377 to be problematic. We now initialize the
AsyncResult field of the `stg_block_async_void` frame to NULL when
pushing, assert that it is NULL in `awaitRequest` and that it is not
NULL in `stg_block_async_void`.

- - - - -
659ab83c by Ben Gamari at 2024-10-16T14:17:51-04:00
rts: Fix resumption of interrupted async IO operations

Issue #25377 revealed a somewhat subtle consequence of thunk resumption
after asynchronous exception suspension: The mutator may enter the
asynchronous I/O completion stack frames (e.g. `stg_block_async`) despite
the associated I/O not having been completed. We now handle this case by
declaring the operation has having failed.

This may result in `threadDelay` delaying less than the requested
duration but I don't consider this to be problematic since it is
impossible to observe this issue without rather dodgy use of
`unsafePerformIO`.

- - - - -


2 changed files:

- rts/HeapStackCheck.cmm
- rts/win32/AsyncMIO.c


Changes:

=====================================
rts/HeapStackCheck.cmm
=====================================
@@ -706,14 +706,75 @@ stg_block_throwto (P_ tso, P_ exception)
 }
 
 #if defined(mingw32_HOST_OS)
+#define ERROR_OPERATION_ABORTED 0x3e3
+
+/*
+ * Note [Resuming of interrupted asynchronous IO operations]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * The stg_block_async stack frames must account for the possibility
+ * that they will be entered without their associated I/O having
+ * been completed. This can happen due to evaluation suspension due to
+ * exception unwinding (see Note []) and manifests as the `ares` field
+ * not being initialized.
+ *
+ * One case where this was noticed is #25377, which involved the testsuite
+ * test `T25300`:
+ *
+ *     x :: Int
+ *     x = unsafePerformIO $ do
+ *       putStrLn "entered x"
+ *       threadDelay 1000000000
+ *       putStrLn "leaving x"
+ *       return 42
+ *
+ *     main :: IO ()
+ *     main = do
+ *       t <- forkIO $ evaluate x >> return ()
+ *       threadDelay 1000 -- ensure that the forked thread hits the `threadDelay` in `x`
+ *       killThread t
+ *       evaluate x
+ *
+ * The failure develops as follows:
+
+ *   1. TSO1 enter main and forks `evaluate x` (TSO2)
+ *   2. TSO2 enters `x`, pushing an update frame
+ *   3. TSO2 blocks due to threadDelay, which pushes a `stg_block_async_void` frame
+ *      to its stack and yields to the scheduler
+ *   4. TSO1 continues, `killThread` throws an asynchronous `KillThread`
+ *      exception to TSO2
+ *   5. TSO2 unwinds its stack up to the update frame, suspending the unwound
+ *      stack in an `AP_STACK` and updating `x` to resume from the suspended stack
+ *   6. TSO2 dies
+ *   7. TSO1 continues execution with `evaluate x`
+ *   8. TSO1 enters `x`
+ *   9. TSO1 resumes at the head of the suspended stack (the
+ *      `stg_block_async_void` frame) despite the fact that the `StgAsyncIOResult`
+ *      field was never initialized.
+ *   10. stg_block_async_void attempted to `free()` an invalid `StgAsyncIOResult*`
+ *
+ * Fixing this in stg_block_async_void is quite straightforward as it is only used by
+ * threadDelay: simply don't attempt to `free()` a NULL `StgAsyncIOResult*`.
+ * However, we need to be more careful in the case of `stg_block_async` which is used
+ * for asynchronous IO; we don't want to mislead the caller into believing that their IO
+ * operation succeeded. For this reason we take care to return an error
+ * (`ERROR_OPERATION_ABORTED`) in this case.
+ *
+ */
+
 INFO_TABLE_RET ( stg_block_async, RET_SMALL, W_ info_ptr, W_ ares )
     return ()
 {
     W_ len, errC;
 
-    len = TO_W_(StgAsyncIOResult_len(ares));
-    errC = TO_W_(StgAsyncIOResult_errCode(ares));
-    ccall free(ares "ptr");
+    if (ares != 0) {
+        len = TO_W_(StgAsyncIOResult_len(ares));
+        errC = TO_W_(StgAsyncIOResult_errCode(ares));
+        ccall free(ares "ptr");
+    } else {
+        // See Note [Resuming interrupted asynchronous IO operations]
+        len = 0;
+        errC = ERROR_OPERATION_ABORTED;
+    }
     return (len, errC);
 }
 
@@ -730,7 +791,10 @@ stg_block_async
 INFO_TABLE_RET ( stg_block_async_void, RET_SMALL, W_ info_ptr, W_ ares )
     return ()
 {
-    ccall free(ares "ptr");
+    if (ares != 0) {
+        // See Note [Resuming interrupted asynchronous IO operations]
+        ccall free(ares "ptr");
+    }
     return ();
 }
 
@@ -738,6 +802,7 @@ stg_block_async_void
 {
     Sp_adj(-2);
     Sp(0) = stg_block_async_void_info;
+    Sp(1) = 0;  // this is the StgAsyncIOResult, which will be filled in by awaitRequests.
     BLOCK_GENERIC;
 }
 


=====================================
rts/win32/AsyncMIO.c
=====================================
@@ -203,6 +203,22 @@ shutdownAsyncIO(bool wait_threads)
     OS_CLOSE_LOCK(&queue_lock);
 }
 
+static void
+assertValidBlockAsyncFrame(StgPtr sp) {
+#if defined(DEBUG)
+    StgPtr info = sp[0];
+    if (info != &stg_block_async_void_info &&
+        info != &stg_block_async_info) {
+        barf("assertValidAsyncFrame: invalid frame type");
+    }
+    if (sp[1] != 0) {
+        barf("assertValidAsyncFrame: non-null StgAsyncIOResult");
+    }
+#else
+    (void) sp;
+#endif
+}
+
 /*
  * Function: awaitRequests(wait)
  *
@@ -326,6 +342,7 @@ start:
                         // stg_block_async_info stack frame, because
                         // the block_info field will be overwritten by
                         // pushOnRunQueue().
+                        assertValidBlockAsyncFrame(tso->stackobj->sp);
                         tso->stackobj->sp[1] = (W_)tso->block_info.async_result;
                         pushOnRunQueue(&MainCapability, tso);
                         break;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/916fd6755ccd01cb4c85db0a12f00c789100c5dd...659ab83c0c8697708820919974cad458558fcadd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/916fd6755ccd01cb4c85db0a12f00c789100c5dd...659ab83c0c8697708820919974cad458558fcadd
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 18:30:06 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Wed, 16 Oct 2024 14:30:06 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/control-category-expand-docs
Message-ID: <6710062ea285e_3c6e606cb68c93710@gitlab.mail>



Bodigrim pushed new branch wip/control-category-expand-docs at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/control-category-expand-docs
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 21:20:54 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Wed, 16 Oct 2024 17:20:54 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/buildplan
Message-ID: <67102e3628ee_3c6e60fcc420123243@gitlab.mail>



Cheng Shao pushed new branch wip/buildplan at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/buildplan
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 21:27:42 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 16 Oct 2024 17:27:42 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Add a
 release-notes entry for -Wincomplete-record-selectors
Message-ID: <67102fceabdb3_3c6e60fc3154125071@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
2424235d by Alan Zimmerman at 2024-10-16T17:27:04-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -


26 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/ThToHs.hs
- docs/users_guide/9.14.1-notes.rst
- ghc/GHCi/UI.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,6 +31,8 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnClassDecl(..),
+  AnnSynDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -353,7 +355,7 @@ instance Outputable SpliceDecoration where
 
 type instance XFamDecl      (GhcPass _) = NoExtField
 
-type instance XSynDecl      GhcPs = [AddEpAnn]
+type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
@@ -368,7 +370,7 @@ data DataDeclRn = DataDeclRn
   deriving Data
 
 type instance XClassDecl    GhcPs =
-  ( [AddEpAnn]
+  ( AnnClassDecl
   , EpLayout              -- See Note [Class EpLayout]
   , AnnSortKey DeclTag )  -- TODO:AZ:tidy up AnnSortKey
 
@@ -380,6 +382,32 @@ type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnClassDecl
+  = AnnClassDecl {
+      acd_class  :: EpToken "class",
+      acd_openp  :: [EpToken "("],
+      acd_closep :: [EpToken ")"],
+      acd_vbar   :: EpToken "|",
+      acd_where  :: EpToken "where",
+      acd_openc  :: EpToken "{",
+      acd_closec :: EpToken "}",
+      acd_semis  :: [EpToken ";"]
+  } deriving Data
+
+instance NoAnn AnnClassDecl where
+  noAnn = AnnClassDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
+data AnnSynDecl
+  = AnnSynDecl {
+    asd_opens  :: [EpToken "("],
+    asd_closes :: [EpToken ")"],
+    asd_type   :: EpToken "type",
+    asd_equal  :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnSynDecl where
+  noAnn = AnnSynDecl noAnn noAnn noAnn noAnn
+
 ------------- Pretty printing FamilyDecls -----------
 
 pprFlavour :: FamilyInfo pass -> SDoc


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -67,10 +67,14 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annotationAnnList
               `extQ` annotationEpAnnImportDecl
               `extQ` annotationNoEpAnns
+              `extQ` annotationExprBracket
+              `extQ` annotationTypedBracket
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
               `extQ` annParen
+              `extQ` annClassDecl
+              `extQ` annSynDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -203,6 +207,23 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               parens $ text "AnnParen"
                         $$ vcat [ppr a, epaLocation o, epaLocation c]
 
+            annClassDecl :: AnnClassDecl -> SDoc
+            annClassDecl (AnnClassDecl c ops cps v w oc cc s) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnClassDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClassDecl"
+                        $$ vcat [showAstData' c, showAstData' ops, showAstData' cps,
+                                 showAstData' v, showAstData' w, showAstData' oc,
+                                 showAstData' cc, showAstData' s]
+
+            annSynDecl :: AnnSynDecl -> SDoc
+            annSynDecl (AnnSynDecl ops cps t e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnSynDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnSynDecl"
+                        $$ vcat [showAstData' ops, showAstData' cps,
+                                 showAstData' t, showAstData' e]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -210,6 +231,22 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "AddEpAnn" <+> ppr a <+> epaLocation s
 
+            annotationExprBracket :: BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|") -> SDoc
+            annotationExprBracket = annotationBracket
+
+            annotationTypedBracket :: BracketAnn (EpToken "[||") (EpToken "[e||") -> SDoc
+            annotationTypedBracket = annotationBracket
+
+            annotationBracket ::forall n h .(Data n, Data h, Typeable n, Typeable h)
+              => BracketAnn n h -> SDoc
+            annotationBracket a = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "BracketAnn"
+             NoBlankEpAnnotations ->
+              parens $ case a of
+                BracketNoE  t -> text "BracketNoE"  <+> showAstData' t
+                BracketHasE t -> text "BracketHasE" <+> showAstData' t
+
             epTokenOC :: EpToken "{" -> SDoc
             epTokenOC  = epToken'
 


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -181,15 +181,23 @@ data HsBracketTc = HsBracketTc
                                         -- pasted back in by the desugarer
   }
 
-type instance XTypedBracket GhcPs = [AddEpAnn]
+type instance XTypedBracket GhcPs = (BracketAnn (EpToken "[||") (EpToken "[e||"), EpToken "||]")
 type instance XTypedBracket GhcRn = NoExtField
 type instance XTypedBracket GhcTc = HsBracketTc
-type instance XUntypedBracket GhcPs = [AddEpAnn]
+type instance XUntypedBracket GhcPs = NoExtField
 type instance XUntypedBracket GhcRn = [PendingRnSplice] -- See Note [Pending Splices]
                                                         -- Output of the renamer is the *original* renamed expression,
                                                         -- plus _renamed_ splices to be type checked
 type instance XUntypedBracket GhcTc = HsBracketTc
 
+data BracketAnn noE hasE
+  = BracketNoE noE
+  | BracketHasE hasE
+  deriving Data
+
+instance (NoAnn n, NoAnn h) => NoAnn (BracketAnn n h) where
+  noAnn = BracketNoE noAnn
+
 -- ---------------------------------------------------------------------
 
 -- API Annotations types
@@ -2141,12 +2149,12 @@ ppr_splice herald mn e
     <> ppr e
 
 
-type instance XExpBr  GhcPs       = NoExtField
-type instance XPatBr  GhcPs       = NoExtField
-type instance XDecBrL GhcPs       = NoExtField
+type instance XExpBr  GhcPs       = (BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|"), EpUniToken "|]" "⟧")
+type instance XPatBr  GhcPs       = (EpToken "[p|", EpUniToken "|]" "⟧")
+type instance XDecBrL GhcPs       = (EpToken "[d|", EpUniToken "|]" "⟧", (EpToken "{", EpToken "}"))
 type instance XDecBrG GhcPs       = NoExtField
-type instance XTypBr  GhcPs       = NoExtField
-type instance XVarBr  GhcPs       = NoExtField
+type instance XTypBr  GhcPs       = (EpToken "[t|", EpUniToken "|]" "⟧")
+type instance XVarBr  GhcPs       = EpaLocation
 type instance XXQuote GhcPs       = DataConCantHappen
 
 type instance XExpBr  GhcRn       = NoExtField


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -475,18 +475,18 @@ type instance XSpliceTy        GhcPs = NoExtField
 type instance XSpliceTy        GhcRn = HsUntypedSpliceResult (LHsType GhcRn)
 type instance XSpliceTy        GhcTc = Kind
 
-type instance XDocTy           (GhcPass _) = [AddEpAnn]
-type instance XBangTy          (GhcPass _) = ([AddEpAnn], SourceText)
+type instance XDocTy           (GhcPass _) = NoExtField
+type instance XBangTy          (GhcPass _) = ((EpaLocation, EpaLocation, EpaLocation), SourceText)
 
 type instance XRecTy           GhcPs = AnnList
 type instance XRecTy           GhcRn = NoExtField
 type instance XRecTy           GhcTc = NoExtField
 
-type instance XExplicitListTy  GhcPs = [AddEpAnn]
+type instance XExplicitListTy  GhcPs = (EpToken "'", EpToken "[", EpToken "]")
 type instance XExplicitListTy  GhcRn = NoExtField
 type instance XExplicitListTy  GhcTc = Kind
 
-type instance XExplicitTupleTy GhcPs = [AddEpAnn]
+type instance XExplicitTupleTy GhcPs = (EpToken "'", EpToken "(", EpToken ")")
 type instance XExplicitTupleTy GhcRn = NoExtField
 type instance XExplicitTupleTy GhcTc = [Kind]
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1292,8 +1292,9 @@ topdecl :: { LHsDecl GhcPs }
 --
 cl_decl :: { LTyClDecl GhcPs }
         : 'class' tycl_hdr fds where_cls
-                {% (mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4))
-                        (mj AnnClass $1:(fst $ unLoc $3)++(fstOf3 $ unLoc $4)) }
+                {% do { let {(wtok, (oc,semis,cc)) = fstOf3 $ unLoc $4}
+                      ; mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4)
+                        (AnnClassDecl (epTok $1) [] [] (fst $ unLoc $3) wtok oc cc semis) }}
 
 -- Default declarations (toplevel)
 --
@@ -1314,7 +1315,7 @@ ty_decl :: { LTyClDecl GhcPs }
                 --
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkTySynonym (comb2 $1 $4) $2 $4 [mj AnnType $1,mj AnnEqual $3] }
+                {% mkTySynonym (comb2 $1 $4) $2 $4 (epTok $1) (epTok $3) }
 
            -- type family declarations
         | 'type' 'family' type opt_tyfam_kind_sig opt_injective_info
@@ -1749,9 +1750,9 @@ decl_cls  : at_decl_cls                 { $1 }
                                       quotes (ppr $2)
                           ; amsA' (sLL $1 $> $ SigD noExtField $ ClassOpSig (AnnSig (epUniTok $3) Nothing (Just (epTok $1))) True [v] $4) }}
 
-decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
+decls_cls :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }  -- Reversed
           : decls_cls ';' decl_cls      {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unitOL $3))
                                             else case (snd $ unLoc $1) of
                                               SnocOL hs t -> do
@@ -1759,7 +1760,7 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
                                                  return (sLL $1 $> (fst $ unLoc $1
                                                                 , snocOL hs t' `appOL` unitOL $3)) }
           | decls_cls ';'               {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1770,24 +1771,24 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
           | {- empty -}                 { noLoc ([],nilOL) }
 
 decllist_cls
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", [EpToken ";"], EpToken "}")
                      , OrdList (LHsDecl GhcPs)
                      , EpLayout) }      -- Reversed
-        : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
+        : '{'         decls_cls '}'     { sLL $1 $> ((epTok $1, fst $ unLoc $2, epTok $3)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
         |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
-                                           in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
+                                           in L l ((NoEpTok, anns, NoEpTok), decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
 --
-where_cls :: { Located ([AddEpAnn]
+where_cls :: { Located ((EpToken "where", (EpToken "{", [EpToken ";"], EpToken "}"))
                        ,(OrdList (LHsDecl GhcPs))    -- Reversed
                        ,EpLayout) }
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_cls          { sLL $1 $> (mj AnnWhere $1:(fstOf3 $ unLoc $2)
+        : 'where' decllist_cls          { sLL $1 $> ((epTok $1,fstOf3 $ unLoc $2)
                                              ,sndOf3 $ unLoc $2,thdOf3 $ unLoc $2) }
-        | {- empty -}                   { noLoc ([],nilOL,EpNoLayout) }
+        | {- empty -}                   { noLoc ((noAnn, noAnn),nilOL,EpNoLayout) }
 
 -- Declarations in instance bodies
 --
@@ -2177,8 +2178,8 @@ sigtypes1 :: { OrdList (LHsSigType GhcPs) }
 -- Types
 
 unpackedness :: { Located UnpackednessPragma }
-        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getUNPACK_PRAGs $1) SrcUnpack) }
-        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
+        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getUNPACK_PRAGs $1) SrcUnpack) }
+        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
 
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
@@ -2304,8 +2305,8 @@ atype :: { LHsType GhcPs }
                                                ; return $ sL1a $1 (HsStarTy noExtField (isUnicode $1)) } }
 
         -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer
-        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnTilde $1] SrcLazy $2)) }
-        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnBang $1] SrcStrict $2)) }
+        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcLazy $2)) }
+        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcStrict $2)) }
 
         | '{' fielddecls '}'             {% do { decls <- amsA' (sLL $1 $> $ HsRecTy (AnnList (listAsAnchorM $2) (Just $ moc $1) (Just $ mcc $3) [] []) $2)
                                                ; checkRecordSyntax decls }}
@@ -2325,17 +2326,17 @@ atype :: { LHsType GhcPs }
         | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $3] []) }}
+                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
         | SIMPLEQUOTE gen_qcon {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
         | SIMPLEQUOTE sysdcon_nolist {% do { requireLTPuns PEP_QuoteDisambiguation $1 (reLoc $>)
                                            ; amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted (L (getLoc $2) $ nameRdrName (dataConName (unLoc $2)))) }}
         | SIMPLEQUOTE  '(' ktype ',' comma_types1 ')'
                              {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                    ; h <- addTrailingCommaA $3 (gl $4)
-                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $6] (h : $5)) }}
+                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $6) (h : $5)) }}
         | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (glR $1) (glR $2)) }
         | SIMPLEQUOTE  '[' comma_types0 ']'     {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy [mj AnnSimpleQuote $1,mos $2,mcs $4] IsPromoted $3) }}
+                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy (epTok $1, epTok $2, epTok $4) IsPromoted $3) }}
         | SIMPLEQUOTE var                       {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
 
         | quasiquote                  { mapLocA (HsSpliceTy noExtField) $1 }
@@ -2346,7 +2347,7 @@ atype :: { LHsType GhcPs }
         -- (One means a list type, zero means the list type constructor,
         -- so you have to quote those.)
         | '[' ktype ',' comma_types1 ']'  {% do { h <- addTrailingCommaA $2 (gl $3)
-                                                ; amsA' (sLL $1 $> $ HsExplicitListTy [mos $1,mcs $5] NotPromoted (h:$4)) }}
+                                                ; amsA' (sLL $1 $> $ HsExplicitListTy (NoEpTok,epTok $1,epTok $5) NotPromoted (h:$4)) }}
         | INTEGER              { sLLa $1 $> $ HsTyLit noExtField $ HsNumTy (getINTEGERs $1)
                                                            (il_value (getINTEGER $1)) }
         | CHAR                 { sLLa $1 $> $ HsTyLit noExtField $ HsCharTy (getCHARs $1)
@@ -2420,10 +2421,9 @@ tyvar_wc :: { Located (HsBndrVar GhcPs) }
         : tyvar                         { sL1 $1 (HsBndrVar noExtField $1) }
         | '_'                           { sL1 $1 (HsBndrWildCard noExtField) }
 
-fds :: { Located ([AddEpAnn],[LHsFunDep GhcPs]) }
-        : {- empty -}                   { noLoc ([],[]) }
-        | '|' fds1                      { (sLL $1 $> ([mj AnnVbar $1]
-                                                 ,reverse (unLoc $2))) }
+fds :: { Located (EpToken "|",[LHsFunDep GhcPs]) }
+        : {- empty -}                   { noLoc (NoEpTok,[]) }
+        | '|' fds1                      { (sLL $1 $> (epTok $1 ,reverse (unLoc $2))) }
 
 fds1 :: { Located [LHsFunDep GhcPs] }
         : fds1 ',' fd   {%
@@ -3138,26 +3138,26 @@ aexp2   :: { ECP }
         | splice_untyped { ECP $ mkHsSplicePV $1 }
         | splice_typed   { ecpFromExp $ fmap (uncurry HsTypedSplice) (reLoc $1) }
 
-        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
-        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
+        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
+        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
         -- See Note [%shift: aexp2 -> TH_TY_QUOTE]
         | TH_TY_QUOTE %shift    {% reportEmptyDoubleQuotes (getLoc $1) }
         | '[|' exp '|]'       {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3]
-                                                                                         else [mu AnnOpenEQ $1,mu AnnCloseQ $3]) (ExpBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (ExpBr (if (hasE $1) then (BracketHasE (epTok $1),   epUniTok $3)
+                                                                                                     else (BracketNoE (epUniTok $1), epUniTok $3)) $2)) }
         | '[||' exp '||]'     {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) $2) }
+                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then (BracketHasE (epTok $1),epTok $3) else (BracketNoE (epTok $1),epTok $3)) $2) }
         | '[t|' ktype '|]'    {% fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (TypBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (TypBr (epTok $1,epUniTok $3) $2)) }
         | '[p|' infixexp '|]' {% (checkPattern <=< runPV) (unECP $2) >>= \p ->
                                       fmap ecpFromExp $
-                                      amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (PatBr noExtField p)) }
+                                      amsA' (sLL $1 $> $ HsUntypedBracket noExtField (PatBr (epTok $1,epUniTok $3) p)) }
         | '[d|' cvtopbody '|]' {% fmap ecpFromExp $
-                                  amsA' (sLL $1 $> $ HsUntypedBracket (mo $1:mu AnnCloseQ $3:fst $2) (DecBrL noExtField (snd $2))) }
+                                  amsA' (sLL $1 $> $ HsUntypedBracket noExtField (DecBrL (epTok $1,epUniTok $3, fst $2) (snd $2))) }
         | quasiquote          { ECP $ mkHsSplicePV $1 }
 
         -- arrow notation extension
@@ -3197,10 +3197,9 @@ acmd    :: { LHsCmdTop GhcPs }
                                    runPV (checkCmdBlockArguments cmd) >>= \ _ ->
                                    return (sL1a cmd $ HsCmdTop noExtField cmd) }
 
-cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
-        :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
-                                                  ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+cvtopbody :: { ((EpToken "{", EpToken "}"),[LHsDecl GhcPs]) }
+        :  '{'            cvtopdecls0 '}'      { ((epTok $1 ,epTok $3),$2) }
+        |      vocurly    cvtopdecls0 close    { ((NoEpTok, NoEpTok),$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -4641,6 +4640,10 @@ epUniTok t@(L !l _) = EpUniTok (EpaSpan l) u
   where
     u = if isUnicode t then UnicodeSyntax else NormalSyntax
 
+-- |Construct an EpToken from the location of the token, provided the span is not zero width
+mzEpTok :: Located Token -> EpToken tok
+mzEpTok !l = if isZeroWidthSpan (gl l) then NoEpTok else (epTok l)
+
 epExplicitBraces :: Located Token -> Located Token -> EpLayout
 epExplicitBraces !t1 !t2 = EpExplicitBraces (epTok t1) (epTok t2)
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -10,7 +10,7 @@ module GHC.Parser.Annotation (
   -- * Core Exact Print Annotation types
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
-  getEpTokenSrcSpan, getEpTokenLocs,
+  getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
   TokDcolon,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
@@ -406,6 +406,10 @@ getEpTokenLocs ls = concatMap go ls
     go NoEpTok   = []
     go (EpTok l) = [l]
 
+getEpTokenLoc :: EpToken tok -> EpaLocation
+getEpTokenLoc NoEpTok   = noAnn
+getEpTokenLoc (EpTok l) = l
+
 type TokDcolon = EpUniToken "::" "∷"
 
 -- | Layout information for declarations.


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -71,7 +71,7 @@ module GHC.Parser.Lexer (
    xtest, xunset, xset,
    disableHaddock,
    lexTokenStream,
-   mkParensEpAnn,
+   mkParensEpToks,
    mkParensLocs,
    getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
    getEofPos,
@@ -3628,13 +3628,14 @@ warn_unknown_prag prags span buf len buf2 = do
 %************************************************************************
 -}
 
+-- TODO:AZ: we should have only mkParensEpToks. Delee mkParensEpAnn, mkParensLocs
 
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'AddEpAnn' values for the opening and closing bordering on the start
 -- and end of the span
-mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
-mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
-                    AddEpAnn AnnCloseP (EpaSpan (RealSrcSpan lc Strict.Nothing)))
+mkParensEpToks :: RealSrcSpan -> (EpToken "(", EpToken ")")
+mkParensEpToks ss = (EpTok (EpaSpan (RealSrcSpan lo Strict.Nothing)),
+                    EpTok (EpaSpan (RealSrcSpan lc Strict.Nothing)))
   where
     f = srcSpanFile ss
     sl = srcSpanStartLine ss
@@ -3644,6 +3645,7 @@ mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
     lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
     lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
 
+
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'EpaLocation' values for the opening and closing bordering on the start
 -- and end of the span


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -161,7 +161,7 @@ import GHC.Utils.Error
 import GHC.Utils.Misc
 import GHC.Utils.Monad (unlessM)
 import Data.Either
-import Data.List        ( findIndex, partition )
+import Data.List        ( findIndex )
 import Data.Foldable
 import qualified Data.Semigroup as Semi
 import GHC.Unit.Module.Warnings
@@ -204,14 +204,14 @@ mkClassDecl :: SrcSpan
             -> Located (a,[LHsFunDep GhcPs])
             -> OrdList (LHsDecl GhcPs)
             -> EpLayout
-            -> [AddEpAnn]
+            -> AnnClassDecl
             -> P (LTyClDecl GhcPs)
 
 mkClassDecl loc' (L _ (mcxt, tycl_hdr)) fds where_cls layout annsIn
   = do { (binds, sigs, ats, at_defs, _, docs) <- cvBindsAndSigs where_cls
-       ; (cls, tparams, fixity, ann, cs) <- checkTyClHdr True tycl_hdr
+       ; (cls, tparams, fixity, ops, cps, cs) <- checkTyClHdr True tycl_hdr
        ; tyvars <- checkTyVars (text "class") whereDots cls tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn { acd_openp = ops, acd_closep = cps}
        ; let loc = EpAnn (spanAsAnchor loc') noAnn cs
        ; return (L loc (ClassDecl { tcdCExt = (anns', layout, NoAnnSortKey)
                                   , tcdCtxt = mcxt
@@ -235,9 +235,10 @@ mkTyData :: SrcSpan
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; !cs' <- getCommentsFor loc'
@@ -247,6 +248,15 @@ mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
+-- TODO:AZ:temporary
+openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
+openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
+openParen2AddEpAnn NoEpTok = []
+
+closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
+closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
+closeParen2AddEpAnn NoEpTok = []
+
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
@@ -265,14 +275,15 @@ mkDataDefn cType mcxt ksig data_cons maybe_deriv
 mkTySynonym :: SrcSpan
             -> LHsType GhcPs  -- LHS
             -> LHsType GhcPs  -- RHS
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "="
             -> P (LTyClDecl GhcPs)
-mkTySynonym loc lhs rhs annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+mkTySynonym loc lhs rhs antype aneq
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (text "type") equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns = AnnSynDecl ops cps antype aneq
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; return (L loc' (SynDecl { tcdSExt = anns'
+       ; return (L loc' (SynDecl { tcdSExt = anns
                                  , tcdLName = tc, tcdTyVars = tyvars
                                  , tcdFixity = fixity
                                  , tcdRhs = rhs })) }
@@ -308,10 +319,12 @@ mkTyFamInstEqn :: SrcSpan
                -> [AddEpAnn]
                -> P (LTyFamInstEqn GhcPs)
 mkTyFamInstEqn loc bndrs lhs rhs anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns `mappend` ann
+                        { feqn_ext    = anns'
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -330,32 +343,20 @@ mkDataFamInst :: SrcSpan
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = ann Semi.<> anns
+                  (FamEqn { feqn_ext    = anns'
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
                           , feqn_fixity = fixity
                           , feqn_rhs    = defn })))) }
 
--- mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
---               ksig data_cons (L _ maybe_deriv) anns
---   = do { (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr
---        ; cs <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan
---        ; let anns' = addAnns (EpAnn (spanAsAnchor loc) ann cs) anns emptyComments
---        ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv
---        ; return (L (noAnnSrcSpan loc) (DataFamInstD anns' (DataFamInstDecl
---                   (FamEqn { feqn_ext    = anns'
---                           , feqn_tycon  = tc
---                           , feqn_bndrs  = bndrs
---                           , feqn_pats   = tparams
---                           , feqn_fixity = fixity
---                           , feqn_rhs    = defn })))) }
-
 
 
 mkTyFamInst :: SrcSpan
@@ -375,11 +376,13 @@ mkFamDecl :: SrcSpan
           -> [AddEpAnn]
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (FamDecl noExtField (FamilyDecl
-                                           { fdExt       = annsIn Semi.<> ann
+                                           { fdExt       = anns'
                                            , fdTopLevel  = topLevel
                                            , fdInfo      = info, fdLName = tc
                                            , fdTyVars    = tyvars
@@ -738,8 +741,7 @@ mkPatSynMatchGroup (L loc patsyn_name) (L ld decls) =
         do { unless (name == patsyn_name) $
                wrongNameBindingErr (locA loc) decl
            -- conAnn should only be AnnOpenP, AnnCloseP, so the rest should be empty
-           ; let (ann_fun, rest) = mk_ann_funrhs []
-           ; unless (null rest) $ return $ panic "mkPatSynMatchGroup: unexpected anns"
+           ; let ann_fun = mk_ann_funrhs [] []
            ; match <- case details of
                PrefixCon _ pats -> return $ Match { m_ext = noExtField
                                                   , m_ctxt = ctxt, m_pats = L l pats
@@ -1063,8 +1065,8 @@ checkTyClHdr :: Bool               -- True  <=> class header
              -> P (LocatedN RdrName,     -- the head symbol (type or class name)
                    [LHsTypeArg GhcPs],   -- parameters of head symbol
                    LexicalFixity,        -- the declaration is in infix format
-                   [AddEpAnn],           -- API Annotation for HsParTy
-                                         -- when stripping parens
+                   [EpToken "("],        -- API Annotation for HsParTy
+                   [EpToken ")"],        -- when stripping parens
                    EpAnnComments)        -- Accumulated comments from re-arranging
 -- Well-formedness check and decomposition of type and class heads.
 -- Decomposes   T ty1 .. tyn   into    (T, [ty1, ..., tyn])
@@ -1081,22 +1083,22 @@ checkTyClHdr is_cls ty
            ; let name = mkOccNameFS tcClsName (starSym isUni)
            ; let a' = newAnns ll l an
            ; return (L a' (Unqual name), acc, fix
-                    , (reverse ops') ++ cps', cs) }
+                    , (reverse ops'), cps', cs) }
 
     go cs l (HsTyVar _ _ ltc@(L _ tc)) acc ops cps fix
-      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops), cps, cs Semi.<> comments l)
     go cs l (HsOpTy _ _ t1 ltc@(L _ tc) t2) acc ops cps _fix
-      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
     go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
       where
-        (o,c) = mkParensEpAnn (realSrcSpan (locA l))
+        (o,c) = mkParensEpToks (realSrcSpan (locA l))
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
       = return (L (l2l l) (nameRdrName tup_name)
-               , map (HsValArg noExtField) ts, fix, (reverse ops)++cps, cs Semi.<> comments l)
+               , map (HsValArg noExtField) ts, fix, (reverse ops), cps, cs Semi.<> comments l)
       where
         arity = length ts
         tup_name | is_cls    = cTupleTyConName arity
@@ -1170,15 +1172,16 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
   -- With NoListTuplePuns, contexts are parsed as data constructors, which causes failure
   -- downstream.
   -- This converts them just like when they are parsed as types in the punned case.
-  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy anns ts))
+  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy (q,o,c) ts))
     = punsAllowed >>= \case
       True -> unprocessed
       False -> do
         let
-          (op, cp) = case anns of
-            [o, c] -> ([o], [c])
-            [q, _, c] -> ([q], [c])
-            _ -> ([], [])
+          ol = AddEpAnn AnnOpenP (getEpTokenLoc o)
+          cl = AddEpAnn AnnCloseP (getEpTokenLoc c)
+          (op, cp) = case q of
+            EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
+            _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
   check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
                                   -- to be sure HsParTy doesn't get into the way
@@ -1331,12 +1334,12 @@ checkAPat loc e0 = do
      addError $ mkPlainErrorMsgEnvelope (getLocA op) PsErrAtInPatPos
      return (WildPat noExtField)
 
-   PatBuilderOpApp l (L cl c) r anns
+   PatBuilderOpApp l (L cl c) r (_os,_cs)
      | isRdrDataCon c || isRdrTc c -> do
          l <- checkLPat l
          r <- checkLPat r
          return $ ConPat
-           { pat_con_ext = mk_ann_conpat anns
+           { pat_con_ext = noAnn
            , pat_con = L cl c
            , pat_args = InfixCon l r
            }
@@ -1389,9 +1392,8 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
   = do  { mb_fun <- isFunLhs lhs
         ; case mb_fun of
-            Just (fun, is_infix, pats, ann) -> do
-              let (ann_fun, ann_rest) = mk_ann_funrhs ann
-              unless (null ann_rest) $ panic "checkValDef: unexpected anns"
+            Just (fun, is_infix, pats, ops, cps) -> do
+              let ann_fun = mk_ann_funrhs ops cps
               let l = listLocation pats
               checkFunBind loc ann_fun
                            fun is_infix (L l pats) grhss
@@ -1404,29 +1406,8 @@ checkValDef loc lhs (mult_ann, Nothing) ghrss
   = do lhs' <- checkPattern lhs
        checkPatBind loc lhs' ghrss mult_ann
 
-mk_ann_funrhs :: [AddEpAnn] -> (AnnFunRhs, [AddEpAnn])
-mk_ann_funrhs ann = (AnnFunRhs strict (map to_tok opens) (map to_tok closes), rest)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenP) ann
-    (closes, ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseP) ra0
-    (bangs, rest) = partition (\(AddEpAnn kw _) -> kw == AnnBang) ra1
-    strict = case bangs of
-               (AddEpAnn _ s:_) -> EpTok s
-               _ -> NoEpTok
-    to_tok (AddEpAnn _ s) = EpTok s
-
-mk_ann_conpat :: [AddEpAnn] -> (Maybe (EpToken "{"), Maybe (EpToken "}"))
-mk_ann_conpat ann = (open, close)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenC) ann
-    (closes, _ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseC) ra0
-    open = case opens of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    close = case closes of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    to_tok (AddEpAnn _ s) = EpTok s
+mk_ann_funrhs :: [EpToken "("] -> [EpToken ")"] -> AnnFunRhs
+mk_ann_funrhs ops cps = AnnFunRhs NoEpTok ops cps
 
 checkFunBind :: SrcSpan
              -> AnnFunRhs
@@ -1468,10 +1449,10 @@ checkPatBind :: SrcSpan
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat an (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m ans v)]))
+                [L (noAnnSrcSpan loc) (m an v)]))
   where
     m a v = Match { m_ext = noExtField
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1517,7 +1498,7 @@ checkDoAndIfThenElse err guardExpr semiThen thenExpr semiElse elseExpr
 
 isFunLhs :: LocatedA (PatBuilder GhcPs)
       -> P (Maybe (LocatedN RdrName, LexicalFixity,
-                   [LocatedA (ArgPatBuilder GhcPs)],[AddEpAnn]))
+                   [LocatedA (ArgPatBuilder GhcPs)],[EpToken "("],[EpToken ")"]))
 -- A variable binding is parsed as a FunBind.
 -- Just (fun, is_infix, arg_pats) if e is a function LHS
 isFunLhs e = go e [] [] []
@@ -1527,7 +1508,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderVar (L loc f))) es ops cps
        | not (isRdrDataCon f)        = do
            let (_l, loc') = transferCommentsOnlyA l loc
-           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+           return (Just (L loc' f, Prefix, es, (reverse ops), cps))
    go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
      let (_l, lf') = transferCommentsOnlyA l lf
      go (L lf' f) (mk e:es) ops cps
@@ -1537,21 +1518,21 @@ isFunLhs e = go e [] [] []
       -- of funlhs.
      where
        (_l, le') = transferCommentsOnlyA l le
-       (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
+       (o,c) = mkParensEpToks (realSrcSpan $ locA l)
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r (os,cs))) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
-           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (os ++ reverse ops), (cs ++ cps))) }
       | otherwise                     -- Infix data con; keep going
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
            ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
-          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
-            = Just (op', Infix, j : op_app : es', anns')
+          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', ops', cps')
+            = Just (op', Infix, j : op_app : es', ops', cps')
             where
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
-                                    (L loc' op) r (reverse ops ++ cps))
+                                    (L loc' op) r (reverse ops, cps))
           reassociate _other = Nothing
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
@@ -1570,13 +1551,13 @@ instance Outputable (ArgPatBuilder GhcPs) where
   ppr (ArgPatBuilderVisPat p) = ppr p
   ppr (ArgPatBuilderArgPat p) = ppr p
 
-mkBangTy :: [AddEpAnn] -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
-mkBangTy anns strictness =
-  HsBangTy (anns, NoSourceText) (HsBang NoSrcUnpack strictness)
+mkBangTy :: EpaLocation -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
+mkBangTy tok_loc strictness =
+  HsBangTy ((noAnn, noAnn, tok_loc), NoSourceText) (HsBang NoSrcUnpack strictness)
 
 -- | Result of parsing @{-\# UNPACK \#-}@ or @{-\# NOUNPACK \#-}@.
 data UnpackednessPragma =
-  UnpackednessPragma [AddEpAnn] SourceText SrcUnpackedness
+  UnpackednessPragma (EpaLocation, EpaLocation) SourceText SrcUnpackedness
 
 -- | Annotate a type with either an @{-\# UNPACK \#-}@ or a @{-\# NOUNPACK \#-}@ pragma.
 addUnpackednessP :: MonadP m => Located UnpackednessPragma -> LHsType GhcPs -> m (LHsType GhcPs)
@@ -1589,11 +1570,11 @@ addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do
     -- such as ~T or !T, then add the pragma to the existing HsBangTy.
     --
     -- Otherwise, wrap the type in a new HsBangTy constructor.
-    addUnpackedness an (L _ (HsBangTy (anns, NoSourceText) bang t))
+    addUnpackedness (o,c) (L _ (HsBangTy ((_,_,tl), NoSourceText) bang t))
       | HsBang NoSrcUnpack strictness <- bang
-      = HsBangTy (an Semi.<> anns, prag) (HsBang unpk strictness) t
-    addUnpackedness an t
-      = HsBangTy (an, prag) (HsBang unpk NoSrcStrict) t
+      = HsBangTy ((o,c,tl), prag) (HsBang unpk strictness) t
+    addUnpackedness (o,c) t
+      = HsBangTy ((o,c,noAnn), prag) (HsBang unpk NoSrcStrict) t
 
 ---------------------------------------------------------------------------
 -- | Check for monad comprehensions
@@ -2051,7 +2032,7 @@ instance DisambECP (PatBuilder GhcPs) where
   superInfixOp m = m
   mkHsOpAppPV l p1 op p2 = do
     !cs <- getCommentsFor l
-    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 []
+    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 ([],[])
 
   mkHsLamPV l lam_variant _ _     = addFatalError $ mkPlainErrorMsgEnvelope l (PsErrLambdaInPat lam_variant)
 
@@ -3658,7 +3639,7 @@ mkTupleSyntaxTy parOpen args parClose =
       HsExplicitTupleTy annsKeyword args
 
     annParen = AnnParen AnnParens parOpen parClose
-    annsKeyword = [AddEpAnn AnnOpenP parOpen, AddEpAnn AnnCloseP parClose]
+    annsKeyword = (NoEpTok, EpTok parOpen, EpTok parClose)
 
 -- | Decide whether to parse tuple con syntax @(,)@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
@@ -3690,7 +3671,7 @@ mkListSyntaxTy0 brkOpen brkClose span =
       HsExplicitListTy annsKeyword NotPromoted []
 
     rdrNameAnn = NameAnnOnly NameSquare brkOpen brkClose []
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     fullLoc = EpaSpan span
 
 -- | Decide whether to parse list type syntax @[Int]@ in a type as a
@@ -3709,5 +3690,5 @@ mkListSyntaxTy1 brkOpen t brkClose =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted [t]
 
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     annParen = AnnParen AnnParensSquare brkOpen brkClose


=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1460,7 +1460,7 @@ instance Monoid ColumnBound where
 
 mkLHsDocTy :: LHsType GhcPs -> Maybe (Located HsDocString) -> LHsType GhcPs
 mkLHsDocTy t Nothing = t
-mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noAnn t $ lexLHsDocString doc)
+mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noExtField t $ lexLHsDocString doc)
 
 getForAllTeleLoc :: HsForAllTelescope GhcPs -> SrcSpan
 getForAllTeleLoc tele =


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -57,7 +57,7 @@ data PatBuilder p
   | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p))
   | PatBuilderAppType (LocatedA (PatBuilder p)) (EpToken "@") (HsTyPat GhcPs)
   | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName)
-                    (LocatedA (PatBuilder p)) [AddEpAnn]
+                    (LocatedA (PatBuilder p)) ([EpToken "("], [EpToken ")"])
   | PatBuilderVar (LocatedN RdrName)
   | PatBuilderOverLit (HsOverLit GhcPs)
 


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -181,7 +181,7 @@ rnUntypedBracket e br_body
        }
 
 rn_utbracket :: ThStage -> HsQuote GhcPs -> RnM (HsQuote GhcRn, FreeVars)
-rn_utbracket outer_stage br@(VarBr x flg rdr_name)
+rn_utbracket outer_stage br@(VarBr _ flg rdr_name)
   = do { name <- lookupOccRn (unLoc rdr_name)
        ; check_namespace flg name
        ; this_mod <- getModule
@@ -204,18 +204,18 @@ rn_utbracket outer_stage br@(VarBr x flg rdr_name)
                                       TcRnTHError $ THNameError $ QuotedNameWrongStage br }
                         }
                     }
-       ; return (VarBr x flg (noLocA name), unitFV name) }
+       ; return (VarBr noExtField flg (noLocA name), unitFV name) }
 
-rn_utbracket _ (ExpBr x e) = do { (e', fvs) <- rnLExpr e
-                                ; return (ExpBr x e', fvs) }
+rn_utbracket _ (ExpBr _ e) = do { (e', fvs) <- rnLExpr e
+                                ; return (ExpBr noExtField e', fvs) }
 
-rn_utbracket _ (PatBr x p)
-  = rnPat ThPatQuote p $ \ p' -> return (PatBr x p', emptyFVs)
+rn_utbracket _ (PatBr _ p)
+  = rnPat ThPatQuote p $ \ p' -> return (PatBr noExtField p', emptyFVs)
 
-rn_utbracket _ (TypBr x t) = do { (t', fvs) <- rnLHsType TypBrCtx t
-                                ; return (TypBr x t', fvs) }
+rn_utbracket _ (TypBr _ t) = do { (t', fvs) <- rnLHsType TypBrCtx t
+                                ; return (TypBr noExtField t', fvs) }
 
-rn_utbracket _ (DecBrL x decls)
+rn_utbracket _ (DecBrL _ decls)
   = do { group <- groupDecls decls
        ; gbl_env  <- getGblEnv
        ; let new_gbl_env = gbl_env { tcg_dus = emptyDUs }
@@ -227,7 +227,7 @@ rn_utbracket _ (DecBrL x decls)
               -- Discard the tcg_env; it contains only extra info about fixity
         ; traceRn "rn_utbracket dec" (ppr (tcg_dus tcg_env) $$
                    ppr (duUses (tcg_dus tcg_env)))
-        ; return (DecBrG x group', duUses (tcg_dus tcg_env)) }
+        ; return (DecBrG noExtField group', duUses (tcg_dus tcg_env)) }
   where
     groupDecls :: [LHsDecl GhcPs] -> RnM (HsGroup GhcPs)
     groupDecls decls


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1655,7 +1655,7 @@ gen_Lift_binds loc (DerivInstTys{ dit_rep_tc = tycon
     liftTyped_bind = mkFunBindEC 1 loc liftTyped_RDR (nlHsApp unsafeCodeCoerce_Expr . nlHsApp pure_Expr)
                                  (map (pats_etc mk_typed_bracket mk_tsplice liftTypedName) data_cons)
 
-    mk_untyped_bracket = HsUntypedBracket noAnn . ExpBr noExtField
+    mk_untyped_bracket = HsUntypedBracket noExtField . ExpBr noAnn
     mk_typed_bracket = HsTypedBracket noAnn
 
     mk_tsplice = HsTypedSplice noAnn


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -319,7 +319,7 @@ cvtDec (ClassD ctxt cl tvs fds decs)
                     , tcdFDs = fds', tcdSigs = Hs.mkClassOpSigs sigs'
                     , tcdMeths = binds'
                     , tcdATs = fams', tcdATDefs = at_defs', tcdDocs = [] }
-                              -- no docs in TH ^^
+                                                     -- no docs in TH ^^
         }
 
 cvtDec (InstanceD o ctxt ty decs)


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -11,6 +11,15 @@ for specific guidance on migrating programs to this release.
 Language
 ~~~~~~~~
 
+* ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
+  by `GHC Proposal 516: add warning for incomplete record selectors _`.
+  Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
+  Workaround: add ``-Werror=no-incomplete-record-selectors``.
+
+  Note that this warning is at least
+  as serious as a warning about missing patterns from a function definition, perhaps even
+  more so, since it is invisible in the source program.
+
 Compiler
 ~~~~~~~~
 


=====================================
ghc/GHCi/UI.hs
=====================================
@@ -641,30 +641,27 @@ ghciLogAction lastErrLocations old_log_action
             _ -> return ()
         _ -> return ()
 
--- | Takes a file name and prefixes it with the appropriate
--- GHC appdir.
--- Uses ~/.ghc (getAppUserDataDirectory) if it exists
--- If it doesn't, then it uses $XDG_DATA_HOME/ghc
--- Earlier we always used to use ~/.ghc, but we want
--- to gradually move to $XDG_DATA_HOME to respect the XDG specification
---
--- As a migration strategy, we will only create new directories in
--- the appropriate XDG location. However, we will use the old directory
--- if it already exists.
-getAppDataFile :: FilePath -> IO (Maybe FilePath)
-getAppDataFile file = do
-    let new_path = tryIO (getXdgDirectory XdgConfig "ghc") >>= \case
-          Left _ -> pure Nothing
-          Right dir -> flip catchIO (const $ return Nothing) $ do
-            createDirectoryIfMissing False dir
-            pure $ Just $ dir  file
-
-    e_old_path <- tryIO (getAppUserDataDirectory "ghc")
-    case e_old_path of
-      Right old_path -> doesDirectoryExist old_path >>= \case
-        True -> pure $ Just $ old_path  file
-        False -> new_path
-      Left _ -> new_path
+-- | Takes a file name and prefixes it with the appropriate GHC appdir.
+-- ~/.ghc (getAppUserDataDirectory) is used if it exists, or XDG directories
+-- are used to respect the XDG specification.
+-- As a migration strategy, currently we will only create new directories in
+-- the appropriate XDG location.
+getAppDataFile :: XdgDirectory -> FilePath -> IO (Maybe FilePath)
+getAppDataFile xdgDir file = do
+  xdgAppDir <-
+    tryIO (getXdgDirectory xdgDir "ghc") >>= \case
+      Left _ -> pure Nothing
+      Right dir -> flip catchIO (const $ pure Nothing) $ do
+        createDirectoryIfMissing False dir
+        pure $ Just dir
+  appDir <-
+    tryIO (getAppUserDataDirectory "ghc") >>= \case
+      Right dir ->
+        doesDirectoryExist dir >>= \case
+          True -> pure $ Just dir
+          False -> pure xdgAppDir
+      Left _ -> pure xdgAppDir
+  pure $ appDir >>= \dir -> Just $ dir  file
 
 runGHCi :: [(FilePath, Maybe UnitId, Maybe Phase)] -> Maybe [String] -> GHCi ()
 runGHCi paths maybe_exprs = do
@@ -672,13 +669,12 @@ runGHCi paths maybe_exprs = do
   let
    ignore_dot_ghci = gopt Opt_IgnoreDotGhci dflags
 
-   app_user_dir = liftIO $ getAppDataFile "ghci.conf"
+   appDataCfg = liftIO $ getAppDataFile XdgConfig "ghci.conf"
 
-   home_dir = do
-    either_dir <- liftIO $ tryIO (getEnv "HOME")
-    case either_dir of
-      Right home -> return (Just (home  ".ghci"))
-      _ -> return Nothing
+   homeCfg = do
+    liftIO $ tryIO (getEnv "HOME") >>= \case
+      Right home -> pure $ Just $ home  ".ghci"
+      _ -> pure Nothing
 
    canonicalizePath' :: FilePath -> IO (Maybe FilePath)
    canonicalizePath' fp = liftM Just (canonicalizePath fp)
@@ -712,7 +708,7 @@ runGHCi paths maybe_exprs = do
     then pure []
     else do
       userCfgs <- do
-        paths <- catMaybes <$> sequence [ app_user_dir, home_dir ]
+        paths <- catMaybes <$> sequence [ appDataCfg, homeCfg ]
         checkedPaths <- liftIO $ filterM checkFileAndDirPerms paths
         liftIO . fmap (nub . catMaybes) $ mapM canonicalizePath' checkedPaths
 
@@ -799,12 +795,12 @@ runGHCiInput f = do
     dflags <- getDynFlags
     let ghciHistory = gopt Opt_GhciHistory dflags
     let localGhciHistory = gopt Opt_LocalGhciHistory dflags
-    currentDirectory <- liftIO $ getCurrentDirectory
+    currentDirectory <- liftIO getCurrentDirectory
 
     histFile <- case (ghciHistory, localGhciHistory) of
-      (True, True) -> return (Just (currentDirectory  ".ghci_history"))
-      (True, _) -> liftIO $ getAppDataFile "ghci_history"
-      _ -> return Nothing
+      (True, True) -> pure $ Just $ currentDirectory  ".ghci_history"
+      (True, _) -> liftIO $ getAppDataFile XdgData "ghci_history"
+      _ -> pure Nothing
 
     runInputT
         (setComplete ghciCompleteWord $ defaultSettings {historyFile = histFile})


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -48,8 +48,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:5:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:5:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:5:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:5:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -170,7 +179,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T17544.hs:6:14-16 })
@@ -217,8 +226,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:9:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:9:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -384,8 +402,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:13:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:13:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:13:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:13:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -554,8 +581,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:17:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:17:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:17:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:17:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -788,10 +824,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:22:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:22:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:22:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:22:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:22:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:22:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:22:18 }))
+        (EpTok (EpaSpan { T17544.hs:22:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:22:18 }))
         (EpTok (EpaSpan { T17544.hs:22:30 })))
@@ -1129,10 +1172,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:28:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:28:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:28:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:28:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:28:18 }))
+        (EpTok (EpaSpan { T17544.hs:28:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:28:18 }))
         (EpTok (EpaSpan { T17544.hs:28:30 })))
@@ -1470,10 +1520,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:34:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:34:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:34:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:34:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:34:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:34:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:34:18 }))
+        (EpTok (EpaSpan { T17544.hs:34:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:34:18 }))
         (EpTok (EpaSpan { T17544.hs:34:30 })))
@@ -1811,10 +1868,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:40:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:40:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:40:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:40:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:40:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:40:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:40:18 }))
+        (EpTok (EpaSpan { T17544.hs:40:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:40:18 }))
         (EpTok (EpaSpan { T17544.hs:40:30 })))
@@ -2152,10 +2216,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:46:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:46:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:46:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:46:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:46:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:46:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:46:18 }))
+        (EpTok (EpaSpan { T17544.hs:46:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:46:18 }))
         (EpTok (EpaSpan { T17544.hs:46:30 })))
@@ -2493,10 +2564,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:52:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:52:13-17 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:52:19 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:52:32 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:52:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:52:13-17 }))
+        (EpTok (EpaSpan { T17544.hs:52:19 }))
+        (EpTok (EpaSpan { T17544.hs:52:32 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:52:19 }))
         (EpTok (EpaSpan { T17544.hs:52:32 })))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -281,8 +281,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544_kw.hs:21:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:23:3-7 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544_kw.hs:21:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:23:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (5))
        (NoAnnSortKey))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -458,7 +458,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:15:3-5 })
@@ -503,7 +503,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:17:3-6 })
@@ -616,7 +616,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:21:3-5 })
@@ -661,7 +661,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:25:3-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -501,9 +501,13 @@
                 (EpaComments
                  []))
                (HsExplicitListTy
-                [(AddEpAnn AnnSimpleQuote (EpaSpan { DumpParsedAst.hs:12:10 }))
-                ,(AddEpAnn AnnOpenS (EpaSpan { DumpParsedAst.hs:12:11 }))
-                ,(AddEpAnn AnnCloseS (EpaSpan { DumpParsedAst.hs:12:12 }))]
+                ((,,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:11 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:12 })))
                 (IsPromoted)
                 [])))]
             (Prefix)


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -1302,8 +1302,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { DumpSemis.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpSemis.hs:28:40-44 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:40-44 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -240,8 +240,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:15:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:15:6-8 })
@@ -452,8 +457,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:16:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:16:13 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:13 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:16:6-9 })
@@ -664,8 +674,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:19:10 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:10 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:19:6-8 })
@@ -1069,8 +1084,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:26:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:26:11 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:11 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:26:6-9 })
@@ -1092,9 +1112,13 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:26:13 }))
-        ,(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:26:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:26:29 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:13 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:29 })))
         (IsPromoted)
         [(L
           (EpAnn
@@ -1155,8 +1179,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:27:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:27:6-10 })
@@ -1178,8 +1207,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:27:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:27:45 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:45 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -1290,8 +1323,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:28:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:28:14 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:14 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:28:6-10 })
@@ -1340,9 +1378,13 @@
         (EpaComments
          []))
        (HsExplicitTupleTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:28:16 }))
-        ,(AddEpAnn AnnOpenP (EpaSpan { KindSigs.hs:28:17 }))
-        ,(AddEpAnn AnnCloseP (EpaSpan { KindSigs.hs:28:44 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:16 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:17 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:44 })))
         [(L
           (EpAnn
            (EpaSpan { KindSigs.hs:28:19-39 })
@@ -1363,8 +1405,12 @@
              (EpaComments
               []))
             (HsExplicitListTy
-             [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:28:19 }))
-             ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:28:29 }))]
+             ((,,)
+              (NoEpTok)
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:19 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:29 })))
              (NotPromoted)
              [(L
                (EpAnn
@@ -1465,8 +1511,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:31:19 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:19 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:31:6-17 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -262,10 +262,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:8:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:8:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:8:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:8:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:8:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:8:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:8:84 }))
+        (EpTok (EpaSpan { T20452.hs:8:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:8:84 }))
         (EpTok (EpaSpan { T20452.hs:8:85 })))
@@ -492,10 +499,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:9:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:9:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:9:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:9:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:9:84 }))
+        (EpTok (EpaSpan { T20452.hs:9:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:9:84 }))
         (EpTok (EpaSpan { T20452.hs:9:85 })))


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
=====================================
@@ -72,8 +72,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:5:6 })
@@ -101,8 +106,12 @@
              "-- comment inside A")
             { AnnotationNoListTuplePuns.hs:7:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -128,8 +137,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:12:6 })
@@ -157,8 +171,12 @@
              "-- comment inside B")
             { AnnotationNoListTuplePuns.hs:14:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -243,8 +261,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:6 })
@@ -266,8 +289,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -280,8 +307,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:6 })
@@ -303,8 +335,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 })))
         (NotPromoted)
         [(L
           (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -308,7 +308,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.hs:11:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.hs:11:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)
@@ -933,7 +942,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.ppr.hs:4:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.ppr.hs:4:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -837,21 +837,6 @@ markEpAnnLMS'' a l kw (Just str) = do
 
 -- -------------------------------------
 
-markEpAnnMS' :: (Monad m, Monoid w)
-  => [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m [AddEpAnn]
-markEpAnnMS' anns kw Nothing = mark anns kw
-markEpAnnMS' anns kw (Just str) = do
-  mapM go anns
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
--- -------------------------------------
-
 markEpAnnLMS' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
 markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
@@ -3286,51 +3271,53 @@ instance ExactPrint (HsExpr GhcPs) where
     return (ArithSeq (AnnArithSeq o' mc' dd' c') s seqInfo')
 
 
-  exact (HsTypedBracket an e) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[||")
-    an1 <- markEpAnnLMS'' an0 lidl AnnOpenE (Just "[e||")
+  exact (HsTypedBracket (o,c) e) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnLMS'' an1 lidl AnnClose (Just "||]")
-    return (HsTypedBracket an2 e')
+    c' <- markEpToken c
+    return (HsTypedBracket (o',c') e')
 
-  exact (HsUntypedBracket an (ExpBr a e)) = do
-    an0 <- markEpAnnL an  lidl AnnOpenEQ -- "[|"
-    an1 <- markEpAnnL an0 lidl AnnOpenE  -- "[e|" -- optional
+  exact (HsUntypedBracket a (ExpBr (o,c) e)) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpUniToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an2 (ExpBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (ExpBr (o',c') e'))
 
-  exact (HsUntypedBracket an (PatBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[p|")
+  exact (HsUntypedBracket a (PatBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (PatBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (PatBr (o',c') e'))
 
-  exact (HsUntypedBracket an (DecBrL a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[d|")
-    an1 <- markEpAnnL an0 lidl AnnOpenC
+  exact (HsUntypedBracket a (DecBrL (o,c, (oc,cc)) e)) = do
+    o' <- markEpToken o
+    oc' <- markEpToken oc
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseC
-    an3 <- markEpAnnL an2 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an3 (DecBrL a e'))
+    cc' <- markEpToken cc
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (DecBrL (o',c',(oc',cc')) e'))
 
-  exact (HsUntypedBracket an (TypBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[t|")
+  exact (HsUntypedBracket a (TypBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (TypBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (TypBr (o',c') e'))
 
-  exact (HsUntypedBracket an (VarBr a b e)) = do
+  exact (HsUntypedBracket a (VarBr an b e)) = do
     (an0, e') <- if b
       then do
-        an' <- markEpAnnL an lidl AnnSimpleQuote
+        an' <- printStringAtAA an "'"
         e' <- markAnnotated e
         return (an', e')
       else do
-        an' <- markEpAnnL an lidl AnnThTyQuote
+        an' <- printStringAtAA an "''"
         e' <- markAnnotated e
         return (an', e')
-    return (HsUntypedBracket an0 (VarBr a b e'))
+    return (HsUntypedBracket a (VarBr an0 b e'))
 
   exact (HsTypedSplice an s)   = do
     an0 <- markEpToken an
@@ -3768,24 +3755,24 @@ instance ExactPrint (TyClDecl GhcPs) where
     decl' <- markAnnotated decl
     return (FamDecl a decl')
 
-  exact (SynDecl { tcdSExt = an
+  exact (SynDecl { tcdSExt = AnnSynDecl ops cps t eq
                  , tcdLName = ltycon, tcdTyVars = tyvars, tcdFixity = fixity
                  , tcdRhs = rhs }) = do
     -- There may be arbitrary parens around parts of the constructor
     -- that are infix.  Turn these into comments so that they feed
     -- into the right place automatically
     -- TODO: no longer sorting on insert. What now?
-    an0 <- annotationsToComments an lidl [AnnOpenP,AnnCloseP]
-    an1 <- markEpAnnL an0 lidl AnnType
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
+    t' <- markEpToken t
 
     (_anx, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    an2 <- markEpAnnL an1 lidl AnnEqual
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (SynDecl { tcdSExt = an2
+    return (SynDecl { tcdSExt = AnnSynDecl [] [] t' eq'
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  -- TODO: add a workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/20452
   exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
     (_, an', ltycon', tyvars', _, defn') <-
@@ -3795,7 +3782,7 @@ instance ExactPrint (TyClDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ClassDecl {tcdCExt = (an, lo, sortKey),
+  exact (ClassDecl {tcdCExt = (AnnClassDecl c ops cps vb w oc cc semis, lo, sortKey),
                     tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars,
                     tcdFixity = fixity,
                     tcdFDs  = fds,
@@ -3805,10 +3792,10 @@ instance ExactPrint (TyClDecl GhcPs) where
       -- TODO: add a test that demonstrates tcdDocs
       | null sigs && null methods && null ats && null at_defs -- No "where" part
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnL an1 lidl AnnCloseC
-          return (ClassDecl {tcdCExt = (an2, lo, sortKey),
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          cc' <- markEpToken cc
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis, lo, sortKey),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3818,9 +3805,9 @@ instance ExactPrint (TyClDecl GhcPs) where
 
       | otherwise       -- Laid out
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL    an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lidl AnnSemi
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsSigTag, prepareListAnnotationA sigs),
                                 (ClsMethodTag, prepareListAnnotationA methods),
@@ -3828,13 +3815,13 @@ instance ExactPrint (TyClDecl GhcPs) where
                                 (ClsAtdTag, prepareListAnnotationA at_defs)
                              -- ++ prepareListAnnotation docs
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC
+          cc' <- markEpToken cc
           let
             sigs'    = undynamic ds
             methods' = undynamic ds
             ats'     = undynamic ds
             at_defs' = undynamic ds
-          return (ClassDecl {tcdCExt = (an3, lo, sortKey'),
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis', lo, sortKey'),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3843,17 +3830,18 @@ instance ExactPrint (TyClDecl GhcPs) where
                              tcdDocs = _docs})
       where
         top_matter = do
-          an' <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
-          an0 <- markEpAnnL an' lidl AnnClass
+          epTokensToComments AnnOpenP ops
+          epTokensToComments AnnCloseP cps
+          c' <- markEpToken c
           (_, lclas', tyvars',_,context') <-  exactVanillaDeclHead lclas tyvars fixity context
-          (an1, fds') <- if (null fds)
-            then return (an0, fds)
+          (vb', fds') <- if (null fds)
+            then return (vb, fds)
             else do
-              an1 <- markEpAnnL an0 lidl AnnVbar
+              vb' <- markEpToken vb
               fds' <- markAnnotated fds
-              return (an1, fds')
-          an2 <- markEpAnnL an1 lidl AnnWhere
-          return (an2, fds', lclas', tyvars',context')
+              return (vb', fds')
+          w' <- markEpToken w
+          return (c', w', vb', fds', lclas', tyvars',context')
 
 
 -- ---------------------------------------------------------------------
@@ -4202,37 +4190,36 @@ instance ExactPrint (HsType GhcPs) where
   exact (HsDocTy an ty doc) = do
     ty' <- markAnnotated ty
     return (HsDocTy an ty' doc)
-  exact (HsBangTy (an, mt) (HsBang up str) ty) = do
-    an0 <-
+  exact (HsBangTy ((o,c,tk), mt) (HsBang up str) ty) = do
+    (o',c') <-
       case mt of
-        NoSourceText -> return an
+        NoSourceText -> return (o,c)
         SourceText src -> do
           debugM $ "HsBangTy: src=" ++ showAst src
-          an0 <- markEpAnnMS' an AnnOpen  (Just $ unpackFS src)
-          an1 <- markEpAnnMS' an0 AnnClose (Just "#-}")
-          debugM $ "HsBangTy: done unpackedness"
-          return an1
-    an1 <-
+          o' <- printStringAtAA o (unpackFS src)
+          c' <- printStringAtAA c "#-}"
+          return (o',c')
+    tk' <-
       case str of
-        SrcLazy     -> mark an0 AnnTilde
-        SrcStrict   -> mark an0 AnnBang
-        NoSrcStrict -> return an0
+        SrcLazy     -> printStringAtAA tk "~"
+        SrcStrict   -> printStringAtAA tk "!"
+        NoSrcStrict -> return tk
     ty' <- markAnnotated ty
-    return (HsBangTy (an1, mt) (HsBang up str) ty')
-  exact (HsExplicitListTy an prom tys) = do
-    an0 <- if (isPromoted prom)
-             then mark an AnnSimpleQuote
-             else return an
-    an1 <- mark an0 AnnOpenS
+    return (HsBangTy ((o',c',tk'), mt) (HsBang up str) ty')
+  exact (HsExplicitListTy (sq,o,c) prom tys) = do
+    sq' <- if (isPromoted prom)
+             then markEpToken sq
+             else return sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseS
-    return (HsExplicitListTy an2 prom tys')
-  exact (HsExplicitTupleTy an tys) = do
-    an0 <- mark an AnnSimpleQuote
-    an1 <- mark an0 AnnOpenP
+    c' <- markEpToken c
+    return (HsExplicitListTy (sq',o',c') prom tys')
+  exact (HsExplicitTupleTy (sq, o, c) tys) = do
+    sq' <- markEpToken sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseP
-    return (HsExplicitTupleTy an2 tys')
+    c' <- markEpToken c
+    return (HsExplicitTupleTy (sq', o', c') tys')
   exact (HsTyLit a lit) = do
     case lit of
       (HsNumTy src v) -> printSourceText src (show v)


=====================================
utils/check-exact/Main.hs
=====================================
@@ -166,7 +166,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/T18052a.hs" Nothing
  -- "../../testsuite/tests/printer/T18247a.hs" Nothing
  -- "../../testsuite/tests/printer/Test10268.hs" Nothing
- "../../testsuite/tests/printer/Test10269.hs" Nothing
+ -- "../../testsuite/tests/printer/Test10269.hs" Nothing
  -- "../../testsuite/tests/printer/Test10276.hs" Nothing
  -- "../../testsuite/tests/printer/Test10278.hs" Nothing
  -- "../../testsuite/tests/printer/Test10312.hs" Nothing
@@ -209,6 +209,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
+ "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
  -- "../../testsuite/tests/printer/Test23465.hs" Nothing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b9f398ae94206d0cda2e644729a88e835db1ef7...2424235d74fc5ea634ee68f2381ef657071c6a0b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b9f398ae94206d0cda2e644729a88e835db1ef7...2424235d74fc5ea634ee68f2381ef657071c6a0b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 16 22:33:05 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 16 Oct 2024 18:33:05 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-4] 6 commits: EPA: Remove
 [AddEpAnn] for FunDep
Message-ID: <67103f214e285_2e7851406a64817a6@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC


Commits:
d0ff68e9 by Alan Zimmerman at 2024-10-15T21:15:24+01:00
EPA: Remove [AddEpAnn] for FunDep

- - - - -
9679181e by Alan Zimmerman at 2024-10-16T19:31:04+01:00
EPA: Remove [AddEpann] from FamilyDecl

- - - - -
62dbf4de by Alan Zimmerman at 2024-10-16T20:09:33+01:00
EPA: Remove [AddEpAnn] From InjectivityAnn

- - - - -
e719f43e by Alan Zimmerman at 2024-10-16T21:09:32+01:00
EPA: Remove [AddEpAnn] from DefaultDecl

- - - - -
17d54803 by Alan Zimmerman at 2024-10-16T22:06:40+01:00
EPA: Remove [AddEpAnn] from RuleDecls

- - - - -
70243684 by Alan Zimmerman at 2024-10-16T22:53:24+01:00
EPA: Remove [AddEpAnn] from Warnings

- - - - -


11 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -34,6 +34,7 @@ module GHC.Hs.Decls (
   AnnDataDefn(..),
   AnnClassDecl(..),
   AnnSynDecl(..),
+  AnnFamilyDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -578,7 +579,7 @@ pprTyClDeclFlavour (DataDecl { tcdDataDefn = HsDataDefn { dd_cons = nd } })
 instance OutputableBndrId p => Outputable (FunDep (GhcPass p)) where
   ppr = pprFunDep
 
-type instance XCFunDep    (GhcPass _) = [AddEpAnn]
+type instance XCFunDep    (GhcPass _) = TokRarrow
 type instance XXFunDep    (GhcPass _) = DataConCantHappen
 
 pprFundeps :: OutputableBndrId p => [FunDep (GhcPass p)] -> SDoc
@@ -612,9 +613,27 @@ type instance XCKindSig         (GhcPass _) = NoExtField
 type instance XTyVarSig         (GhcPass _) = NoExtField
 type instance XXFamilyResultSig (GhcPass _) = DataConCantHappen
 
-type instance XCFamilyDecl    (GhcPass _) = [AddEpAnn]
+type instance XCFamilyDecl    (GhcPass _) = AnnFamilyDecl
 type instance XXFamilyDecl    (GhcPass _) = DataConCantHappen
 
+data AnnFamilyDecl
+  = AnnFamilyDecl {
+      afd_openp  :: [EpToken "("],
+      afd_closep :: [EpToken ")"],
+      afd_type   :: EpToken "type",
+      afd_data   :: EpToken "data",
+      afd_family :: EpToken "family",
+      afd_dcolon :: TokDcolon,
+      afd_equal  :: EpToken "=",
+      afd_vbar   :: EpToken "|",
+      afd_where  :: EpToken "where",
+      afd_openc  :: EpToken "{",
+      afd_dotdot :: EpToken "..",
+      afd_closec :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnFamilyDecl where
+  noAnn = AnnFamilyDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 ------------- Functions over FamilyDecls -----------
 
@@ -639,7 +658,7 @@ resultVariableName _                = Nothing
 
 ------------- Pretty printing FamilyDecls -----------
 
-type instance XCInjectivityAnn  (GhcPass _) = [AddEpAnn]
+type instance XCInjectivityAnn  (GhcPass _) = TokRarrow
 type instance XXInjectivityAnn  (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -1164,7 +1183,7 @@ mapDerivStrategy f ds = foldDerivStrategy ds (ViaStrategy . f) ds
 ************************************************************************
 -}
 
-type instance XCDefaultDecl    GhcPs = [AddEpAnn]
+type instance XCDefaultDecl    GhcPs = (EpToken "default", EpToken "(", EpToken ")")
 type instance XCDefaultDecl    GhcRn = NoExtField
 type instance XCDefaultDecl    GhcTc = NoExtField
 
@@ -1252,7 +1271,7 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XCRuleDecls    GhcPs = ([AddEpAnn], SourceText)
+type instance XCRuleDecls    GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XCRuleDecls    GhcRn = SourceText
 type instance XCRuleDecls    GhcTc = SourceText
 
@@ -1337,7 +1356,7 @@ pprFullRuleName st (L _ n) = pprWithSourceText st (doubleQuotes $ ftext n)
 ************************************************************************
 -}
 
-type instance XWarnings      GhcPs = ([AddEpAnn], SourceText)
+type instance XWarnings      GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XWarnings      GhcRn = SourceText
 type instance XWarnings      GhcTc = SourceText
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -80,6 +80,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annClassDecl
               `extQ` annSynDecl
               `extQ` annDataDefn
+              `extQ` annFamilyDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -251,6 +252,16 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                  showAstData' g, showAstData' h, showAstData' i,
                                  showAstData' j, showAstData' k]
 
+            annFamilyDecl :: AnnFamilyDecl -> SDoc
+            annFamilyDecl (AnnFamilyDecl a b c d e f g h i j k l) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnFamilyDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k, showAstData' l]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1275,9 +1275,9 @@ topdecl :: { LHsDecl GhcPs }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
         | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
-        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
-        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getWARNING_PRAGs $1)) (fromOL $2))) }
-        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ([mo $1,mc $3], (getRULES_PRAGs $1)) (reverse $2))) }
+        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
+        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
+        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
         | annotation { $1 }
         | decl_no_th                            { $1 }
 
@@ -1300,7 +1300,7 @@ cl_decl :: { LTyClDecl GhcPs }
 --
 default_decl :: { LDefaultDecl GhcPs }
              : 'default' opt_class '(' comma_types0 ')'
-               {% amsA' (sLL $1 $> (DefaultDecl [mj AnnDefault $1,mop $3,mcp $5] $2 $4)) }
+               {% amsA' (sLL $1 $> (DefaultDecl (epTok $1,epTok $3,epTok $5) $2 $4)) }
 
 
 -- Type declarations (toplevel)
@@ -1322,10 +1322,12 @@ ty_decl :: { LTyClDecl GhcPs }
                           where_type_family
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
+             {% do { let { (tdcolon, tequal) = fst $ unLoc $4 }
+                   ; let { tvbar = fst $ unLoc $5 }
+                   ; let { (twhere, (toc, tdd, tcc)) = fst $ unLoc $6  }
+                   ; mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
                                    (snd $ unLoc $4) (snd $ unLoc $5)
-                           (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)
-                           ++ (fst $ unLoc $5) ++ (fst $ unLoc $6))  }
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar twhere toc tdd tcc) }}
 
           -- ordinary data type or newtype declaration
         | type_data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings
@@ -1355,9 +1357,10 @@ ty_decl :: { LTyClDecl GhcPs }
 
           -- data/newtype family
         | 'data' 'family' type opt_datafam_kind_sig
-                {% mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
                                    (snd $ unLoc $4) Nothing
-                          (mj AnnData $1:mj AnnFamily $2:(fst $ unLoc $4)) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) (epTok $2) tdcolon noAnn noAnn noAnn noAnn noAnn noAnn) }}
 
 -- standalone kind signature
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
@@ -1449,14 +1452,14 @@ opt_class :: { Maybe (LIdP GhcPs) }
 
 -- Injective type families
 
-opt_injective_info :: { Located ([AddEpAnn], Maybe (LInjectivityAnn GhcPs)) }
-        : {- empty -}               { noLoc ([], Nothing) }
-        | '|' injectivity_cond      { sLL $1 $> ([mj AnnVbar $1]
+opt_injective_info :: { Located (EpToken "|", Maybe (LInjectivityAnn GhcPs)) }
+        : {- empty -}               { noLoc (noAnn, Nothing) }
+        | '|' injectivity_cond      { sLL $1 $> ((epTok $1)
                                                 , Just ($2)) }
 
 injectivity_cond :: { LInjectivityAnn GhcPs }
         : tyvarid '->' inj_varids
-           {% amsA' (sLL $1 $> (InjectivityAnn [mu AnnRarrow $2] $1 (reverse (unLoc $3)))) }
+           {% amsA' (sLL $1 $> (InjectivityAnn (epUniTok $2) $1 (reverse (unLoc $3)))) }
 
 inj_varids :: { Located [LocatedN RdrName] }
         : inj_varids tyvarid  { sLL $1 $> ($2 : unLoc $1) }
@@ -1464,21 +1467,20 @@ inj_varids :: { Located [LocatedN RdrName] }
 
 -- Closed type families
 
-where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
-        : {- empty -}                      { noLoc ([],OpenTypeFamily) }
+where_type_family :: { Located ((EpToken "where", (EpToken "{", EpToken "..", EpToken "}")),FamilyInfo GhcPs) }
+        : {- empty -}                      { noLoc (noAnn,OpenTypeFamily) }
         | 'where' ty_fam_inst_eqn_list
-               { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
+               { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
                     ,ClosedTypeFamily (fmap reverse $ snd $ unLoc $2)) }
 
-ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
-        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
+ty_fam_inst_eqn_list :: { Located ((EpToken "{", EpToken "..", EpToken "}"),Maybe [LTyFamInstEqn GhcPs]) }
+        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ((epTok $1,noAnn, epTok $3)
                                                 ,Just (unLoc $2)) }
         | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
-                                             L loc ([],Just (unLoc $2)) }
-        |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
-                                                 ,mcc $3],Nothing) }
+                                             L loc (noAnn,Just (unLoc $2)) }
+        |     '{' '..' '}'                 { sLL $1 $> ((epTok $1,epTok $2 ,epTok $3),Nothing) }
         | vocurly '..' close               { let (L loc _) = $2 in
-                                             L loc ([mj AnnDotdot $2],Nothing) }
+                                             L loc ((noAnn,epTok $2, noAnn),Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
         : ty_fam_inst_eqns ';' ty_fam_inst_eqn
@@ -1520,25 +1522,27 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
 at_decl_cls :: { LHsDecl GhcPs }
         :  -- data family declarations, with optional 'family' keyword
           'data' opt_family type opt_datafam_kind_sig
-                {% liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
                                                   (snd $ unLoc $4) Nothing
-                        (mj AnnData $1:$2++(fst $ unLoc $4))) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) $2 tdcolon noAnn noAnn noAnn noAnn noAnn noAnn)) }}
 
            -- type family declarations, with optional 'family' keyword
            -- (can't use opt_instance because you get shift/reduce errors
         | 'type' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $3 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $2 $3) OpenTypeFamily NotTopLevel $2
                                    (fst . snd $ unLoc $3)
                                    (snd . snd $ unLoc $3)
-                         (mj AnnType $1:(fst $ unLoc $3)) )}
+                         (AnnFamilyDecl [] [] (epTok $1) noAnn noAnn tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
         | 'type' 'family' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $4 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $3 $4) OpenTypeFamily NotTopLevel $3
                                    (fst . snd $ unLoc $4)
                                    (snd . snd $ unLoc $4)
-                         (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)))}
-
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
            -- default type instances, with optional 'instance' keyword
         | 'type' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $2) (unLoc $2)
@@ -1547,9 +1551,9 @@ at_decl_cls :: { LHsDecl GhcPs }
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $3) (unLoc $3)
                               (epTok $1) (epTok $2) )}
 
-opt_family   :: { [AddEpAnn] }
-              : {- empty -}   { [] }
-              | 'family'      { [mj AnnFamily $1] }
+opt_family   :: { EpToken "family" }
+              : {- empty -}   { noAnn }
+              | 'family'      { (epTok $1) }
 
 opt_instance :: { EpToken "instance" }
               : {- empty -} { NoEpTok }
@@ -1602,24 +1606,24 @@ opt_kind_sig :: { Located (TokDcolon, Maybe (LHsKind GhcPs)) }
         :               { noLoc     (NoEpUniTok , Nothing) }
         | '::' kind     { sLL $1 $> (epUniTok $1, Just $2) }
 
-opt_datafam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :               { noLoc     ([]               , noLocA (NoSig noExtField)         )}
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig noExtField $2))}
+opt_datafam_kind_sig :: { Located (TokDcolon, LFamilyResultSig GhcPs) }
+        :               { noLoc     (noAnn,       noLocA (NoSig noExtField)         )}
+        | '::' kind     { sLL $1 $> (epUniTok $1, sLLa $1 $> (KindSig noExtField $2))}
 
-opt_tyfam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :              { noLoc     ([]               , noLocA     (NoSig    noExtField)   )}
-        | '::' kind    { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig  noExtField $2))}
+opt_tyfam_kind_sig :: { Located ((TokDcolon, EpToken "="), LFamilyResultSig GhcPs) }
+        :              { noLoc     (noAnn               , noLocA     (NoSig    noExtField)   )}
+        | '::' kind    { sLL $1 $> ((epUniTok $1, noAnn), sLLa $1 $> (KindSig  noExtField $2))}
         | '='  tv_bndr {% do { tvb <- fromSpecTyVarBndr $2
-                             ; return $ sLL $1 $> ([mj AnnEqual $1], sLLa $1 $> (TyVarSig noExtField tvb))} }
+                             ; return $ sLL $1 $> ((noAnn, epTok $1), sLLa $1 $> (TyVarSig noExtField tvb))} }
 
-opt_at_kind_inj_sig :: { Located ([AddEpAnn], ( LFamilyResultSig GhcPs
+opt_at_kind_inj_sig :: { Located ((TokDcolon, EpToken "=", EpToken "|"), ( LFamilyResultSig GhcPs
                                             , Maybe (LInjectivityAnn GhcPs)))}
-        :            { noLoc ([], (noLocA (NoSig noExtField), Nothing)) }
-        | '::' kind  { sLL $1 $> ( [mu AnnDcolon $1]
+        :            { noLoc (noAnn, (noLocA (NoSig noExtField), Nothing)) }
+        | '::' kind  { sLL $1 $> ( (epUniTok $1, noAnn, noAnn)
                                  , (sL1a $> (KindSig noExtField $2), Nothing)) }
         | '='  tv_bndr_no_braces '|' injectivity_cond
                 {% do { tvb <- fromSpecTyVarBndr $2
-                      ; return $ sLL $1 $> ([mj AnnEqual $1, mj AnnVbar $3]
+                      ; return $ sLL $1 $> ((noAnn, epTok $1, epTok $3)
                                            , (sLLa $1 $2 (TyVarSig noExtField tvb), Just $4))} }
 
 -- tycl_hdr parses the header of a class or data type decl,
@@ -2450,7 +2454,7 @@ fds1 :: { Located [LHsFunDep GhcPs] }
 
 fd :: { LHsFunDep GhcPs }
         : varids0 '->' varids0  {% amsA' (L (comb3 $1 $2 $3)
-                                       (FunDep [mu AnnRarrow $2]
+                                       (FunDep (epUniTok $2)
                                                (reverse (unLoc $1))
                                                (reverse (unLoc $3)))) }
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon,
+  TokDcolon, TokRarrow,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -411,6 +411,7 @@ getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
 type TokDcolon = EpUniToken "::" "∷"
+type TokRarrow = EpUniToken "->" "→"
 
 -- | Layout information for declarations.
 data EpLayout =


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -247,15 +247,6 @@ mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
--- TODO:AZ:temporary
-openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
-openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
-openParen2AddEpAnn NoEpTok = []
-
-closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
-closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
-closeParen2AddEpAnn NoEpTok = []
-
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
@@ -371,14 +362,13 @@ mkFamDecl :: SrcSpan
           -> LHsType GhcPs                   -- LHS
           -> LFamilyResultSig GhcPs          -- Optional result signature
           -> Maybe (LInjectivityAnn GhcPs)   -- Injectivity annotation
-          -> [AddEpAnn]
+          -> AnnFamilyDecl
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns' = annsIn { afd_openp = ops, afd_closep = cps }
        ; return (L loc' (FamDecl noExtField (FamilyDecl
                                            { fdExt       = anns'
                                            , fdTopLevel  = topLevel


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -891,7 +891,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:22:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:22:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1254,7 +1267,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:28:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:28:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1617,7 +1643,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:34:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:34:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1980,7 +2019,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:40:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:40:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2343,7 +2395,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:46:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:46:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2706,7 +2771,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:52:21-24 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:52:21-24 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -298,10 +298,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:10:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:10:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:10:32-33 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:10:41-45 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:10:32-33 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:41-45 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1032,10 +1046,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:18:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:18:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:18:42-43 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:18:50-54 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:18:42-43 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:50-54 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1414,9 +1442,23 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:21:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:21:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:21:17-18 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:1-4 }))
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:21:17-18 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (DataFamily)
        (TopLevel)
        (L


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -256,7 +256,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -688,7 +700,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (TopLevel)
          (L
@@ -1494,7 +1518,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -2051,7 +2087,19 @@
            (EpaComments
             []))
           (FamilyDecl
-           []
+           (AnnFamilyDecl
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (OpenTypeFamily)
            (NotTopLevel)
            (L


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -84,9 +84,22 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:11:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { KindSigs.hs:11:6-11 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { KindSigs.hs:11:19-23 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:6-11 }))
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:19-23 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2154,11 +2154,11 @@ instance ExactPrint (WarnDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warnings (an,src) warns) = do
-    an0 <- markAnnOpen an src "{-# WARNING" -- Note: might be {-# DEPRECATED
+  exact (Warnings ((o,c),src) warns) = do
+    o' <- markAnnOpen'' o src "{-# WARNING" -- Note: might be {-# DEPRECATED
     warns' <- markAnnotated warns
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (Warnings (an1,src) warns')
+    c' <- printStringAtAA c "#-}"
+    return (Warnings ((o',c'),src) warns')
 
 -- ---------------------------------------------------------------------
 
@@ -2220,14 +2220,14 @@ instance ExactPrint FastString where
 instance ExactPrint (RuleDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (HsRules (an, src) rules) = do
-    an0 <-
+  exact (HsRules ((o,c), src) rules) = do
+    o' <-
       case src of
-        NoSourceText      -> markEpAnnLMS'' an lidl AnnOpen  (Just "{-# RULES")
-        SourceText srcTxt -> markEpAnnLMS'' an lidl AnnOpen  (Just $ unpackFS srcTxt)
+        NoSourceText      -> printStringAtAA o "{-# RULES"
+        SourceText srcTxt -> printStringAtAA o (unpackFS srcTxt)
     rules' <- markAnnotated rules
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (HsRules (an1,src) rules')
+    c' <- printStringAtAA c "#-}"
+    return (HsRules ((o',c'),src) rules')
 
 -- ---------------------------------------------------------------------
 
@@ -2979,13 +2979,13 @@ instance ExactPrint (DefaultDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DefaultDecl an cl tys) = do
-    an0 <- markEpAnnL an lidl AnnDefault
-    an1 <- markEpAnnL an0 lidl AnnOpenP
+  exact (DefaultDecl (d,op,cp) cl tys) = do
+    d' <- markEpToken d
+    op' <- markEpToken op
     cl' <- markAnnotated cl
     tys' <- markAnnotated tys
-    an2 <- markEpAnnL an1 lidl AnnCloseP
-    return (DefaultDecl an2 cl' tys')
+    cp' <- markEpToken cp
+    return (DefaultDecl (d',op',cp') cl' tys')
 
 -- ---------------------------------------------------------------------
 
@@ -3864,7 +3864,7 @@ instance ExactPrint (FunDep GhcPs) where
 
   exact (FunDep an ls rs') = do
     ls' <- markAnnotated ls
-    an0 <- markEpAnnL an lidl AnnRarrow
+    an0 <- markEpUniToken an
     rs'' <- markAnnotated rs'
     return (FunDep an0 ls' rs'')
 
@@ -3874,7 +3874,7 @@ instance ExactPrint (FamilyDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (FamilyDecl { fdExt = an
+  exact (FamilyDecl { fdExt = AnnFamilyDecl ops cps t d f dc eq vb w oc dd cc
                     , fdInfo = info
                     , fdTopLevel = top_level
                     , fdLName = ltycon
@@ -3882,35 +3882,37 @@ instance ExactPrint (FamilyDecl GhcPs) where
                     , fdFixity = fixity
                     , fdResultSig = L lr result
                     , fdInjectivityAnn = mb_inj }) = do
-    an0 <- exactFlavour an info
-    an1 <- exact_top_level an0
-    an2 <- annotationsToComments an1 lidl [AnnOpenP,AnnCloseP]
+    (d',t') <- exactFlavour (d,t) info
+    f' <- exact_top_level f
+
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
     (_, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    (an3, result') <- exact_kind an2
-    (an4, mb_inj') <-
+    (dc', eq', result') <- exact_kind (dc, eq)
+    (vb', mb_inj') <-
       case mb_inj of
-        Nothing -> return (an3, mb_inj)
+        Nothing -> return (vb, mb_inj)
         Just inj -> do
-          an4 <- markEpAnnL an3 lidl AnnVbar
+          vb' <- markEpToken vb
           inj' <- markAnnotated inj
-          return (an4, Just inj')
-    (an5, info') <-
+          return (vb', Just inj')
+    (w', oc', dd', cc', info') <-
              case info of
                ClosedTypeFamily mb_eqns -> do
-                 an5 <- markEpAnnL an4 lidl AnnWhere
-                 an6 <- markEpAnnL an5 lidl AnnOpenC
-                 (an7, mb_eqns') <-
+                 w' <- markEpToken w
+                 oc' <- markEpToken oc
+                 (dd', mb_eqns') <-
                    case mb_eqns of
                      Nothing -> do
-                       an7 <- markEpAnnL an6 lidl AnnDotdot
-                       return (an7, mb_eqns)
+                       dd' <- markEpToken dd
+                       return (dd', mb_eqns)
                      Just eqns -> do
                        eqns' <- markAnnotated eqns
-                       return (an6, Just eqns')
-                 an8 <- markEpAnnL an7 lidl AnnCloseC
-                 return (an8, ClosedTypeFamily mb_eqns')
-               _ -> return (an4, info)
-    return (FamilyDecl { fdExt = an5
+                       return (dd, Just eqns')
+                 cc' <- markEpToken cc
+                 return (w',oc',dd',cc', ClosedTypeFamily mb_eqns')
+               _ -> return (w,oc,dd,cc, info)
+    return (FamilyDecl { fdExt = AnnFamilyDecl [] [] t' d' f' dc' eq' vb' w' oc' dd' cc'
                        , fdInfo = info'
                        , fdTopLevel = top_level
                        , fdLName = ltycon'
@@ -3919,32 +3921,32 @@ instance ExactPrint (FamilyDecl GhcPs) where
                        , fdResultSig = L lr result'
                        , fdInjectivityAnn = mb_inj' })
     where
-      exact_top_level an' =
+      exact_top_level tfamily =
         case top_level of
-          TopLevel    -> markEpAnnL an' lidl AnnFamily
+          TopLevel    -> markEpToken tfamily
           NotTopLevel -> do
             -- It seems that in some kind of legacy
             -- mode the 'family' keyword is still
             -- accepted.
-            markEpAnnL an' lidl AnnFamily
+            markEpToken tfamily
 
-      exact_kind an' =
+      exact_kind (tdcolon, tequal) =
         case result of
-          NoSig    _         -> return (an', result)
+          NoSig    _         -> return (tdcolon, tequal, result)
           KindSig  x kind    -> do
-            an0 <- markEpAnnL an' lidl AnnDcolon
+            tdcolon' <- markEpUniToken tdcolon
             kind' <- markAnnotated kind
-            return (an0, KindSig  x kind')
+            return (tdcolon', tequal, KindSig  x kind')
           TyVarSig x tv_bndr -> do
-            an0 <- markEpAnnL an' lidl AnnEqual
+            tequal' <- markEpToken tequal
             tv_bndr' <- markAnnotated tv_bndr
-            return (an0, TyVarSig x tv_bndr')
+            return (tdcolon, tequal', TyVarSig x tv_bndr')
 
 
-exactFlavour :: (Monad m, Monoid w) => [AddEpAnn] -> FamilyInfo GhcPs -> EP w m [AddEpAnn]
-exactFlavour an DataFamily            = markEpAnnL an lidl AnnData
-exactFlavour an OpenTypeFamily        = markEpAnnL an lidl AnnType
-exactFlavour an (ClosedTypeFamily {}) = markEpAnnL an lidl AnnType
+exactFlavour :: (Monad m, Monoid w) => (EpToken "data", EpToken "type") -> FamilyInfo GhcPs -> EP w m (EpToken "data", EpToken "type")
+exactFlavour (td,tt) DataFamily            = (\td' -> (td',tt)) <$> markEpToken td
+exactFlavour (td,tt) OpenTypeFamily        = (td,)              <$> markEpToken tt
+exactFlavour (td,tt) (ClosedTypeFamily {}) = (td,)              <$> markEpToken tt
 
 -- ---------------------------------------------------------------------
 
@@ -4049,12 +4051,11 @@ exactVanillaDeclHead thing tvs@(HsQTvs { hsq_explicit = tyvars }) fixity context
 instance ExactPrint (InjectivityAnn GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (InjectivityAnn an lhs rhs) = do
-    an0 <- markEpAnnL an lidl AnnVbar
+  exact (InjectivityAnn rarrow lhs rhs) = do
     lhs' <- markAnnotated lhs
-    an1 <- markEpAnnL an0 lidl AnnRarrow
+    rarrow' <- markEpUniToken rarrow
     rhs' <- mapM markAnnotated rhs
-    return (InjectivityAnn an1 lhs' rhs')
+    return (InjectivityAnn rarrow' lhs' rhs')
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -94,7 +94,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Ppr002.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr002a.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr003.hs" Nothing
- "../../testsuite/tests/printer/Ppr004.hs" Nothing
+ -- "../../testsuite/tests/printer/Ppr004.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr005.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr006.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr007.hs" Nothing
@@ -212,7 +212,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- -- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f4c2b3bd6a7ffe280a31fac7d0eef34c9934f9ba...702436846e62fe35f25edddfe7ff86ea7694b43c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f4c2b3bd6a7ffe280a31fac7d0eef34c9934f9ba...702436846e62fe35f25edddfe7ff86ea7694b43c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 03:28:24 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 16 Oct 2024 23:28:24 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: EPA: Remove
 [AddEpAnn] commit 3
Message-ID: <6710845875478_2e78511293de8113824@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
53009148 by Alan Zimmerman at 2024-10-16T23:27:48-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
cf72d5f7 by Daan Rijks at 2024-10-16T23:27:48-04:00
Expand the haddocks for Control.Category

- - - - -
cecae385 by Andrew Lelechenko at 2024-10-16T23:27:48-04:00
documentation: more examples for Control.Category

- - - - -


26 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/ThToHs.hs
- libraries/base/src/Control/Category.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Category.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,6 +31,8 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnClassDecl(..),
+  AnnSynDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -353,7 +355,7 @@ instance Outputable SpliceDecoration where
 
 type instance XFamDecl      (GhcPass _) = NoExtField
 
-type instance XSynDecl      GhcPs = [AddEpAnn]
+type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
@@ -368,7 +370,7 @@ data DataDeclRn = DataDeclRn
   deriving Data
 
 type instance XClassDecl    GhcPs =
-  ( [AddEpAnn]
+  ( AnnClassDecl
   , EpLayout              -- See Note [Class EpLayout]
   , AnnSortKey DeclTag )  -- TODO:AZ:tidy up AnnSortKey
 
@@ -380,6 +382,32 @@ type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnClassDecl
+  = AnnClassDecl {
+      acd_class  :: EpToken "class",
+      acd_openp  :: [EpToken "("],
+      acd_closep :: [EpToken ")"],
+      acd_vbar   :: EpToken "|",
+      acd_where  :: EpToken "where",
+      acd_openc  :: EpToken "{",
+      acd_closec :: EpToken "}",
+      acd_semis  :: [EpToken ";"]
+  } deriving Data
+
+instance NoAnn AnnClassDecl where
+  noAnn = AnnClassDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
+data AnnSynDecl
+  = AnnSynDecl {
+    asd_opens  :: [EpToken "("],
+    asd_closes :: [EpToken ")"],
+    asd_type   :: EpToken "type",
+    asd_equal  :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnSynDecl where
+  noAnn = AnnSynDecl noAnn noAnn noAnn noAnn
+
 ------------- Pretty printing FamilyDecls -----------
 
 pprFlavour :: FamilyInfo pass -> SDoc


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -67,10 +67,14 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annotationAnnList
               `extQ` annotationEpAnnImportDecl
               `extQ` annotationNoEpAnns
+              `extQ` annotationExprBracket
+              `extQ` annotationTypedBracket
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
               `extQ` annParen
+              `extQ` annClassDecl
+              `extQ` annSynDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -203,6 +207,23 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               parens $ text "AnnParen"
                         $$ vcat [ppr a, epaLocation o, epaLocation c]
 
+            annClassDecl :: AnnClassDecl -> SDoc
+            annClassDecl (AnnClassDecl c ops cps v w oc cc s) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnClassDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClassDecl"
+                        $$ vcat [showAstData' c, showAstData' ops, showAstData' cps,
+                                 showAstData' v, showAstData' w, showAstData' oc,
+                                 showAstData' cc, showAstData' s]
+
+            annSynDecl :: AnnSynDecl -> SDoc
+            annSynDecl (AnnSynDecl ops cps t e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnSynDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnSynDecl"
+                        $$ vcat [showAstData' ops, showAstData' cps,
+                                 showAstData' t, showAstData' e]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -210,6 +231,22 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "AddEpAnn" <+> ppr a <+> epaLocation s
 
+            annotationExprBracket :: BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|") -> SDoc
+            annotationExprBracket = annotationBracket
+
+            annotationTypedBracket :: BracketAnn (EpToken "[||") (EpToken "[e||") -> SDoc
+            annotationTypedBracket = annotationBracket
+
+            annotationBracket ::forall n h .(Data n, Data h, Typeable n, Typeable h)
+              => BracketAnn n h -> SDoc
+            annotationBracket a = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "BracketAnn"
+             NoBlankEpAnnotations ->
+              parens $ case a of
+                BracketNoE  t -> text "BracketNoE"  <+> showAstData' t
+                BracketHasE t -> text "BracketHasE" <+> showAstData' t
+
             epTokenOC :: EpToken "{" -> SDoc
             epTokenOC  = epToken'
 


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -181,15 +181,23 @@ data HsBracketTc = HsBracketTc
                                         -- pasted back in by the desugarer
   }
 
-type instance XTypedBracket GhcPs = [AddEpAnn]
+type instance XTypedBracket GhcPs = (BracketAnn (EpToken "[||") (EpToken "[e||"), EpToken "||]")
 type instance XTypedBracket GhcRn = NoExtField
 type instance XTypedBracket GhcTc = HsBracketTc
-type instance XUntypedBracket GhcPs = [AddEpAnn]
+type instance XUntypedBracket GhcPs = NoExtField
 type instance XUntypedBracket GhcRn = [PendingRnSplice] -- See Note [Pending Splices]
                                                         -- Output of the renamer is the *original* renamed expression,
                                                         -- plus _renamed_ splices to be type checked
 type instance XUntypedBracket GhcTc = HsBracketTc
 
+data BracketAnn noE hasE
+  = BracketNoE noE
+  | BracketHasE hasE
+  deriving Data
+
+instance (NoAnn n, NoAnn h) => NoAnn (BracketAnn n h) where
+  noAnn = BracketNoE noAnn
+
 -- ---------------------------------------------------------------------
 
 -- API Annotations types
@@ -2141,12 +2149,12 @@ ppr_splice herald mn e
     <> ppr e
 
 
-type instance XExpBr  GhcPs       = NoExtField
-type instance XPatBr  GhcPs       = NoExtField
-type instance XDecBrL GhcPs       = NoExtField
+type instance XExpBr  GhcPs       = (BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|"), EpUniToken "|]" "⟧")
+type instance XPatBr  GhcPs       = (EpToken "[p|", EpUniToken "|]" "⟧")
+type instance XDecBrL GhcPs       = (EpToken "[d|", EpUniToken "|]" "⟧", (EpToken "{", EpToken "}"))
 type instance XDecBrG GhcPs       = NoExtField
-type instance XTypBr  GhcPs       = NoExtField
-type instance XVarBr  GhcPs       = NoExtField
+type instance XTypBr  GhcPs       = (EpToken "[t|", EpUniToken "|]" "⟧")
+type instance XVarBr  GhcPs       = EpaLocation
 type instance XXQuote GhcPs       = DataConCantHappen
 
 type instance XExpBr  GhcRn       = NoExtField


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -475,18 +475,18 @@ type instance XSpliceTy        GhcPs = NoExtField
 type instance XSpliceTy        GhcRn = HsUntypedSpliceResult (LHsType GhcRn)
 type instance XSpliceTy        GhcTc = Kind
 
-type instance XDocTy           (GhcPass _) = [AddEpAnn]
-type instance XBangTy          (GhcPass _) = ([AddEpAnn], SourceText)
+type instance XDocTy           (GhcPass _) = NoExtField
+type instance XBangTy          (GhcPass _) = ((EpaLocation, EpaLocation, EpaLocation), SourceText)
 
 type instance XRecTy           GhcPs = AnnList
 type instance XRecTy           GhcRn = NoExtField
 type instance XRecTy           GhcTc = NoExtField
 
-type instance XExplicitListTy  GhcPs = [AddEpAnn]
+type instance XExplicitListTy  GhcPs = (EpToken "'", EpToken "[", EpToken "]")
 type instance XExplicitListTy  GhcRn = NoExtField
 type instance XExplicitListTy  GhcTc = Kind
 
-type instance XExplicitTupleTy GhcPs = [AddEpAnn]
+type instance XExplicitTupleTy GhcPs = (EpToken "'", EpToken "(", EpToken ")")
 type instance XExplicitTupleTy GhcRn = NoExtField
 type instance XExplicitTupleTy GhcTc = [Kind]
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1292,8 +1292,9 @@ topdecl :: { LHsDecl GhcPs }
 --
 cl_decl :: { LTyClDecl GhcPs }
         : 'class' tycl_hdr fds where_cls
-                {% (mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4))
-                        (mj AnnClass $1:(fst $ unLoc $3)++(fstOf3 $ unLoc $4)) }
+                {% do { let {(wtok, (oc,semis,cc)) = fstOf3 $ unLoc $4}
+                      ; mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4)
+                        (AnnClassDecl (epTok $1) [] [] (fst $ unLoc $3) wtok oc cc semis) }}
 
 -- Default declarations (toplevel)
 --
@@ -1314,7 +1315,7 @@ ty_decl :: { LTyClDecl GhcPs }
                 --
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkTySynonym (comb2 $1 $4) $2 $4 [mj AnnType $1,mj AnnEqual $3] }
+                {% mkTySynonym (comb2 $1 $4) $2 $4 (epTok $1) (epTok $3) }
 
            -- type family declarations
         | 'type' 'family' type opt_tyfam_kind_sig opt_injective_info
@@ -1749,9 +1750,9 @@ decl_cls  : at_decl_cls                 { $1 }
                                       quotes (ppr $2)
                           ; amsA' (sLL $1 $> $ SigD noExtField $ ClassOpSig (AnnSig (epUniTok $3) Nothing (Just (epTok $1))) True [v] $4) }}
 
-decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
+decls_cls :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }  -- Reversed
           : decls_cls ';' decl_cls      {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unitOL $3))
                                             else case (snd $ unLoc $1) of
                                               SnocOL hs t -> do
@@ -1759,7 +1760,7 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
                                                  return (sLL $1 $> (fst $ unLoc $1
                                                                 , snocOL hs t' `appOL` unitOL $3)) }
           | decls_cls ';'               {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1770,24 +1771,24 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
           | {- empty -}                 { noLoc ([],nilOL) }
 
 decllist_cls
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", [EpToken ";"], EpToken "}")
                      , OrdList (LHsDecl GhcPs)
                      , EpLayout) }      -- Reversed
-        : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
+        : '{'         decls_cls '}'     { sLL $1 $> ((epTok $1, fst $ unLoc $2, epTok $3)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
         |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
-                                           in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
+                                           in L l ((NoEpTok, anns, NoEpTok), decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
 --
-where_cls :: { Located ([AddEpAnn]
+where_cls :: { Located ((EpToken "where", (EpToken "{", [EpToken ";"], EpToken "}"))
                        ,(OrdList (LHsDecl GhcPs))    -- Reversed
                        ,EpLayout) }
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_cls          { sLL $1 $> (mj AnnWhere $1:(fstOf3 $ unLoc $2)
+        : 'where' decllist_cls          { sLL $1 $> ((epTok $1,fstOf3 $ unLoc $2)
                                              ,sndOf3 $ unLoc $2,thdOf3 $ unLoc $2) }
-        | {- empty -}                   { noLoc ([],nilOL,EpNoLayout) }
+        | {- empty -}                   { noLoc ((noAnn, noAnn),nilOL,EpNoLayout) }
 
 -- Declarations in instance bodies
 --
@@ -2177,8 +2178,8 @@ sigtypes1 :: { OrdList (LHsSigType GhcPs) }
 -- Types
 
 unpackedness :: { Located UnpackednessPragma }
-        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getUNPACK_PRAGs $1) SrcUnpack) }
-        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
+        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getUNPACK_PRAGs $1) SrcUnpack) }
+        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
 
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
@@ -2304,8 +2305,8 @@ atype :: { LHsType GhcPs }
                                                ; return $ sL1a $1 (HsStarTy noExtField (isUnicode $1)) } }
 
         -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer
-        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnTilde $1] SrcLazy $2)) }
-        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnBang $1] SrcStrict $2)) }
+        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcLazy $2)) }
+        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcStrict $2)) }
 
         | '{' fielddecls '}'             {% do { decls <- amsA' (sLL $1 $> $ HsRecTy (AnnList (listAsAnchorM $2) (Just $ moc $1) (Just $ mcc $3) [] []) $2)
                                                ; checkRecordSyntax decls }}
@@ -2325,17 +2326,17 @@ atype :: { LHsType GhcPs }
         | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $3] []) }}
+                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
         | SIMPLEQUOTE gen_qcon {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
         | SIMPLEQUOTE sysdcon_nolist {% do { requireLTPuns PEP_QuoteDisambiguation $1 (reLoc $>)
                                            ; amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted (L (getLoc $2) $ nameRdrName (dataConName (unLoc $2)))) }}
         | SIMPLEQUOTE  '(' ktype ',' comma_types1 ')'
                              {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                    ; h <- addTrailingCommaA $3 (gl $4)
-                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $6] (h : $5)) }}
+                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $6) (h : $5)) }}
         | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (glR $1) (glR $2)) }
         | SIMPLEQUOTE  '[' comma_types0 ']'     {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy [mj AnnSimpleQuote $1,mos $2,mcs $4] IsPromoted $3) }}
+                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy (epTok $1, epTok $2, epTok $4) IsPromoted $3) }}
         | SIMPLEQUOTE var                       {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
 
         | quasiquote                  { mapLocA (HsSpliceTy noExtField) $1 }
@@ -2346,7 +2347,7 @@ atype :: { LHsType GhcPs }
         -- (One means a list type, zero means the list type constructor,
         -- so you have to quote those.)
         | '[' ktype ',' comma_types1 ']'  {% do { h <- addTrailingCommaA $2 (gl $3)
-                                                ; amsA' (sLL $1 $> $ HsExplicitListTy [mos $1,mcs $5] NotPromoted (h:$4)) }}
+                                                ; amsA' (sLL $1 $> $ HsExplicitListTy (NoEpTok,epTok $1,epTok $5) NotPromoted (h:$4)) }}
         | INTEGER              { sLLa $1 $> $ HsTyLit noExtField $ HsNumTy (getINTEGERs $1)
                                                            (il_value (getINTEGER $1)) }
         | CHAR                 { sLLa $1 $> $ HsTyLit noExtField $ HsCharTy (getCHARs $1)
@@ -2420,10 +2421,9 @@ tyvar_wc :: { Located (HsBndrVar GhcPs) }
         : tyvar                         { sL1 $1 (HsBndrVar noExtField $1) }
         | '_'                           { sL1 $1 (HsBndrWildCard noExtField) }
 
-fds :: { Located ([AddEpAnn],[LHsFunDep GhcPs]) }
-        : {- empty -}                   { noLoc ([],[]) }
-        | '|' fds1                      { (sLL $1 $> ([mj AnnVbar $1]
-                                                 ,reverse (unLoc $2))) }
+fds :: { Located (EpToken "|",[LHsFunDep GhcPs]) }
+        : {- empty -}                   { noLoc (NoEpTok,[]) }
+        | '|' fds1                      { (sLL $1 $> (epTok $1 ,reverse (unLoc $2))) }
 
 fds1 :: { Located [LHsFunDep GhcPs] }
         : fds1 ',' fd   {%
@@ -3138,26 +3138,26 @@ aexp2   :: { ECP }
         | splice_untyped { ECP $ mkHsSplicePV $1 }
         | splice_typed   { ecpFromExp $ fmap (uncurry HsTypedSplice) (reLoc $1) }
 
-        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
-        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
+        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
+        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
         -- See Note [%shift: aexp2 -> TH_TY_QUOTE]
         | TH_TY_QUOTE %shift    {% reportEmptyDoubleQuotes (getLoc $1) }
         | '[|' exp '|]'       {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3]
-                                                                                         else [mu AnnOpenEQ $1,mu AnnCloseQ $3]) (ExpBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (ExpBr (if (hasE $1) then (BracketHasE (epTok $1),   epUniTok $3)
+                                                                                                     else (BracketNoE (epUniTok $1), epUniTok $3)) $2)) }
         | '[||' exp '||]'     {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) $2) }
+                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then (BracketHasE (epTok $1),epTok $3) else (BracketNoE (epTok $1),epTok $3)) $2) }
         | '[t|' ktype '|]'    {% fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (TypBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (TypBr (epTok $1,epUniTok $3) $2)) }
         | '[p|' infixexp '|]' {% (checkPattern <=< runPV) (unECP $2) >>= \p ->
                                       fmap ecpFromExp $
-                                      amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (PatBr noExtField p)) }
+                                      amsA' (sLL $1 $> $ HsUntypedBracket noExtField (PatBr (epTok $1,epUniTok $3) p)) }
         | '[d|' cvtopbody '|]' {% fmap ecpFromExp $
-                                  amsA' (sLL $1 $> $ HsUntypedBracket (mo $1:mu AnnCloseQ $3:fst $2) (DecBrL noExtField (snd $2))) }
+                                  amsA' (sLL $1 $> $ HsUntypedBracket noExtField (DecBrL (epTok $1,epUniTok $3, fst $2) (snd $2))) }
         | quasiquote          { ECP $ mkHsSplicePV $1 }
 
         -- arrow notation extension
@@ -3197,10 +3197,9 @@ acmd    :: { LHsCmdTop GhcPs }
                                    runPV (checkCmdBlockArguments cmd) >>= \ _ ->
                                    return (sL1a cmd $ HsCmdTop noExtField cmd) }
 
-cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
-        :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
-                                                  ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+cvtopbody :: { ((EpToken "{", EpToken "}"),[LHsDecl GhcPs]) }
+        :  '{'            cvtopdecls0 '}'      { ((epTok $1 ,epTok $3),$2) }
+        |      vocurly    cvtopdecls0 close    { ((NoEpTok, NoEpTok),$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -4641,6 +4640,10 @@ epUniTok t@(L !l _) = EpUniTok (EpaSpan l) u
   where
     u = if isUnicode t then UnicodeSyntax else NormalSyntax
 
+-- |Construct an EpToken from the location of the token, provided the span is not zero width
+mzEpTok :: Located Token -> EpToken tok
+mzEpTok !l = if isZeroWidthSpan (gl l) then NoEpTok else (epTok l)
+
 epExplicitBraces :: Located Token -> Located Token -> EpLayout
 epExplicitBraces !t1 !t2 = EpExplicitBraces (epTok t1) (epTok t2)
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -10,7 +10,7 @@ module GHC.Parser.Annotation (
   -- * Core Exact Print Annotation types
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
-  getEpTokenSrcSpan, getEpTokenLocs,
+  getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
   TokDcolon,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
@@ -406,6 +406,10 @@ getEpTokenLocs ls = concatMap go ls
     go NoEpTok   = []
     go (EpTok l) = [l]
 
+getEpTokenLoc :: EpToken tok -> EpaLocation
+getEpTokenLoc NoEpTok   = noAnn
+getEpTokenLoc (EpTok l) = l
+
 type TokDcolon = EpUniToken "::" "∷"
 
 -- | Layout information for declarations.


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -71,7 +71,7 @@ module GHC.Parser.Lexer (
    xtest, xunset, xset,
    disableHaddock,
    lexTokenStream,
-   mkParensEpAnn,
+   mkParensEpToks,
    mkParensLocs,
    getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
    getEofPos,
@@ -3628,13 +3628,14 @@ warn_unknown_prag prags span buf len buf2 = do
 %************************************************************************
 -}
 
+-- TODO:AZ: we should have only mkParensEpToks. Delee mkParensEpAnn, mkParensLocs
 
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'AddEpAnn' values for the opening and closing bordering on the start
 -- and end of the span
-mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
-mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
-                    AddEpAnn AnnCloseP (EpaSpan (RealSrcSpan lc Strict.Nothing)))
+mkParensEpToks :: RealSrcSpan -> (EpToken "(", EpToken ")")
+mkParensEpToks ss = (EpTok (EpaSpan (RealSrcSpan lo Strict.Nothing)),
+                    EpTok (EpaSpan (RealSrcSpan lc Strict.Nothing)))
   where
     f = srcSpanFile ss
     sl = srcSpanStartLine ss
@@ -3644,6 +3645,7 @@ mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
     lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
     lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
 
+
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'EpaLocation' values for the opening and closing bordering on the start
 -- and end of the span


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -161,7 +161,7 @@ import GHC.Utils.Error
 import GHC.Utils.Misc
 import GHC.Utils.Monad (unlessM)
 import Data.Either
-import Data.List        ( findIndex, partition )
+import Data.List        ( findIndex )
 import Data.Foldable
 import qualified Data.Semigroup as Semi
 import GHC.Unit.Module.Warnings
@@ -204,14 +204,14 @@ mkClassDecl :: SrcSpan
             -> Located (a,[LHsFunDep GhcPs])
             -> OrdList (LHsDecl GhcPs)
             -> EpLayout
-            -> [AddEpAnn]
+            -> AnnClassDecl
             -> P (LTyClDecl GhcPs)
 
 mkClassDecl loc' (L _ (mcxt, tycl_hdr)) fds where_cls layout annsIn
   = do { (binds, sigs, ats, at_defs, _, docs) <- cvBindsAndSigs where_cls
-       ; (cls, tparams, fixity, ann, cs) <- checkTyClHdr True tycl_hdr
+       ; (cls, tparams, fixity, ops, cps, cs) <- checkTyClHdr True tycl_hdr
        ; tyvars <- checkTyVars (text "class") whereDots cls tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn { acd_openp = ops, acd_closep = cps}
        ; let loc = EpAnn (spanAsAnchor loc') noAnn cs
        ; return (L loc (ClassDecl { tcdCExt = (anns', layout, NoAnnSortKey)
                                   , tcdCtxt = mcxt
@@ -235,9 +235,10 @@ mkTyData :: SrcSpan
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; !cs' <- getCommentsFor loc'
@@ -247,6 +248,15 @@ mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
+-- TODO:AZ:temporary
+openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
+openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
+openParen2AddEpAnn NoEpTok = []
+
+closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
+closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
+closeParen2AddEpAnn NoEpTok = []
+
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
@@ -265,14 +275,15 @@ mkDataDefn cType mcxt ksig data_cons maybe_deriv
 mkTySynonym :: SrcSpan
             -> LHsType GhcPs  -- LHS
             -> LHsType GhcPs  -- RHS
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "="
             -> P (LTyClDecl GhcPs)
-mkTySynonym loc lhs rhs annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+mkTySynonym loc lhs rhs antype aneq
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (text "type") equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns = AnnSynDecl ops cps antype aneq
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; return (L loc' (SynDecl { tcdSExt = anns'
+       ; return (L loc' (SynDecl { tcdSExt = anns
                                  , tcdLName = tc, tcdTyVars = tyvars
                                  , tcdFixity = fixity
                                  , tcdRhs = rhs })) }
@@ -308,10 +319,12 @@ mkTyFamInstEqn :: SrcSpan
                -> [AddEpAnn]
                -> P (LTyFamInstEqn GhcPs)
 mkTyFamInstEqn loc bndrs lhs rhs anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns `mappend` ann
+                        { feqn_ext    = anns'
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -330,32 +343,20 @@ mkDataFamInst :: SrcSpan
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = ann Semi.<> anns
+                  (FamEqn { feqn_ext    = anns'
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
                           , feqn_fixity = fixity
                           , feqn_rhs    = defn })))) }
 
--- mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
---               ksig data_cons (L _ maybe_deriv) anns
---   = do { (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr
---        ; cs <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan
---        ; let anns' = addAnns (EpAnn (spanAsAnchor loc) ann cs) anns emptyComments
---        ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv
---        ; return (L (noAnnSrcSpan loc) (DataFamInstD anns' (DataFamInstDecl
---                   (FamEqn { feqn_ext    = anns'
---                           , feqn_tycon  = tc
---                           , feqn_bndrs  = bndrs
---                           , feqn_pats   = tparams
---                           , feqn_fixity = fixity
---                           , feqn_rhs    = defn })))) }
-
 
 
 mkTyFamInst :: SrcSpan
@@ -375,11 +376,13 @@ mkFamDecl :: SrcSpan
           -> [AddEpAnn]
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (FamDecl noExtField (FamilyDecl
-                                           { fdExt       = annsIn Semi.<> ann
+                                           { fdExt       = anns'
                                            , fdTopLevel  = topLevel
                                            , fdInfo      = info, fdLName = tc
                                            , fdTyVars    = tyvars
@@ -738,8 +741,7 @@ mkPatSynMatchGroup (L loc patsyn_name) (L ld decls) =
         do { unless (name == patsyn_name) $
                wrongNameBindingErr (locA loc) decl
            -- conAnn should only be AnnOpenP, AnnCloseP, so the rest should be empty
-           ; let (ann_fun, rest) = mk_ann_funrhs []
-           ; unless (null rest) $ return $ panic "mkPatSynMatchGroup: unexpected anns"
+           ; let ann_fun = mk_ann_funrhs [] []
            ; match <- case details of
                PrefixCon _ pats -> return $ Match { m_ext = noExtField
                                                   , m_ctxt = ctxt, m_pats = L l pats
@@ -1063,8 +1065,8 @@ checkTyClHdr :: Bool               -- True  <=> class header
              -> P (LocatedN RdrName,     -- the head symbol (type or class name)
                    [LHsTypeArg GhcPs],   -- parameters of head symbol
                    LexicalFixity,        -- the declaration is in infix format
-                   [AddEpAnn],           -- API Annotation for HsParTy
-                                         -- when stripping parens
+                   [EpToken "("],        -- API Annotation for HsParTy
+                   [EpToken ")"],        -- when stripping parens
                    EpAnnComments)        -- Accumulated comments from re-arranging
 -- Well-formedness check and decomposition of type and class heads.
 -- Decomposes   T ty1 .. tyn   into    (T, [ty1, ..., tyn])
@@ -1081,22 +1083,22 @@ checkTyClHdr is_cls ty
            ; let name = mkOccNameFS tcClsName (starSym isUni)
            ; let a' = newAnns ll l an
            ; return (L a' (Unqual name), acc, fix
-                    , (reverse ops') ++ cps', cs) }
+                    , (reverse ops'), cps', cs) }
 
     go cs l (HsTyVar _ _ ltc@(L _ tc)) acc ops cps fix
-      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops), cps, cs Semi.<> comments l)
     go cs l (HsOpTy _ _ t1 ltc@(L _ tc) t2) acc ops cps _fix
-      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
     go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
       where
-        (o,c) = mkParensEpAnn (realSrcSpan (locA l))
+        (o,c) = mkParensEpToks (realSrcSpan (locA l))
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
       = return (L (l2l l) (nameRdrName tup_name)
-               , map (HsValArg noExtField) ts, fix, (reverse ops)++cps, cs Semi.<> comments l)
+               , map (HsValArg noExtField) ts, fix, (reverse ops), cps, cs Semi.<> comments l)
       where
         arity = length ts
         tup_name | is_cls    = cTupleTyConName arity
@@ -1170,15 +1172,16 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
   -- With NoListTuplePuns, contexts are parsed as data constructors, which causes failure
   -- downstream.
   -- This converts them just like when they are parsed as types in the punned case.
-  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy anns ts))
+  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy (q,o,c) ts))
     = punsAllowed >>= \case
       True -> unprocessed
       False -> do
         let
-          (op, cp) = case anns of
-            [o, c] -> ([o], [c])
-            [q, _, c] -> ([q], [c])
-            _ -> ([], [])
+          ol = AddEpAnn AnnOpenP (getEpTokenLoc o)
+          cl = AddEpAnn AnnCloseP (getEpTokenLoc c)
+          (op, cp) = case q of
+            EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
+            _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
   check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
                                   -- to be sure HsParTy doesn't get into the way
@@ -1331,12 +1334,12 @@ checkAPat loc e0 = do
      addError $ mkPlainErrorMsgEnvelope (getLocA op) PsErrAtInPatPos
      return (WildPat noExtField)
 
-   PatBuilderOpApp l (L cl c) r anns
+   PatBuilderOpApp l (L cl c) r (_os,_cs)
      | isRdrDataCon c || isRdrTc c -> do
          l <- checkLPat l
          r <- checkLPat r
          return $ ConPat
-           { pat_con_ext = mk_ann_conpat anns
+           { pat_con_ext = noAnn
            , pat_con = L cl c
            , pat_args = InfixCon l r
            }
@@ -1389,9 +1392,8 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
   = do  { mb_fun <- isFunLhs lhs
         ; case mb_fun of
-            Just (fun, is_infix, pats, ann) -> do
-              let (ann_fun, ann_rest) = mk_ann_funrhs ann
-              unless (null ann_rest) $ panic "checkValDef: unexpected anns"
+            Just (fun, is_infix, pats, ops, cps) -> do
+              let ann_fun = mk_ann_funrhs ops cps
               let l = listLocation pats
               checkFunBind loc ann_fun
                            fun is_infix (L l pats) grhss
@@ -1404,29 +1406,8 @@ checkValDef loc lhs (mult_ann, Nothing) ghrss
   = do lhs' <- checkPattern lhs
        checkPatBind loc lhs' ghrss mult_ann
 
-mk_ann_funrhs :: [AddEpAnn] -> (AnnFunRhs, [AddEpAnn])
-mk_ann_funrhs ann = (AnnFunRhs strict (map to_tok opens) (map to_tok closes), rest)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenP) ann
-    (closes, ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseP) ra0
-    (bangs, rest) = partition (\(AddEpAnn kw _) -> kw == AnnBang) ra1
-    strict = case bangs of
-               (AddEpAnn _ s:_) -> EpTok s
-               _ -> NoEpTok
-    to_tok (AddEpAnn _ s) = EpTok s
-
-mk_ann_conpat :: [AddEpAnn] -> (Maybe (EpToken "{"), Maybe (EpToken "}"))
-mk_ann_conpat ann = (open, close)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenC) ann
-    (closes, _ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseC) ra0
-    open = case opens of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    close = case closes of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    to_tok (AddEpAnn _ s) = EpTok s
+mk_ann_funrhs :: [EpToken "("] -> [EpToken ")"] -> AnnFunRhs
+mk_ann_funrhs ops cps = AnnFunRhs NoEpTok ops cps
 
 checkFunBind :: SrcSpan
              -> AnnFunRhs
@@ -1468,10 +1449,10 @@ checkPatBind :: SrcSpan
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat an (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m ans v)]))
+                [L (noAnnSrcSpan loc) (m an v)]))
   where
     m a v = Match { m_ext = noExtField
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1517,7 +1498,7 @@ checkDoAndIfThenElse err guardExpr semiThen thenExpr semiElse elseExpr
 
 isFunLhs :: LocatedA (PatBuilder GhcPs)
       -> P (Maybe (LocatedN RdrName, LexicalFixity,
-                   [LocatedA (ArgPatBuilder GhcPs)],[AddEpAnn]))
+                   [LocatedA (ArgPatBuilder GhcPs)],[EpToken "("],[EpToken ")"]))
 -- A variable binding is parsed as a FunBind.
 -- Just (fun, is_infix, arg_pats) if e is a function LHS
 isFunLhs e = go e [] [] []
@@ -1527,7 +1508,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderVar (L loc f))) es ops cps
        | not (isRdrDataCon f)        = do
            let (_l, loc') = transferCommentsOnlyA l loc
-           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+           return (Just (L loc' f, Prefix, es, (reverse ops), cps))
    go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
      let (_l, lf') = transferCommentsOnlyA l lf
      go (L lf' f) (mk e:es) ops cps
@@ -1537,21 +1518,21 @@ isFunLhs e = go e [] [] []
       -- of funlhs.
      where
        (_l, le') = transferCommentsOnlyA l le
-       (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
+       (o,c) = mkParensEpToks (realSrcSpan $ locA l)
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r (os,cs))) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
-           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (os ++ reverse ops), (cs ++ cps))) }
       | otherwise                     -- Infix data con; keep going
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
            ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
-          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
-            = Just (op', Infix, j : op_app : es', anns')
+          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', ops', cps')
+            = Just (op', Infix, j : op_app : es', ops', cps')
             where
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
-                                    (L loc' op) r (reverse ops ++ cps))
+                                    (L loc' op) r (reverse ops, cps))
           reassociate _other = Nothing
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
@@ -1570,13 +1551,13 @@ instance Outputable (ArgPatBuilder GhcPs) where
   ppr (ArgPatBuilderVisPat p) = ppr p
   ppr (ArgPatBuilderArgPat p) = ppr p
 
-mkBangTy :: [AddEpAnn] -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
-mkBangTy anns strictness =
-  HsBangTy (anns, NoSourceText) (HsBang NoSrcUnpack strictness)
+mkBangTy :: EpaLocation -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
+mkBangTy tok_loc strictness =
+  HsBangTy ((noAnn, noAnn, tok_loc), NoSourceText) (HsBang NoSrcUnpack strictness)
 
 -- | Result of parsing @{-\# UNPACK \#-}@ or @{-\# NOUNPACK \#-}@.
 data UnpackednessPragma =
-  UnpackednessPragma [AddEpAnn] SourceText SrcUnpackedness
+  UnpackednessPragma (EpaLocation, EpaLocation) SourceText SrcUnpackedness
 
 -- | Annotate a type with either an @{-\# UNPACK \#-}@ or a @{-\# NOUNPACK \#-}@ pragma.
 addUnpackednessP :: MonadP m => Located UnpackednessPragma -> LHsType GhcPs -> m (LHsType GhcPs)
@@ -1589,11 +1570,11 @@ addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do
     -- such as ~T or !T, then add the pragma to the existing HsBangTy.
     --
     -- Otherwise, wrap the type in a new HsBangTy constructor.
-    addUnpackedness an (L _ (HsBangTy (anns, NoSourceText) bang t))
+    addUnpackedness (o,c) (L _ (HsBangTy ((_,_,tl), NoSourceText) bang t))
       | HsBang NoSrcUnpack strictness <- bang
-      = HsBangTy (an Semi.<> anns, prag) (HsBang unpk strictness) t
-    addUnpackedness an t
-      = HsBangTy (an, prag) (HsBang unpk NoSrcStrict) t
+      = HsBangTy ((o,c,tl), prag) (HsBang unpk strictness) t
+    addUnpackedness (o,c) t
+      = HsBangTy ((o,c,noAnn), prag) (HsBang unpk NoSrcStrict) t
 
 ---------------------------------------------------------------------------
 -- | Check for monad comprehensions
@@ -2051,7 +2032,7 @@ instance DisambECP (PatBuilder GhcPs) where
   superInfixOp m = m
   mkHsOpAppPV l p1 op p2 = do
     !cs <- getCommentsFor l
-    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 []
+    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 ([],[])
 
   mkHsLamPV l lam_variant _ _     = addFatalError $ mkPlainErrorMsgEnvelope l (PsErrLambdaInPat lam_variant)
 
@@ -3658,7 +3639,7 @@ mkTupleSyntaxTy parOpen args parClose =
       HsExplicitTupleTy annsKeyword args
 
     annParen = AnnParen AnnParens parOpen parClose
-    annsKeyword = [AddEpAnn AnnOpenP parOpen, AddEpAnn AnnCloseP parClose]
+    annsKeyword = (NoEpTok, EpTok parOpen, EpTok parClose)
 
 -- | Decide whether to parse tuple con syntax @(,)@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
@@ -3690,7 +3671,7 @@ mkListSyntaxTy0 brkOpen brkClose span =
       HsExplicitListTy annsKeyword NotPromoted []
 
     rdrNameAnn = NameAnnOnly NameSquare brkOpen brkClose []
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     fullLoc = EpaSpan span
 
 -- | Decide whether to parse list type syntax @[Int]@ in a type as a
@@ -3709,5 +3690,5 @@ mkListSyntaxTy1 brkOpen t brkClose =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted [t]
 
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     annParen = AnnParen AnnParensSquare brkOpen brkClose


=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1460,7 +1460,7 @@ instance Monoid ColumnBound where
 
 mkLHsDocTy :: LHsType GhcPs -> Maybe (Located HsDocString) -> LHsType GhcPs
 mkLHsDocTy t Nothing = t
-mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noAnn t $ lexLHsDocString doc)
+mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noExtField t $ lexLHsDocString doc)
 
 getForAllTeleLoc :: HsForAllTelescope GhcPs -> SrcSpan
 getForAllTeleLoc tele =


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -57,7 +57,7 @@ data PatBuilder p
   | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p))
   | PatBuilderAppType (LocatedA (PatBuilder p)) (EpToken "@") (HsTyPat GhcPs)
   | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName)
-                    (LocatedA (PatBuilder p)) [AddEpAnn]
+                    (LocatedA (PatBuilder p)) ([EpToken "("], [EpToken ")"])
   | PatBuilderVar (LocatedN RdrName)
   | PatBuilderOverLit (HsOverLit GhcPs)
 


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -181,7 +181,7 @@ rnUntypedBracket e br_body
        }
 
 rn_utbracket :: ThStage -> HsQuote GhcPs -> RnM (HsQuote GhcRn, FreeVars)
-rn_utbracket outer_stage br@(VarBr x flg rdr_name)
+rn_utbracket outer_stage br@(VarBr _ flg rdr_name)
   = do { name <- lookupOccRn (unLoc rdr_name)
        ; check_namespace flg name
        ; this_mod <- getModule
@@ -204,18 +204,18 @@ rn_utbracket outer_stage br@(VarBr x flg rdr_name)
                                       TcRnTHError $ THNameError $ QuotedNameWrongStage br }
                         }
                     }
-       ; return (VarBr x flg (noLocA name), unitFV name) }
+       ; return (VarBr noExtField flg (noLocA name), unitFV name) }
 
-rn_utbracket _ (ExpBr x e) = do { (e', fvs) <- rnLExpr e
-                                ; return (ExpBr x e', fvs) }
+rn_utbracket _ (ExpBr _ e) = do { (e', fvs) <- rnLExpr e
+                                ; return (ExpBr noExtField e', fvs) }
 
-rn_utbracket _ (PatBr x p)
-  = rnPat ThPatQuote p $ \ p' -> return (PatBr x p', emptyFVs)
+rn_utbracket _ (PatBr _ p)
+  = rnPat ThPatQuote p $ \ p' -> return (PatBr noExtField p', emptyFVs)
 
-rn_utbracket _ (TypBr x t) = do { (t', fvs) <- rnLHsType TypBrCtx t
-                                ; return (TypBr x t', fvs) }
+rn_utbracket _ (TypBr _ t) = do { (t', fvs) <- rnLHsType TypBrCtx t
+                                ; return (TypBr noExtField t', fvs) }
 
-rn_utbracket _ (DecBrL x decls)
+rn_utbracket _ (DecBrL _ decls)
   = do { group <- groupDecls decls
        ; gbl_env  <- getGblEnv
        ; let new_gbl_env = gbl_env { tcg_dus = emptyDUs }
@@ -227,7 +227,7 @@ rn_utbracket _ (DecBrL x decls)
               -- Discard the tcg_env; it contains only extra info about fixity
         ; traceRn "rn_utbracket dec" (ppr (tcg_dus tcg_env) $$
                    ppr (duUses (tcg_dus tcg_env)))
-        ; return (DecBrG x group', duUses (tcg_dus tcg_env)) }
+        ; return (DecBrG noExtField group', duUses (tcg_dus tcg_env)) }
   where
     groupDecls :: [LHsDecl GhcPs] -> RnM (HsGroup GhcPs)
     groupDecls decls


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1655,7 +1655,7 @@ gen_Lift_binds loc (DerivInstTys{ dit_rep_tc = tycon
     liftTyped_bind = mkFunBindEC 1 loc liftTyped_RDR (nlHsApp unsafeCodeCoerce_Expr . nlHsApp pure_Expr)
                                  (map (pats_etc mk_typed_bracket mk_tsplice liftTypedName) data_cons)
 
-    mk_untyped_bracket = HsUntypedBracket noAnn . ExpBr noExtField
+    mk_untyped_bracket = HsUntypedBracket noExtField . ExpBr noAnn
     mk_typed_bracket = HsTypedBracket noAnn
 
     mk_tsplice = HsTypedSplice noAnn


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -319,7 +319,7 @@ cvtDec (ClassD ctxt cl tvs fds decs)
                     , tcdFDs = fds', tcdSigs = Hs.mkClassOpSigs sigs'
                     , tcdMeths = binds'
                     , tcdATs = fams', tcdATDefs = at_defs', tcdDocs = [] }
-                              -- no docs in TH ^^
+                                                     -- no docs in TH ^^
         }
 
 cvtDec (InstanceD o ctxt ty decs)


=====================================
libraries/base/src/Control/Category.hs
=====================================
@@ -11,9 +11,26 @@
 --
 
 module Control.Category
-  ( Category(..)
+  ( -- * Class
+    Category(..)
+
+    -- * Combinators
   , (<<<)
   , (>>>)
+
+  -- $namingConflicts
   ) where
 
 import GHC.Internal.Control.Category
+
+-- $namingConflicts
+--
+-- == A note on naming conflicts
+--
+-- The methods from 'Category' conflict with 'Prelude.id' and 'Prelude..' from the
+-- prelude; you will likely want to either import this module qualified, or hide the
+-- prelude functions:
+--
+-- @
+-- import "Prelude" hiding (id, (.))
+-- @


=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Category.hs
=====================================
@@ -28,17 +28,81 @@ import GHC.Internal.Data.Coerce (coerce)
 infixr 9 .
 infixr 1 >>>, <<<
 
--- | A class for categories. Instances should satisfy the laws
+-- | A class for categories.
 --
--- [Right identity] @f '.' 'id'  =  f@
--- [Left identity]  @'id' '.' f  =  f@
--- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+-- In mathematics, a /category/ is defined as a collection of /objects/ and a collection
+-- of /morphisms/ between objects, together with an /identity morphism/ 'id' for every
+-- object and an operation '(.)' that /composes/ compatible morphisms.
+--
+-- This class is defined in an analogous way. The collection of morphisms is represented
+-- by a type parameter @cat@, which has kind @k -> k -> 'Data.Kind.Type'@ for some kind variable @k@
+-- that represents the collection of objects; most of the time the choice of @k@ will be
+-- 'Data.Kind.Type'.
+--
+-- ==== __Examples__
+--
+-- As the method names suggest, there's a category of functions:
+--
+-- @
+-- instance Category '(->)' where
+--   id = \\x -> x
+--   f . g = \\x -> f (g x)
+-- @
+--
+-- Isomorphisms form a category as well:
+--
+-- @
+-- data Iso a b = Iso (a -> b) (b -> a)
+--
+-- instance Category Iso where
+--   id = Iso id id
+--   Iso f1 g1 . Iso f2 g2 = Iso (f1 . f2) (g2 . g1)
+-- @
+--
+-- Natural transformations are another important example:
+--
+-- @
+-- newtype f ~> g = NatTransform (forall x. f x -> g x)
+--
+-- instance Category (~>) where
+--   id = NatTransform id
+--   NatTransform f . NatTransform g = NatTransform (f . g)
+-- @
+--
+-- Using the `TypeData` language extension, we can also make a category where `k` isn't
+-- `Type`, but a custom kind `Door` instead:
+--
+-- @
+-- type data Door = DoorOpen | DoorClosed
+--
+-- data Action (before :: Door) (after :: Door) where
+--   DoNothing :: Action door door
+--   OpenDoor :: Action start DoorClosed -> Action start DoorOpen
+--   CloseDoor :: Action start DoorOpen -> Action start DoorClosed
+--
+-- instance Category Action where
+--   id = DoNothing
+--
+--   DoNothing . action = action
+--   OpenDoor rest . action = OpenDoor (rest . action)
+--   CloseDoor rest . action = CloseDoor (rest . action)
+-- @
 --
 class Category cat where
-    -- | the identity morphism
+    -- | The identity morphism. Implementations should satisfy two laws:
+    --
+    -- [Right identity] @f '.' 'id'  =  f@
+    -- [Left identity]  @'id' '.' f  =  f@
+    --
+    -- These essentially state that 'id' should "do nothing".
     id :: cat a a
 
-    -- | morphism composition
+    -- | Morphism composition. Implementations should satisfy the law:
+    --
+    -- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+    --
+    -- This means that the way morphisms are grouped is irrelevant, so it is unambiguous
+    -- to write a composition of morphisms as @f '.' g '.' h@, without parentheses.
     (.) :: cat b c -> cat a b -> cat a c
 
 {-# RULES
@@ -70,11 +134,13 @@ instance Category Coercion where
   id = Coercion
   (.) Coercion = coerce
 
--- | Right-to-left composition
+-- | Right-to-left composition. This is a synonym for '(.)', but it can be useful to make
+-- the order of composition more apparent.
 (<<<) :: Category cat => cat b c -> cat a b -> cat a c
 (<<<) = (.)
 
--- | Left-to-right composition
+-- | Left-to-right composition. This is useful if you want to write a morphism as a
+-- pipeline going from left to right.
 (>>>) :: Category cat => cat a b -> cat b c -> cat a c
 f >>> g = g . f
 {-# INLINE (>>>) #-} -- see Note [INLINE on >>>]


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -48,8 +48,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:5:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:5:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:5:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:5:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -170,7 +179,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T17544.hs:6:14-16 })
@@ -217,8 +226,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:9:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:9:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -384,8 +402,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:13:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:13:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:13:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:13:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -554,8 +581,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:17:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:17:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:17:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:17:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -788,10 +824,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:22:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:22:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:22:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:22:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:22:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:22:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:22:18 }))
+        (EpTok (EpaSpan { T17544.hs:22:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:22:18 }))
         (EpTok (EpaSpan { T17544.hs:22:30 })))
@@ -1129,10 +1172,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:28:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:28:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:28:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:28:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:28:18 }))
+        (EpTok (EpaSpan { T17544.hs:28:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:28:18 }))
         (EpTok (EpaSpan { T17544.hs:28:30 })))
@@ -1470,10 +1520,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:34:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:34:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:34:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:34:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:34:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:34:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:34:18 }))
+        (EpTok (EpaSpan { T17544.hs:34:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:34:18 }))
         (EpTok (EpaSpan { T17544.hs:34:30 })))
@@ -1811,10 +1868,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:40:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:40:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:40:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:40:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:40:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:40:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:40:18 }))
+        (EpTok (EpaSpan { T17544.hs:40:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:40:18 }))
         (EpTok (EpaSpan { T17544.hs:40:30 })))
@@ -2152,10 +2216,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:46:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:46:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:46:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:46:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:46:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:46:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:46:18 }))
+        (EpTok (EpaSpan { T17544.hs:46:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:46:18 }))
         (EpTok (EpaSpan { T17544.hs:46:30 })))
@@ -2493,10 +2564,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:52:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:52:13-17 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:52:19 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:52:32 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:52:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:52:13-17 }))
+        (EpTok (EpaSpan { T17544.hs:52:19 }))
+        (EpTok (EpaSpan { T17544.hs:52:32 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:52:19 }))
         (EpTok (EpaSpan { T17544.hs:52:32 })))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -281,8 +281,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544_kw.hs:21:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:23:3-7 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544_kw.hs:21:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:23:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (5))
        (NoAnnSortKey))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -458,7 +458,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:15:3-5 })
@@ -503,7 +503,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:17:3-6 })
@@ -616,7 +616,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:21:3-5 })
@@ -661,7 +661,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:25:3-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -501,9 +501,13 @@
                 (EpaComments
                  []))
                (HsExplicitListTy
-                [(AddEpAnn AnnSimpleQuote (EpaSpan { DumpParsedAst.hs:12:10 }))
-                ,(AddEpAnn AnnOpenS (EpaSpan { DumpParsedAst.hs:12:11 }))
-                ,(AddEpAnn AnnCloseS (EpaSpan { DumpParsedAst.hs:12:12 }))]
+                ((,,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:11 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:12 })))
                 (IsPromoted)
                 [])))]
             (Prefix)


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -1302,8 +1302,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { DumpSemis.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpSemis.hs:28:40-44 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:40-44 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -240,8 +240,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:15:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:15:6-8 })
@@ -452,8 +457,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:16:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:16:13 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:13 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:16:6-9 })
@@ -664,8 +674,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:19:10 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:10 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:19:6-8 })
@@ -1069,8 +1084,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:26:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:26:11 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:11 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:26:6-9 })
@@ -1092,9 +1112,13 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:26:13 }))
-        ,(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:26:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:26:29 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:13 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:29 })))
         (IsPromoted)
         [(L
           (EpAnn
@@ -1155,8 +1179,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:27:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:27:6-10 })
@@ -1178,8 +1207,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:27:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:27:45 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:45 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -1290,8 +1323,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:28:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:28:14 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:14 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:28:6-10 })
@@ -1340,9 +1378,13 @@
         (EpaComments
          []))
        (HsExplicitTupleTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:28:16 }))
-        ,(AddEpAnn AnnOpenP (EpaSpan { KindSigs.hs:28:17 }))
-        ,(AddEpAnn AnnCloseP (EpaSpan { KindSigs.hs:28:44 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:16 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:17 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:44 })))
         [(L
           (EpAnn
            (EpaSpan { KindSigs.hs:28:19-39 })
@@ -1363,8 +1405,12 @@
              (EpaComments
               []))
             (HsExplicitListTy
-             [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:28:19 }))
-             ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:28:29 }))]
+             ((,,)
+              (NoEpTok)
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:19 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:29 })))
              (NotPromoted)
              [(L
                (EpAnn
@@ -1465,8 +1511,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:31:19 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:19 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:31:6-17 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -262,10 +262,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:8:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:8:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:8:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:8:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:8:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:8:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:8:84 }))
+        (EpTok (EpaSpan { T20452.hs:8:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:8:84 }))
         (EpTok (EpaSpan { T20452.hs:8:85 })))
@@ -492,10 +499,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:9:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:9:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:9:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:9:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:9:84 }))
+        (EpTok (EpaSpan { T20452.hs:9:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:9:84 }))
         (EpTok (EpaSpan { T20452.hs:9:85 })))


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
=====================================
@@ -72,8 +72,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:5:6 })
@@ -101,8 +106,12 @@
              "-- comment inside A")
             { AnnotationNoListTuplePuns.hs:7:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -128,8 +137,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:12:6 })
@@ -157,8 +171,12 @@
              "-- comment inside B")
             { AnnotationNoListTuplePuns.hs:14:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -243,8 +261,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:6 })
@@ -266,8 +289,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -280,8 +307,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:6 })
@@ -303,8 +335,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 })))
         (NotPromoted)
         [(L
           (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -308,7 +308,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.hs:11:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.hs:11:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)
@@ -933,7 +942,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.ppr.hs:4:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.ppr.hs:4:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -837,21 +837,6 @@ markEpAnnLMS'' a l kw (Just str) = do
 
 -- -------------------------------------
 
-markEpAnnMS' :: (Monad m, Monoid w)
-  => [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m [AddEpAnn]
-markEpAnnMS' anns kw Nothing = mark anns kw
-markEpAnnMS' anns kw (Just str) = do
-  mapM go anns
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
--- -------------------------------------
-
 markEpAnnLMS' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
 markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
@@ -3286,51 +3271,53 @@ instance ExactPrint (HsExpr GhcPs) where
     return (ArithSeq (AnnArithSeq o' mc' dd' c') s seqInfo')
 
 
-  exact (HsTypedBracket an e) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[||")
-    an1 <- markEpAnnLMS'' an0 lidl AnnOpenE (Just "[e||")
+  exact (HsTypedBracket (o,c) e) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnLMS'' an1 lidl AnnClose (Just "||]")
-    return (HsTypedBracket an2 e')
+    c' <- markEpToken c
+    return (HsTypedBracket (o',c') e')
 
-  exact (HsUntypedBracket an (ExpBr a e)) = do
-    an0 <- markEpAnnL an  lidl AnnOpenEQ -- "[|"
-    an1 <- markEpAnnL an0 lidl AnnOpenE  -- "[e|" -- optional
+  exact (HsUntypedBracket a (ExpBr (o,c) e)) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpUniToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an2 (ExpBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (ExpBr (o',c') e'))
 
-  exact (HsUntypedBracket an (PatBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[p|")
+  exact (HsUntypedBracket a (PatBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (PatBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (PatBr (o',c') e'))
 
-  exact (HsUntypedBracket an (DecBrL a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[d|")
-    an1 <- markEpAnnL an0 lidl AnnOpenC
+  exact (HsUntypedBracket a (DecBrL (o,c, (oc,cc)) e)) = do
+    o' <- markEpToken o
+    oc' <- markEpToken oc
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseC
-    an3 <- markEpAnnL an2 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an3 (DecBrL a e'))
+    cc' <- markEpToken cc
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (DecBrL (o',c',(oc',cc')) e'))
 
-  exact (HsUntypedBracket an (TypBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[t|")
+  exact (HsUntypedBracket a (TypBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (TypBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (TypBr (o',c') e'))
 
-  exact (HsUntypedBracket an (VarBr a b e)) = do
+  exact (HsUntypedBracket a (VarBr an b e)) = do
     (an0, e') <- if b
       then do
-        an' <- markEpAnnL an lidl AnnSimpleQuote
+        an' <- printStringAtAA an "'"
         e' <- markAnnotated e
         return (an', e')
       else do
-        an' <- markEpAnnL an lidl AnnThTyQuote
+        an' <- printStringAtAA an "''"
         e' <- markAnnotated e
         return (an', e')
-    return (HsUntypedBracket an0 (VarBr a b e'))
+    return (HsUntypedBracket a (VarBr an0 b e'))
 
   exact (HsTypedSplice an s)   = do
     an0 <- markEpToken an
@@ -3768,24 +3755,24 @@ instance ExactPrint (TyClDecl GhcPs) where
     decl' <- markAnnotated decl
     return (FamDecl a decl')
 
-  exact (SynDecl { tcdSExt = an
+  exact (SynDecl { tcdSExt = AnnSynDecl ops cps t eq
                  , tcdLName = ltycon, tcdTyVars = tyvars, tcdFixity = fixity
                  , tcdRhs = rhs }) = do
     -- There may be arbitrary parens around parts of the constructor
     -- that are infix.  Turn these into comments so that they feed
     -- into the right place automatically
     -- TODO: no longer sorting on insert. What now?
-    an0 <- annotationsToComments an lidl [AnnOpenP,AnnCloseP]
-    an1 <- markEpAnnL an0 lidl AnnType
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
+    t' <- markEpToken t
 
     (_anx, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    an2 <- markEpAnnL an1 lidl AnnEqual
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (SynDecl { tcdSExt = an2
+    return (SynDecl { tcdSExt = AnnSynDecl [] [] t' eq'
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  -- TODO: add a workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/20452
   exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
     (_, an', ltycon', tyvars', _, defn') <-
@@ -3795,7 +3782,7 @@ instance ExactPrint (TyClDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ClassDecl {tcdCExt = (an, lo, sortKey),
+  exact (ClassDecl {tcdCExt = (AnnClassDecl c ops cps vb w oc cc semis, lo, sortKey),
                     tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars,
                     tcdFixity = fixity,
                     tcdFDs  = fds,
@@ -3805,10 +3792,10 @@ instance ExactPrint (TyClDecl GhcPs) where
       -- TODO: add a test that demonstrates tcdDocs
       | null sigs && null methods && null ats && null at_defs -- No "where" part
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnL an1 lidl AnnCloseC
-          return (ClassDecl {tcdCExt = (an2, lo, sortKey),
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          cc' <- markEpToken cc
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis, lo, sortKey),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3818,9 +3805,9 @@ instance ExactPrint (TyClDecl GhcPs) where
 
       | otherwise       -- Laid out
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL    an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lidl AnnSemi
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsSigTag, prepareListAnnotationA sigs),
                                 (ClsMethodTag, prepareListAnnotationA methods),
@@ -3828,13 +3815,13 @@ instance ExactPrint (TyClDecl GhcPs) where
                                 (ClsAtdTag, prepareListAnnotationA at_defs)
                              -- ++ prepareListAnnotation docs
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC
+          cc' <- markEpToken cc
           let
             sigs'    = undynamic ds
             methods' = undynamic ds
             ats'     = undynamic ds
             at_defs' = undynamic ds
-          return (ClassDecl {tcdCExt = (an3, lo, sortKey'),
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis', lo, sortKey'),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3843,17 +3830,18 @@ instance ExactPrint (TyClDecl GhcPs) where
                              tcdDocs = _docs})
       where
         top_matter = do
-          an' <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
-          an0 <- markEpAnnL an' lidl AnnClass
+          epTokensToComments AnnOpenP ops
+          epTokensToComments AnnCloseP cps
+          c' <- markEpToken c
           (_, lclas', tyvars',_,context') <-  exactVanillaDeclHead lclas tyvars fixity context
-          (an1, fds') <- if (null fds)
-            then return (an0, fds)
+          (vb', fds') <- if (null fds)
+            then return (vb, fds)
             else do
-              an1 <- markEpAnnL an0 lidl AnnVbar
+              vb' <- markEpToken vb
               fds' <- markAnnotated fds
-              return (an1, fds')
-          an2 <- markEpAnnL an1 lidl AnnWhere
-          return (an2, fds', lclas', tyvars',context')
+              return (vb', fds')
+          w' <- markEpToken w
+          return (c', w', vb', fds', lclas', tyvars',context')
 
 
 -- ---------------------------------------------------------------------
@@ -4202,37 +4190,36 @@ instance ExactPrint (HsType GhcPs) where
   exact (HsDocTy an ty doc) = do
     ty' <- markAnnotated ty
     return (HsDocTy an ty' doc)
-  exact (HsBangTy (an, mt) (HsBang up str) ty) = do
-    an0 <-
+  exact (HsBangTy ((o,c,tk), mt) (HsBang up str) ty) = do
+    (o',c') <-
       case mt of
-        NoSourceText -> return an
+        NoSourceText -> return (o,c)
         SourceText src -> do
           debugM $ "HsBangTy: src=" ++ showAst src
-          an0 <- markEpAnnMS' an AnnOpen  (Just $ unpackFS src)
-          an1 <- markEpAnnMS' an0 AnnClose (Just "#-}")
-          debugM $ "HsBangTy: done unpackedness"
-          return an1
-    an1 <-
+          o' <- printStringAtAA o (unpackFS src)
+          c' <- printStringAtAA c "#-}"
+          return (o',c')
+    tk' <-
       case str of
-        SrcLazy     -> mark an0 AnnTilde
-        SrcStrict   -> mark an0 AnnBang
-        NoSrcStrict -> return an0
+        SrcLazy     -> printStringAtAA tk "~"
+        SrcStrict   -> printStringAtAA tk "!"
+        NoSrcStrict -> return tk
     ty' <- markAnnotated ty
-    return (HsBangTy (an1, mt) (HsBang up str) ty')
-  exact (HsExplicitListTy an prom tys) = do
-    an0 <- if (isPromoted prom)
-             then mark an AnnSimpleQuote
-             else return an
-    an1 <- mark an0 AnnOpenS
+    return (HsBangTy ((o',c',tk'), mt) (HsBang up str) ty')
+  exact (HsExplicitListTy (sq,o,c) prom tys) = do
+    sq' <- if (isPromoted prom)
+             then markEpToken sq
+             else return sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseS
-    return (HsExplicitListTy an2 prom tys')
-  exact (HsExplicitTupleTy an tys) = do
-    an0 <- mark an AnnSimpleQuote
-    an1 <- mark an0 AnnOpenP
+    c' <- markEpToken c
+    return (HsExplicitListTy (sq',o',c') prom tys')
+  exact (HsExplicitTupleTy (sq, o, c) tys) = do
+    sq' <- markEpToken sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseP
-    return (HsExplicitTupleTy an2 tys')
+    c' <- markEpToken c
+    return (HsExplicitTupleTy (sq', o', c') tys')
   exact (HsTyLit a lit) = do
     case lit of
       (HsNumTy src v) -> printSourceText src (show v)


=====================================
utils/check-exact/Main.hs
=====================================
@@ -166,7 +166,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/T18052a.hs" Nothing
  -- "../../testsuite/tests/printer/T18247a.hs" Nothing
  -- "../../testsuite/tests/printer/Test10268.hs" Nothing
- "../../testsuite/tests/printer/Test10269.hs" Nothing
+ -- "../../testsuite/tests/printer/Test10269.hs" Nothing
  -- "../../testsuite/tests/printer/Test10276.hs" Nothing
  -- "../../testsuite/tests/printer/Test10278.hs" Nothing
  -- "../../testsuite/tests/printer/Test10312.hs" Nothing
@@ -209,6 +209,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
+ "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
  -- "../../testsuite/tests/printer/Test23465.hs" Nothing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2424235d74fc5ea634ee68f2381ef657071c6a0b...cecae38586355beeb2d88c326dfe4d645041b7af

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2424235d74fc5ea634ee68f2381ef657071c6a0b...cecae38586355beeb2d88c326dfe4d645041b7af
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:01:48 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 17 Oct 2024 05:01:48 -0400
Subject: [Git][ghc/ghc][wip/T23490-part2] 137 commits: ci: Run abi-test on
 test-abi label
Message-ID: <6710d27c6dd8d_25e7222b2d4879186@gitlab.mail>



Matthew Pickering pushed to branch wip/T23490-part2 at Glasgow Haskell Compiler / GHC


Commits:
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
1e8a8f7c by Matthew Craven at 2024-10-17T10:01:24+01:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
1654b581 by Matthew Craven at 2024-10-17T10:01:24+01:00
Remove reference to non-existent file in haddock.cabal

- - - - -
f462f7e1 by Matthew Craven at 2024-10-17T10:01:24+01:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
999f7c6a by Matthew Craven at 2024-10-17T10:01:24+01:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
42ad05c0 by Matthew Craven at 2024-10-17T10:01:24+01:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- cabal.project-reinstall
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Lint.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3b81447cb71a89ca5c547f1c7e854cd0516b024...42ad05c0ad423eb99fcfdd5269cf2bb3a57a4f4c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3b81447cb71a89ca5c547f1c7e854cd0516b024...42ad05c0ad423eb99fcfdd5269cf2bb3a57a4f4c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:14:14 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 17 Oct 2024 05:14:14 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] Temp workaround
Message-ID: <6710d56634adf_25e7222a86cc9081a@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
1fbb3a00 by Sjoerd Visscher at 2024-10-17T11:14:08+02:00
Temp workaround

- - - - -


1 changed file:

- compiler/GHC/Unit/Finder.hs


Changes:

=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -462,7 +462,7 @@ findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation"))
+         then return (InstalledFound OsPathModLocation{}) -- (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -495,7 +495,7 @@ findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation"))
+          then return (InstalledFound OsPathModLocation{}) -- (error "GHC.Prim ModLocation"))
           else
 
     let



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1fbb3a00063b75706effc83628699358f0f9b300

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:18:34 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 05:18:34 -0400
Subject: [Git][ghc/ghc][master] GHCi: fix improper location of ghci_history
 file
Message-ID: <6710d66a1ae01_25e7223401981013dc@gitlab.mail>



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


Commits:
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -


1 changed file:

- ghc/GHCi/UI.hs


Changes:

=====================================
ghc/GHCi/UI.hs
=====================================
@@ -641,30 +641,27 @@ ghciLogAction lastErrLocations old_log_action
             _ -> return ()
         _ -> return ()
 
--- | Takes a file name and prefixes it with the appropriate
--- GHC appdir.
--- Uses ~/.ghc (getAppUserDataDirectory) if it exists
--- If it doesn't, then it uses $XDG_DATA_HOME/ghc
--- Earlier we always used to use ~/.ghc, but we want
--- to gradually move to $XDG_DATA_HOME to respect the XDG specification
---
--- As a migration strategy, we will only create new directories in
--- the appropriate XDG location. However, we will use the old directory
--- if it already exists.
-getAppDataFile :: FilePath -> IO (Maybe FilePath)
-getAppDataFile file = do
-    let new_path = tryIO (getXdgDirectory XdgConfig "ghc") >>= \case
-          Left _ -> pure Nothing
-          Right dir -> flip catchIO (const $ return Nothing) $ do
-            createDirectoryIfMissing False dir
-            pure $ Just $ dir  file
-
-    e_old_path <- tryIO (getAppUserDataDirectory "ghc")
-    case e_old_path of
-      Right old_path -> doesDirectoryExist old_path >>= \case
-        True -> pure $ Just $ old_path  file
-        False -> new_path
-      Left _ -> new_path
+-- | Takes a file name and prefixes it with the appropriate GHC appdir.
+-- ~/.ghc (getAppUserDataDirectory) is used if it exists, or XDG directories
+-- are used to respect the XDG specification.
+-- As a migration strategy, currently we will only create new directories in
+-- the appropriate XDG location.
+getAppDataFile :: XdgDirectory -> FilePath -> IO (Maybe FilePath)
+getAppDataFile xdgDir file = do
+  xdgAppDir <-
+    tryIO (getXdgDirectory xdgDir "ghc") >>= \case
+      Left _ -> pure Nothing
+      Right dir -> flip catchIO (const $ pure Nothing) $ do
+        createDirectoryIfMissing False dir
+        pure $ Just dir
+  appDir <-
+    tryIO (getAppUserDataDirectory "ghc") >>= \case
+      Right dir ->
+        doesDirectoryExist dir >>= \case
+          True -> pure $ Just dir
+          False -> pure xdgAppDir
+      Left _ -> pure xdgAppDir
+  pure $ appDir >>= \dir -> Just $ dir  file
 
 runGHCi :: [(FilePath, Maybe UnitId, Maybe Phase)] -> Maybe [String] -> GHCi ()
 runGHCi paths maybe_exprs = do
@@ -672,13 +669,12 @@ runGHCi paths maybe_exprs = do
   let
    ignore_dot_ghci = gopt Opt_IgnoreDotGhci dflags
 
-   app_user_dir = liftIO $ getAppDataFile "ghci.conf"
+   appDataCfg = liftIO $ getAppDataFile XdgConfig "ghci.conf"
 
-   home_dir = do
-    either_dir <- liftIO $ tryIO (getEnv "HOME")
-    case either_dir of
-      Right home -> return (Just (home  ".ghci"))
-      _ -> return Nothing
+   homeCfg = do
+    liftIO $ tryIO (getEnv "HOME") >>= \case
+      Right home -> pure $ Just $ home  ".ghci"
+      _ -> pure Nothing
 
    canonicalizePath' :: FilePath -> IO (Maybe FilePath)
    canonicalizePath' fp = liftM Just (canonicalizePath fp)
@@ -712,7 +708,7 @@ runGHCi paths maybe_exprs = do
     then pure []
     else do
       userCfgs <- do
-        paths <- catMaybes <$> sequence [ app_user_dir, home_dir ]
+        paths <- catMaybes <$> sequence [ appDataCfg, homeCfg ]
         checkedPaths <- liftIO $ filterM checkFileAndDirPerms paths
         liftIO . fmap (nub . catMaybes) $ mapM canonicalizePath' checkedPaths
 
@@ -799,12 +795,12 @@ runGHCiInput f = do
     dflags <- getDynFlags
     let ghciHistory = gopt Opt_GhciHistory dflags
     let localGhciHistory = gopt Opt_LocalGhciHistory dflags
-    currentDirectory <- liftIO $ getCurrentDirectory
+    currentDirectory <- liftIO getCurrentDirectory
 
     histFile <- case (ghciHistory, localGhciHistory) of
-      (True, True) -> return (Just (currentDirectory  ".ghci_history"))
-      (True, _) -> liftIO $ getAppDataFile "ghci_history"
-      _ -> return Nothing
+      (True, True) -> pure $ Just $ currentDirectory  ".ghci_history"
+      (True, _) -> liftIO $ getAppDataFile XdgData "ghci_history"
+      _ -> pure Nothing
 
     runInputT
         (setComplete ghciCompleteWord $ defaultSettings {historyFile = histFile})



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f0a62db5dc79640433c61e83ea1427665304869

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:19:34 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 05:19:34 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove [AddEpAnn] commit 3
Message-ID: <6710d6a680fd6_25e722273cc4105091@gitlab.mail>



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


Commits:
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -


24 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,6 +31,8 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnClassDecl(..),
+  AnnSynDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -353,7 +355,7 @@ instance Outputable SpliceDecoration where
 
 type instance XFamDecl      (GhcPass _) = NoExtField
 
-type instance XSynDecl      GhcPs = [AddEpAnn]
+type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
@@ -368,7 +370,7 @@ data DataDeclRn = DataDeclRn
   deriving Data
 
 type instance XClassDecl    GhcPs =
-  ( [AddEpAnn]
+  ( AnnClassDecl
   , EpLayout              -- See Note [Class EpLayout]
   , AnnSortKey DeclTag )  -- TODO:AZ:tidy up AnnSortKey
 
@@ -380,6 +382,32 @@ type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnClassDecl
+  = AnnClassDecl {
+      acd_class  :: EpToken "class",
+      acd_openp  :: [EpToken "("],
+      acd_closep :: [EpToken ")"],
+      acd_vbar   :: EpToken "|",
+      acd_where  :: EpToken "where",
+      acd_openc  :: EpToken "{",
+      acd_closec :: EpToken "}",
+      acd_semis  :: [EpToken ";"]
+  } deriving Data
+
+instance NoAnn AnnClassDecl where
+  noAnn = AnnClassDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
+data AnnSynDecl
+  = AnnSynDecl {
+    asd_opens  :: [EpToken "("],
+    asd_closes :: [EpToken ")"],
+    asd_type   :: EpToken "type",
+    asd_equal  :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnSynDecl where
+  noAnn = AnnSynDecl noAnn noAnn noAnn noAnn
+
 ------------- Pretty printing FamilyDecls -----------
 
 pprFlavour :: FamilyInfo pass -> SDoc


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -67,10 +67,14 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annotationAnnList
               `extQ` annotationEpAnnImportDecl
               `extQ` annotationNoEpAnns
+              `extQ` annotationExprBracket
+              `extQ` annotationTypedBracket
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
               `extQ` annParen
+              `extQ` annClassDecl
+              `extQ` annSynDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -203,6 +207,23 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               parens $ text "AnnParen"
                         $$ vcat [ppr a, epaLocation o, epaLocation c]
 
+            annClassDecl :: AnnClassDecl -> SDoc
+            annClassDecl (AnnClassDecl c ops cps v w oc cc s) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnClassDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClassDecl"
+                        $$ vcat [showAstData' c, showAstData' ops, showAstData' cps,
+                                 showAstData' v, showAstData' w, showAstData' oc,
+                                 showAstData' cc, showAstData' s]
+
+            annSynDecl :: AnnSynDecl -> SDoc
+            annSynDecl (AnnSynDecl ops cps t e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnSynDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnSynDecl"
+                        $$ vcat [showAstData' ops, showAstData' cps,
+                                 showAstData' t, showAstData' e]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -210,6 +231,22 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "AddEpAnn" <+> ppr a <+> epaLocation s
 
+            annotationExprBracket :: BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|") -> SDoc
+            annotationExprBracket = annotationBracket
+
+            annotationTypedBracket :: BracketAnn (EpToken "[||") (EpToken "[e||") -> SDoc
+            annotationTypedBracket = annotationBracket
+
+            annotationBracket ::forall n h .(Data n, Data h, Typeable n, Typeable h)
+              => BracketAnn n h -> SDoc
+            annotationBracket a = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "BracketAnn"
+             NoBlankEpAnnotations ->
+              parens $ case a of
+                BracketNoE  t -> text "BracketNoE"  <+> showAstData' t
+                BracketHasE t -> text "BracketHasE" <+> showAstData' t
+
             epTokenOC :: EpToken "{" -> SDoc
             epTokenOC  = epToken'
 


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -181,15 +181,23 @@ data HsBracketTc = HsBracketTc
                                         -- pasted back in by the desugarer
   }
 
-type instance XTypedBracket GhcPs = [AddEpAnn]
+type instance XTypedBracket GhcPs = (BracketAnn (EpToken "[||") (EpToken "[e||"), EpToken "||]")
 type instance XTypedBracket GhcRn = NoExtField
 type instance XTypedBracket GhcTc = HsBracketTc
-type instance XUntypedBracket GhcPs = [AddEpAnn]
+type instance XUntypedBracket GhcPs = NoExtField
 type instance XUntypedBracket GhcRn = [PendingRnSplice] -- See Note [Pending Splices]
                                                         -- Output of the renamer is the *original* renamed expression,
                                                         -- plus _renamed_ splices to be type checked
 type instance XUntypedBracket GhcTc = HsBracketTc
 
+data BracketAnn noE hasE
+  = BracketNoE noE
+  | BracketHasE hasE
+  deriving Data
+
+instance (NoAnn n, NoAnn h) => NoAnn (BracketAnn n h) where
+  noAnn = BracketNoE noAnn
+
 -- ---------------------------------------------------------------------
 
 -- API Annotations types
@@ -2141,12 +2149,12 @@ ppr_splice herald mn e
     <> ppr e
 
 
-type instance XExpBr  GhcPs       = NoExtField
-type instance XPatBr  GhcPs       = NoExtField
-type instance XDecBrL GhcPs       = NoExtField
+type instance XExpBr  GhcPs       = (BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|"), EpUniToken "|]" "⟧")
+type instance XPatBr  GhcPs       = (EpToken "[p|", EpUniToken "|]" "⟧")
+type instance XDecBrL GhcPs       = (EpToken "[d|", EpUniToken "|]" "⟧", (EpToken "{", EpToken "}"))
 type instance XDecBrG GhcPs       = NoExtField
-type instance XTypBr  GhcPs       = NoExtField
-type instance XVarBr  GhcPs       = NoExtField
+type instance XTypBr  GhcPs       = (EpToken "[t|", EpUniToken "|]" "⟧")
+type instance XVarBr  GhcPs       = EpaLocation
 type instance XXQuote GhcPs       = DataConCantHappen
 
 type instance XExpBr  GhcRn       = NoExtField


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -475,18 +475,18 @@ type instance XSpliceTy        GhcPs = NoExtField
 type instance XSpliceTy        GhcRn = HsUntypedSpliceResult (LHsType GhcRn)
 type instance XSpliceTy        GhcTc = Kind
 
-type instance XDocTy           (GhcPass _) = [AddEpAnn]
-type instance XBangTy          (GhcPass _) = ([AddEpAnn], SourceText)
+type instance XDocTy           (GhcPass _) = NoExtField
+type instance XBangTy          (GhcPass _) = ((EpaLocation, EpaLocation, EpaLocation), SourceText)
 
 type instance XRecTy           GhcPs = AnnList
 type instance XRecTy           GhcRn = NoExtField
 type instance XRecTy           GhcTc = NoExtField
 
-type instance XExplicitListTy  GhcPs = [AddEpAnn]
+type instance XExplicitListTy  GhcPs = (EpToken "'", EpToken "[", EpToken "]")
 type instance XExplicitListTy  GhcRn = NoExtField
 type instance XExplicitListTy  GhcTc = Kind
 
-type instance XExplicitTupleTy GhcPs = [AddEpAnn]
+type instance XExplicitTupleTy GhcPs = (EpToken "'", EpToken "(", EpToken ")")
 type instance XExplicitTupleTy GhcRn = NoExtField
 type instance XExplicitTupleTy GhcTc = [Kind]
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1292,8 +1292,9 @@ topdecl :: { LHsDecl GhcPs }
 --
 cl_decl :: { LTyClDecl GhcPs }
         : 'class' tycl_hdr fds where_cls
-                {% (mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4))
-                        (mj AnnClass $1:(fst $ unLoc $3)++(fstOf3 $ unLoc $4)) }
+                {% do { let {(wtok, (oc,semis,cc)) = fstOf3 $ unLoc $4}
+                      ; mkClassDecl (comb4 $1 $2 $3 $4) $2 $3 (sndOf3 $ unLoc $4) (thdOf3 $ unLoc $4)
+                        (AnnClassDecl (epTok $1) [] [] (fst $ unLoc $3) wtok oc cc semis) }}
 
 -- Default declarations (toplevel)
 --
@@ -1314,7 +1315,7 @@ ty_decl :: { LTyClDecl GhcPs }
                 --
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkTySynonym (comb2 $1 $4) $2 $4 [mj AnnType $1,mj AnnEqual $3] }
+                {% mkTySynonym (comb2 $1 $4) $2 $4 (epTok $1) (epTok $3) }
 
            -- type family declarations
         | 'type' 'family' type opt_tyfam_kind_sig opt_injective_info
@@ -1749,9 +1750,9 @@ decl_cls  : at_decl_cls                 { $1 }
                                       quotes (ppr $2)
                           ; amsA' (sLL $1 $> $ SigD noExtField $ ClassOpSig (AnnSig (epUniTok $3) Nothing (Just (epTok $1))) True [v] $4) }}
 
-decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
+decls_cls :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }  -- Reversed
           : decls_cls ';' decl_cls      {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unitOL $3))
                                             else case (snd $ unLoc $1) of
                                               SnocOL hs t -> do
@@ -1759,7 +1760,7 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
                                                  return (sLL $1 $> (fst $ unLoc $1
                                                                 , snocOL hs t' `appOL` unitOL $3)) }
           | decls_cls ';'               {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ( (fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1770,24 +1771,24 @@ decls_cls :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }  -- Reversed
           | {- empty -}                 { noLoc ([],nilOL) }
 
 decllist_cls
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", [EpToken ";"], EpToken "}")
                      , OrdList (LHsDecl GhcPs)
                      , EpLayout) }      -- Reversed
-        : '{'         decls_cls '}'     { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2)
+        : '{'         decls_cls '}'     { sLL $1 $> ((epTok $1, fst $ unLoc $2, epTok $3)
                                              ,snd $ unLoc $2, epExplicitBraces $1 $3) }
         |     vocurly decls_cls close   { let { L l (anns, decls) = $2 }
-                                           in L l (anns, decls, EpVirtualBraces (getVOCURLY $1)) }
+                                           in L l ((NoEpTok, anns, NoEpTok), decls, EpVirtualBraces (getVOCURLY $1)) }
 
 -- Class body
 --
-where_cls :: { Located ([AddEpAnn]
+where_cls :: { Located ((EpToken "where", (EpToken "{", [EpToken ";"], EpToken "}"))
                        ,(OrdList (LHsDecl GhcPs))    -- Reversed
                        ,EpLayout) }
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_cls          { sLL $1 $> (mj AnnWhere $1:(fstOf3 $ unLoc $2)
+        : 'where' decllist_cls          { sLL $1 $> ((epTok $1,fstOf3 $ unLoc $2)
                                              ,sndOf3 $ unLoc $2,thdOf3 $ unLoc $2) }
-        | {- empty -}                   { noLoc ([],nilOL,EpNoLayout) }
+        | {- empty -}                   { noLoc ((noAnn, noAnn),nilOL,EpNoLayout) }
 
 -- Declarations in instance bodies
 --
@@ -2177,8 +2178,8 @@ sigtypes1 :: { OrdList (LHsSigType GhcPs) }
 -- Types
 
 unpackedness :: { Located UnpackednessPragma }
-        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getUNPACK_PRAGs $1) SrcUnpack) }
-        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma [mo $1, mc $2] (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
+        : '{-# UNPACK' '#-}'   { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getUNPACK_PRAGs $1) SrcUnpack) }
+        | '{-# NOUNPACK' '#-}' { sLL $1 $> (UnpackednessPragma (glR $1, glR $2) (getNOUNPACK_PRAGs $1) SrcNoUnpack) }
 
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
@@ -2304,8 +2305,8 @@ atype :: { LHsType GhcPs }
                                                ; return $ sL1a $1 (HsStarTy noExtField (isUnicode $1)) } }
 
         -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer
-        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnTilde $1] SrcLazy $2)) }
-        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy [mj AnnBang $1] SrcStrict $2)) }
+        | PREFIX_TILDE atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcLazy $2)) }
+        | PREFIX_BANG  atype             {% amsA' (sLL $1 $> (mkBangTy (glR $1) SrcStrict $2)) }
 
         | '{' fielddecls '}'             {% do { decls <- amsA' (sLL $1 $> $ HsRecTy (AnnList (listAsAnchorM $2) (Just $ moc $1) (Just $ mcc $3) [] []) $2)
                                                ; checkRecordSyntax decls }}
@@ -2325,17 +2326,17 @@ atype :: { LHsType GhcPs }
         | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $3] []) }}
+                                            ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
         | SIMPLEQUOTE gen_qcon {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
         | SIMPLEQUOTE sysdcon_nolist {% do { requireLTPuns PEP_QuoteDisambiguation $1 (reLoc $>)
                                            ; amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted (L (getLoc $2) $ nameRdrName (dataConName (unLoc $2)))) }}
         | SIMPLEQUOTE  '(' ktype ',' comma_types1 ')'
                              {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                    ; h <- addTrailingCommaA $3 (gl $4)
-                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy [mj AnnSimpleQuote $1,mop $2,mcp $6] (h : $5)) }}
+                                   ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $6) (h : $5)) }}
         | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (glR $1) (glR $2)) }
         | SIMPLEQUOTE  '[' comma_types0 ']'     {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
-                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy [mj AnnSimpleQuote $1,mos $2,mcs $4] IsPromoted $3) }}
+                                                      ; amsA' (sLL $1 $> $ HsExplicitListTy (epTok $1, epTok $2, epTok $4) IsPromoted $3) }}
         | SIMPLEQUOTE var                       {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
 
         | quasiquote                  { mapLocA (HsSpliceTy noExtField) $1 }
@@ -2346,7 +2347,7 @@ atype :: { LHsType GhcPs }
         -- (One means a list type, zero means the list type constructor,
         -- so you have to quote those.)
         | '[' ktype ',' comma_types1 ']'  {% do { h <- addTrailingCommaA $2 (gl $3)
-                                                ; amsA' (sLL $1 $> $ HsExplicitListTy [mos $1,mcs $5] NotPromoted (h:$4)) }}
+                                                ; amsA' (sLL $1 $> $ HsExplicitListTy (NoEpTok,epTok $1,epTok $5) NotPromoted (h:$4)) }}
         | INTEGER              { sLLa $1 $> $ HsTyLit noExtField $ HsNumTy (getINTEGERs $1)
                                                            (il_value (getINTEGER $1)) }
         | CHAR                 { sLLa $1 $> $ HsTyLit noExtField $ HsCharTy (getCHARs $1)
@@ -2420,10 +2421,9 @@ tyvar_wc :: { Located (HsBndrVar GhcPs) }
         : tyvar                         { sL1 $1 (HsBndrVar noExtField $1) }
         | '_'                           { sL1 $1 (HsBndrWildCard noExtField) }
 
-fds :: { Located ([AddEpAnn],[LHsFunDep GhcPs]) }
-        : {- empty -}                   { noLoc ([],[]) }
-        | '|' fds1                      { (sLL $1 $> ([mj AnnVbar $1]
-                                                 ,reverse (unLoc $2))) }
+fds :: { Located (EpToken "|",[LHsFunDep GhcPs]) }
+        : {- empty -}                   { noLoc (NoEpTok,[]) }
+        | '|' fds1                      { (sLL $1 $> (epTok $1 ,reverse (unLoc $2))) }
 
 fds1 :: { Located [LHsFunDep GhcPs] }
         : fds1 ',' fd   {%
@@ -3138,26 +3138,26 @@ aexp2   :: { ECP }
         | splice_untyped { ECP $ mkHsSplicePV $1 }
         | splice_typed   { ecpFromExp $ fmap (uncurry HsTypedSplice) (reLoc $1) }
 
-        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnSimpleQuote $1] (VarBr noExtField True  $2)) }
-        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
-        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket [mj AnnThTyQuote $1  ] (VarBr noExtField False $2)) }
+        | SIMPLEQUOTE  qvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | SIMPLEQUOTE  qcon     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) True  $2)) }
+        | TH_TY_QUOTE tyvar     {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
+        | TH_TY_QUOTE gtycon    {% fmap ecpFromExp $ amsA' (sLL $1 $> $ HsUntypedBracket noExtField (VarBr (glR $1) False $2)) }
         -- See Note [%shift: aexp2 -> TH_TY_QUOTE]
         | TH_TY_QUOTE %shift    {% reportEmptyDoubleQuotes (getLoc $1) }
         | '[|' exp '|]'       {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket (if (hasE $1) then [mj AnnOpenE $1, mu AnnCloseQ $3]
-                                                                                         else [mu AnnOpenEQ $1,mu AnnCloseQ $3]) (ExpBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (ExpBr (if (hasE $1) then (BracketHasE (epTok $1),   epUniTok $3)
+                                                                                                     else (BracketNoE (epUniTok $1), epUniTok $3)) $2)) }
         | '[||' exp '||]'     {% runPV (unECP $2) >>= \ $2 ->
                                  fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then [mj AnnOpenE $1,mc $3] else [mo $1,mc $3]) $2) }
+                                 amsA' (sLL $1 $> $ HsTypedBracket (if (hasE $1) then (BracketHasE (epTok $1),epTok $3) else (BracketNoE (epTok $1),epTok $3)) $2) }
         | '[t|' ktype '|]'    {% fmap ecpFromExp $
-                                 amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (TypBr noExtField $2)) }
+                                 amsA' (sLL $1 $> $ HsUntypedBracket noExtField (TypBr (epTok $1,epUniTok $3) $2)) }
         | '[p|' infixexp '|]' {% (checkPattern <=< runPV) (unECP $2) >>= \p ->
                                       fmap ecpFromExp $
-                                      amsA' (sLL $1 $> $ HsUntypedBracket [mo $1,mu AnnCloseQ $3] (PatBr noExtField p)) }
+                                      amsA' (sLL $1 $> $ HsUntypedBracket noExtField (PatBr (epTok $1,epUniTok $3) p)) }
         | '[d|' cvtopbody '|]' {% fmap ecpFromExp $
-                                  amsA' (sLL $1 $> $ HsUntypedBracket (mo $1:mu AnnCloseQ $3:fst $2) (DecBrL noExtField (snd $2))) }
+                                  amsA' (sLL $1 $> $ HsUntypedBracket noExtField (DecBrL (epTok $1,epUniTok $3, fst $2) (snd $2))) }
         | quasiquote          { ECP $ mkHsSplicePV $1 }
 
         -- arrow notation extension
@@ -3197,10 +3197,9 @@ acmd    :: { LHsCmdTop GhcPs }
                                    runPV (checkCmdBlockArguments cmd) >>= \ _ ->
                                    return (sL1a cmd $ HsCmdTop noExtField cmd) }
 
-cvtopbody :: { ([AddEpAnn],[LHsDecl GhcPs]) }
-        :  '{'            cvtopdecls0 '}'      { ([mj AnnOpenC $1
-                                                  ,mj AnnCloseC $3],$2) }
-        |      vocurly    cvtopdecls0 close    { ([],$2) }
+cvtopbody :: { ((EpToken "{", EpToken "}"),[LHsDecl GhcPs]) }
+        :  '{'            cvtopdecls0 '}'      { ((epTok $1 ,epTok $3),$2) }
+        |      vocurly    cvtopdecls0 close    { ((NoEpTok, NoEpTok),$2) }
 
 cvtopdecls0 :: { [LHsDecl GhcPs] }
         : topdecls_semi         { cvTopDecls $1 }
@@ -4641,6 +4640,10 @@ epUniTok t@(L !l _) = EpUniTok (EpaSpan l) u
   where
     u = if isUnicode t then UnicodeSyntax else NormalSyntax
 
+-- |Construct an EpToken from the location of the token, provided the span is not zero width
+mzEpTok :: Located Token -> EpToken tok
+mzEpTok !l = if isZeroWidthSpan (gl l) then NoEpTok else (epTok l)
+
 epExplicitBraces :: Located Token -> Located Token -> EpLayout
 epExplicitBraces !t1 !t2 = EpExplicitBraces (epTok t1) (epTok t2)
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -10,7 +10,7 @@ module GHC.Parser.Annotation (
   -- * Core Exact Print Annotation types
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
-  getEpTokenSrcSpan, getEpTokenLocs,
+  getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
   TokDcolon,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
@@ -406,6 +406,10 @@ getEpTokenLocs ls = concatMap go ls
     go NoEpTok   = []
     go (EpTok l) = [l]
 
+getEpTokenLoc :: EpToken tok -> EpaLocation
+getEpTokenLoc NoEpTok   = noAnn
+getEpTokenLoc (EpTok l) = l
+
 type TokDcolon = EpUniToken "::" "∷"
 
 -- | Layout information for declarations.


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -71,7 +71,7 @@ module GHC.Parser.Lexer (
    xtest, xunset, xset,
    disableHaddock,
    lexTokenStream,
-   mkParensEpAnn,
+   mkParensEpToks,
    mkParensLocs,
    getCommentsFor, getPriorCommentsFor, getFinalCommentsFor,
    getEofPos,
@@ -3628,13 +3628,14 @@ warn_unknown_prag prags span buf len buf2 = do
 %************************************************************************
 -}
 
+-- TODO:AZ: we should have only mkParensEpToks. Delee mkParensEpAnn, mkParensLocs
 
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'AddEpAnn' values for the opening and closing bordering on the start
 -- and end of the span
-mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
-mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
-                    AddEpAnn AnnCloseP (EpaSpan (RealSrcSpan lc Strict.Nothing)))
+mkParensEpToks :: RealSrcSpan -> (EpToken "(", EpToken ")")
+mkParensEpToks ss = (EpTok (EpaSpan (RealSrcSpan lo Strict.Nothing)),
+                    EpTok (EpaSpan (RealSrcSpan lc Strict.Nothing)))
   where
     f = srcSpanFile ss
     sl = srcSpanStartLine ss
@@ -3644,6 +3645,7 @@ mkParensEpAnn ss = (AddEpAnn AnnOpenP (EpaSpan (RealSrcSpan lo Strict.Nothing)),
     lo = mkRealSrcSpan (realSrcSpanStart ss)        (mkRealSrcLoc f sl (sc+1))
     lc = mkRealSrcSpan (mkRealSrcLoc f el (ec - 1)) (realSrcSpanEnd ss)
 
+
 -- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
 -- 'EpaLocation' values for the opening and closing bordering on the start
 -- and end of the span


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -161,7 +161,7 @@ import GHC.Utils.Error
 import GHC.Utils.Misc
 import GHC.Utils.Monad (unlessM)
 import Data.Either
-import Data.List        ( findIndex, partition )
+import Data.List        ( findIndex )
 import Data.Foldable
 import qualified Data.Semigroup as Semi
 import GHC.Unit.Module.Warnings
@@ -204,14 +204,14 @@ mkClassDecl :: SrcSpan
             -> Located (a,[LHsFunDep GhcPs])
             -> OrdList (LHsDecl GhcPs)
             -> EpLayout
-            -> [AddEpAnn]
+            -> AnnClassDecl
             -> P (LTyClDecl GhcPs)
 
 mkClassDecl loc' (L _ (mcxt, tycl_hdr)) fds where_cls layout annsIn
   = do { (binds, sigs, ats, at_defs, _, docs) <- cvBindsAndSigs where_cls
-       ; (cls, tparams, fixity, ann, cs) <- checkTyClHdr True tycl_hdr
+       ; (cls, tparams, fixity, ops, cps, cs) <- checkTyClHdr True tycl_hdr
        ; tyvars <- checkTyVars (text "class") whereDots cls tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn { acd_openp = ops, acd_closep = cps}
        ; let loc = EpAnn (spanAsAnchor loc') noAnn cs
        ; return (L loc (ClassDecl { tcdCExt = (anns', layout, NoAnnSortKey)
                                   , tcdCtxt = mcxt
@@ -235,9 +235,10 @@ mkTyData :: SrcSpan
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; !cs' <- getCommentsFor loc'
@@ -247,6 +248,15 @@ mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
+-- TODO:AZ:temporary
+openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
+openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
+openParen2AddEpAnn NoEpTok = []
+
+closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
+closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
+closeParen2AddEpAnn NoEpTok = []
+
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
@@ -265,14 +275,15 @@ mkDataDefn cType mcxt ksig data_cons maybe_deriv
 mkTySynonym :: SrcSpan
             -> LHsType GhcPs  -- LHS
             -> LHsType GhcPs  -- RHS
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "="
             -> P (LTyClDecl GhcPs)
-mkTySynonym loc lhs rhs annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+mkTySynonym loc lhs rhs antype aneq
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (text "type") equalsDots tc tparams
-       ; let anns' = annsIn Semi.<> ann
+       ; let anns = AnnSynDecl ops cps antype aneq
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; return (L loc' (SynDecl { tcdSExt = anns'
+       ; return (L loc' (SynDecl { tcdSExt = anns
                                  , tcdLName = tc, tcdTyVars = tyvars
                                  , tcdFixity = fixity
                                  , tcdRhs = rhs })) }
@@ -308,10 +319,12 @@ mkTyFamInstEqn :: SrcSpan
                -> [AddEpAnn]
                -> P (LTyFamInstEqn GhcPs)
 mkTyFamInstEqn loc bndrs lhs rhs anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns `mappend` ann
+                        { feqn_ext    = anns'
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -330,32 +343,20 @@ mkDataFamInst :: SrcSpan
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False tycl_hdr
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
        ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = anns Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = ann Semi.<> anns
+                  (FamEqn { feqn_ext    = anns'
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
                           , feqn_fixity = fixity
                           , feqn_rhs    = defn })))) }
 
--- mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
---               ksig data_cons (L _ maybe_deriv) anns
---   = do { (tc, tparams, fixity, ann) <- checkTyClHdr False tycl_hdr
---        ; cs <- getCommentsFor loc -- Add any API Annotations to the top SrcSpan
---        ; let anns' = addAnns (EpAnn (spanAsAnchor loc) ann cs) anns emptyComments
---        ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv
---        ; return (L (noAnnSrcSpan loc) (DataFamInstD anns' (DataFamInstDecl
---                   (FamEqn { feqn_ext    = anns'
---                           , feqn_tycon  = tc
---                           , feqn_bndrs  = bndrs
---                           , feqn_pats   = tparams
---                           , feqn_fixity = fixity
---                           , feqn_rhs    = defn })))) }
-
 
 
 mkTyFamInst :: SrcSpan
@@ -375,11 +376,13 @@ mkFamDecl :: SrcSpan
           -> [AddEpAnn]
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
-  = do { (tc, tparams, fixity, ann, cs) <- checkTyClHdr False lhs
+  = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
+       ; let anns' = annsIn Semi.<>
+                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (FamDecl noExtField (FamilyDecl
-                                           { fdExt       = annsIn Semi.<> ann
+                                           { fdExt       = anns'
                                            , fdTopLevel  = topLevel
                                            , fdInfo      = info, fdLName = tc
                                            , fdTyVars    = tyvars
@@ -738,8 +741,7 @@ mkPatSynMatchGroup (L loc patsyn_name) (L ld decls) =
         do { unless (name == patsyn_name) $
                wrongNameBindingErr (locA loc) decl
            -- conAnn should only be AnnOpenP, AnnCloseP, so the rest should be empty
-           ; let (ann_fun, rest) = mk_ann_funrhs []
-           ; unless (null rest) $ return $ panic "mkPatSynMatchGroup: unexpected anns"
+           ; let ann_fun = mk_ann_funrhs [] []
            ; match <- case details of
                PrefixCon _ pats -> return $ Match { m_ext = noExtField
                                                   , m_ctxt = ctxt, m_pats = L l pats
@@ -1063,8 +1065,8 @@ checkTyClHdr :: Bool               -- True  <=> class header
              -> P (LocatedN RdrName,     -- the head symbol (type or class name)
                    [LHsTypeArg GhcPs],   -- parameters of head symbol
                    LexicalFixity,        -- the declaration is in infix format
-                   [AddEpAnn],           -- API Annotation for HsParTy
-                                         -- when stripping parens
+                   [EpToken "("],        -- API Annotation for HsParTy
+                   [EpToken ")"],        -- when stripping parens
                    EpAnnComments)        -- Accumulated comments from re-arranging
 -- Well-formedness check and decomposition of type and class heads.
 -- Decomposes   T ty1 .. tyn   into    (T, [ty1, ..., tyn])
@@ -1081,22 +1083,22 @@ checkTyClHdr is_cls ty
            ; let name = mkOccNameFS tcClsName (starSym isUni)
            ; let a' = newAnns ll l an
            ; return (L a' (Unqual name), acc, fix
-                    , (reverse ops') ++ cps', cs) }
+                    , (reverse ops'), cps', cs) }
 
     go cs l (HsTyVar _ _ ltc@(L _ tc)) acc ops cps fix
-      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, acc, fix, (reverse ops), cps, cs Semi.<> comments l)
     go cs l (HsOpTy _ _ t1 ltc@(L _ tc) t2) acc ops cps _fix
-      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops) ++ cps, cs Semi.<> comments l)
+      | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
     go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
       where
-        (o,c) = mkParensEpAnn (realSrcSpan (locA l))
+        (o,c) = mkParensEpToks (realSrcSpan (locA l))
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
       = return (L (l2l l) (nameRdrName tup_name)
-               , map (HsValArg noExtField) ts, fix, (reverse ops)++cps, cs Semi.<> comments l)
+               , map (HsValArg noExtField) ts, fix, (reverse ops), cps, cs Semi.<> comments l)
       where
         arity = length ts
         tup_name | is_cls    = cTupleTyConName arity
@@ -1170,15 +1172,16 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
   -- With NoListTuplePuns, contexts are parsed as data constructors, which causes failure
   -- downstream.
   -- This converts them just like when they are parsed as types in the punned case.
-  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy anns ts))
+  check (oparens,cparens,cs) (L _l (HsExplicitTupleTy (q,o,c) ts))
     = punsAllowed >>= \case
       True -> unprocessed
       False -> do
         let
-          (op, cp) = case anns of
-            [o, c] -> ([o], [c])
-            [q, _, c] -> ([q], [c])
-            _ -> ([], [])
+          ol = AddEpAnn AnnOpenP (getEpTokenLoc o)
+          cl = AddEpAnn AnnCloseP (getEpTokenLoc c)
+          (op, cp) = case q of
+            EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
+            _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
   check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
                                   -- to be sure HsParTy doesn't get into the way
@@ -1331,12 +1334,12 @@ checkAPat loc e0 = do
      addError $ mkPlainErrorMsgEnvelope (getLocA op) PsErrAtInPatPos
      return (WildPat noExtField)
 
-   PatBuilderOpApp l (L cl c) r anns
+   PatBuilderOpApp l (L cl c) r (_os,_cs)
      | isRdrDataCon c || isRdrTc c -> do
          l <- checkLPat l
          r <- checkLPat r
          return $ ConPat
-           { pat_con_ext = mk_ann_conpat anns
+           { pat_con_ext = noAnn
            , pat_con = L cl c
            , pat_args = InfixCon l r
            }
@@ -1389,9 +1392,8 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
   = do  { mb_fun <- isFunLhs lhs
         ; case mb_fun of
-            Just (fun, is_infix, pats, ann) -> do
-              let (ann_fun, ann_rest) = mk_ann_funrhs ann
-              unless (null ann_rest) $ panic "checkValDef: unexpected anns"
+            Just (fun, is_infix, pats, ops, cps) -> do
+              let ann_fun = mk_ann_funrhs ops cps
               let l = listLocation pats
               checkFunBind loc ann_fun
                            fun is_infix (L l pats) grhss
@@ -1404,29 +1406,8 @@ checkValDef loc lhs (mult_ann, Nothing) ghrss
   = do lhs' <- checkPattern lhs
        checkPatBind loc lhs' ghrss mult_ann
 
-mk_ann_funrhs :: [AddEpAnn] -> (AnnFunRhs, [AddEpAnn])
-mk_ann_funrhs ann = (AnnFunRhs strict (map to_tok opens) (map to_tok closes), rest)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenP) ann
-    (closes, ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseP) ra0
-    (bangs, rest) = partition (\(AddEpAnn kw _) -> kw == AnnBang) ra1
-    strict = case bangs of
-               (AddEpAnn _ s:_) -> EpTok s
-               _ -> NoEpTok
-    to_tok (AddEpAnn _ s) = EpTok s
-
-mk_ann_conpat :: [AddEpAnn] -> (Maybe (EpToken "{"), Maybe (EpToken "}"))
-mk_ann_conpat ann = (open, close)
-  where
-    (opens, ra0) = partition (\(AddEpAnn kw _) -> kw == AnnOpenC) ann
-    (closes, _ra1) = partition (\(AddEpAnn kw _) -> kw == AnnCloseC) ra0
-    open = case opens of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    close = case closes of
-      (o:_) -> Just (to_tok o)
-      _ -> Nothing
-    to_tok (AddEpAnn _ s) = EpTok s
+mk_ann_funrhs :: [EpToken "("] -> [EpToken ")"] -> AnnFunRhs
+mk_ann_funrhs ops cps = AnnFunRhs NoEpTok ops cps
 
 checkFunBind :: SrcSpan
              -> AnnFunRhs
@@ -1468,10 +1449,10 @@ checkPatBind :: SrcSpan
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat an (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m ans v)]))
+                [L (noAnnSrcSpan loc) (m an v)]))
   where
     m a v = Match { m_ext = noExtField
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1517,7 +1498,7 @@ checkDoAndIfThenElse err guardExpr semiThen thenExpr semiElse elseExpr
 
 isFunLhs :: LocatedA (PatBuilder GhcPs)
       -> P (Maybe (LocatedN RdrName, LexicalFixity,
-                   [LocatedA (ArgPatBuilder GhcPs)],[AddEpAnn]))
+                   [LocatedA (ArgPatBuilder GhcPs)],[EpToken "("],[EpToken ")"]))
 -- A variable binding is parsed as a FunBind.
 -- Just (fun, is_infix, arg_pats) if e is a function LHS
 isFunLhs e = go e [] [] []
@@ -1527,7 +1508,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderVar (L loc f))) es ops cps
        | not (isRdrDataCon f)        = do
            let (_l, loc') = transferCommentsOnlyA l loc
-           return (Just (L loc' f, Prefix, es, (reverse ops) ++ cps))
+           return (Just (L loc' f, Prefix, es, (reverse ops), cps))
    go (L l (PatBuilderApp (L lf f) e))   es       ops cps = do
      let (_l, lf') = transferCommentsOnlyA l lf
      go (L lf' f) (mk e:es) ops cps
@@ -1537,21 +1518,21 @@ isFunLhs e = go e [] [] []
       -- of funlhs.
      where
        (_l, le') = transferCommentsOnlyA l le
-       (o,c) = mkParensEpAnn (realSrcSpan $ locA l)
-   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r anns)) es ops cps
+       (o,c) = mkParensEpToks (realSrcSpan $ locA l)
+   go (L loc (PatBuilderOpApp (L ll l) (L loc' op) r (os,cs))) es ops cps
       | not (isRdrDataCon op)         -- We have found the function!
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
-           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (anns ++ reverse ops ++ cps))) }
+           ; return (Just (L loc' op, Infix, (mk (L ll' l):mk r:es), (os ++ reverse ops), (cs ++ cps))) }
       | otherwise                     -- Infix data con; keep going
       = do { let (_l, ll') = transferCommentsOnlyA loc ll
            ; mb_l <- go (L ll' l) es ops cps
            ; return (reassociate =<< mb_l) }
         where
-          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', anns')
-            = Just (op', Infix, j : op_app : es', anns')
+          reassociate (op', Infix, j : L k_loc (ArgPatBuilderVisPat k) : es', ops', cps')
+            = Just (op', Infix, j : op_app : es', ops', cps')
             where
               op_app = mk $ L loc (PatBuilderOpApp (L k_loc k)
-                                    (L loc' op) r (reverse ops ++ cps))
+                                    (L loc' op) r (reverse ops, cps))
           reassociate _other = Nothing
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
@@ -1570,13 +1551,13 @@ instance Outputable (ArgPatBuilder GhcPs) where
   ppr (ArgPatBuilderVisPat p) = ppr p
   ppr (ArgPatBuilderArgPat p) = ppr p
 
-mkBangTy :: [AddEpAnn] -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
-mkBangTy anns strictness =
-  HsBangTy (anns, NoSourceText) (HsBang NoSrcUnpack strictness)
+mkBangTy :: EpaLocation -> SrcStrictness -> LHsType GhcPs -> HsType GhcPs
+mkBangTy tok_loc strictness =
+  HsBangTy ((noAnn, noAnn, tok_loc), NoSourceText) (HsBang NoSrcUnpack strictness)
 
 -- | Result of parsing @{-\# UNPACK \#-}@ or @{-\# NOUNPACK \#-}@.
 data UnpackednessPragma =
-  UnpackednessPragma [AddEpAnn] SourceText SrcUnpackedness
+  UnpackednessPragma (EpaLocation, EpaLocation) SourceText SrcUnpackedness
 
 -- | Annotate a type with either an @{-\# UNPACK \#-}@ or a @{-\# NOUNPACK \#-}@ pragma.
 addUnpackednessP :: MonadP m => Located UnpackednessPragma -> LHsType GhcPs -> m (LHsType GhcPs)
@@ -1589,11 +1570,11 @@ addUnpackednessP (L lprag (UnpackednessPragma anns prag unpk)) ty = do
     -- such as ~T or !T, then add the pragma to the existing HsBangTy.
     --
     -- Otherwise, wrap the type in a new HsBangTy constructor.
-    addUnpackedness an (L _ (HsBangTy (anns, NoSourceText) bang t))
+    addUnpackedness (o,c) (L _ (HsBangTy ((_,_,tl), NoSourceText) bang t))
       | HsBang NoSrcUnpack strictness <- bang
-      = HsBangTy (an Semi.<> anns, prag) (HsBang unpk strictness) t
-    addUnpackedness an t
-      = HsBangTy (an, prag) (HsBang unpk NoSrcStrict) t
+      = HsBangTy ((o,c,tl), prag) (HsBang unpk strictness) t
+    addUnpackedness (o,c) t
+      = HsBangTy ((o,c,noAnn), prag) (HsBang unpk NoSrcStrict) t
 
 ---------------------------------------------------------------------------
 -- | Check for monad comprehensions
@@ -2051,7 +2032,7 @@ instance DisambECP (PatBuilder GhcPs) where
   superInfixOp m = m
   mkHsOpAppPV l p1 op p2 = do
     !cs <- getCommentsFor l
-    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 []
+    return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ PatBuilderOpApp p1 op p2 ([],[])
 
   mkHsLamPV l lam_variant _ _     = addFatalError $ mkPlainErrorMsgEnvelope l (PsErrLambdaInPat lam_variant)
 
@@ -3658,7 +3639,7 @@ mkTupleSyntaxTy parOpen args parClose =
       HsExplicitTupleTy annsKeyword args
 
     annParen = AnnParen AnnParens parOpen parClose
-    annsKeyword = [AddEpAnn AnnOpenP parOpen, AddEpAnn AnnCloseP parClose]
+    annsKeyword = (NoEpTok, EpTok parOpen, EpTok parClose)
 
 -- | Decide whether to parse tuple con syntax @(,)@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
@@ -3690,7 +3671,7 @@ mkListSyntaxTy0 brkOpen brkClose span =
       HsExplicitListTy annsKeyword NotPromoted []
 
     rdrNameAnn = NameAnnOnly NameSquare brkOpen brkClose []
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     fullLoc = EpaSpan span
 
 -- | Decide whether to parse list type syntax @[Int]@ in a type as a
@@ -3709,5 +3690,5 @@ mkListSyntaxTy1 brkOpen t brkClose =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted [t]
 
-    annsKeyword = [AddEpAnn AnnOpenS brkOpen, AddEpAnn AnnCloseS brkClose]
+    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
     annParen = AnnParen AnnParensSquare brkOpen brkClose


=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1460,7 +1460,7 @@ instance Monoid ColumnBound where
 
 mkLHsDocTy :: LHsType GhcPs -> Maybe (Located HsDocString) -> LHsType GhcPs
 mkLHsDocTy t Nothing = t
-mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noAnn t $ lexLHsDocString doc)
+mkLHsDocTy t (Just doc) = L (getLoc t) (HsDocTy noExtField t $ lexLHsDocString doc)
 
 getForAllTeleLoc :: HsForAllTelescope GhcPs -> SrcSpan
 getForAllTeleLoc tele =


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -57,7 +57,7 @@ data PatBuilder p
   | PatBuilderApp (LocatedA (PatBuilder p)) (LocatedA (PatBuilder p))
   | PatBuilderAppType (LocatedA (PatBuilder p)) (EpToken "@") (HsTyPat GhcPs)
   | PatBuilderOpApp (LocatedA (PatBuilder p)) (LocatedN RdrName)
-                    (LocatedA (PatBuilder p)) [AddEpAnn]
+                    (LocatedA (PatBuilder p)) ([EpToken "("], [EpToken ")"])
   | PatBuilderVar (LocatedN RdrName)
   | PatBuilderOverLit (HsOverLit GhcPs)
 


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -181,7 +181,7 @@ rnUntypedBracket e br_body
        }
 
 rn_utbracket :: ThStage -> HsQuote GhcPs -> RnM (HsQuote GhcRn, FreeVars)
-rn_utbracket outer_stage br@(VarBr x flg rdr_name)
+rn_utbracket outer_stage br@(VarBr _ flg rdr_name)
   = do { name <- lookupOccRn (unLoc rdr_name)
        ; check_namespace flg name
        ; this_mod <- getModule
@@ -204,18 +204,18 @@ rn_utbracket outer_stage br@(VarBr x flg rdr_name)
                                       TcRnTHError $ THNameError $ QuotedNameWrongStage br }
                         }
                     }
-       ; return (VarBr x flg (noLocA name), unitFV name) }
+       ; return (VarBr noExtField flg (noLocA name), unitFV name) }
 
-rn_utbracket _ (ExpBr x e) = do { (e', fvs) <- rnLExpr e
-                                ; return (ExpBr x e', fvs) }
+rn_utbracket _ (ExpBr _ e) = do { (e', fvs) <- rnLExpr e
+                                ; return (ExpBr noExtField e', fvs) }
 
-rn_utbracket _ (PatBr x p)
-  = rnPat ThPatQuote p $ \ p' -> return (PatBr x p', emptyFVs)
+rn_utbracket _ (PatBr _ p)
+  = rnPat ThPatQuote p $ \ p' -> return (PatBr noExtField p', emptyFVs)
 
-rn_utbracket _ (TypBr x t) = do { (t', fvs) <- rnLHsType TypBrCtx t
-                                ; return (TypBr x t', fvs) }
+rn_utbracket _ (TypBr _ t) = do { (t', fvs) <- rnLHsType TypBrCtx t
+                                ; return (TypBr noExtField t', fvs) }
 
-rn_utbracket _ (DecBrL x decls)
+rn_utbracket _ (DecBrL _ decls)
   = do { group <- groupDecls decls
        ; gbl_env  <- getGblEnv
        ; let new_gbl_env = gbl_env { tcg_dus = emptyDUs }
@@ -227,7 +227,7 @@ rn_utbracket _ (DecBrL x decls)
               -- Discard the tcg_env; it contains only extra info about fixity
         ; traceRn "rn_utbracket dec" (ppr (tcg_dus tcg_env) $$
                    ppr (duUses (tcg_dus tcg_env)))
-        ; return (DecBrG x group', duUses (tcg_dus tcg_env)) }
+        ; return (DecBrG noExtField group', duUses (tcg_dus tcg_env)) }
   where
     groupDecls :: [LHsDecl GhcPs] -> RnM (HsGroup GhcPs)
     groupDecls decls


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1655,7 +1655,7 @@ gen_Lift_binds loc (DerivInstTys{ dit_rep_tc = tycon
     liftTyped_bind = mkFunBindEC 1 loc liftTyped_RDR (nlHsApp unsafeCodeCoerce_Expr . nlHsApp pure_Expr)
                                  (map (pats_etc mk_typed_bracket mk_tsplice liftTypedName) data_cons)
 
-    mk_untyped_bracket = HsUntypedBracket noAnn . ExpBr noExtField
+    mk_untyped_bracket = HsUntypedBracket noExtField . ExpBr noAnn
     mk_typed_bracket = HsTypedBracket noAnn
 
     mk_tsplice = HsTypedSplice noAnn


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -319,7 +319,7 @@ cvtDec (ClassD ctxt cl tvs fds decs)
                     , tcdFDs = fds', tcdSigs = Hs.mkClassOpSigs sigs'
                     , tcdMeths = binds'
                     , tcdATs = fams', tcdATDefs = at_defs', tcdDocs = [] }
-                              -- no docs in TH ^^
+                                                     -- no docs in TH ^^
         }
 
 cvtDec (InstanceD o ctxt ty decs)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -48,8 +48,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:5:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:5:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:5:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:5:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -170,7 +179,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T17544.hs:6:14-16 })
@@ -217,8 +226,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:9:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:9:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -384,8 +402,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:13:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:13:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:13:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:13:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -554,8 +581,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:17:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:17:12-16 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:17:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:17:12-16 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))
@@ -788,10 +824,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:22:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:22:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:22:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:22:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:22:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:22:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:22:18 }))
+        (EpTok (EpaSpan { T17544.hs:22:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:22:18 }))
         (EpTok (EpaSpan { T17544.hs:22:30 })))
@@ -1129,10 +1172,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:28:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:28:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:28:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:28:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:28:18 }))
+        (EpTok (EpaSpan { T17544.hs:28:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:28:18 }))
         (EpTok (EpaSpan { T17544.hs:28:30 })))
@@ -1470,10 +1520,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:34:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:34:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:34:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:34:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:34:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:34:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:34:18 }))
+        (EpTok (EpaSpan { T17544.hs:34:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:34:18 }))
         (EpTok (EpaSpan { T17544.hs:34:30 })))
@@ -1811,10 +1868,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:40:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:40:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:40:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:40:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:40:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:40:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:40:18 }))
+        (EpTok (EpaSpan { T17544.hs:40:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:40:18 }))
         (EpTok (EpaSpan { T17544.hs:40:30 })))
@@ -2152,10 +2216,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:46:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:46:12-16 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:46:18 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:46:30 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:46:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:46:12-16 }))
+        (EpTok (EpaSpan { T17544.hs:46:18 }))
+        (EpTok (EpaSpan { T17544.hs:46:30 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:46:18 }))
         (EpTok (EpaSpan { T17544.hs:46:30 })))
@@ -2493,10 +2564,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544.hs:52:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:52:13-17 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T17544.hs:52:19 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T17544.hs:52:32 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544.hs:52:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544.hs:52:13-17 }))
+        (EpTok (EpaSpan { T17544.hs:52:19 }))
+        (EpTok (EpaSpan { T17544.hs:52:32 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T17544.hs:52:19 }))
         (EpTok (EpaSpan { T17544.hs:52:32 })))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -281,8 +281,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T17544_kw.hs:21:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:23:3-7 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T17544_kw.hs:21:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:23:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (5))
        (NoAnnSortKey))


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -458,7 +458,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:15:3-5 })
@@ -503,7 +503,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:17:3-6 })
@@ -616,7 +616,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:21:3-5 })
@@ -661,7 +661,7 @@
                (EpaComments
                 []))
               (HsDocTy
-               []
+               (NoExtField)
                (L
                 (EpAnn
                  (EpaSpan { T24221.hs:25:3-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -501,9 +501,13 @@
                 (EpaComments
                  []))
                (HsExplicitListTy
-                [(AddEpAnn AnnSimpleQuote (EpaSpan { DumpParsedAst.hs:12:10 }))
-                ,(AddEpAnn AnnOpenS (EpaSpan { DumpParsedAst.hs:12:11 }))
-                ,(AddEpAnn AnnCloseS (EpaSpan { DumpParsedAst.hs:12:12 }))]
+                ((,,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:11 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:12:12 })))
                 (IsPromoted)
                 [])))]
             (Prefix)


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -1302,8 +1302,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { DumpSemis.hs:28:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpSemis.hs:28:40-44 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpSemis.hs:28:40-44 }))
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpVirtualBraces
         (3))
        (NoAnnSortKey))


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -240,8 +240,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:15:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:15:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:15:6-8 })
@@ -452,8 +457,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:16:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:16:13 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:16:13 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:16:6-9 })
@@ -664,8 +674,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:19:10 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:19:10 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:19:6-8 })
@@ -1069,8 +1084,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:26:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:26:11 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:26:11 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:26:6-9 })
@@ -1092,9 +1112,13 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:26:13 }))
-        ,(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:26:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:26:29 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:13 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:26:29 })))
         (IsPromoted)
         [(L
           (EpAnn
@@ -1155,8 +1179,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:27:12 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:27:12 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:27:6-10 })
@@ -1178,8 +1207,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:27:14 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:27:45 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:27:45 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -1290,8 +1323,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:28:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:28:14 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:28:14 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:28:6-10 })
@@ -1340,9 +1378,13 @@
         (EpaComments
          []))
        (HsExplicitTupleTy
-        [(AddEpAnn AnnSimpleQuote (EpaSpan { KindSigs.hs:28:16 }))
-        ,(AddEpAnn AnnOpenP (EpaSpan { KindSigs.hs:28:17 }))
-        ,(AddEpAnn AnnCloseP (EpaSpan { KindSigs.hs:28:44 }))]
+        ((,,)
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:16 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:17 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:28:44 })))
         [(L
           (EpAnn
            (EpaSpan { KindSigs.hs:28:19-39 })
@@ -1363,8 +1405,12 @@
              (EpaComments
               []))
             (HsExplicitListTy
-             [(AddEpAnn AnnOpenS (EpaSpan { KindSigs.hs:28:19 }))
-             ,(AddEpAnn AnnCloseS (EpaSpan { KindSigs.hs:28:29 }))]
+             ((,,)
+              (NoEpTok)
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:19 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:29 })))
              (NotPromoted)
              [(L
                (EpAnn
@@ -1465,8 +1511,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:31:19 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:1-4 }))
+       (EpTok
+        (EpaSpan { KindSigs.hs:31:19 })))
       (L
        (EpAnn
         (EpaSpan { KindSigs.hs:31:6-17 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -262,10 +262,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:8:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:8:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:8:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:8:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:8:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:8:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:8:84 }))
+        (EpTok (EpaSpan { T20452.hs:8:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:8:84 }))
         (EpTok (EpaSpan { T20452.hs:8:85 })))
@@ -492,10 +499,17 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { T20452.hs:9:1-5 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { T20452.hs:9:78-82 }))
-       ,(AddEpAnn AnnOpenC (EpaSpan { T20452.hs:9:84 }))
-       ,(AddEpAnn AnnCloseC (EpaSpan { T20452.hs:9:85 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { T20452.hs:9:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:9:78-82 }))
+        (EpTok (EpaSpan { T20452.hs:9:84 }))
+        (EpTok (EpaSpan { T20452.hs:9:85 }))
+        [])
        (EpExplicitBraces
         (EpTok (EpaSpan { T20452.hs:9:84 }))
         (EpTok (EpaSpan { T20452.hs:9:85 })))


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
=====================================
@@ -72,8 +72,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:5:6 })
@@ -101,8 +106,12 @@
              "-- comment inside A")
             { AnnotationNoListTuplePuns.hs:7:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -128,8 +137,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.hs:12:6 })
@@ -157,8 +171,12 @@
              "-- comment inside B")
             { AnnotationNoListTuplePuns.hs:14:3 }))]))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 })))
         (NotPromoted)
         [(L
           (EpAnn
@@ -243,8 +261,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:6 })
@@ -266,8 +289,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 })))
         (NotPromoted)
         [])))))
   ,(L
@@ -280,8 +307,13 @@
     (TyClD
      (NoExtField)
      (SynDecl
-      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 }))]
+      (AnnSynDecl
+       []
+       []
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
+       (EpTok
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 })))
       (L
        (EpAnn
         (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:6 })
@@ -303,8 +335,12 @@
         (EpaComments
          []))
        (HsExplicitListTy
-        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
-        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 }))]
+        ((,,)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
+         (EpTok
+          (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 })))
         (NotPromoted)
         [(L
           (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -308,7 +308,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.hs:11:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.hs:11:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)
@@ -933,7 +942,16 @@
      (NoExtField)
      (ClassDecl
       ((,,)
-       [(AddEpAnn AnnClass (EpaSpan { Test24533.ppr.hs:4:1-5 }))]
+       (AnnClassDecl
+        (EpTok
+         (EpaSpan { Test24533.ppr.hs:4:1-5 }))
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        [])
        (EpNoLayout)
        (NoAnnSortKey))
       (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -837,21 +837,6 @@ markEpAnnLMS'' a l kw (Just str) = do
 
 -- -------------------------------------
 
-markEpAnnMS' :: (Monad m, Monoid w)
-  => [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m [AddEpAnn]
-markEpAnnMS' anns kw Nothing = mark anns kw
-markEpAnnMS' anns kw (Just str) = do
-  mapM go anns
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
--- -------------------------------------
-
 markEpAnnLMS' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
 markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
@@ -3286,51 +3271,53 @@ instance ExactPrint (HsExpr GhcPs) where
     return (ArithSeq (AnnArithSeq o' mc' dd' c') s seqInfo')
 
 
-  exact (HsTypedBracket an e) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[||")
-    an1 <- markEpAnnLMS'' an0 lidl AnnOpenE (Just "[e||")
+  exact (HsTypedBracket (o,c) e) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnLMS'' an1 lidl AnnClose (Just "||]")
-    return (HsTypedBracket an2 e')
+    c' <- markEpToken c
+    return (HsTypedBracket (o',c') e')
 
-  exact (HsUntypedBracket an (ExpBr a e)) = do
-    an0 <- markEpAnnL an  lidl AnnOpenEQ -- "[|"
-    an1 <- markEpAnnL an0 lidl AnnOpenE  -- "[e|" -- optional
+  exact (HsUntypedBracket a (ExpBr (o,c) e)) = do
+    o' <- case o of
+      BracketNoE  t -> BracketNoE  <$> markEpUniToken t
+      BracketHasE t -> BracketHasE <$> markEpToken t
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an2 (ExpBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (ExpBr (o',c') e'))
 
-  exact (HsUntypedBracket an (PatBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[p|")
+  exact (HsUntypedBracket a (PatBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (PatBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (PatBr (o',c') e'))
 
-  exact (HsUntypedBracket an (DecBrL a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[d|")
-    an1 <- markEpAnnL an0 lidl AnnOpenC
+  exact (HsUntypedBracket a (DecBrL (o,c, (oc,cc)) e)) = do
+    o' <- markEpToken o
+    oc' <- markEpToken oc
     e' <- markAnnotated e
-    an2 <- markEpAnnL an1 lidl AnnCloseC
-    an3 <- markEpAnnL an2 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an3 (DecBrL a e'))
+    cc' <- markEpToken cc
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (DecBrL (o',c',(oc',cc')) e'))
 
-  exact (HsUntypedBracket an (TypBr a e)) = do
-    an0 <- markEpAnnLMS'' an lidl AnnOpen (Just "[t|")
+  exact (HsUntypedBracket a (TypBr (o,c) e)) = do
+    o' <- markEpToken o
     e' <- markAnnotated e
-    an1 <- markEpAnnL an0 lidl AnnCloseQ -- "|]"
-    return (HsUntypedBracket an1 (TypBr a e'))
+    c' <- markEpUniToken c
+    return (HsUntypedBracket a (TypBr (o',c') e'))
 
-  exact (HsUntypedBracket an (VarBr a b e)) = do
+  exact (HsUntypedBracket a (VarBr an b e)) = do
     (an0, e') <- if b
       then do
-        an' <- markEpAnnL an lidl AnnSimpleQuote
+        an' <- printStringAtAA an "'"
         e' <- markAnnotated e
         return (an', e')
       else do
-        an' <- markEpAnnL an lidl AnnThTyQuote
+        an' <- printStringAtAA an "''"
         e' <- markAnnotated e
         return (an', e')
-    return (HsUntypedBracket an0 (VarBr a b e'))
+    return (HsUntypedBracket a (VarBr an0 b e'))
 
   exact (HsTypedSplice an s)   = do
     an0 <- markEpToken an
@@ -3768,24 +3755,24 @@ instance ExactPrint (TyClDecl GhcPs) where
     decl' <- markAnnotated decl
     return (FamDecl a decl')
 
-  exact (SynDecl { tcdSExt = an
+  exact (SynDecl { tcdSExt = AnnSynDecl ops cps t eq
                  , tcdLName = ltycon, tcdTyVars = tyvars, tcdFixity = fixity
                  , tcdRhs = rhs }) = do
     -- There may be arbitrary parens around parts of the constructor
     -- that are infix.  Turn these into comments so that they feed
     -- into the right place automatically
     -- TODO: no longer sorting on insert. What now?
-    an0 <- annotationsToComments an lidl [AnnOpenP,AnnCloseP]
-    an1 <- markEpAnnL an0 lidl AnnType
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
+    t' <- markEpToken t
 
     (_anx, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    an2 <- markEpAnnL an1 lidl AnnEqual
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (SynDecl { tcdSExt = an2
+    return (SynDecl { tcdSExt = AnnSynDecl [] [] t' eq'
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  -- TODO: add a workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/20452
   exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
     (_, an', ltycon', tyvars', _, defn') <-
@@ -3795,7 +3782,7 @@ instance ExactPrint (TyClDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ClassDecl {tcdCExt = (an, lo, sortKey),
+  exact (ClassDecl {tcdCExt = (AnnClassDecl c ops cps vb w oc cc semis, lo, sortKey),
                     tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars,
                     tcdFixity = fixity,
                     tcdFDs  = fds,
@@ -3805,10 +3792,10 @@ instance ExactPrint (TyClDecl GhcPs) where
       -- TODO: add a test that demonstrates tcdDocs
       | null sigs && null methods && null ats && null at_defs -- No "where" part
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnL an1 lidl AnnCloseC
-          return (ClassDecl {tcdCExt = (an2, lo, sortKey),
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          cc' <- markEpToken cc
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis, lo, sortKey),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3818,9 +3805,9 @@ instance ExactPrint (TyClDecl GhcPs) where
 
       | otherwise       -- Laid out
       = do
-          (an0, fds', lclas', tyvars',context') <- top_matter
-          an1 <- markEpAnnL    an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lidl AnnSemi
+          (c', w', vb', fds', lclas', tyvars',context') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsSigTag, prepareListAnnotationA sigs),
                                 (ClsMethodTag, prepareListAnnotationA methods),
@@ -3828,13 +3815,13 @@ instance ExactPrint (TyClDecl GhcPs) where
                                 (ClsAtdTag, prepareListAnnotationA at_defs)
                              -- ++ prepareListAnnotation docs
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC
+          cc' <- markEpToken cc
           let
             sigs'    = undynamic ds
             methods' = undynamic ds
             ats'     = undynamic ds
             at_defs' = undynamic ds
-          return (ClassDecl {tcdCExt = (an3, lo, sortKey'),
+          return (ClassDecl {tcdCExt = (AnnClassDecl c' [] [] vb' w' oc' cc' semis', lo, sortKey'),
                              tcdCtxt = context', tcdLName = lclas', tcdTyVars = tyvars',
                              tcdFixity = fixity,
                              tcdFDs  = fds',
@@ -3843,17 +3830,18 @@ instance ExactPrint (TyClDecl GhcPs) where
                              tcdDocs = _docs})
       where
         top_matter = do
-          an' <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
-          an0 <- markEpAnnL an' lidl AnnClass
+          epTokensToComments AnnOpenP ops
+          epTokensToComments AnnCloseP cps
+          c' <- markEpToken c
           (_, lclas', tyvars',_,context') <-  exactVanillaDeclHead lclas tyvars fixity context
-          (an1, fds') <- if (null fds)
-            then return (an0, fds)
+          (vb', fds') <- if (null fds)
+            then return (vb, fds)
             else do
-              an1 <- markEpAnnL an0 lidl AnnVbar
+              vb' <- markEpToken vb
               fds' <- markAnnotated fds
-              return (an1, fds')
-          an2 <- markEpAnnL an1 lidl AnnWhere
-          return (an2, fds', lclas', tyvars',context')
+              return (vb', fds')
+          w' <- markEpToken w
+          return (c', w', vb', fds', lclas', tyvars',context')
 
 
 -- ---------------------------------------------------------------------
@@ -4202,37 +4190,36 @@ instance ExactPrint (HsType GhcPs) where
   exact (HsDocTy an ty doc) = do
     ty' <- markAnnotated ty
     return (HsDocTy an ty' doc)
-  exact (HsBangTy (an, mt) (HsBang up str) ty) = do
-    an0 <-
+  exact (HsBangTy ((o,c,tk), mt) (HsBang up str) ty) = do
+    (o',c') <-
       case mt of
-        NoSourceText -> return an
+        NoSourceText -> return (o,c)
         SourceText src -> do
           debugM $ "HsBangTy: src=" ++ showAst src
-          an0 <- markEpAnnMS' an AnnOpen  (Just $ unpackFS src)
-          an1 <- markEpAnnMS' an0 AnnClose (Just "#-}")
-          debugM $ "HsBangTy: done unpackedness"
-          return an1
-    an1 <-
+          o' <- printStringAtAA o (unpackFS src)
+          c' <- printStringAtAA c "#-}"
+          return (o',c')
+    tk' <-
       case str of
-        SrcLazy     -> mark an0 AnnTilde
-        SrcStrict   -> mark an0 AnnBang
-        NoSrcStrict -> return an0
+        SrcLazy     -> printStringAtAA tk "~"
+        SrcStrict   -> printStringAtAA tk "!"
+        NoSrcStrict -> return tk
     ty' <- markAnnotated ty
-    return (HsBangTy (an1, mt) (HsBang up str) ty')
-  exact (HsExplicitListTy an prom tys) = do
-    an0 <- if (isPromoted prom)
-             then mark an AnnSimpleQuote
-             else return an
-    an1 <- mark an0 AnnOpenS
+    return (HsBangTy ((o',c',tk'), mt) (HsBang up str) ty')
+  exact (HsExplicitListTy (sq,o,c) prom tys) = do
+    sq' <- if (isPromoted prom)
+             then markEpToken sq
+             else return sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseS
-    return (HsExplicitListTy an2 prom tys')
-  exact (HsExplicitTupleTy an tys) = do
-    an0 <- mark an AnnSimpleQuote
-    an1 <- mark an0 AnnOpenP
+    c' <- markEpToken c
+    return (HsExplicitListTy (sq',o',c') prom tys')
+  exact (HsExplicitTupleTy (sq, o, c) tys) = do
+    sq' <- markEpToken sq
+    o' <- markEpToken o
     tys' <- markAnnotated tys
-    an2 <- mark an1 AnnCloseP
-    return (HsExplicitTupleTy an2 tys')
+    c' <- markEpToken c
+    return (HsExplicitTupleTy (sq', o', c') tys')
   exact (HsTyLit a lit) = do
     case lit of
       (HsNumTy src v) -> printSourceText src (show v)


=====================================
utils/check-exact/Main.hs
=====================================
@@ -166,7 +166,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/T18052a.hs" Nothing
  -- "../../testsuite/tests/printer/T18247a.hs" Nothing
  -- "../../testsuite/tests/printer/Test10268.hs" Nothing
- "../../testsuite/tests/printer/Test10269.hs" Nothing
+ -- "../../testsuite/tests/printer/Test10269.hs" Nothing
  -- "../../testsuite/tests/printer/Test10276.hs" Nothing
  -- "../../testsuite/tests/printer/Test10278.hs" Nothing
  -- "../../testsuite/tests/printer/Test10312.hs" Nothing
@@ -209,6 +209,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
+ "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
  -- "../../testsuite/tests/printer/Test23465.hs" Nothing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f67db48bdef51905132d990cfaaa0df6532ea99

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:20:22 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 05:20:22 -0400
Subject: [Git][ghc/ghc][master] 2 commits: Expand the haddocks for
 Control.Category
Message-ID: <6710d6d6ac65a_25e7222760f0108131@gitlab.mail>



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


Commits:
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -


2 changed files:

- libraries/base/src/Control/Category.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Category.hs


Changes:

=====================================
libraries/base/src/Control/Category.hs
=====================================
@@ -11,9 +11,26 @@
 --
 
 module Control.Category
-  ( Category(..)
+  ( -- * Class
+    Category(..)
+
+    -- * Combinators
   , (<<<)
   , (>>>)
+
+  -- $namingConflicts
   ) where
 
 import GHC.Internal.Control.Category
+
+-- $namingConflicts
+--
+-- == A note on naming conflicts
+--
+-- The methods from 'Category' conflict with 'Prelude.id' and 'Prelude..' from the
+-- prelude; you will likely want to either import this module qualified, or hide the
+-- prelude functions:
+--
+-- @
+-- import "Prelude" hiding (id, (.))
+-- @


=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Category.hs
=====================================
@@ -28,17 +28,81 @@ import GHC.Internal.Data.Coerce (coerce)
 infixr 9 .
 infixr 1 >>>, <<<
 
--- | A class for categories. Instances should satisfy the laws
+-- | A class for categories.
 --
--- [Right identity] @f '.' 'id'  =  f@
--- [Left identity]  @'id' '.' f  =  f@
--- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+-- In mathematics, a /category/ is defined as a collection of /objects/ and a collection
+-- of /morphisms/ between objects, together with an /identity morphism/ 'id' for every
+-- object and an operation '(.)' that /composes/ compatible morphisms.
+--
+-- This class is defined in an analogous way. The collection of morphisms is represented
+-- by a type parameter @cat@, which has kind @k -> k -> 'Data.Kind.Type'@ for some kind variable @k@
+-- that represents the collection of objects; most of the time the choice of @k@ will be
+-- 'Data.Kind.Type'.
+--
+-- ==== __Examples__
+--
+-- As the method names suggest, there's a category of functions:
+--
+-- @
+-- instance Category '(->)' where
+--   id = \\x -> x
+--   f . g = \\x -> f (g x)
+-- @
+--
+-- Isomorphisms form a category as well:
+--
+-- @
+-- data Iso a b = Iso (a -> b) (b -> a)
+--
+-- instance Category Iso where
+--   id = Iso id id
+--   Iso f1 g1 . Iso f2 g2 = Iso (f1 . f2) (g2 . g1)
+-- @
+--
+-- Natural transformations are another important example:
+--
+-- @
+-- newtype f ~> g = NatTransform (forall x. f x -> g x)
+--
+-- instance Category (~>) where
+--   id = NatTransform id
+--   NatTransform f . NatTransform g = NatTransform (f . g)
+-- @
+--
+-- Using the `TypeData` language extension, we can also make a category where `k` isn't
+-- `Type`, but a custom kind `Door` instead:
+--
+-- @
+-- type data Door = DoorOpen | DoorClosed
+--
+-- data Action (before :: Door) (after :: Door) where
+--   DoNothing :: Action door door
+--   OpenDoor :: Action start DoorClosed -> Action start DoorOpen
+--   CloseDoor :: Action start DoorOpen -> Action start DoorClosed
+--
+-- instance Category Action where
+--   id = DoNothing
+--
+--   DoNothing . action = action
+--   OpenDoor rest . action = OpenDoor (rest . action)
+--   CloseDoor rest . action = CloseDoor (rest . action)
+-- @
 --
 class Category cat where
-    -- | the identity morphism
+    -- | The identity morphism. Implementations should satisfy two laws:
+    --
+    -- [Right identity] @f '.' 'id'  =  f@
+    -- [Left identity]  @'id' '.' f  =  f@
+    --
+    -- These essentially state that 'id' should "do nothing".
     id :: cat a a
 
-    -- | morphism composition
+    -- | Morphism composition. Implementations should satisfy the law:
+    --
+    -- [Associativity]  @f '.' (g '.' h)  =  (f '.' g) '.' h@
+    --
+    -- This means that the way morphisms are grouped is irrelevant, so it is unambiguous
+    -- to write a composition of morphisms as @f '.' g '.' h@, without parentheses.
     (.) :: cat b c -> cat a b -> cat a c
 
 {-# RULES
@@ -70,11 +134,13 @@ instance Category Coercion where
   id = Coercion
   (.) Coercion = coerce
 
--- | Right-to-left composition
+-- | Right-to-left composition. This is a synonym for '(.)', but it can be useful to make
+-- the order of composition more apparent.
 (<<<) :: Category cat => cat b c -> cat a b -> cat a c
 (<<<) = (.)
 
--- | Left-to-right composition
+-- | Left-to-right composition. This is useful if you want to write a morphism as a
+-- pipeline going from left to right.
 (>>>) :: Category cat => cat a b -> cat b c -> cat a c
 f >>> g = g . f
 {-# INLINE (>>>) #-} -- see Note [INLINE on >>>]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f67db48bdef51905132d990cfaaa0df6532ea99...076c1a104f55750a49de03694786180bd78eb9b6

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f67db48bdef51905132d990cfaaa0df6532ea99...076c1a104f55750a49de03694786180bd78eb9b6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:41:31 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 17 Oct 2024 05:41:31 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] Temp workaround
Message-ID: <6710dbcaebedb_25e722bb235811586b@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
008c7af8 by Sjoerd Visscher at 2024-10-17T11:41:22+02:00
Temp workaround

- - - - -


1 changed file:

- compiler/GHC/Unit/Finder.hs


Changes:

=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -462,7 +462,7 @@ findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation"))
+         then return (InstalledFound (OsPathModLocation undefined undefined undefined undefined undefined undefined)) -- (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -495,7 +495,7 @@ findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation"))
+          then return (InstalledFound (OsPathModLocation undefined undefined undefined undefined undefined undefined)) -- (error "GHC.Prim ModLocation"))
           else
 
     let



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/008c7af8dcfaa70a7c005e72a6e69ff8a39899e9

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 09:51:04 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 05:51:04 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 53 commits: EPA: Remove
 [AddEpAnn] commit 3
Message-ID: <6710de08d49f7_89197d705013561@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
92798629 by Cheng Shao at 2024-10-17T05:50:46-04:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
04495800 by Cheng Shao at 2024-10-17T05:50:46-04:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
d664309b by Cheng Shao at 2024-10-17T05:50:46-04:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
65548fe7 by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
2f98356c by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
e89c4deb by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: correct stale link in comment

- - - - -
558ea1e0 by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
dbd031b5 by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
7af521ed by Cheng Shao at 2024-10-17T05:50:46-04:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
6692ea6f by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
d9fcf0c2 by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
bc78a01f by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
5fc094fb by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
74f5331c by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
fbf96ff4 by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
3d4a1619 by Cheng Shao at 2024-10-17T05:50:46-04:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
ec3e555f by Cheng Shao at 2024-10-17T05:50:46-04:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
b38bad63 by Cheng Shao at 2024-10-17T05:50:47-04:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
73720945 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
23506412 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
98a6a358 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
f42fa8de by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: bump T17572 timeout

- - - - -
2a4122fb by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
2bacf5b4 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: skip terminfo_so for cross ghc

- - - - -
6f1f78db by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
04a62e73 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
29e0d1ef by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
989caa03 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
d5b338d1 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: skip rdynamic on wasm

- - - - -
70aaeef9 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
61a4c165 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
d408e280 by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
8f8b3e0d by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
e7c1cac4 by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
cc32d062 by Cheng Shao at 2024-10-17T05:50:47-04:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
176fa668 by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
55e7fc10 by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
9131cefc by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
5d17bf55 by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
bf143273 by Cheng Shao at 2024-10-17T05:50:47-04:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
25f73860 by Cheng Shao at 2024-10-17T05:50:47-04:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
a695ce3d by Cheng Shao at 2024-10-17T05:50:47-04:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
bfd6f3fd by Cheng Shao at 2024-10-17T05:50:47-04:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
fe1d7d8b by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
86c31839 by Cheng Shao at 2024-10-17T05:50:47-04:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
947431ae by Cheng Shao at 2024-10-17T05:50:47-04:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
3c69b11b by Cheng Shao at 2024-10-17T05:50:47-04:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
cec3ef7b by Cheng Shao at 2024-10-17T05:50:47-04:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
fe9ab7ab by Matthew Pickering at 2024-10-17T05:50:51-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
72e8f628 by Cheng Shao at 2024-10-17T05:50:52-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cecae38586355beeb2d88c326dfe4d645041b7af...72e8f628cecf5502541b3ef9f6d30f71f74f4a6f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cecae38586355beeb2d88c326dfe4d645041b7af...72e8f628cecf5502541b3ef9f6d30f71f74f4a6f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 10:01:29 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 17 Oct 2024 06:01:29 -0400
Subject: [Git][ghc/ghc][wip/9.12-testsuite-fixes] 6 commits: testsuite:
 normalise some versions in callstacks
Message-ID: <6710e079dbb2b_891972b27e423125@gitlab.mail>



Zubin pushed to branch wip/9.12-testsuite-fixes at Glasgow Haskell Compiler / GHC


Commits:
fba5f4f3 by Zubin Duggal at 2024-10-17T15:30:00+05:30
testsuite: normalise some versions in callstacks

(cherry picked from commit f230e29f30d0c1c566d4dd251807fcab76a2710e)

- - - - -
7a806727 by Zubin Duggal at 2024-10-17T15:30:00+05:30
testsuite: use -fhide-source-paths to normalise some backpack tests

(cherry picked from commit b19de476bc5ce5c7792e8af1354b94a4286a1a13)

- - - - -
e34864aa by Zubin Duggal at 2024-10-17T15:30:00+05:30
testsuite/haddock: strip version identifiers and unit hashes from html tests

(cherry picked from commit fbf0889eadc410d43dd5c1657e320634b6738fa5)

- - - - -
1d973d3f by Zubin Duggal at 2024-10-17T15:30:16+05:30
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

(cherry picked from commit e78c7ef96e395f1ef41f04790aebecd0409b92b9)

- - - - -
75a356e1 by Zubin Duggal at 2024-10-17T15:30:27+05:30
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

(cherry picked from commit a79a587e025d42d34bb30e115fc5c7cab6c1e030)

- - - - -
72db6625 by Zubin Duggal at 2024-10-17T15:30:35+05:30
testsuite: normalise windows file seperators

(cherry picked from commit f858875e03b9609656b542aaaaff85ad0a83878a)

- - - - -


15 changed files:

- testsuite/tests/backpack/should_compile/all.T
- testsuite/tests/backpack/should_compile/bkp16.stderr
- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-api/T20757.stderr
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-e/should_fail/all.T
- testsuite/tests/profiling/should_run/all.T
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
- utils/haddock/html-test/Main.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html


Changes:

=====================================
testsuite/tests/backpack/should_compile/all.T
=====================================
@@ -8,7 +8,7 @@ test('bkp11', normal, backpack_compile, [''])
 test('bkp12', normal, backpack_compile, [''])
 test('bkp14', normal, backpack_compile, [''])
 test('bkp15', normal, backpack_compile, [''])
-test('bkp16', normalise_version('base', 'ghc-internal'), backpack_compile, [''])
+test('bkp16', [normalise_version('base', 'ghc-internal')], backpack_compile, ['-fhide-source-paths'])
 test('bkp17', normal, backpack_compile, [''])
 test('bkp18', normal, backpack_compile, [''])
 test('bkp19', normal, backpack_compile, [''])
@@ -60,4 +60,4 @@ test('T13214', normal, backpack_compile, [''])
 test('T13250', normal, backpack_compile, [''])
 test('T13323', normal, backpack_compile, [''])
 test('T20396', normal, backpack_compile, [''])
-test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])
\ No newline at end of file
+test('T23424', [ignore_stdout, ignore_stderr], backpack_compile, ['-ddump-rn-trace -ddump-if-trace -ddump-tc-trace'])


=====================================
testsuite/tests/backpack/should_compile/bkp16.stderr
=====================================
@@ -1,9 +1,9 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling Int[sig]         ( p/Int.hsig, nothing )
+  [1 of 1] Compiling Int[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[Int=base-4.20.0.0:GHC.Exts]
     Instantiating p[Int=base-4.20.0.0:GHC.Exts]
     [1 of 1] Including base-4.20.0.0
-    [1 of 1] Compiling Int[sig]         ( p/Int.hsig, bkp16.out/p/p-3JmGAx0a1DyKjX6bh7CxGJ/Int.o )
+    [1 of 1] Compiling Int[sig]
   [1 of 1] Instantiating p


=====================================
testsuite/tests/backpack/should_fail/all.T
=====================================
@@ -12,9 +12,9 @@ test('bkpfail13', normal, backpack_compile_fail, [''])
 test('bkpfail14', normal, backpack_compile_fail, [''])
 test('bkpfail15', normal, backpack_compile_fail, [''])
 test('bkpfail16', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
-test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail17', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail18', normal, backpack_compile_fail, [''])
-test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, [''])
+test('bkpfail19', normalise_version('ghc-internal', 'base'), backpack_compile_fail, ['-fhide-source-paths'])
 test('bkpfail20', normal, backpack_compile_fail, [''])
 test('bkpfail21', normal, backpack_compile_fail, [''])
 test('bkpfail22', normal, backpack_compile_fail, [''])


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Prelude]
     Instantiating p[ShouldFail=base-4.20.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9R9TTjIBG3MEjwCQffKVYM/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-15843]
     • Type constructor ‘Either’ has conflicting definitions in the module
       and its hsig file.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,10 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]
 [2 of 2] Processing q
   Instantiating q
   [1 of 1] Including p[ShouldFail=base-4.20.0.0:Data.STRef]
     Instantiating p[ShouldFail=base-4.20.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Gwl8Z2CPH0M7Zi2wPSYSbs/ShouldFail.o )
+    [1 of 1] Compiling ShouldFail[sig]
 : error: [GHC-12424]
     • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
       but the implementing module exports a different identifier ‘GHC.Internal.STRef.newSTRef’


=====================================
testsuite/tests/gadt/all.T
=====================================
@@ -127,7 +127,7 @@ test('T20485', normal, compile, [''])
 test('T20485a', normal, compile, [''])
 test('T22235', normal, compile, [''])
 test('T19847', normal, compile, [''])
-test('T19847a', normal, compile, ['-ddump-types'])
+test('T19847a', normalise_version('base'), compile, ['-ddump-types'])
 test('T19847b', normal, compile, [''])
 test('T23022', normal, compile, ['-dcore-lint'])
 test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test?


=====================================
testsuite/tests/ghc-api/T20757.stderr
=====================================
@@ -2,11 +2,11 @@ T20757: Exception:
 
 could not detect mingw toolchain in the following paths: ["/..//mingw","/..//..//mingw","/..//..//..//mingw"]
 
-Package: ghc-inplace
+Package: ghc--
 Module: GHC.Utils.Panic
 Type: GhcException
 
 HasCallStack backtrace:
   collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:: in :GHC.Internal.Exception
   toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/IO.hs:: in :GHC.Internal.IO
-  throwIO, called at compiler/GHC/Utils/Panic.hs:: in :GHC.Utils.Panic
+  throwIO, called at compiler/GHC/Utils/Panic.hs:183:23 in ghc--:GHC.Utils.Panic


=====================================
testsuite/tests/ghc-api/all.T
=====================================
@@ -36,7 +36,7 @@ test('T19156', [ extra_run_opts('"' + config.libdir + '"')
                ],
                compile_and_run,
                ['-package ghc'])
-test('T20757', [unless(opsys('mingw32'), skip), exit_code(1)],
+test('T20757', [unless(opsys('mingw32'), skip), exit_code(1), normalise_version('ghc')],
                compile_and_run,
                ['-package ghc'])
 test('PrimOpEffect_Sanity', normal, compile_and_run, ['-Wall -Werror -package ghc'])


=====================================
testsuite/tests/ghc-e/should_fail/all.T
=====================================
@@ -15,6 +15,7 @@ test('ghc-e-fail2', req_interp, makefile_test, ['ghc-e-fail2'])
 test('T9930fail',
      [extra_files(['T9930']),
       when(opsys('mingw32'), skip),
+      normalise_errmsg_fun(lambda s: normalise_version_("ghc")(s).replace('ghc--','ghc')),
       # broken for JS until cross-compilers become stage2 compilers (#19174)
       # or until we bootstrap with a 9.10 compiler
       js_broken(19174)],
@@ -24,7 +25,7 @@ test('T18441fail0', req_interp, makefile_test, ['T18441fail0'])
 
 test('T18441fail1', req_interp, makefile_test, ['T18441fail1'])
 
-test('T18441fail2', req_interp, makefile_test, ['T18441fail2'])
+test('T18441fail2', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail2'])
 
 test('T18441fail3', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":! abcde"'])
 
@@ -34,9 +35,9 @@ test('T18441fail5', req_interp, makefile_test, ['T18441fail5'])
 
 test('T18441fail6', req_interp, makefile_test, ['T18441fail6'])
 
-test('T18441fail7', req_interp, makefile_test, ['T18441fail7'])
+test('T18441fail7', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail7'])
 
-test('T18441fail8', req_interp, makefile_test, ['T18441fail8'])
+test('T18441fail8', [req_interp, normalise_version('ghc')], makefile_test, ['T18441fail8'])
 
 test('T18441fail9', req_interp, makefile_test, ['T18441fail9'])
 
@@ -60,6 +61,6 @@ test('T18441fail18', req_interp, makefile_test, ['T18441fail18'])
 
 test('T18441fail19', [ignore_stderr, exit_code(1)], run_command, ['{compiler} -e ":cd abcd"'])
 
-test('T23663', req_interp, makefile_test, ['T23663'])
+test('T23663', [req_interp, normalise_version('ghc')], makefile_test, ['T23663'])
 
 test('T24172', normal, compile_fail, ['-fdiagnostics-color=always'])


=====================================
testsuite/tests/profiling/should_run/all.T
=====================================
@@ -145,11 +145,13 @@ test('T7275', test_opts_dot_prof, makefile_test, [])
 test('callstack001',
      # unoptimised results are different w.r.t. CAF attribution
      [test_opts_dot_prof # produces a different stack
+     ,normalise_fun(lambda s: re.sub(r"(? 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
+      filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (\mt -> ((mt,file),file)) <$> getModificationTime (hiDir  file)) files
       let srcRef = if "--hyperlinked-source" `elem` cfgHaddockArgs then ",src,visible," else ""
           loop [] = pure True
           loop (file : files) = do


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Xhtml.hs
=====================================
@@ -8,6 +8,7 @@ module Test.Haddock.Xhtml
   , stripIdsWhen
   , stripFooter
   , fixAttrValueWhen
+  , stripVersions
   ) where
 
 {-
@@ -22,7 +23,7 @@ and since the `xhtml` library already handles the pretty-printing aspect,
 this would appear to be a reasonable compromise for now.
 -}
 
-import Data.Char (isSpace)
+import Data.Char (isSpace, isAlphaNum)
 import Data.List (isPrefixOf, stripPrefix)
 
 -- | Simple wrapper around the pretty-printed HTML source
@@ -142,3 +143,18 @@ stripFooter (Xml body) = Xml (findDiv body)
           Just valRest''
       | otherwise =
           dropToDiv cs
+
+-- | Strip strings of the form --
+-- to just 
+stripVersions :: [String] -> Xml -> Xml
+stripVersions xs (Xml body) = Xml $ foldr id body $ map go xs
+  where
+    go pkg "" = ""
+    go pkg body@(x:body') = case stripPrefix pkg body of
+      Just ('-':rest)
+        | (version,'-':rest') <- span (/= '-') rest
+        , all (`elem` ('.':['0'..'9'])) version
+        , let (hash, rest'') = span isAlphaNum rest'
+        -> pkg ++ go pkg rest''
+      _ -> x:go pkg body'
+


=====================================
utils/haddock/html-test/Main.hs
=====================================
@@ -42,7 +42,7 @@ main = do
 
 stripIfRequired :: String -> Xml -> Xml
 stripIfRequired mdl =
-    stripLinks' . stripFooter
+    stripLinks' . stripFooter . stripVersions ["base"]
   where
     stripLinks'
         | mdl `elem` preserveLinksModules = id


=====================================
utils/haddock/html-test/ref/Bug1004.html
=====================================
@@ -210,7 +210,7 @@
 				  >D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "Product" "Data.Functor.Product" "base-4.20.0.0-inplace" ' "Product" "Data.Functor.Product" "base" 'False) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.20.0.0-inplace" ' "WrappedArrow" "Control.Applicative" "base" 'True) (C1

From gitlab at gitlab.haskell.org  Thu Oct 17 10:14:03 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 17 Oct 2024 06:14:03 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/release-ci-2
Message-ID: <6710e36b57ea9_891973cf578249da@gitlab.mail>



Matthew Pickering pushed new branch wip/release-ci-2 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/release-ci-2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 11:15:22 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Thu, 17 Oct 2024 07:15:22 -0400
Subject: [Git][ghc/ghc][wip/romes/exceptions-propagate] 7 commits: exceptions:
 Improve the message layout as per #285
Message-ID: <6710f1cabc306_9f342646b94303e7@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC


Commits:
dff0d559 by Rodrigo Mesquita at 2024-10-17T12:14:30+01:00
exceptions: Improve the message layout as per #285

This commit fixes the layout of the additional information included when
displaying an exception, namely the type of the exception.

It also fixes the default handler's heading message to work well
together with the improved display message of SomeException.

CLC proposal#285

- - - - -
1207736e by Rodrigo Mesquita at 2024-10-17T12:14:30+01:00
Display type and callstack of exception on handler

This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.

At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.

However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).

This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.

The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.

Discussion of the ammendment is part of CLC#285.

- - - - -
99bfaf19 by Rodrigo Mesquita at 2024-10-17T12:14:30+01:00
Remove redundant CallStack from exceptions

Before the exception backtraces proposal was implemented, ErrorCall
accumulated its own callstack via HasCallStack constraints, but
ExceptionContext is now accumulated automatically.

The original ErrorCall mechanism is now redundant and we get a duplicate
CallStack

Updates Cabal submodule to fix their usage of ErrorCallWithLocation to ErrorCall

CLC proposal#285

Fixes #25283

- - - - -
9866ca04 by Rodrigo Mesquita at 2024-10-17T12:14:30+01:00
Freeze call stack in error throwing functions

CLC proposal#285

- - - - -
3d3657f7 by Rodrigo Mesquita at 2024-10-17T12:14:30+01:00
De-duplicate displayContext and displayExceptionContext

The former was unused except for one module where it was essentially
re-defining displayExceptionContext.

Moreover, this commit extends the fix from
bfe600f5bb3ecd2c8fa71c536c63d3c46984e3f8 to displayExceptionContext too,
which was missing.

- - - - -
518aef2b by Rodrigo Mesquita at 2024-10-17T12:14:31+01:00
Re-export NoBacktrace from Control.Exception

This was originally proposed and accepted in section
    "2.7   Capturing Backtraces on Exceptions"
of the CLC proposal for exception backtraces.

However, the implementation missed this re-export, which this commit now
fixes.

- - - - -
27a20764 by Rodrigo Mesquita at 2024-10-17T12:14:31+01:00
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

The !13301 MR (not this commit in particular) improves performance of
MultiLayerModulesRecomp:

-------------------------
Metric Decrease:
    MultiLayerModulesRecomp
-------------------------

- - - - -


30 changed files:

- compiler/GHC/Utils/Panic/Plain.hs
- ghc/GHCi/UI/Monad.hs
- libraries/base/src/Control/Exception.hs
- libraries/base/src/GHC/Exception.hs
- libraries/base/tests/IO/T21336/T21336a.stderr
- libraries/base/tests/IO/T21336/T21336b.stderr
- libraries/base/tests/IO/T4808.stderr
- libraries/base/tests/IO/mkdirExists.stderr
- libraries/base/tests/IO/openFile002.stderr
- libraries/base/tests/IO/openFile002.stderr-mingw32
- libraries/base/tests/IO/withBinaryFile001.stderr
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile001.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking001.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/T15349.stderr
- libraries/base/tests/T16111.stderr
- libraries/base/tests/T19288.stderr
- libraries/base/tests/T24807.stderr
- libraries/base/tests/all.T
- libraries/base/tests/assert.stderr
- libraries/base/tests/readFloat.stderr
- − libraries/base/tests/topHandler04.hs
- − libraries/base/tests/topHandler04.stderr
- libraries/ghc-compact/tests/compact_function.stderr
- libraries/ghc-compact/tests/compact_mutable.stderr
- libraries/ghc-compact/tests/compact_pinned.stderr
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68b4fe075d2847f1ef7b49cd51a4cdcaff77c31a...27a207643d6aa19aa526be75cb1935ff310690b0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68b4fe075d2847f1ef7b49cd51a4cdcaff77c31a...27a207643d6aa19aa526be75cb1935ff310690b0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 12:10:02 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 17 Oct 2024 08:10:02 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] Temp workaround
Message-ID: <6710fe9abe6d8_1f80ac3b15282093e@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
fb6fbede by Sjoerd Visscher at 2024-10-17T14:09:55+02:00
Temp workaround

- - - - -


1 changed file:

- utils/haddock/haddock-api/src/Haddock.hs


Changes:

=====================================
utils/haddock/haddock-api/src/Haddock.hs
=====================================
@@ -202,7 +202,8 @@ haddockWithGhc ghc args = handleTopExceptions $ do
     when noChecks $
       hPutStrLn stderr noCheckWarning
 
-  ghc flags' $ withDir $ do
+  unless ("ghc-prim" `elem` ghcFlags flags')
+   $ ghc flags' $ withDir $ do
     dflags' <- getDynFlags
     let unicode = Flag_UseUnicode `elem` flags
     let dflags



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 12:10:53 2024
From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott))
Date: Thu, 17 Oct 2024 08:10:53 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T16234
Message-ID: <6710fecd2b651_1f80ac30857c21861@gitlab.mail>



Ryan Scott pushed new branch wip/T16234 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T16234
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 12:21:30 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 08:21:30 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 50 commits: ghci:
 mitigate host/target word size mismatch in BCOByteArray serialization
Message-ID: <6711014a91ac3_1f80ac47ba1c28225@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
b0e7b7e3 by Cheng Shao at 2024-10-17T08:21:17-04:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
a1135946 by Cheng Shao at 2024-10-17T08:21:17-04:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
ac65afdc by Cheng Shao at 2024-10-17T08:21:17-04:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
a4db0679 by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
f0eb6f67 by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0baf127e by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: correct stale link in comment

- - - - -
cd7a5c43 by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
e33fdf29 by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bbcb1520 by Cheng Shao at 2024-10-17T08:21:17-04:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
b4ab64ed by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
9e3f8f3d by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
b865b6ae by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
4c52be8d by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
e3375654 by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
4d3fcac0 by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
07089b17 by Cheng Shao at 2024-10-17T08:21:17-04:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
428f020b by Cheng Shao at 2024-10-17T08:21:17-04:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
ed08b7d3 by Cheng Shao at 2024-10-17T08:21:18-04:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
7d342a15 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
ee227950 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
0c8931fb by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
756bc177 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: bump T17572 timeout

- - - - -
65b8a5c7 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
3262a5b7 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: skip terminfo_so for cross ghc

- - - - -
8a7812a9 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
bd89f26d by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
11d01de6 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
5de14d79 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
57a9635a by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: skip rdynamic on wasm

- - - - -
4494e5cc by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
8fee655d by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
49d41da3 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
16cef0d3 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
ca549bfa by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
bc52a146 by Cheng Shao at 2024-10-17T08:21:18-04:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
738e75f7 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
d523a32b by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
c0d23718 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
15f4af71 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
0b531fe3 by Cheng Shao at 2024-10-17T08:21:18-04:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
63763f57 by Cheng Shao at 2024-10-17T08:21:18-04:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
3462ca24 by Cheng Shao at 2024-10-17T08:21:18-04:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
0169289a by Cheng Shao at 2024-10-17T08:21:18-04:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
c4d89f70 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
de186605 by Cheng Shao at 2024-10-17T08:21:18-04:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
0b480f9f by Cheng Shao at 2024-10-17T08:21:18-04:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
d5dd5685 by Cheng Shao at 2024-10-17T08:21:18-04:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
c5415ee1 by Cheng Shao at 2024-10-17T08:21:18-04:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
9271ffac by Cheng Shao at 2024-10-17T08:21:22-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
d7d1da7d by Cheng Shao at 2024-10-17T08:21:22-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- + compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/ghc.cabal.in
- ghc/Main.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/doc/flavours.md
- hadrian/src/Base.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72e8f628cecf5502541b3ef9f6d30f71f74f4a6f...d7d1da7d919d7f52867977edb8a721a306fb1cec

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72e8f628cecf5502541b3ef9f6d30f71f74f4a6f...d7d1da7d919d7f52867977edb8a721a306fb1cec
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 13:17:41 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Thu, 17 Oct 2024 09:17:41 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] 55 commits:
 javascript: Read fields of ObjectBlock lazily
Message-ID: <67110e7550d2f_3f20a615872c24957@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
eb21183c by Andreas Klebinger at 2024-10-17T14:57:52+02:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
e36102d1 by Andreas Klebinger at 2024-10-17T14:57:53+02:00
Don't push breakpoints because they are urkh

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d17c1c55397c9e1929d711b29a060b056fd3348a...e36102d1c402de7647e8576a9b79c288eccd6a60

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d17c1c55397c9e1929d711b29a060b056fd3348a...e36102d1c402de7647e8576a9b79c288eccd6a60
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 13:21:29 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Thu, 17 Oct 2024 09:21:29 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] Don't push
 breakpoints because they are urkh
Message-ID: <67110f593f62c_3f20a61584e8269e0@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
c767846f by Andreas Klebinger at 2024-10-17T15:02:04+02:00
Don't push breakpoints because they are urkh

- - - - -


1 changed file:

- compiler/GHC/Core/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -305,7 +305,9 @@ mkTick t orig_expr = mkTick' id id orig_expr
   -- Some ticks (cost-centres) can be split in two, with the
   -- non-counting part having laxer placement properties.
   canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t
-
+  isBreakpoint = case t of
+    Breakpoint{}  -> True
+    _             -> False
   -- mkTick' handles floating of ticks *into* the expression.
   -- In this function, `top` is applied after adding the tick, and `rest` before.
   -- This will result in applications that look like (top $ Tick t $ rest expr).
@@ -319,6 +321,10 @@ mkTick t orig_expr = mkTick' id id orig_expr
     -- Float ticks into unsafe coerce.
     Case scrut bndr ty alts@[Alt ac abs _rhs]
       | Just rhs <- isUnsafeEqualityCase scrut bndr alts
+      -- Moving breakpoints is around can be tricky. They capture in-scope Id's which
+      -- means there can be problems around shadowing and such.
+      -- Rather than deal with that complexity, we simply don't move them.
+      , not isBreakpoint
       -> mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
 
     -- Cost centre ticks should never be reordered relative to each



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 13:34:05 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 17 Oct 2024 09:34:05 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/generate-ghcup-anchors
Message-ID: <6711124d2d813_3f20a619c97c31441@gitlab.mail>



Zubin pushed new branch wip/generate-ghcup-anchors at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/generate-ghcup-anchors
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 13:41:03 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 17 Oct 2024 09:41:03 -0400
Subject: [Git][ghc/ghc][wip/generate-ghcup-anchors] rel-eng: ghcup metadata
 generation: generated yaml anchors with meaningful names
Message-ID: <671113efe4645_3f20a653a34033263@gitlab.mail>



Zubin pushed to branch wip/generate-ghcup-anchors at Glasgow Haskell Compiler / GHC


Commits:
759d5b2f by Zubin Duggal at 2024-10-17T19:10:56+05:30
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -


1 changed file:

- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py


Changes:

=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -67,6 +67,7 @@ class Artifact(NamedTuple):
     download_name: str
     output_name: str
     subdir: str
+    anchor_name: str
 
 # Platform spec provides a specification which is agnostic to Job
 # PlatformSpecs are converted into Artifacts by looking in the jobs-metadata.json file.
@@ -77,11 +78,13 @@ class PlatformSpec(NamedTuple):
 source_artifact = Artifact('source-tarball'
                           , 'ghc-{version}-src.tar.xz'
                           , 'ghc-{version}-src.tar.xz'
-                          , 'ghc-{version}' )
+                          , 'ghc-{version}'
+                          , 'ghc{version}-src')
 test_artifact = Artifact('source-tarball'
                         , 'ghc-{version}-testsuite.tar.xz'
                         , 'ghc-{version}-testsuite.tar.xz'
-                        , 'ghc-{version}/testsuite' )
+                        , 'ghc-{version}/testsuite'
+                        , 'ghc{version}-testsuite')
 
 def debian(n, arch='x86_64'):
     return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
@@ -132,6 +135,8 @@ def download_and_hash(url):
     hash_cache[url] = digest
     return digest
 
+uri_to_anchor_cache=dict()
+
 # Make the metadata for one platform.
 def mk_one_metadata(release_mode, version, job_map, artifact):
     job_id = job_map[artifact.job_name].id
@@ -169,6 +174,9 @@ def mk_one_metadata(release_mode, version, job_map, artifact):
         res["dlOutput"] = output
 
     eprint(res)
+
+    # add the uri to the anchor name cache so we can lookup an anchor for this uri
+    uri_to_anchor_cache[final_url] = artifact.anchor_name
     return res
 
 # Turns a platform into an Artifact respecting pipeline_type
@@ -179,7 +187,8 @@ def mk_from_platform(pipeline_type, platform):
     return Artifact(info['name']
                    , f"{info['jobInfo']['bindistName']}.tar.xz"
                    , "ghc-{version}-{pn}.tar.xz".format(version="{version}", pn=platform.name)
-                   , platform.subdir)
+                   , platform.subdir
+                   , f"ghc{{version}}-{platform.name}")
 
 
 # Generate the new metadata for a specific GHC mode etc
@@ -297,6 +306,26 @@ def setNightlyTags(ghcup_metadata):
             ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly")
 
 
+def mk_dumper(release_mode, version, date):
+  class CustomAliasDumper(yaml.Dumper):
+      def __init__(self, *args, **kwargs):
+          super().__init__(*args, **kwargs)
+          self.anchors_mapping = {}
+
+      def generate_anchor(self, node):
+          if isinstance(node, yaml.MappingNode):
+            node_dict = { k.value : v.value for (k,v) in node.value }
+            return uri_to_anchor_cache[node_dict['dlUri']].format(version=version.replace('.',''))
+          else:
+            return super().generate_anchor(node)
+
+      def represent(self, data):
+          if isinstance(data, (list, dict)) and id(data) in self.anchors:
+              if self.anchors_mapping.get(id(data)) is None:
+                  self.anchors_mapping[id(data)] = self.generate_anchor(data)
+              self.anchors[data] = self.anchors_mapping[id(data)]
+          return super().represent(data)
+  return CustomAliasDumper
 
 
 def main() -> None:
@@ -332,7 +361,7 @@ def main() -> None:
 
     new_yaml = mk_new_yaml(args.release_mode, args.version, args.date, pipeline_type, job_map)
     if args.fragment:
-        print(yaml.dump({ args.version : new_yaml }))
+        print(yaml.dump({ args.version : new_yaml }, Dumper=mk_dumper(args.release_mode, args.version, args.date)))
 
     else:
         with open(args.metadata, 'r') as file:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/759d5b2f3b7171fa42b9f4400c98b8ab81ed37d1

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 14:02:22 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 17 Oct 2024 10:02:22 -0400
Subject: [Git][ghc/ghc][wip/generate-ghcup-anchors] rel-eng: ghcup metadata
 generation: generated yaml anchors with meaningful names
Message-ID: <671118eeb336e_3f20a6578078356be@gitlab.mail>



Zubin pushed to branch wip/generate-ghcup-anchors at Glasgow Haskell Compiler / GHC


Commits:
9084fc88 by Zubin Duggal at 2024-10-17T19:32:10+05:30
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -


1 changed file:

- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py


Changes:

=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -67,6 +67,7 @@ class Artifact(NamedTuple):
     download_name: str
     output_name: str
     subdir: str
+    anchor_name: str
 
 # Platform spec provides a specification which is agnostic to Job
 # PlatformSpecs are converted into Artifacts by looking in the jobs-metadata.json file.
@@ -77,11 +78,13 @@ class PlatformSpec(NamedTuple):
 source_artifact = Artifact('source-tarball'
                           , 'ghc-{version}-src.tar.xz'
                           , 'ghc-{version}-src.tar.xz'
-                          , 'ghc-{version}' )
+                          , 'ghc-{version}'
+                          , 'ghc{version}-src')
 test_artifact = Artifact('source-tarball'
                         , 'ghc-{version}-testsuite.tar.xz'
                         , 'ghc-{version}-testsuite.tar.xz'
-                        , 'ghc-{version}/testsuite' )
+                        , 'ghc-{version}/testsuite'
+                        , 'ghc{version}-testsuite')
 
 def debian(n, arch='x86_64'):
     return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
@@ -132,6 +135,8 @@ def download_and_hash(url):
     hash_cache[url] = digest
     return digest
 
+uri_to_anchor_cache=dict()
+
 # Make the metadata for one platform.
 def mk_one_metadata(release_mode, version, job_map, artifact):
     job_id = job_map[artifact.job_name].id
@@ -169,6 +174,9 @@ def mk_one_metadata(release_mode, version, job_map, artifact):
         res["dlOutput"] = output
 
     eprint(res)
+
+    # add the uri to the anchor name cache so we can lookup an anchor for this uri
+    uri_to_anchor_cache[final_url] = artifact.anchor_name
     return res
 
 # Turns a platform into an Artifact respecting pipeline_type
@@ -179,7 +187,8 @@ def mk_from_platform(pipeline_type, platform):
     return Artifact(info['name']
                    , f"{info['jobInfo']['bindistName']}.tar.xz"
                    , "ghc-{version}-{pn}.tar.xz".format(version="{version}", pn=platform.name)
-                   , platform.subdir)
+                   , platform.subdir
+                   , f"ghc{{version}}-{platform.name}")
 
 
 # Generate the new metadata for a specific GHC mode etc
@@ -297,6 +306,19 @@ def setNightlyTags(ghcup_metadata):
             ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly")
 
 
+def mk_dumper(version):
+  class CustomAliasDumper(yaml.Dumper):
+      def __init__(self, *args, **kwargs):
+          super().__init__(*args, **kwargs)
+
+      def generate_anchor(self, node):
+          if isinstance(node, yaml.MappingNode):
+            node_dict = { k.value : v.value for (k,v) in node.value }
+            if 'dlUri' in node_dict:
+              return uri_to_anchor_cache[node_dict['dlUri']].format(version=version.replace('.',''))
+          return super().generate_anchor(node)
+
+  return CustomAliasDumper
 
 
 def main() -> None:
@@ -332,7 +354,7 @@ def main() -> None:
 
     new_yaml = mk_new_yaml(args.release_mode, args.version, args.date, pipeline_type, job_map)
     if args.fragment:
-        print(yaml.dump({ args.version : new_yaml }))
+        print(yaml.dump({ args.version : new_yaml }, Dumper=mk_dumper(args.version)))
 
     else:
         with open(args.metadata, 'r') as file:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9084fc8824b6ec53c3fabf82b22f2c93933d01ff

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 14:50:59 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Thu, 17 Oct 2024 10:50:59 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] Uphold the zipper
 structure.
Message-ID: <6711245355f7c_3f20a6afe8e4512a5@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
1328fe35 by Andreas Klebinger at 2024-10-17T16:31:20+02:00
Uphold the zipper structure.

- - - - -


1 changed file:

- compiler/GHC/Core/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -305,7 +305,6 @@ mkTick t orig_expr = mkTick' id id orig_expr
   -- Some ticks (cost-centres) can be split in two, with the
   -- non-counting part having laxer placement properties.
   canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t
-
   -- mkTick' handles floating of ticks *into* the expression.
   -- In this function, `top` is applied after adding the tick, and `rest` before.
   -- This will result in applications that look like (top $ Tick t $ rest expr).
@@ -316,10 +315,10 @@ mkTick t orig_expr = mkTick' id id orig_expr
           -> CoreExpr               -- current expression
           -> CoreExpr
   mkTick' top rest expr = case expr of
-    -- Float ticks into unsafe coerce.
+    -- Float ticks into unsafe coerce the same way we would do with a cast.
     Case scrut bndr ty alts@[Alt ac abs _rhs]
       | Just rhs <- isUnsafeEqualityCase scrut bndr alts
-      -> mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
+      -> top $ mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
 
     -- Cost centre ticks should never be reordered relative to each
     -- other. Therefore we can stop whenever two collide.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1328fe354923e2cbf84a5cd34bf1e47215f25141

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 15:55:20 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 17 Oct 2024 11:55:20 -0400
Subject: [Git][ghc/ghc][wip/T25266] 6 commits: GHCi: fix improper location of
 ghci_history file
Message-ID: <6711336829aad_16e9a324df887708f@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
787187fc by Simon Peyton Jones at 2024-10-17T16:52:26+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a26899fa by Simon Peyton Jones at 2024-10-17T16:53:34+01:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


19 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/458764e15adce1436c6877deaa657b8cfaaa9825...a26899fa6f44cae04a715a6ede70cf2804e2ce61

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/458764e15adce1436c6877deaa657b8cfaaa9825...a26899fa6f44cae04a715a6ede70cf2804e2ce61
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 17:13:48 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 17 Oct 2024 13:13:48 -0400
Subject: [Git][ghc/ghc][ghc-9.8] bindist: Use complete relative paths when
 cding to directories
Message-ID: <671145cc20c18_19a3565259e0109020@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
e9aabcf5 by Matthew Pickering at 2024-10-17T13:10:09-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

(cherry picked from commit 383c01a8928779920b4edea2f9d886ff303b8bd3)

- - - - -


1 changed file:

- hadrian/bindist/Makefile


Changes:

=====================================
hadrian/bindist/Makefile
=====================================
@@ -165,7 +165,7 @@ install_lib: lib/settings
 	$(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)"
 	
 	@dest="$(DESTDIR)$(ActualLibsDir)"; \
-	cd lib; \
+	cd ./lib; \
 	for i in `$(FIND) . -type f`; do \
 		$(INSTALL_DIR) "$$dest/`dirname $$i`" ; \
 		case $$i in \
@@ -195,7 +195,7 @@ install_docs:
 	$(INSTALL_DIR) "$(DESTDIR)$(docdir)"
 
 	if [ -d doc ]; then \
-		cd doc; $(FIND) . -type f -exec sh -c \
+		cd ./doc; $(FIND) . -type f -exec sh -c \
 			'$(INSTALL_DIR) "$(DESTDIR)$(docdir)/`dirname $$1`" && $(INSTALL_DATA) "$$1" "$(DESTDIR)$(docdir)/`dirname $$1`"' \
 			sh '{}' ';'; \
 	fi
@@ -210,7 +210,7 @@ install_docs:
 install_data:
 	@echo "Copying data to $(DESTDIR)share"
 	$(INSTALL_DIR) "$(DESTDIR)$(datadir)"
-	cd share; $(FIND) . -type f -exec sh -c \
+	cd ./share; $(FIND) . -type f -exec sh -c \
 		'$(INSTALL_DIR) "$(DESTDIR)$(datadir)/`dirname $$1`" && \
 		$(INSTALL_DATA) "$$1" "$(DESTDIR)$(datadir)/`dirname $$1`"' \
 		sh '{}' ';';
@@ -231,7 +231,7 @@ export SHELL
 install_wrappers: install_bin_libdir install_hsc2hs_wrapper
 	@echo "Installing wrapper scripts"
 	$(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)"
-	for p in `cd wrappers; $(FIND) . ! -type d`; do \
+	for p in `cd ./wrappers; $(FIND) . ! -type d`; do \
 	    mk/install_script.sh "$$p" "$(DESTDIR)/$(WrapperBinsDir)/$$p" "$(WrapperBinsDir)" "$(ActualBinsDir)" "$(ActualBinsDir)/$$p" "$(ActualLibsDir)" "$(docdir)" "$(includedir)"; \
 	done
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 17:22:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 13:22:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Revert
 "compiler: start deprecating cmmToRawCmmHook"
Message-ID: <671147ba663ee_19a3564a35301133aa@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
9dc9be7e by Cheng Shao at 2024-10-17T13:21:53-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
b9b59b69 by Cheng Shao at 2024-10-17T13:21:53-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -


3 changed files:

- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- rts/Interpreter.c


Changes:

=====================================
compiler/GHC/Driver/Hooks.hs
=====================================
@@ -154,8 +154,6 @@ data Hooks = Hooks
                                  -> IO (CgStream RawCmmGroup a)))
   }
 
-{-# DEPRECATED cmmToRawCmmHook "cmmToRawCmmHook is being deprecated. If you do use it in your project, please raise a GHC issue!" #-}
-
 class HasHooks m where
     getHooks :: m Hooks
 


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -5,9 +5,6 @@
 
 {-# OPTIONS_GHC -fprof-auto-top #-}
 
--- Remove this after cmmToRawCmmHook removal
-{-# OPTIONS_GHC -Wno-deprecations #-}
-
 -------------------------------------------------------------------------------
 --
 -- | Main API for compiling plain Haskell source code.


=====================================
rts/Interpreter.c
=====================================
@@ -157,11 +157,11 @@ tag functions as tag inference currently doesn't rely on those being properly ta
    cap->r.rRet = (retcode);                             \
    return cap;
 
-#define Sp_plusB(n)  ((void *)(((StgWord8*)Sp) + (n)))
-#define Sp_minusB(n) ((void *)(((StgWord8*)Sp) - (n)))
+#define Sp_plusB(n)  ((void *)((StgWord8*)Sp + (ptrdiff_t)(n)))
+#define Sp_minusB(n) ((void *)((StgWord8*)Sp - (ptrdiff_t)(n)))
 
-#define Sp_plusW(n)  (Sp_plusB((n) * sizeof(W_)))
-#define Sp_minusW(n) (Sp_minusB((n) * sizeof(W_)))
+#define Sp_plusW(n)  (Sp_plusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
+#define Sp_minusW(n) (Sp_minusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
 
 #define Sp_addB(n)   (Sp = Sp_plusB(n))
 #define Sp_subB(n)   (Sp = Sp_minusB(n))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7d1da7d919d7f52867977edb8a721a306fb1cec...b9b59b69a905bcbc7175e2c654614da47d8e6f3b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7d1da7d919d7f52867977edb8a721a306fb1cec...b9b59b69a905bcbc7175e2c654614da47d8e6f3b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 18:18:25 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Thu, 17 Oct 2024 14:18:25 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-4] 13 commits: Changed
 import from Ghc.  module to L.H.S module
Message-ID: <671154f14f45d_1773722959784947a@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
1d3de5e8 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

This has a knock-on to everything that uses HsDataDefn

- - - - -
cc7cdde2 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] for FunDep

- - - - -
ab14b939 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpann] from FamilyDecl

- - - - -
c9b60172 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] From InjectivityAnn

- - - - -
5a08aa13 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] from DefaultDecl

- - - - -
f87911b3 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] from RuleDecls

- - - - -
36635f27 by Alan Zimmerman at 2024-10-17T18:22:18+01:00
EPA: Remove [AddEpAnn] from Warnings

- - - - -


30 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- docs/users_guide/9.14.1-notes.rst
- ghc/GHCi/UI.hs
- libraries/base/src/Control/Category.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Category.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/702436846e62fe35f25edddfe7ff86ea7694b43c...36635f27a55a3d8d9f1ad1314d09d02b212a9040

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/702436846e62fe35f25edddfe7ff86ea7694b43c...36635f27a55a3d8d9f1ad1314d09d02b212a9040
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 19:58:27 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Thu, 17 Oct 2024 15:58:27 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-4] EPA: Remove [AddEpAnn]
 Commit 4
Message-ID: <67116c61b5cea_3076e040838c33295@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC


Commits:
f8d5ddc6 by Alan Zimmerman at 2024-10-17T20:56:36+01:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -


22 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,8 +31,10 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnDataDefn(..),
   AnnClassDecl(..),
   AnnSynDecl(..),
+  AnnFamilyDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -359,7 +361,7 @@ type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
-type instance XDataDecl     GhcPs = [AddEpAnn]
+type instance XDataDecl     GhcPs = NoExtField
 type instance XDataDecl     GhcRn = DataDeclRn
 type instance XDataDecl     GhcTc = DataDeclRn
 
@@ -379,9 +381,27 @@ type instance XClassDecl    GhcTc = NameSet -- FVs
 
 type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 
-type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
+type instance XCTyFamInstDecl (GhcPass _) = (EpToken "type", EpToken "instance")
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnDataDefn
+  = AnnDataDefn {
+      andd_openp    :: [EpToken "("],
+      andd_closep   :: [EpToken ")"],
+      andd_type     :: EpToken "type",
+      andd_newtype  :: EpToken "newtype",
+      andd_data     :: EpToken "data",
+      andd_instance :: EpToken "instance",
+      andd_dcolon   :: TokDcolon,
+      andd_where    :: EpToken "where",
+      andd_openc    :: EpToken "{",
+      andd_closec   :: EpToken "}",
+      andd_equal    :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnDataDefn where
+  noAnn = AnnDataDefn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
 data AnnClassDecl
   = AnnClassDecl {
       acd_class  :: EpToken "class",
@@ -559,7 +579,7 @@ pprTyClDeclFlavour (DataDecl { tcdDataDefn = HsDataDefn { dd_cons = nd } })
 instance OutputableBndrId p => Outputable (FunDep (GhcPass p)) where
   ppr = pprFunDep
 
-type instance XCFunDep    (GhcPass _) = [AddEpAnn]
+type instance XCFunDep    (GhcPass _) = TokRarrow
 type instance XXFunDep    (GhcPass _) = DataConCantHappen
 
 pprFundeps :: OutputableBndrId p => [FunDep (GhcPass p)] -> SDoc
@@ -593,9 +613,27 @@ type instance XCKindSig         (GhcPass _) = NoExtField
 type instance XTyVarSig         (GhcPass _) = NoExtField
 type instance XXFamilyResultSig (GhcPass _) = DataConCantHappen
 
-type instance XCFamilyDecl    (GhcPass _) = [AddEpAnn]
+type instance XCFamilyDecl    (GhcPass _) = AnnFamilyDecl
 type instance XXFamilyDecl    (GhcPass _) = DataConCantHappen
 
+data AnnFamilyDecl
+  = AnnFamilyDecl {
+      afd_openp  :: [EpToken "("],
+      afd_closep :: [EpToken ")"],
+      afd_type   :: EpToken "type",
+      afd_data   :: EpToken "data",
+      afd_family :: EpToken "family",
+      afd_dcolon :: TokDcolon,
+      afd_equal  :: EpToken "=",
+      afd_vbar   :: EpToken "|",
+      afd_where  :: EpToken "where",
+      afd_openc  :: EpToken "{",
+      afd_dotdot :: EpToken "..",
+      afd_closec :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnFamilyDecl where
+  noAnn = AnnFamilyDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 ------------- Functions over FamilyDecls -----------
 
@@ -620,7 +658,7 @@ resultVariableName _                = Nothing
 
 ------------- Pretty printing FamilyDecls -----------
 
-type instance XCInjectivityAnn  (GhcPass _) = [AddEpAnn]
+type instance XCInjectivityAnn  (GhcPass _) = TokRarrow
 type instance XXInjectivityAnn  (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -664,7 +702,7 @@ instance OutputableBndrId p
 *                                                                      *
 ********************************************************************* -}
 
-type instance XCHsDataDefn    (GhcPass _) = NoExtField
+type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
 type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
@@ -854,7 +892,7 @@ ppr_con_names = pprWithCommas (pprPrefixOcc . unLoc)
 ************************************************************************
 -}
 
-type instance XCFamEqn    (GhcPass _) r = [AddEpAnn]
+type instance XCFamEqn    (GhcPass _) r = ([EpToken "("], [EpToken ")"], EpToken "=")
 type instance XXFamEqn    (GhcPass _) r = DataConCantHappen
 
 ----------------- Class instances -------------
@@ -1145,7 +1183,7 @@ mapDerivStrategy f ds = foldDerivStrategy ds (ViaStrategy . f) ds
 ************************************************************************
 -}
 
-type instance XCDefaultDecl    GhcPs = [AddEpAnn]
+type instance XCDefaultDecl    GhcPs = (EpToken "default", EpToken "(", EpToken ")")
 type instance XCDefaultDecl    GhcRn = NoExtField
 type instance XCDefaultDecl    GhcTc = NoExtField
 
@@ -1233,7 +1271,7 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XCRuleDecls    GhcPs = ([AddEpAnn], SourceText)
+type instance XCRuleDecls    GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XCRuleDecls    GhcRn = SourceText
 type instance XCRuleDecls    GhcTc = SourceText
 
@@ -1318,7 +1356,7 @@ pprFullRuleName st (L _ n) = pprWithSourceText st (doubleQuotes $ ftext n)
 ************************************************************************
 -}
 
-type instance XWarnings      GhcPs = ([AddEpAnn], SourceText)
+type instance XWarnings      GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XWarnings      GhcRn = SourceText
 type instance XWarnings      GhcTc = SourceText
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -61,6 +61,8 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `ext1Q` list
               `extQ` list_addEpAnn
               `extQ` list_epaLocation
+              `extQ` list_epTokenOpenP
+              `extQ` list_epTokenCloseP
               `extQ` string `extQ` fastString `extQ` srcSpan `extQ` realSrcSpan
               `extQ` annotationModule
               `extQ` annotationGrhsAnn
@@ -72,9 +74,13 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
+              `extQ` epTokenInstance
+              `extQ` epTokenForall
               `extQ` annParen
               `extQ` annClassDecl
               `extQ` annSynDecl
+              `extQ` annDataDefn
+              `extQ` annFamilyDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -118,6 +124,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                        $ text "blanked:" <+> text "[EpaLocation]"
               NoBlankEpAnnotations -> list ls
 
+            list_epTokenOpenP :: [EpToken "("] -> SDoc
+            list_epTokenOpenP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
+            list_epTokenCloseP :: [EpToken ")"] -> SDoc
+            list_epTokenCloseP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
             list []    = brackets empty
             list [x]   = brackets (showAstData' x)
             list (x1 : x2 : xs) =  (text "[" <> showAstData' x1)
@@ -224,6 +242,26 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                         $$ vcat [showAstData' ops, showAstData' cps,
                                  showAstData' t, showAstData' e]
 
+            annDataDefn :: AnnDataDefn -> SDoc
+            annDataDefn (AnnDataDefn a b c d e f g h i j k) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnDataDefn"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnDataDefn"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k]
+
+            annFamilyDecl :: AnnFamilyDecl -> SDoc
+            annFamilyDecl (AnnFamilyDecl a b c d e f g h i j k l) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnFamilyDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k, showAstData' l]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -253,6 +291,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenCC :: EpToken "}" -> SDoc
             epTokenCC = epToken'
 
+            epTokenInstance :: EpToken "instance" -> SDoc
+            epTokenInstance = epToken'
+
+            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall = epUniToken'
+
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc
             epToken' (EpTok s) = case ba of
              BlankEpAnnotations -> parens
@@ -265,6 +309,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "NoEpTok"
 
+            epUniToken' :: EpUniToken sym1 sym2 -> SDoc
+            epUniToken' (EpUniTok s f) = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "EpUniTok" <+> epaLocation s <+> ppr f
+            epUniToken' NoEpUniTok = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "NoEpUniTok"
+
 
             var  :: Var -> SDoc
             var v      = braces $ text "Var:" <+> ppr v


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.Hs.Type (
         pprHsArrow,
 
         HsType(..), HsCoreTy, LHsType, HsKind, LHsKind,
-        HsForAllTelescope(..), EpAnnForallTy,
+        HsForAllTelescope(..), EpAnnForallVis, EpAnnForallInvis,
         HsTyVarBndr(..), LHsTyVarBndr, AnnTyVarBndr(..),
         HsBndrKind(..),
         HsBndrVar(..),
@@ -163,16 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnnForallTy
+type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnnForallTy
+type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallTy = EpAnn (AddEpAnn, AddEpAnn)
-  -- ^ Location of 'forall' and '->' for HsForAllVis
-  -- Location of 'forall' and '.' for HsForAllInvis
+type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -184,12 +183,12 @@ type instance XHsQTvs GhcTc = HsQTvsRn
 
 type instance XXLHsQTyVars  (GhcPass _) = DataConCantHappen
 
-mkHsForAllVisTele ::EpAnnForallTy ->
+mkHsForAllVisTele ::EpAnnForallVis ->
   [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllVisTele an vis_bndrs =
   HsForAllVis { hsf_xvis = an, hsf_vis_bndrs = vis_bndrs }
 
-mkHsForAllInvisTele :: EpAnnForallTy
+mkHsForAllInvisTele :: EpAnnForallInvis
   -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllInvisTele an invis_bndrs =
   HsForAllInvis { hsf_xinvis = an, hsf_invis_bndrs = invis_bndrs }
@@ -207,7 +206,7 @@ type instance XHsOuterImplicit GhcPs = NoExtField
 type instance XHsOuterImplicit GhcRn = [Name]
 type instance XHsOuterImplicit GhcTc = [TyVar]
 
-type instance XHsOuterExplicit GhcPs _    = EpAnnForallTy
+type instance XHsOuterExplicit GhcPs _    = EpAnnForallInvis
 type instance XHsOuterExplicit GhcRn _    = NoExtField
 type instance XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag]
 
@@ -323,7 +322,7 @@ hsOuterExplicitBndrs (HsOuterImplicit{})                  = []
 mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs
 mkHsOuterImplicit = HsOuterImplicit{hso_ximplicit = noExtField}
 
-mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs]
+mkHsOuterExplicit :: EpAnnForallInvis -> [LHsTyVarBndr flag GhcPs]
                   -> HsOuterTyVarBndrs flag GhcPs
 mkHsOuterExplicit an bndrs = HsOuterExplicit { hso_xexplicit = an
                                              , hso_bndrs     = bndrs }
@@ -333,7 +332,7 @@ mkHsImplicitSigType body =
   HsSig { sig_ext   = noExtField
         , sig_bndrs = mkHsOuterImplicit, sig_body = body }
 
-mkHsExplicitSigType :: EpAnnForallTy
+mkHsExplicitSigType :: EpAnnForallInvis
                     -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs
                     -> HsSigType GhcPs
 mkHsExplicitSigType an bndrs body =


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1275,9 +1275,9 @@ topdecl :: { LHsDecl GhcPs }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
         | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
-        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
-        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getWARNING_PRAGs $1)) (fromOL $2))) }
-        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ([mo $1,mc $3], (getRULES_PRAGs $1)) (reverse $2))) }
+        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
+        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
+        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
         | annotation { $1 }
         | decl_no_th                            { $1 }
 
@@ -1300,7 +1300,7 @@ cl_decl :: { LTyClDecl GhcPs }
 --
 default_decl :: { LDefaultDecl GhcPs }
              : 'default' opt_class '(' comma_types0 ')'
-               {% amsA' (sLL $1 $> (DefaultDecl [mj AnnDefault $1,mop $3,mcp $5] $2 $4)) }
+               {% amsA' (sLL $1 $> (DefaultDecl (epTok $1,epTok $3,epTok $5) $2 $4)) }
 
 
 -- Type declarations (toplevel)
@@ -1322,17 +1322,22 @@ ty_decl :: { LTyClDecl GhcPs }
                           where_type_family
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
+             {% do { let { (tdcolon, tequal) = fst $ unLoc $4 }
+                   ; let { tvbar = fst $ unLoc $5 }
+                   ; let { (twhere, (toc, tdd, tcc)) = fst $ unLoc $6  }
+                   ; mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
                                    (snd $ unLoc $4) (snd $ unLoc $5)
-                           (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)
-                           ++ (fst $ unLoc $5) ++ (fst $ unLoc $6))  }
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar twhere toc tdd tcc) }}
 
           -- ordinary data type or newtype declaration
         | type_data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings
-                {% mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tequal = fst $ unLoc $4 }
+                  ; mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                            Nothing (reverse (snd $ unLoc $4))
                                    (fmap reverse $5)
-                           ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)) }
+                           (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)
+                             }}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
@@ -1340,18 +1345,22 @@ ty_decl :: { LTyClDecl GhcPs }
         | type_data_or_newtype capi_ctype tycl_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tdcolon = fst $ unLoc $4 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $5 }
+                  ; mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                             (snd $ unLoc $4) (snd $ unLoc $5)
                             (fmap reverse $6)
-                            ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)++(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok tdcolon twhere oc cc NoEpTok)}}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
           -- data/newtype family
         | 'data' 'family' type opt_datafam_kind_sig
-                {% mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
                                    (snd $ unLoc $4) Nothing
-                          (mj AnnData $1:mj AnnFamily $2:(fst $ unLoc $4)) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) (epTok $2) tdcolon noAnn noAnn noAnn noAnn noAnn noAnn) }}
 
 -- standalone kind signature
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
@@ -1386,25 +1395,29 @@ inst_decl :: { LInstDecl GhcPs }
            -- type instance declarations
         | 'type' 'instance' ty_fam_inst_eqn
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                        (mj AnnType $1:mj AnnInstance $2:[]) }
+                        (epTok $1) (epTok $2) }
 
           -- data/newtype instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr constrs
                           maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                       Nothing (reverse (snd  $ unLoc $5))
                                               (fmap reverse $6)
-                      ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
           -- GADT instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { dcolon = fst $ unLoc $5 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                  ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
                                    (snd $ unLoc $5) (snd $ unLoc $6)
                                    (fmap reverse $7)
-                     ((fst $ unLoc $1):mj AnnInstance $2
-                       :(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) dcolon twhere oc cc NoEpTok)}}
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
@@ -1439,14 +1452,14 @@ opt_class :: { Maybe (LIdP GhcPs) }
 
 -- Injective type families
 
-opt_injective_info :: { Located ([AddEpAnn], Maybe (LInjectivityAnn GhcPs)) }
-        : {- empty -}               { noLoc ([], Nothing) }
-        | '|' injectivity_cond      { sLL $1 $> ([mj AnnVbar $1]
+opt_injective_info :: { Located (EpToken "|", Maybe (LInjectivityAnn GhcPs)) }
+        : {- empty -}               { noLoc (noAnn, Nothing) }
+        | '|' injectivity_cond      { sLL $1 $> ((epTok $1)
                                                 , Just ($2)) }
 
 injectivity_cond :: { LInjectivityAnn GhcPs }
         : tyvarid '->' inj_varids
-           {% amsA' (sLL $1 $> (InjectivityAnn [mu AnnRarrow $2] $1 (reverse (unLoc $3)))) }
+           {% amsA' (sLL $1 $> (InjectivityAnn (epUniTok $2) $1 (reverse (unLoc $3)))) }
 
 inj_varids :: { Located [LocatedN RdrName] }
         : inj_varids tyvarid  { sLL $1 $> ($2 : unLoc $1) }
@@ -1454,21 +1467,20 @@ inj_varids :: { Located [LocatedN RdrName] }
 
 -- Closed type families
 
-where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
-        : {- empty -}                      { noLoc ([],OpenTypeFamily) }
+where_type_family :: { Located ((EpToken "where", (EpToken "{", EpToken "..", EpToken "}")),FamilyInfo GhcPs) }
+        : {- empty -}                      { noLoc (noAnn,OpenTypeFamily) }
         | 'where' ty_fam_inst_eqn_list
-               { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
+               { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
                     ,ClosedTypeFamily (fmap reverse $ snd $ unLoc $2)) }
 
-ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
-        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
+ty_fam_inst_eqn_list :: { Located ((EpToken "{", EpToken "..", EpToken "}"),Maybe [LTyFamInstEqn GhcPs]) }
+        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ((epTok $1,noAnn, epTok $3)
                                                 ,Just (unLoc $2)) }
         | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
-                                             L loc ([],Just (unLoc $2)) }
-        |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
-                                                 ,mcc $3],Nothing) }
+                                             L loc (noAnn,Just (unLoc $2)) }
+        |     '{' '..' '}'                 { sLL $1 $> ((epTok $1,epTok $2 ,epTok $3),Nothing) }
         | vocurly '..' close               { let (L loc _) = $2 in
-                                             L loc ([mj AnnDotdot $2],Nothing) }
+                                             L loc ((noAnn,epTok $2, noAnn),Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
         : ty_fam_inst_eqns ';' ty_fam_inst_eqn
@@ -1492,9 +1504,9 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
                     ; tvbs <- fromSpecTyVarBndrs $2
                     ; let loc = comb2 $1 $>
                     ; !cs <- getCommentsFor loc
-                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs) $4 $6 [mj AnnEqual $5] }}
+                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs) $4 $6 (epTok $5) }}
         | type '=' ktype
-              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (mj AnnEqual $2:[]) }
+              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (epTok $2) }
               -- Note the use of type for the head; this allows
               -- infix type constructors and type patterns
 
@@ -1510,40 +1522,42 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
 at_decl_cls :: { LHsDecl GhcPs }
         :  -- data family declarations, with optional 'family' keyword
           'data' opt_family type opt_datafam_kind_sig
-                {% liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
                                                   (snd $ unLoc $4) Nothing
-                        (mj AnnData $1:$2++(fst $ unLoc $4))) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) $2 tdcolon noAnn noAnn noAnn noAnn noAnn noAnn)) }}
 
            -- type family declarations, with optional 'family' keyword
            -- (can't use opt_instance because you get shift/reduce errors
         | 'type' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $3 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $2 $3) OpenTypeFamily NotTopLevel $2
                                    (fst . snd $ unLoc $3)
                                    (snd . snd $ unLoc $3)
-                         (mj AnnType $1:(fst $ unLoc $3)) )}
+                         (AnnFamilyDecl [] [] (epTok $1) noAnn noAnn tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
         | 'type' 'family' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $4 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $3 $4) OpenTypeFamily NotTopLevel $3
                                    (fst . snd $ unLoc $4)
                                    (snd . snd $ unLoc $4)
-                         (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)))}
-
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
            -- default type instances, with optional 'instance' keyword
         | 'type' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $2) (unLoc $2)
-                          [mj AnnType $1]) }
+                          (epTok $1) NoEpTok) }
         | 'type' 'instance' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                              (mj AnnType $1:mj AnnInstance $2:[]) )}
+                              (epTok $1) (epTok $2) )}
 
-opt_family   :: { [AddEpAnn] }
-              : {- empty -}   { [] }
-              | 'family'      { [mj AnnFamily $1] }
+opt_family   :: { EpToken "family" }
+              : {- empty -}   { noAnn }
+              | 'family'      { (epTok $1) }
 
-opt_instance :: { [AddEpAnn] }
-              : {- empty -} { [] }
-              | 'instance'  { [mj AnnInstance $1] }
+opt_instance :: { EpToken "instance" }
+              : {- empty -} { NoEpTok }
+              | 'instance'  { epTok $1 }
 
 -- Associated type instances
 --
@@ -1553,57 +1567,63 @@ at_decl_inst :: { LInstDecl GhcPs }
                 -- Note the use of type for the head; this allows
                 -- infix type constructors and type patterns
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                          (mj AnnType $1:$2) }
+                          (epTok $1) $2 }
 
         -- data/newtype instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr constrs maybe_derivings
-               {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                     Nothing (reverse (snd $ unLoc $5))
-                                            (fmap reverse $6)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)) }
+                                             (fmap reverse $6)
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
         -- GADT instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-                {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
+             {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                   ; let { dcolon = fst $ unLoc $5 }
+                   ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                   ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
                                 (unLoc $4) (snd $ unLoc $5) (snd $ unLoc $6)
                                 (fmap reverse $7)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 dcolon twhere oc cc NoEpTok)}}
 
-type_data_or_newtype :: { Located ([AddEpAnn], Bool, NewOrData) }
-        : 'data'        { sL1 $1 ([mj AnnData    $1],            False,DataType) }
-        | 'newtype'     { sL1 $1 ([mj AnnNewtype $1],            False,NewType) }
-        | 'type' 'data' { sL1 $1 ([mj AnnType $1, mj AnnData $2],True ,DataType) }
+type_data_or_newtype :: { Located ((EpToken "data", EpToken "newtype", EpToken "type")
+                                   , Bool, NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok,  NoEpTok),  False,DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1, NoEpTok),  False,NewType) }
+        | 'type' 'data' { sL1 $1 ((epTok $2, NoEpTok,  epTok $1), True ,DataType) }
 
-data_or_newtype :: { Located (AddEpAnn, NewOrData) }
-        : 'data'        { sL1 $1 (mj AnnData    $1,DataType) }
-        | 'newtype'     { sL1 $1 (mj AnnNewtype $1,NewType) }
+data_or_newtype :: { Located ((EpToken "data", EpToken "newtype"), NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok), DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1),NewType) }
 
 -- Family result/return kind signatures
 
-opt_kind_sig :: { Located ([AddEpAnn], Maybe (LHsKind GhcPs)) }
-        :               { noLoc     ([]               , Nothing) }
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], Just $2) }
+opt_kind_sig :: { Located (TokDcolon, Maybe (LHsKind GhcPs)) }
+        :               { noLoc     (NoEpUniTok , Nothing) }
+        | '::' kind     { sLL $1 $> (epUniTok $1, Just $2) }
 
-opt_datafam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :               { noLoc     ([]               , noLocA (NoSig noExtField)         )}
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig noExtField $2))}
+opt_datafam_kind_sig :: { Located (TokDcolon, LFamilyResultSig GhcPs) }
+        :               { noLoc     (noAnn,       noLocA (NoSig noExtField)         )}
+        | '::' kind     { sLL $1 $> (epUniTok $1, sLLa $1 $> (KindSig noExtField $2))}
 
-opt_tyfam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :              { noLoc     ([]               , noLocA     (NoSig    noExtField)   )}
-        | '::' kind    { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig  noExtField $2))}
+opt_tyfam_kind_sig :: { Located ((TokDcolon, EpToken "="), LFamilyResultSig GhcPs) }
+        :              { noLoc     (noAnn               , noLocA     (NoSig    noExtField)   )}
+        | '::' kind    { sLL $1 $> ((epUniTok $1, noAnn), sLLa $1 $> (KindSig  noExtField $2))}
         | '='  tv_bndr {% do { tvb <- fromSpecTyVarBndr $2
-                             ; return $ sLL $1 $> ([mj AnnEqual $1], sLLa $1 $> (TyVarSig noExtField tvb))} }
+                             ; return $ sLL $1 $> ((noAnn, epTok $1), sLLa $1 $> (TyVarSig noExtField tvb))} }
 
-opt_at_kind_inj_sig :: { Located ([AddEpAnn], ( LFamilyResultSig GhcPs
+opt_at_kind_inj_sig :: { Located ((TokDcolon, EpToken "=", EpToken "|"), ( LFamilyResultSig GhcPs
                                             , Maybe (LInjectivityAnn GhcPs)))}
-        :            { noLoc ([], (noLocA (NoSig noExtField), Nothing)) }
-        | '::' kind  { sLL $1 $> ( [mu AnnDcolon $1]
+        :            { noLoc (noAnn, (noLocA (NoSig noExtField), Nothing)) }
+        | '::' kind  { sLL $1 $> ( (epUniTok $1, noAnn, noAnn)
                                  , (sL1a $> (KindSig noExtField $2), Nothing)) }
         | '='  tv_bndr_no_braces '|' injectivity_cond
                 {% do { tvb <- fromSpecTyVarBndr $2
-                      ; return $ sLL $1 $> ([mj AnnEqual $1, mj AnnVbar $3]
+                      ; return $ sLL $1 $> ((noAnn, epTok $1, epTok $3)
                                            , (sLLa $1 $2 (TyVarSig noExtField tvb), Just $4))} }
 
 -- tycl_hdr parses the header of a class or data type decl,
@@ -1623,13 +1643,13 @@ datafam_inst_hdr :: { Located (Maybe (LHsContext GhcPs), HsOuterFamEqnTyVarBndrs
                                                          >>= \tvbs ->
                                                              (acs (comb2 $1 $>) (\loc cs -> (L loc
                                                                                   (Just ( addTrailingDarrowC $4 $5 cs)
-                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) emptyComments) tvbs, $6))))
+                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) emptyComments) tvbs, $6))))
                                                     }
         | 'forall' tv_bndrs '.' type   {% do { hintExplicitForall $1
                                              ; tvbs <- fromSpecTyVarBndrs $2
                                              ; let loc = comb2 $1 $>
                                              ; !cs <- getCommentsFor loc
-                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs, $4))
+                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs, $4))
                                        } }
         | context '=>' type         {% acs (comb2 $1 $>) (\loc cs -> (L loc (Just (addTrailingDarrowC $1 $2 cs), mkHsOuterImplicit, $3))) }
         | type                      { sL1 $1 (Nothing, mkHsOuterImplicit, $1) }
@@ -2184,11 +2204,11 @@ unpackedness :: { Located UnpackednessPragma }
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnDot $3) cs) $2 )) }}
+                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (epUniTok $1,epTok $3) cs) $2 )) }}
         | 'forall' tv_bndrs '->' {% do { hintExplicitForall $1
                                        ; req_tvbs <- fromSpecTyVarBndrs $2
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnRarrow $3) cs) req_tvbs )) }}
+                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (epUniTok $1,epUniTok $3) cs) req_tvbs )) }}
 
 -- A ktype is a ctype, possibly with a kind annotation
 ktype :: { LHsType GhcPs }
@@ -2434,7 +2454,7 @@ fds1 :: { Located [LHsFunDep GhcPs] }
 
 fd :: { LHsFunDep GhcPs }
         : varids0 '->' varids0  {% amsA' (L (comb3 $1 $2 $3)
-                                       (FunDep [mu AnnRarrow $2]
+                                       (FunDep (epUniTok $2)
                                                (reverse (unLoc $1))
                                                (reverse (unLoc $3)))) }
 
@@ -2478,20 +2498,20 @@ constructors.
 -----------------------------------------------------------------------------
 -- Datatype declarations
 
-gadt_constrlist :: { Located ([AddEpAnn]
+gadt_constrlist :: { Located ((EpToken "where", EpToken "{", EpToken "}")
                           ,[LConDecl GhcPs]) } -- Returned in order
 
         : 'where' '{'        gadt_constrs '}'    {% checkEmptyGADTs $
                                                       L (comb2 $1 $4)
-                                                        ([mj AnnWhere $1
-                                                         ,moc $2
-                                                         ,mcc $4]
+                                                        ((epTok $1
+                                                         ,epTok $2
+                                                         ,epTok $4)
                                                         , unLoc $3) }
         | 'where' vocurly    gadt_constrs close  {% checkEmptyGADTs $
                                                       L (comb2 $1 $3)
-                                                        ([mj AnnWhere $1]
+                                                        ((epTok $1, NoEpTok, NoEpTok)
                                                         , unLoc $3) }
-        | {- empty -}                            { noLoc ([],[]) }
+        | {- empty -}                            { noLoc (noAnn,[]) }
 
 gadt_constrs :: { Located [LConDecl GhcPs] }
         : gadt_constr ';' gadt_constrs
@@ -2525,8 +2545,8 @@ consequence, GADT constructor names are restricted (names like '(*)' are
 allowed in usual data constructors, but not in GADTs).
 -}
 
-constrs :: { Located ([AddEpAnn],[LConDecl GhcPs]) }
-        : '=' constrs1    { sLL $1 $2 ([mj AnnEqual $1],unLoc $2)}
+constrs :: { Located (EpToken "=",[LConDecl GhcPs]) }
+        : '=' constrs1    { sLL $1 $2 (epTok $1,unLoc $2)}
 
 constrs1 :: { Located [LConDecl GhcPs] }
         : constrs1 '|' constr


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon,
+  TokDcolon, TokRarrow,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -411,6 +411,7 @@ getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
 type TokDcolon = EpUniToken "::" "∷"
+type TokRarrow = EpUniToken "->" "→"
 
 -- | Layout information for declarations.
 data EpLayout =


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -231,41 +231,32 @@ mkTyData :: SrcSpan
          -> Maybe (LHsKind GhcPs)
          -> [LConDecl GhcPs]
          -> Located (HsDeriving GhcPs)
-         -> [AddEpAnn]
+         -> AnnDataDefn
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns = annsIn {andd_openp = ops, andd_closep = cps}
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
        ; !cs' <- getCommentsFor loc'
        ; let loc = EpAnn (spanAsAnchor loc') noAnn (cs' Semi.<> cs)
-       ; return (L loc (DataDecl { tcdDExt = anns',
+       ; return (L loc (DataDecl { tcdDExt = noExtField,
                                    tcdLName = tc, tcdTyVars = tyvars,
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
--- TODO:AZ:temporary
-openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
-openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
-openParen2AddEpAnn NoEpTok = []
-
-closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
-closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
-closeParen2AddEpAnn NoEpTok = []
-
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
            -> DataDefnCons (LConDecl GhcPs)
            -> HsDeriving GhcPs
+           -> AnnDataDefn
            -> P (HsDataDefn GhcPs)
-mkDataDefn cType mcxt ksig data_cons maybe_deriv
+mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
   = do { checkDatatypeContext mcxt
-       ; return (HsDataDefn { dd_ext = noExtField
+       ; return (HsDataDefn { dd_ext = anns
                             , dd_cType = cType
                             , dd_ctxt = mcxt
                             , dd_cons = data_cons
@@ -316,15 +307,13 @@ mkTyFamInstEqn :: SrcSpan
                -> HsOuterFamEqnTyVarBndrs GhcPs
                -> LHsType GhcPs
                -> LHsType GhcPs
-               -> [AddEpAnn]
+               -> EpToken "="
                -> P (LTyFamInstEqn GhcPs)
-mkTyFamInstEqn loc bndrs lhs rhs anns
+mkTyFamInstEqn loc bndrs lhs rhs annEq
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns'
+                        { feqn_ext    = (ops, cps, annEq)
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -339,18 +328,17 @@ mkDataFamInst :: SrcSpan
               -> Maybe (LHsKind GhcPs)
               -> [LConDecl GhcPs]
               -> Located (HsDeriving GhcPs)
-              -> [AddEpAnn]
+              -> AnnDataDefn
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; let anns' = anns {andd_openp = ops, andd_closep = cps}
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns'
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = anns'
+                  (FamEqn { feqn_ext    = ([], [], NoEpTok)
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
@@ -361,11 +349,12 @@ mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
 
 mkTyFamInst :: SrcSpan
             -> TyFamInstEqn GhcPs
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "instance"
             -> P (LInstDecl GhcPs)
-mkTyFamInst loc eqn anns = do
+mkTyFamInst loc eqn t i = do
   return (L (noAnnSrcSpan loc) (TyFamInstD noExtField
-              (TyFamInstDecl anns eqn)))
+              (TyFamInstDecl (t,i) eqn)))
 
 mkFamDecl :: SrcSpan
           -> FamilyInfo GhcPs
@@ -373,14 +362,13 @@ mkFamDecl :: SrcSpan
           -> LHsType GhcPs                   -- LHS
           -> LFamilyResultSig GhcPs          -- Optional result signature
           -> Maybe (LInjectivityAnn GhcPs)   -- Injectivity annotation
-          -> [AddEpAnn]
+          -> AnnFamilyDecl
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns' = annsIn { afd_openp = ops, afd_closep = cps }
        ; return (L loc' (FamDecl noExtField (FamilyDecl
                                            { fdExt       = anns'
                                            , fdTopLevel  = topLevel
@@ -1050,8 +1038,8 @@ checkRecordSyntax lr@(L loc r)
 
 -- | Check if the gadt_constrlist is empty. Only raise parse error for
 -- `data T where` to avoid affecting existing error message, see #8258.
-checkEmptyGADTs :: Located ([AddEpAnn], [LConDecl GhcPs])
-                -> P (Located ([AddEpAnn], [LConDecl GhcPs]))
+checkEmptyGADTs :: Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs])
+                -> P (Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs]))
 checkEmptyGADTs gadts@(L span (_, []))           -- Empty GADT declaration.
     = do gadtSyntax <- getBit GadtSyntaxBit   -- GADTs implies GADTSyntax
          unless gadtSyntax $ addError $ mkPlainErrorMsgEnvelope span $


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -1883,7 +1883,7 @@ rnDataDefn doc (HsDataDefn { dd_cType = cType, dd_ctxt = context, dd_cons = cond
 
         ; let all_fvs = fvs1 `plusFV` fvs3 `plusFV`
                         con_fvs `plusFV` sig_fvs
-        ; return ( HsDataDefn { dd_ext = noExtField, dd_cType = cType
+        ; return ( HsDataDefn { dd_ext = noAnn, dd_cType = cType
                               , dd_ctxt = context', dd_kindSig = m_sig'
                               , dd_cons = condecls'
                               , dd_derivs = derivs' }


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -291,14 +291,14 @@ cvtDec (NewtypeD ctxt tc tvs ksig constr derivs)
         ; ksig' <- cvtKind `traverse` ksig
         ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = con'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }
@@ -363,7 +363,7 @@ cvtDec (DataInstD ctxt bndrs tys ksig constrs derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; cons' <- cvtDataDefnCons False ksig $ DataTypeCons False constrs
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -385,7 +385,7 @@ cvtDec (NewtypeInstD ctxt bndrs tys ksig constr derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -504,14 +504,14 @@ cvtGenDataDec type_data ctxt tc tvs ksig constrs derivs
         ; cons' <- cvtDataDefnCons type_data ksig $
                    DataTypeCons type_data constrs
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = cons'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -76,9 +76,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnData (EpaSpan { Test20239.hs:5:1-4 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { Test20239.hs:5:6-13 }))
-        ,(AddEpAnn AnnEqual (EpaSpan { Test20239.hs:5:34 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { Test20239.hs:5:15-20 })
@@ -113,7 +114,20 @@
               {OccName: PGMigration})))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:1-4 }))
+          (EpTok (EpaSpan { Test20239.hs:5:6-13 }))
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:34 })))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -891,7 +891,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:22:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:22:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1032,8 +1045,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:24:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:24:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:24:8-9 })
@@ -1068,7 +1083,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1239,7 +1267,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:28:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:28:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1380,8 +1421,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:30:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:30:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:30:8-9 })
@@ -1416,7 +1459,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1587,7 +1643,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:34:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:34:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1728,8 +1797,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:36:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:36:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:36:8-9 })
@@ -1764,7 +1835,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1935,7 +2019,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:40:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:40:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2076,8 +2173,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:42:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:42:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:42:8-9 })
@@ -2112,7 +2211,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2283,7 +2395,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:46:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:46:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2424,8 +2549,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:48:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:48:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:48:8-9 })
@@ -2460,7 +2587,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2631,7 +2771,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:52:21-24 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:52:21-24 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2772,8 +2925,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:54:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:54:16-20 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:54:8-10 })
@@ -2808,7 +2963,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:16-20 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -59,8 +59,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T17544_kw.hs:15:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:16:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:15:6-8 })
@@ -75,7 +74,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:16:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -161,8 +173,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnNewtype (EpaSpan { T17544_kw.hs:18:1-7 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:19:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:18:9-11 })
@@ -177,7 +188,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:18:1-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:19:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:3:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:5:3 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:3:6-9 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:3:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:5:3 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -285,8 +297,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:11:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:11:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:11:6-9 })
@@ -301,7 +312,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -401,8 +425,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:14:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:14:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:14:6-9 })
@@ -417,7 +440,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -559,8 +595,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:19:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:19:6-9 })
@@ -575,7 +610,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -717,8 +765,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:27:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:27:6-9 })
@@ -733,7 +780,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -906,8 +966,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:31:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:31:6-9 })
@@ -922,7 +981,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1107,8 +1179,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:36:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:36:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:36:6-9 })
@@ -1123,7 +1194,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:11 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -82,8 +82,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:7:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:7:12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:7:6-10 })
@@ -98,7 +97,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:12 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -286,10 +298,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:10:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:10:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:10:32-33 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:10:41-45 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:10:32-33 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:41-45 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -300,7 +326,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:11:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:11:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:11:3-8 })
@@ -479,7 +509,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:12:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:12:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:12:3-8 })
@@ -642,8 +676,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:15:19 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:15:6 })
@@ -734,7 +767,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:19 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1000,10 +1046,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:18:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:18:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:18:42-43 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:18:50-54 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:18:42-43 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:50-54 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1014,7 +1074,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:19:17 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:19:17 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:19:3-4 })
@@ -1378,9 +1442,23 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:21:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:21:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:21:17-18 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:1-4 }))
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:21:17-18 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (DataFamily)
        (TopLevel)
        (L
@@ -1501,10 +1579,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnNewtype (EpaSpan { DumpParsedAst.hs:22:1-7 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { DumpParsedAst.hs:22:9-16 }))
-        ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:22:39-40 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:22:62-66 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { DumpParsedAst.hs:22:18-20 })
@@ -1613,7 +1691,22 @@
                     {OccName: Type})))))))))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:1-7 }))
+          (NoEpTok)
+          (EpTok (EpaSpan { DumpParsedAst.hs:22:9-16 }))
+          (EpUniTok
+           (EpaSpan { DumpParsedAst.hs:22:39-40 })
+           (NormalSyntax))
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:62-66 }))
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Just
@@ -1779,8 +1872,9 @@
                     (EpAnn
                      (EpaSpan { DumpParsedAst.hs:23:11-20 })
                      ((,)
-                      (AddEpAnn AnnForall (EpaSpan { DumpParsedAst.hs:23:11-16 }))
-                      (AddEpAnn AnnDot (EpaSpan { DumpParsedAst.hs:23:20 })))
+                      (EpUniTok (EpaSpan { DumpParsedAst.hs:23:11-16 }) NormalSyntax)
+                      (EpTok
+                       (EpaSpan { DumpParsedAst.hs:23:20 })))
                      (EpaComments
                       []))
                     [(L


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -154,7 +154,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -245,7 +256,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -256,7 +279,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:13:3-8 })
@@ -429,7 +455,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:14:3-8 })
@@ -671,7 +700,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (TopLevel)
          (L
@@ -784,7 +825,10 @@
         (NoExtField)
         (DataFamInstDecl
          (FamEqn
-          []
+          ((,,)
+           []
+           []
+           (NoEpTok))
           (L
            (EpAnn
             (EpaSpan { DumpRenamedAst.hs:19:18-20 })
@@ -888,7 +932,18 @@
                      {Name: GHC.Types.Type}))))))))))]
           (Prefix)
           (HsDataDefn
-           (NoExtField)
+           (AnnDataDefn
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (Nothing)
            (Nothing)
            (Just
@@ -1041,8 +1096,8 @@
                       (EpAnn
                        (EpaDelta {  } (SameLine 0) [])
                        ((,)
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) []))
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) [])))
+                        (NoEpUniTok)
+                        (NoEpTok))
                        (EpaComments
                         []))
                       [(L
@@ -1347,7 +1402,18 @@
                 {Name: k}))))))])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -1452,7 +1518,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -1463,7 +1541,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:26:3-4 })
@@ -2006,7 +2087,19 @@
            (EpaComments
             []))
           (FamilyDecl
-           []
+           (AnnFamilyDecl
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (OpenTypeFamily)
            (NotTopLevel)
            (L
@@ -2176,9 +2269,15 @@
             (EpaComments
              []))
            (TyFamInstDecl
-            [(AddEpAnn AnnType (EpaSpan { DumpRenamedAst.hs:32:3-6 }))]
+            ((,)
+             (EpTok
+              (EpaSpan { DumpRenamedAst.hs:32:3-6 }))
+             (NoEpTok))
             (FamEqn
-             []
+             ((,,)
+              []
+              []
+              (NoEpTok))
              (L
               (EpAnn
                (EpaSpan { DumpRenamedAst.hs:32:8 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -84,9 +84,22 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:11:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { KindSigs.hs:11:6-11 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { KindSigs.hs:11:19-23 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:6-11 }))
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:19-23 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -97,7 +110,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:12:9 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { KindSigs.hs:12:9 })))
             (L
              (EpAnn
               (EpaSpan { KindSigs.hs:12:3-5 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -37,7 +37,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T15323.hs:5:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T15323.hs:5:21-25 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T15323.hs:5:6-17 })
@@ -90,7 +89,20 @@
            (NoExtField))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:21-25 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -131,8 +143,9 @@
              (EpAnn
               (EpaSpan { T15323.hs:6:20-29 })
               ((,)
-               (AddEpAnn AnnForall (EpaSpan { T15323.hs:6:20-25 }))
-               (AddEpAnn AnnDot (EpaSpan { T15323.hs:6:29 })))
+               (EpUniTok (EpaSpan { T15323.hs:6:20-25 }) NormalSyntax)
+               (EpTok
+                (EpaSpan { T15323.hs:6:29 })))
               (EpaComments
                []))
              [(L


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:5:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:5:6-11 })
@@ -111,7 +110,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:24 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -153,8 +165,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:6:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:6:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:6:6-11 })
@@ -219,7 +230,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:24 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T18791.hs:4:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T18791.hs:4:8-12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T18791.hs:4:6 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:8-12 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -363,6 +363,14 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
+instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+  trailing _ = []
+  setTrailing a _ = a
+
+instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+  trailing _ = []
+  setTrailing a _ = a
+
 -- ---------------------------------------------------------------------
 
 fromAnn' :: (HasEntry a) => a -> Entry
@@ -2004,17 +2012,17 @@ exactDataFamInstDecl :: (Monad m, Monoid w)
                      => [AddEpAnn] -> TopLevelFlag -> DataFamInstDecl GhcPs
                      -> EP w m ([AddEpAnn], DataFamInstDecl GhcPs)
 exactDataFamInstDecl an top_lvl
-  (DataFamInstDecl (FamEqn { feqn_ext    = an2
+  (DataFamInstDecl (FamEqn { feqn_ext    = (ops, cps, eq)
                            , feqn_tycon  = tycon
                            , feqn_bndrs  = bndrs
                            , feqn_pats   = pats
                            , feqn_fixity = fixity
                            , feqn_rhs    = defn })) = do
-    (an', an2', tycon', bndrs', pats', defn') <- exactDataDefn an2 pp_hdr defn
+    ((ops', cps', an'), tycon', bndrs', pats', defn') <- exactDataDefn pp_hdr defn
                                           -- See Note [an and an2 in exactDataFamInstDecl]
     return
       (an',
-       DataFamInstDecl ( FamEqn { feqn_ext    = an2'
+       DataFamInstDecl ( FamEqn { feqn_ext    = (ops', cps', eq)
                                 , feqn_tycon  = tycon'
                                 , feqn_bndrs  = bndrs'
                                 , feqn_pats   = pats'
@@ -2024,7 +2032,7 @@ exactDataFamInstDecl an top_lvl
   where
     pp_hdr :: (Monad m, Monoid w)
            => Maybe (LHsContext GhcPs)
-           -> EP w m ( [AddEpAnn]
+           -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
                      , LocatedN RdrName
                      , HsOuterTyVarBndrs () GhcPs
                      , HsFamEqnPats GhcPs
@@ -2033,7 +2041,7 @@ exactDataFamInstDecl an top_lvl
       an0 <- case top_lvl of
                TopLevel -> markEpAnnL an lidl AnnInstance -- TODO: maybe in toplevel
                NotTopLevel -> return an
-      exactHsFamInstLHS an0 tycon bndrs pats fixity mctxt
+      exactHsFamInstLHS ops cps an0 tycon bndrs pats fixity mctxt
 
 {-
 Note [an and an2 in exactDataFamInstDecl]
@@ -2146,11 +2154,11 @@ instance ExactPrint (WarnDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warnings (an,src) warns) = do
-    an0 <- markAnnOpen an src "{-# WARNING" -- Note: might be {-# DEPRECATED
+  exact (Warnings ((o,c),src) warns) = do
+    o' <- markAnnOpen'' o src "{-# WARNING" -- Note: might be {-# DEPRECATED
     warns' <- markAnnotated warns
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (Warnings (an1,src) warns')
+    c' <- printStringAtAA c "#-}"
+    return (Warnings ((o',c'),src) warns')
 
 -- ---------------------------------------------------------------------
 
@@ -2212,14 +2220,14 @@ instance ExactPrint FastString where
 instance ExactPrint (RuleDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (HsRules (an, src) rules) = do
-    an0 <-
+  exact (HsRules ((o,c), src) rules) = do
+    o' <-
       case src of
-        NoSourceText      -> markEpAnnLMS'' an lidl AnnOpen  (Just "{-# RULES")
-        SourceText srcTxt -> markEpAnnLMS'' an lidl AnnOpen  (Just $ unpackFS srcTxt)
+        NoSourceText      -> printStringAtAA o "{-# RULES"
+        SourceText srcTxt -> printStringAtAA o (unpackFS srcTxt)
     rules' <- markAnnotated rules
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (HsRules (an1,src) rules')
+    c' <- printStringAtAA c "#-}"
+    return (HsRules ((o',c'),src) rules')
 
 -- ---------------------------------------------------------------------
 
@@ -2344,16 +2352,16 @@ instance ExactPrint (RuleBndr GhcPs) where
 instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor fe _ _ _s = fe
-  exact (FamEqn { feqn_ext = an
+  exact (FamEqn { feqn_ext    = (ops, cps, eq)
                 , feqn_tycon  = tycon
                 , feqn_bndrs  = bndrs
                 , feqn_pats   = pats
                 , feqn_fixity = fixity
                 , feqn_rhs    = rhs }) = do
-    (an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS an tycon bndrs pats fixity Nothing
-    an1 <- markEpAnnL an0 lidl AnnEqual
+    (an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (FamEqn { feqn_ext = an1
+    return (FamEqn { feqn_ext    = ([], [], eq')
                    , feqn_tycon  = tycon'
                    , feqn_bndrs  = bndrs'
                    , feqn_pats   = pats'
@@ -2364,48 +2372,52 @@ instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
 
 exactHsFamInstLHS ::
       (Monad m, Monoid w)
-   => [AddEpAnn]
+   => [EpToken "("]
+   -> [EpToken ")"]
+   -> [AddEpAnn]
    -> LocatedN RdrName
    -> HsOuterTyVarBndrs () GhcPs
    -> HsFamEqnPats GhcPs
    -> LexicalFixity
    -> Maybe (LHsContext GhcPs)
-   -> EP w m ( [AddEpAnn]
+   -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
              , LocatedN RdrName
              , HsOuterTyVarBndrs () GhcPs
              , HsFamEqnPats GhcPs, Maybe (LHsContext GhcPs))
-exactHsFamInstLHS an thing bndrs typats fixity mb_ctxt = do
+exactHsFamInstLHS ops cps an thing bndrs typats fixity mb_ctxt = do
+  -- TODO:AZ: do these ans exist? They are in the binders now
   an0 <- markEpAnnL an lidl AnnForall
   bndrs' <- markAnnotated bndrs
   an1 <- markEpAnnL an0 lidl AnnDot
   mb_ctxt' <- mapM markAnnotated mb_ctxt
-  (an2, thing', typats') <- exact_pats an1 typats
-  return (an2, thing', bndrs', typats', mb_ctxt')
+  (ops', cps', thing', typats') <- exact_pats ops cps typats
+  return ((ops', cps', an1), thing', bndrs', typats', mb_ctxt')
   where
     exact_pats :: (Monad m, Monoid w)
-      => [AddEpAnn] -> HsFamEqnPats GhcPs -> EP w m ([AddEpAnn], LocatedN RdrName, HsFamEqnPats GhcPs)
-    exact_pats an' (patl:patr:pats)
+      => [EpToken "("] -> [EpToken ")"] -> HsFamEqnPats GhcPs
+      -> EP w m ([EpToken "("], [EpToken ")"], LocatedN RdrName, HsFamEqnPats GhcPs)
+    exact_pats ops cps (patl:patr:pats)
       | Infix <- fixity
       = let exact_op_app = do
-              an0 <- markEpAnnAllL' an' lidl AnnOpenP
+              ops' <- mapM markEpToken ops
               patl' <- markAnnotated patl
               thing' <- markAnnotated thing
               patr' <- markAnnotated patr
-              an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-              return (an1, thing', [patl',patr'])
+              cps' <- mapM markEpToken cps
+              return (ops', cps', thing', [patl',patr'])
         in case pats of
              [] -> exact_op_app
              _  -> do
-               (an0, thing', p) <- exact_op_app
+               (ops', cps', thing', p) <- exact_op_app
                pats' <- mapM markAnnotated pats
-               return (an0, thing', p++pats')
+               return (ops', cps', thing', p++pats')
 
-    exact_pats an' pats = do
-      an0 <- markEpAnnAllL' an' lidl AnnOpenP
+    exact_pats ops0 cps0 pats = do
+      ops' <- mapM markEpToken ops0
       thing' <- markAnnotated thing
       pats' <- markAnnotated pats
-      an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-      return (an1, thing', pats')
+      cps' <- mapM markEpToken cps0
+      return (ops', cps', thing', pats')
 
 -- ---------------------------------------------------------------------
 
@@ -2471,11 +2483,11 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact d@(TyFamInstDecl { tfid_xtn = an, tfid_eqn = eqn }) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnInstance
+  exact d@(TyFamInstDecl { tfid_xtn = (tt,ti), tfid_eqn = eqn }) = do
+    tt' <- markEpToken tt
+    ti' <- markEpToken ti
     eqn' <- markAnnotated eqn
-    return (d { tfid_xtn = an1, tfid_eqn = eqn' })
+    return (d { tfid_xtn = (tt',ti'), tfid_eqn = eqn' })
 
 -- ---------------------------------------------------------------------
 
@@ -2967,13 +2979,13 @@ instance ExactPrint (DefaultDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DefaultDecl an cl tys) = do
-    an0 <- markEpAnnL an lidl AnnDefault
-    an1 <- markEpAnnL an0 lidl AnnOpenP
+  exact (DefaultDecl (d,op,cp) cl tys) = do
+    d' <- markEpToken d
+    op' <- markEpToken op
     cl' <- markAnnotated cl
     tys' <- markAnnotated tys
-    an2 <- markEpAnnL an1 lidl AnnCloseP
-    return (DefaultDecl an2 cl' tys')
+    cp' <- markEpToken cp
+    return (DefaultDecl (d',op',cp') cl' tys')
 
 -- ---------------------------------------------------------------------
 
@@ -3773,11 +3785,11 @@ instance ExactPrint (TyClDecl GhcPs) where
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
+  exact (DataDecl { tcdDExt = x, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
-    (_, an', ltycon', tyvars', _, defn') <-
-      exactDataDefn an (exactVanillaDeclHead ltycon tyvars fixity) defn
-    return (DataDecl { tcdDExt = an', tcdLName = ltycon', tcdTyVars = tyvars'
+    (_, ltycon', tyvars', _, defn') <-
+      exactDataDefn (exactVanillaDeclHead ltycon tyvars fixity) defn
+    return (DataDecl { tcdDExt = x, tcdLName = ltycon', tcdTyVars = tyvars'
                      , tcdFixity = fixity, tcdDataDefn = defn' })
 
   -- -----------------------------------
@@ -3852,7 +3864,7 @@ instance ExactPrint (FunDep GhcPs) where
 
   exact (FunDep an ls rs') = do
     ls' <- markAnnotated ls
-    an0 <- markEpAnnL an lidl AnnRarrow
+    an0 <- markEpUniToken an
     rs'' <- markAnnotated rs'
     return (FunDep an0 ls' rs'')
 
@@ -3862,7 +3874,7 @@ instance ExactPrint (FamilyDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (FamilyDecl { fdExt = an
+  exact (FamilyDecl { fdExt = AnnFamilyDecl ops cps t d f dc eq vb w oc dd cc
                     , fdInfo = info
                     , fdTopLevel = top_level
                     , fdLName = ltycon
@@ -3870,35 +3882,37 @@ instance ExactPrint (FamilyDecl GhcPs) where
                     , fdFixity = fixity
                     , fdResultSig = L lr result
                     , fdInjectivityAnn = mb_inj }) = do
-    an0 <- exactFlavour an info
-    an1 <- exact_top_level an0
-    an2 <- annotationsToComments an1 lidl [AnnOpenP,AnnCloseP]
+    (d',t') <- exactFlavour (d,t) info
+    f' <- exact_top_level f
+
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
     (_, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    (an3, result') <- exact_kind an2
-    (an4, mb_inj') <-
+    (dc', eq', result') <- exact_kind (dc, eq)
+    (vb', mb_inj') <-
       case mb_inj of
-        Nothing -> return (an3, mb_inj)
+        Nothing -> return (vb, mb_inj)
         Just inj -> do
-          an4 <- markEpAnnL an3 lidl AnnVbar
+          vb' <- markEpToken vb
           inj' <- markAnnotated inj
-          return (an4, Just inj')
-    (an5, info') <-
+          return (vb', Just inj')
+    (w', oc', dd', cc', info') <-
              case info of
                ClosedTypeFamily mb_eqns -> do
-                 an5 <- markEpAnnL an4 lidl AnnWhere
-                 an6 <- markEpAnnL an5 lidl AnnOpenC
-                 (an7, mb_eqns') <-
+                 w' <- markEpToken w
+                 oc' <- markEpToken oc
+                 (dd', mb_eqns') <-
                    case mb_eqns of
                      Nothing -> do
-                       an7 <- markEpAnnL an6 lidl AnnDotdot
-                       return (an7, mb_eqns)
+                       dd' <- markEpToken dd
+                       return (dd', mb_eqns)
                      Just eqns -> do
                        eqns' <- markAnnotated eqns
-                       return (an6, Just eqns')
-                 an8 <- markEpAnnL an7 lidl AnnCloseC
-                 return (an8, ClosedTypeFamily mb_eqns')
-               _ -> return (an4, info)
-    return (FamilyDecl { fdExt = an5
+                       return (dd, Just eqns')
+                 cc' <- markEpToken cc
+                 return (w',oc',dd',cc', ClosedTypeFamily mb_eqns')
+               _ -> return (w,oc,dd,cc, info)
+    return (FamilyDecl { fdExt = AnnFamilyDecl [] [] t' d' f' dc' eq' vb' w' oc' dd' cc'
                        , fdInfo = info'
                        , fdTopLevel = top_level
                        , fdLName = ltycon'
@@ -3907,86 +3921,91 @@ instance ExactPrint (FamilyDecl GhcPs) where
                        , fdResultSig = L lr result'
                        , fdInjectivityAnn = mb_inj' })
     where
-      exact_top_level an' =
+      exact_top_level tfamily =
         case top_level of
-          TopLevel    -> markEpAnnL an' lidl AnnFamily
+          TopLevel    -> markEpToken tfamily
           NotTopLevel -> do
             -- It seems that in some kind of legacy
             -- mode the 'family' keyword is still
             -- accepted.
-            markEpAnnL an' lidl AnnFamily
+            markEpToken tfamily
 
-      exact_kind an' =
+      exact_kind (tdcolon, tequal) =
         case result of
-          NoSig    _         -> return (an', result)
+          NoSig    _         -> return (tdcolon, tequal, result)
           KindSig  x kind    -> do
-            an0 <- markEpAnnL an' lidl AnnDcolon
+            tdcolon' <- markEpUniToken tdcolon
             kind' <- markAnnotated kind
-            return (an0, KindSig  x kind')
+            return (tdcolon', tequal, KindSig  x kind')
           TyVarSig x tv_bndr -> do
-            an0 <- markEpAnnL an' lidl AnnEqual
+            tequal' <- markEpToken tequal
             tv_bndr' <- markAnnotated tv_bndr
-            return (an0, TyVarSig x tv_bndr')
+            return (tdcolon, tequal', TyVarSig x tv_bndr')
 
 
-exactFlavour :: (Monad m, Monoid w) => [AddEpAnn] -> FamilyInfo GhcPs -> EP w m [AddEpAnn]
-exactFlavour an DataFamily            = markEpAnnL an lidl AnnData
-exactFlavour an OpenTypeFamily        = markEpAnnL an lidl AnnType
-exactFlavour an (ClosedTypeFamily {}) = markEpAnnL an lidl AnnType
+exactFlavour :: (Monad m, Monoid w) => (EpToken "data", EpToken "type") -> FamilyInfo GhcPs -> EP w m (EpToken "data", EpToken "type")
+exactFlavour (td,tt) DataFamily            = (\td' -> (td',tt)) <$> markEpToken td
+exactFlavour (td,tt) OpenTypeFamily        = (td,)              <$> markEpToken tt
+exactFlavour (td,tt) (ClosedTypeFamily {}) = (td,)              <$> markEpToken tt
 
 -- ---------------------------------------------------------------------
 
 exactDataDefn
   :: (Monad m, Monoid w)
-  => [AddEpAnn]
-  -> (Maybe (LHsContext GhcPs) -> EP w m ([AddEpAnn]
+  => (Maybe (LHsContext GhcPs) -> EP w m (r
                                          , LocatedN RdrName
                                          , a
                                          , b
                                          , Maybe (LHsContext GhcPs))) -- Printing the header
   -> HsDataDefn GhcPs
-  -> EP w m ( [AddEpAnn] -- ^ from exactHdr
-            , [AddEpAnn] -- ^ updated one passed in
+  -> EP w m ( r -- ^ from exactHdr
             , LocatedN RdrName, a, b, HsDataDefn GhcPs)
-exactDataDefn an exactHdr
-                 (HsDataDefn { dd_ext = x, dd_ctxt = context
+exactDataDefn exactHdr
+                 (HsDataDefn { dd_ext = AnnDataDefn ops cps t nt d i dc w oc cc eq
+                             , dd_ctxt = context
                              , dd_cType = mb_ct
                              , dd_kindSig = mb_sig
                              , dd_cons = condecls, dd_derivs = derivings }) = do
 
-  an' <- annotationsToComments an lidl [AnnOpenP, AnnCloseP]
 
-  an0 <- case condecls of
-    DataTypeCons is_type_data _ -> do
-      an0' <- if is_type_data
-                then markEpAnnL an' lidl AnnType
-                else return an'
-      markEpAnnL an0' lidl AnnData
-    NewTypeCon   _ -> markEpAnnL an' lidl AnnNewtype
+  epTokensToComments AnnOpenP ops
+  epTokensToComments AnnCloseP cps
 
-  an1 <- markEpAnnL an0 lidl AnnInstance -- optional
+  (t',nt',d') <- case condecls of
+    DataTypeCons is_type_data _ -> do
+      t' <- if is_type_data
+                then markEpToken t
+                else return t
+      d' <- markEpToken d
+      return (t',nt,d')
+    NewTypeCon   _ -> do
+      nt' <- markEpToken nt
+      return (t, nt', d)
+
+  i' <- markEpToken i -- optional
   mb_ct' <- mapM markAnnotated mb_ct
   (anx, ln', tvs', b, mctxt') <- exactHdr context
-  (an2, mb_sig') <- case mb_sig of
-    Nothing -> return (an1, Nothing)
+  (dc', mb_sig') <- case mb_sig of
+    Nothing -> return (dc, Nothing)
     Just kind -> do
-      an2 <- markEpAnnL an1 lidl AnnDcolon
+      dc' <- markEpUniToken dc
       kind' <- markAnnotated kind
-      return (an2, Just kind')
-  an3 <- if (needsWhere condecls)
-    then markEpAnnL an2 lidl AnnWhere
-    else return an2
-  an4 <- markEpAnnL an3 lidl AnnOpenC
-  (an5, condecls') <- exact_condecls an4 (toList condecls)
+      return (dc', Just kind')
+  w' <- if (needsWhere condecls)
+    then markEpToken w
+    else return w
+  oc' <- markEpToken oc
+  (eq', condecls') <- exact_condecls eq (toList condecls)
   let condecls'' = case condecls of
-        DataTypeCons d _ -> DataTypeCons d condecls'
+        DataTypeCons td _ -> DataTypeCons td condecls'
         NewTypeCon _     -> case condecls' of
           [decl] -> NewTypeCon decl
           _ -> panic "exacprint NewTypeCon"
-  an6 <- markEpAnnL an5 lidl AnnCloseC
+  cc' <- markEpToken cc
   derivings' <- mapM markAnnotated derivings
-  return (anx, an6, ln', tvs', b,
-                 (HsDataDefn { dd_ext = x, dd_ctxt = mctxt'
+  return (anx, ln', tvs', b,
+                 (HsDataDefn { dd_ext = AnnDataDefn [] [] t' nt' d' i' dc' w' oc' cc' eq'
+                             , dd_ctxt = mctxt'
                              , dd_cType = mb_ct'
                              , dd_kindSig = mb_sig'
                              , dd_cons = condecls'', dd_derivs = derivings' }))
@@ -4032,12 +4051,11 @@ exactVanillaDeclHead thing tvs@(HsQTvs { hsq_explicit = tyvars }) fixity context
 instance ExactPrint (InjectivityAnn GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (InjectivityAnn an lhs rhs) = do
-    an0 <- markEpAnnL an lidl AnnVbar
+  exact (InjectivityAnn rarrow lhs rhs) = do
     lhs' <- markAnnotated lhs
-    an1 <- markEpAnnL an0 lidl AnnRarrow
+    rarrow' <- markEpUniToken rarrow
     rhs' <- mapM markAnnotated rhs
-    return (InjectivityAnn an1 lhs' rhs')
+    return (InjectivityAnn rarrow' lhs' rhs')
 
 -- ---------------------------------------------------------------------
 
@@ -4238,17 +4256,17 @@ instance ExactPrint (HsForAllTelescope GhcPs) where
   setAnnotationAnchor (HsForAllVis an a) anc ts cs = HsForAllVis (setAnchorEpa an anc ts cs) a
   setAnnotationAnchor (HsForAllInvis an a) anc ts cs = HsForAllInvis (setAnchorEpa an anc ts cs) a
 
-  exact (HsForAllVis an bndrs)   = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllVis (EpAnn l (f,r) cs) bndrs)   = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnRarrow
-    return (HsForAllVis an1 bndrs')
+    r' <- markEpUniToken r
+    return (HsForAllVis (EpAnn l (f',r') cs) bndrs')
 
-  exact (HsForAllInvis an bndrs) = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllInvis (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnDot
-    return (HsForAllInvis an1 bndrs')
+    d' <- markEpToken d
+    return (HsForAllInvis (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 
@@ -4430,17 +4448,17 @@ markTrailing ts = do
 
 -- based on pp_condecls in Decls.hs
 exact_condecls :: (Monad m, Monoid w)
-  => [AddEpAnn] -> [LConDecl GhcPs] -> EP w m ([AddEpAnn],[LConDecl GhcPs])
-exact_condecls an cs
+  => EpToken "=" -> [LConDecl GhcPs] -> EP w m (EpToken "=",[LConDecl GhcPs])
+exact_condecls eq cs
   | gadt_syntax                  -- In GADT syntax
   = do
       cs' <- mapM markAnnotated cs
-      return (an, cs')
+      return (eq, cs')
   | otherwise                    -- In H98 syntax
   = do
-      an0 <- markEpAnnL an lidl AnnEqual
+      eq0 <- markEpToken eq
       cs' <- mapM markAnnotated cs
-      return (an0, cs')
+      return (eq0, cs')
   where
     gadt_syntax = case cs of
       []                      -> False
@@ -4553,11 +4571,11 @@ instance ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) wher
   setAnnotationAnchor (HsOuterExplicit an a) anc ts cs = HsOuterExplicit (setAnchorEpa an anc ts cs) a
 
   exact b@(HsOuterImplicit _) = pure b
-  exact (HsOuterExplicit an bndrs) = do
-    an0 <- markLensAA an lfst -- "forall"
+  exact (HsOuterExplicit (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- "."
-    return (HsOuterExplicit an1 bndrs')
+    d' <- markEpToken d
+    return (HsOuterExplicit (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -209,10 +209,10 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
- "../../testsuite/tests/printer/Test21355.hs" Nothing
+ -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- -- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -269,7 +269,7 @@ synifyTyCon prr _coax tc
           , tcdFixity = synifyFixity tc
           , tcdDataDefn =
               HsDataDefn
-                { dd_ext = noExtField
+                { dd_ext = noAnn
                 , dd_cons = DataTypeCons False [] -- No constructors; arbitrary lie, they are neither
                 -- algebraic data nor newtype:
                 , dd_ctxt = Nothing
@@ -401,7 +401,7 @@ synifyTyCon _prr coax tc
         alg_deriv = []
         defn =
           HsDataDefn
-            { dd_ext = noExtField
+            { dd_ext = noAnn
             , dd_ctxt = alg_ctx
             , dd_cType = Nothing
             , dd_kindSig = kindSig



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 21:02:45 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Thu, 17 Oct 2024 17:02:45 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 182 commits: JS: fake support
 for native adjustors (#25159)
Message-ID: <67117b7520d04_29d17e2eb3006729e@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
ebb4021e by Sylvain Henry at 2024-10-17T14:01:02-05:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
2b0fd838 by Sylvain Henry at 2024-10-17T14:01:02-05:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
66fdf170 by Simon Peyton Jones at 2024-10-17T14:01:02-05:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
fa084000 by Simon Peyton Jones at 2024-10-17T14:01:03-05:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
b121615e by Simon Peyton Jones at 2024-10-17T14:01:03-05:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
3ae5fda6 by Andrzej Rybczak at 2024-10-17T14:01:03-05:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
46a16eed by Simon Peyton Jones at 2024-10-17T14:01:03-05:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
ef9d7433 by Hécate Kleidukos at 2024-10-17T14:01:04-05:00
haddock: Remove support for applehelp format in the Manual

- - - - -
18161e0e by doyougnu at 2024-10-17T14:01:04-05:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
e8155cd1 by Sven Tennie at 2024-10-17T14:01:04-05:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
60dddc5d by Sylvain Henry at 2024-10-17T14:01:04-05:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
000fbff0 by Hécate Kleidukos at 2024-10-17T14:01:05-05:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
7099fabf by Hécate Kleidukos at 2024-10-17T14:01:05-05:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
2369481b by Hécate Kleidukos at 2024-10-17T14:01:05-05:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
f76a337a by Simon Peyton Jones at 2024-10-17T14:01:05-05:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
bf5defde by Matthew Pickering at 2024-10-17T14:01:06-05:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
9189c2a9 by Rodrigo Mesquita at 2024-10-17T14:01:06-05:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
94f642cd by Alan Zimmerman at 2024-10-17T14:01:06-05:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
ebf7616a by Andrew Lelechenko at 2024-10-17T14:01:07-05:00
Bump submodule deepseq to 1.5.1.0

- - - - -
6ad08013 by Sebastian Graf at 2024-10-17T14:01:07-05:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
0673ef20 by Sven Tennie at 2024-10-17T14:01:07-05:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
e47315b1 by Sven Tennie at 2024-10-17T14:01:07-05:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
9a2f0019 by Sven Tennie at 2024-10-17T14:01:08-05:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
983d4283 by Sven Tennie at 2024-10-17T14:01:08-05:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
28ffe21d by Sven Tennie at 2024-10-17T14:01:08-05:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
41501f2b by Sven Tennie at 2024-10-17T14:01:08-05:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
082553c9 by Sven Tennie at 2024-10-17T14:01:09-05:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
44751057 by Sven Tennie at 2024-10-17T14:01:09-05:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
fba34da0 by Sven Tennie at 2024-10-17T14:01:09-05:00
RISCV64: Set codeowners of the NCG

- - - - -
dca01c95 by Sven Tennie at 2024-10-17T14:01:09-05:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
4fd53dc7 by Torsten Schmits at 2024-10-17T14:01:10-05:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
29affabf by Alan Zimmerman at 2024-10-17T14:01:10-05:00
EPA: Sync ghc-exactprint to GHC

- - - - -
7b148e02 by Sebastian Graf at 2024-10-17T14:01:10-05:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
3e515994 by Andrew Lelechenko at 2024-10-17T14:01:10-05:00
Bump submodule array to 0.5.8.0

- - - - -
195a2a9e by Sylvain Henry at 2024-10-17T14:01:11-05:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
16bf07f7 by Samuel Thibault at 2024-10-17T14:01:11-05:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b2d658 by Sylvain Henry at 2024-10-17T14:01:11-05:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
000d36ae by Sebastian Graf at 2024-10-17T14:01:12-05:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
cde13fee by Sebastian Graf at 2024-10-17T14:01:12-05:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
4773ad23 by Ben Gamari at 2024-10-17T14:01:12-05:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
7136936f by Mario Blažević at 2024-10-17T14:01:13-05:00
Modified the default export implementation to match the amended spec

- - - - -
0dfa0a13 by Sylvain Henry at 2024-10-17T14:01:13-05:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
e940b868 by Sebastian Graf at 2024-10-17T14:01:13-05:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
47ea99c1 by sheaf at 2024-10-17T14:01:13-05:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
55b094a5 by sheaf at 2024-10-17T14:01:14-05:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
f19c25c5 by Ryan Hendrickson at 2024-10-17T14:01:14-05:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
fd1217da by Zubin Duggal at 2024-10-17T14:01:14-05:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
206b70e8 by Andreas Klebinger at 2024-10-17T14:01:15-05:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
edcdd1ee by Hécate Kleidukos at 2024-10-17T14:01:15-05:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
a5c11517 by Zubin Duggal at 2024-10-17T14:01:15-05:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
8a1e9bc4 by Sven Tennie at 2024-10-17T14:01:16-05:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
ff156961 by Sylvain Henry at 2024-10-17T14:01:16-05:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
188468da by Zubin Duggal at 2024-10-17T14:01:16-05:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
0b7eaad3 by Alan Zimmerman at 2024-10-17T14:01:17-05:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
f0f15383 by Matthew Pickering at 2024-10-17T14:01:17-05:00
ci: Run abi-test on test-abi label

- - - - -
8cd3d240 by Rodrigo Mesquita at 2024-10-17T14:01:17-05:00
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
3f718acd by Rodrigo Mesquita at 2024-10-17T14:01:17-05:00
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
2c396d90 by Rodrigo Mesquita at 2024-10-17T14:01:18-05:00
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
89f37bb9 by Rodrigo Mesquita at 2024-10-17T14:01:19-05:00
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
7c25dfd2 by Rodrigo Mesquita at 2024-10-17T14:01:19-05:00
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
b548554a by Rodrigo Mesquita at 2024-10-17T14:01:19-05:00
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
b2c90377 by Rodrigo Mesquita at 2024-10-17T14:01:19-05:00
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
c14e0909 by Zubin Duggal at 2024-10-17T14:01:20-05:00
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
4b0e0031 by Simon Peyton Jones at 2024-10-17T14:01:20-05:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
3866d31e by Ryan Scott at 2024-10-17T14:01:21-05:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
5829668e by ARATA Mizuki at 2024-10-17T14:01:22-05:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
07766ad2 by Zubin Duggal at 2024-10-17T14:01:22-05:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
198c11cf by Sylvain Henry at 2024-10-17T14:01:22-05:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
01aed266 by Simon Peyton Jones at 2024-10-17T14:01:22-05:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
662f135a by Sylvain Henry at 2024-10-17T14:01:23-05:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
3f766437 by Ben Gamari at 2024-10-17T14:01:23-05:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
36c626ff by Matthew Pickering at 2024-10-17T14:01:23-05:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
980109cb by Sylvain Henry at 2024-10-17T14:01:24-05:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
7f5f179d by Sylvain Henry at 2024-10-17T14:01:24-05:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
ef55c74a by Sylvain Henry at 2024-10-17T14:01:24-05:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
28ed8245 by Matthew Pickering at 2024-10-17T14:01:25-05:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
ac3f3770 by Matthew Pickering at 2024-10-17T14:01:25-05:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9f207ed7 by Matthew Pickering at 2024-10-17T14:01:25-05:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
7fa56551 by Matthew Pickering at 2024-10-17T14:01:25-05:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
2932910d by Brandon Chinn at 2024-10-17T14:01:26-05:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
3bc2e0cb by Matthew Pickering at 2024-10-17T14:01:26-05:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
17ea8466 by Matthew Pickering at 2024-10-17T14:01:26-05:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
60d04250 by Matthew Pickering at 2024-10-17T14:01:26-05:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
6f31b2b5 by Matthew Pickering at 2024-10-17T14:01:27-05:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
205d2909 by Matthew Pickering at 2024-10-17T14:01:27-05:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
b93b4405 by Matthew Pickering at 2024-10-17T14:01:27-05:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
91687ae3 by Patrick at 2024-10-17T14:01:28-05:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
481cd387 by sheaf at 2024-10-17T14:01:28-05:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
b3206fb4 by sheaf at 2024-10-17T14:01:30-05:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
9e3770a2 by sheaf at 2024-10-17T14:01:30-05:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
68a57036 by sheaf at 2024-10-17T14:01:31-05:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
2b1f60c5 by sheaf at 2024-10-17T14:01:31-05:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
ce6b8581 by sheaf at 2024-10-17T14:01:31-05:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
0cc2287a by sheaf at 2024-10-17T14:01:32-05:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
d5ce4fbd by sheaf at 2024-10-17T14:01:32-05:00
Add test for C calls & SIMD vectors

- - - - -
eeb17ac1 by sheaf at 2024-10-17T14:01:32-05:00
Add test for #25169

- - - - -
e1b799f6 by sheaf at 2024-10-17T14:01:33-05:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
191065fc by sheaf at 2024-10-17T14:01:33-05:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
20d9d55a by sheaf at 2024-10-17T14:01:34-05:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
67681b82 by sheaf at 2024-10-17T14:01:34-05:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
25085083 by sheaf at 2024-10-17T14:01:34-05:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
d03ef1f9 by sheaf at 2024-10-17T14:01:34-05:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
1ac53eab by Cheng Shao at 2024-10-17T14:01:35-05:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
1acb8a44 by Matthew Pickering at 2024-10-17T14:01:35-05:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
ddaf48d5 by Leo at 2024-10-17T14:01:35-05:00
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
9704e65b by Vladislav Zavialov at 2024-10-17T14:01:35-05:00
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
3b4e5fd1 by Matthew Pickering at 2024-10-17T14:01:36-05:00
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
12fe762a by Zubin Duggal at 2024-10-17T14:01:36-05:00
Bump GHC version to 9.12

- - - - -
e12c8f34 by Zubin Duggal at 2024-10-17T14:01:36-05:00
Bump GHC version to 9.13

- - - - -
c46b6cf8 by Andreas Klebinger at 2024-10-17T14:01:37-05:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
f505ce68 by Andreas Klebinger at 2024-10-17T14:01:37-05:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
2613a82a by Sylvain Henry at 2024-10-17T14:01:37-05:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
3fd0fd22 by Rodrigo Mesquita at 2024-10-17T14:01:38-05:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
4c409e84 by Matthew Pickering at 2024-10-17T14:01:38-05:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
53a69f24 by Matthew Pickering at 2024-10-17T14:01:38-05:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
27b77a63 by ARATA Mizuki at 2024-10-17T14:01:38-05:00
Use bundled llc/opt on Windows (#22438)

- - - - -
a238794a by Matthew Pickering at 2024-10-17T14:01:38-05:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
620a4077 by Matthew Pickering at 2024-10-17T14:01:39-05:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
dc82bdc1 by Andreas Klebinger at 2024-10-17T14:01:39-05:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
ea7820c1 by Ben Gamari at 2024-10-17T14:01:39-05:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
33492ccf by Ben Gamari at 2024-10-17T14:01:39-05:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
655c1b9f by Matthew Pickering at 2024-10-17T14:01:39-05:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
f2578952 by Zubin Duggal at 2024-10-17T14:01:40-05:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
6de41949 by Andreas Klebinger at 2024-10-17T14:01:40-05:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
a57d61ad by Ben Gamari at 2024-10-17T14:01:40-05:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
87101278 by Matthew Pickering at 2024-10-17T14:01:40-05:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
06efc73d by Matthew Pickering at 2024-10-17T14:01:41-05:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
c8e51f6e by Cheng Shao at 2024-10-17T14:01:41-05:00
testsuite: remove accidentally checked in debug print logic

- - - - -
3dfb00b6 by Rodrigo Mesquita at 2024-10-17T14:01:42-05:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
a6c871ce by Andrew Lelechenko at 2024-10-17T14:01:42-05:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
3aa1f155 by Cheng Shao at 2024-10-17T14:01:42-05:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
4e673f6d by Torsten Schmits at 2024-10-17T14:01:42-05:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
e18e6575 by Daniel Díaz at 2024-10-17T14:01:43-05:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
fd637871 by Krzysztof Gogolewski at 2024-10-17T14:01:43-05:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
75d651a2 by Alan Zimmerman at 2024-10-17T14:01:43-05:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
74e57052 by John Paul Adrian Glaubitz at 2024-10-17T14:01:43-05:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
a99afa23 by Teo Camarasu at 2024-10-17T14:01:44-05:00
Add changelog entries for !12479

- - - - -
1ab4c517 by Matthew Pickering at 2024-10-17T14:01:44-05:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
46b5240b by Matthew Pickering at 2024-10-17T14:01:44-05:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
982aaf08 by Matthew Pickering at 2024-10-17T14:01:44-05:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
03a5d01a by Arnaud Spiwack at 2024-10-17T15:35:35-05:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
0d5f1527 by Sven Tennie at 2024-10-17T15:36:19-05:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3d939b41 by Mario Blažević at 2024-10-17T15:36:19-05:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
d4b86a75 by ARATA Mizuki at 2024-10-17T15:36:19-05:00
Better documentation for floatRange function

Closes #16479

- - - - -
ab90d98f by Andreas Klebinger at 2024-10-17T15:36:20-05:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
80097aa2 by Sven Tennie at 2024-10-17T15:36:20-05:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
48fabdd3 by Cheng Shao at 2024-10-17T15:36:20-05:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
842cb073 by sheaf at 2024-10-17T15:36:20-05:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
49026b6a by Sven Tennie at 2024-10-17T15:36:20-05:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
b388eddf by Arnaud Spiwack at 2024-10-17T15:36:21-05:00
Remove unused accumulators in partition_errors

- - - - -
fc42ee37 by Andrzej Rybczak at 2024-10-17T15:36:21-05:00
Fix typo in the @since annotation of annotateIO

- - - - -
fd9c442e by Alan Zimmerman at 2024-10-17T15:36:21-05:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
8b6fef2c by Fabian Thorand at 2024-10-17T15:36:23-05:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
42e7d864 by Hassan Al-Awwadi at 2024-10-17T15:38:06-05:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
8434a5e8 by Cheng Shao at 2024-10-17T15:39:25-05:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
ce79c9e4 by Cristiano Moraes at 2024-10-17T15:39:25-05:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
a6fb8fc7 by Simon Peyton Jones at 2024-10-17T15:39:25-05:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
6011ffe9 by Simon Peyton Jones at 2024-10-17T15:39:26-05:00
Wibbles

- - - - -
721d4d11 by Simon Peyton Jones at 2024-10-17T15:39:26-05:00
Spelling errors

- - - - -
c46179ed by sheaf at 2024-10-17T15:39:26-05:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
4ec84989 by sheaf at 2024-10-17T15:39:26-05:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
1e9c09be by Cheng Shao at 2024-10-17T15:39:27-05:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
3d4c6917 by Ben Gamari at 2024-10-17T15:39:27-05:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
a15248a1 by Matthew Pickering at 2024-10-17T15:39:27-05:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
1dc44943 by Ben Gamari at 2024-10-17T15:39:27-05:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
b9dae58c by Ben Gamari at 2024-10-17T15:39:28-05:00
base: Add test for #25066

- - - - -
905209e1 by Ben Gamari at 2024-10-17T15:39:28-05:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
ee93eaa7 by Ben Gamari at 2024-10-17T15:39:28-05:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
e6248462 by Ben Gamari at 2024-10-17T15:39:28-05:00
Bump process submodule to v1.6.25.0

- - - - -
5f70faf1 by Hassan Al-Awwadi at 2024-10-17T15:39:29-05:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
7e6adf6b by Artem Pelenitsyn at 2024-10-17T15:39:29-05:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
5ef3c162 by Ben Gamari at 2024-10-17T15:39:29-05:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
2b264078 by Sylvain Henry at 2024-10-17T15:39:30-05:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
b1106ec9 by Sven Tennie at 2024-10-17T15:39:30-05:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
35aace08 by Zubin Duggal at 2024-10-17T15:39:30-05:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
c9b69663 by Zubin Duggal at 2024-10-17T15:39:30-05:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
d188488c by Zubin Duggal at 2024-10-17T15:39:31-05:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
be1424c0 by Apoorv Ingle at 2024-10-17T15:47:16-05:00
Make ApplicativeDo work with HsExpansions
testcase added: T24406
Issues Fixed: #24406, #16135

Code Changes:
- Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc`
- The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide
  if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr`

Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail

- - - - -
0619b00d by Apoorv Ingle at 2024-10-17T15:48:57-05:00
simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts

- - - - -
e396392a by Apoorv Ingle at 2024-10-17T15:49:50-05:00
make caller wrap the pop err ctxt

- - - - -
75bf3de0 by Simon Peyton Jones at 2024-10-17T15:57:58-05:00
Remove special cases

... to see what breaks

- - - - -
14dd132f by Simon Peyton Jones at 2024-10-17T16:01:04-05:00
Don't use a user SrcSpan on a Stmt expansoin

- - - - -


23 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b30ee4cc02b99251f2b5957d2cc2e82428e4e7c3...14dd132f6b335c07494bd45efd74176601f99be7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b30ee4cc02b99251f2b5957d2cc2e82428e4e7c3...14dd132f6b335c07494bd45efd74176601f99be7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 21:33:34 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Thu, 17 Oct 2024 17:33:34 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 182 commits: JS: fake support
 for native adjustors (#25159)
Message-ID: <671182ae3c744_29d17e4d6c28719c6@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
709bb3a3 by Apoorv Ingle at 2024-10-17T16:25:26-05:00
Make ApplicativeDo work with HsExpansions
testcase added: T24406
Issues Fixed: #24406, #16135

Code Changes:
- Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc`
- The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide
  if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr`

Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail

- - - - -
4bfef26a by Apoorv Ingle at 2024-10-17T16:27:04-05:00
simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts

- - - - -
63bcd2b5 by Simon Peyton Jones at 2024-10-17T16:28:56-05:00
Remove special cases

... to see what breaks

- - - - -
0f907c1a by Simon Peyton Jones at 2024-10-17T16:30:45-05:00
Don't use a user SrcSpan on a Stmt expansoin

- - - - -
fb2a76c5 by Apoorv Ingle at 2024-10-17T16:32:24-05:00
make caller wrap the pop err ctxt

- - - - -


23 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14dd132f6b335c07494bd45efd74176601f99be7...fb2a76c55fbead298474d442b6578cd2b83de316

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14dd132f6b335c07494bd45efd74176601f99be7...fb2a76c55fbead298474d442b6578cd2b83de316
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 21:53:44 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 17 Oct 2024 17:53:44 -0400
Subject: [Git][ghc/ghc][wip/T25266] Improve the generalisation code in
 Solver.simplifyInfer
Message-ID: <67118768c3c70_29d17e68559c7521a@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
3fb9764f by Simon Peyton Jones at 2024-10-17T22:53:12+01:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


23 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/typecheck/should_compile/T13785.hs
- testsuite/tests/typecheck/should_compile/T13785.stderr
- + testsuite/tests/typecheck/should_compile/T25266.hs
- + testsuite/tests/typecheck/should_compile/T25266a.hs
- + testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T25266b.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T18398.stderr


Changes:

=====================================
compiler/GHC/Data/Bag.hs
=====================================
@@ -16,7 +16,7 @@ module GHC.Data.Bag (
         mapBag, pprBag,
         elemBag, lengthBag,
         filterBag, partitionBag, partitionBagWith,
-        concatBag, catBagMaybes, foldBag,
+        concatBag, catBagMaybes, foldBag_flip,
         isEmptyBag, isSingletonBag, consBag, snocBag, anyBag, allBag,
         listToBag, nonEmptyToBag, bagToList, headMaybe, mapAccumBagL,
         concatMapBag, concatMapBagPair, mapMaybeBag, mapMaybeBagM, unzipBag,
@@ -194,24 +194,10 @@ partitionBagWith pred (TwoBags b1 b2)
 partitionBagWith pred (ListBag vs) = (listToBag sats, listToBag fails)
   where (sats, fails) = partitionWith pred (toList vs)
 
-foldBag :: (r -> r -> r) -- Replace TwoBags with this; should be associative
-        -> (a -> r)      -- Replace UnitBag with this
-        -> r             -- Replace EmptyBag with this
-        -> Bag a
-        -> r
-
-{- Standard definition
-foldBag t u e EmptyBag        = e
-foldBag t u e (UnitBag x)     = u x
-foldBag t u e (TwoBags b1 b2) = (foldBag t u e b1) `t` (foldBag t u e b2)
-foldBag t u e (ListBag xs)    = foldr (t.u) e xs
--}
-
--- More tail-recursive definition, exploiting associativity of "t"
-foldBag _ _ e EmptyBag        = e
-foldBag t u e (UnitBag x)     = u x `t` e
-foldBag t u e (TwoBags b1 b2) = foldBag t u (foldBag t u e b2) b1
-foldBag t u e (ListBag xs)    = foldr (t.u) e xs
+foldBag_flip :: (a -> b -> b) -> Bag a -> b -> b
+-- Just foldr with flipped arguments,
+-- so it can be chained more nicely
+foldBag_flip k bag z = foldr k z bag
 
 mapBag :: (a -> b) -> Bag a -> Bag b
 mapBag = fmap


=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -763,9 +763,11 @@ simplifyDeriv (DS { ds_loc = loc, ds_tvs = tvs
        -- See [STEP DAC HOIST]
        -- From the simplified constraints extract a subset 'good' that will
        -- become the context 'min_theta' for the derived instance.
-       ; let residual_simple = approximateWC True solved_wanteds
-             head_size       = pSizeClassPred clas inst_tys
-             good = mapMaybeBag get_good residual_simple
+       ; let residual_simple = approximateWC False solved_wanteds
+                -- False: ignore any non-quantifiable constraints,
+                --        including equalities hidden under Given equalities
+             head_size = pSizeClassPred clas inst_tys
+             good      = mapMaybeBag get_good residual_simple
 
              -- Returns @Just p@ (where @p@ is the type of the Ct) if a Ct is
              -- suitable to be inferred in the context of a derived instance.


=====================================
compiler/GHC/Tc/Gen/Bind.hs
=====================================
@@ -490,8 +490,8 @@ tcPolyBinds top_lvl sig_fn prag_fn rec_group rec_tc closed bind_list
     ; let plan = decideGeneralisationPlan dflags top_lvl closed sig_fn bind_list
     ; traceTc "Generalisation plan" (ppr plan)
     ; result@(_, scaled_poly_ids) <- case plan of
-         NoGen              -> tcPolyNoGen rec_tc prag_fn sig_fn bind_list
-         InferGen           -> tcPolyInfer rec_tc prag_fn sig_fn bind_list
+         NoGen              -> tcPolyNoGen         rec_tc prag_fn sig_fn bind_list
+         InferGen           -> tcPolyInfer top_lvl rec_tc prag_fn sig_fn bind_list
          CheckGen lbind sig -> tcPolyCheck prag_fn sig lbind
 
     ; let poly_ids = map scaledThing scaled_poly_ids
@@ -708,12 +708,13 @@ To address this we to do a few things
 -}
 
 tcPolyInfer
-  :: RecFlag       -- Whether it's recursive after breaking
+  :: TopLevelFlag
+  -> RecFlag       -- Whether it's recursive after breaking
                    -- dependencies based on type signatures
   -> TcPragEnv -> TcSigFun
   -> [LHsBind GhcRn]
   -> TcM (LHsBinds GhcTc, [Scaled TcId])
-tcPolyInfer rec_tc prag_fn tc_sig_fn bind_list
+tcPolyInfer top_lvl rec_tc prag_fn tc_sig_fn bind_list
   = do { (tclvl, wanted, (binds', mono_infos))
              <- pushLevelAndCaptureConstraints  $
                 tcMonoBinds rec_tc tc_sig_fn LetLclBndr bind_list
@@ -733,7 +734,7 @@ tcPolyInfer rec_tc prag_fn tc_sig_fn bind_list
 
        ; traceTc "simplifyInfer call" (ppr tclvl $$ ppr name_taus $$ ppr wanted)
        ; ((qtvs, givens, ev_binds, insoluble), residual)
-            <- captureConstraints $ simplifyInfer tclvl infer_mode sigs name_taus wanted
+            <- captureConstraints $ simplifyInfer top_lvl tclvl infer_mode sigs name_taus wanted
 
        ; let inferred_theta = map evVarPred givens
        ; scaled_exports <- checkNoErrs $


=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -696,7 +696,8 @@ tcExprSig expr sig@(TcPartialSig (PSig { psig_name = name, psig_loc = loc }))
                         | otherwise
                         = NoRestrictions
        ; ((qtvs, givens, ev_binds, _), residual)
-           <- captureConstraints $ simplifyInfer tclvl infer_mode [sig_inst] [(name, tau)] wanted
+           <- captureConstraints $
+              simplifyInfer NotTopLevel tclvl infer_mode [sig_inst] [(name, tau)] wanted
        ; emitConstraints residual
 
        ; tau <- liftZonkM $ zonkTcType tau


=====================================
compiler/GHC/Tc/Instance/FunDeps.hs
=====================================
@@ -578,11 +578,22 @@ closeWrtFunDeps preds fixed_tvs
        = case classifyPredType pred of
             EqPred NomEq t1 t2 -> [([t1],[t2]), ([t2],[t1])]
                -- See Note [Equality superclasses]
-            ClassPred cls tys  -> [ instFD fd cls_tvs tys
-                                  | let (cls_tvs, cls_fds) = classTvsFds cls
-                                  , fd <- cls_fds ]
+
+            ClassPred cls tys | not (isIPClass cls)
+               -- isIPClass: see Note [closeWrtFunDeps ignores implicit parameters]
+                              -> [ instFD fd cls_tvs tys
+                                 | let (cls_tvs, cls_fds) = classTvsFds cls
+                                 , fd <- cls_fds ]
             _ -> []
 
+{- Note [closeWrtFunDeps ignores implicit parameters]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Implicit params don't really determine a type variable (that is, we might have
+IP "c" Bool and IP "c" Int in different places within the same program), and
+skipping this causes implicit params to monomorphise too many variables; see
+Note [Inheriting implicit parameters] in GHC.Tc.Solver.  Skipping causes
+typecheck/should_compile/tc219 to fail.
+-}
 
 {- *********************************************************************
 *                                                                      *


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -2582,7 +2582,7 @@ tcRnExpr hsc_env mode rdr_expr
     let { fresh_it = itName uniq (getLocA rdr_expr) } ;
     ((qtvs, dicts, _, _), residual)
          <- captureConstraints $
-            simplifyInfer tclvl infer_mode
+            simplifyInfer TopLevel tclvl infer_mode
                           []    {- No sig vars -}
                           [(fresh_it, res_ty)]
                           lie ;


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -14,6 +14,7 @@ module GHC.Tc.Solver(
        tcCheckGivens,
        tcCheckWanteds,
        tcNormalise,
+       approximateWC,    -- Exported for plugins to use
 
        captureTopConstraints,
 
@@ -48,7 +49,7 @@ import GHC.Tc.Utils.TcType
 import GHC.Core.Predicate
 import GHC.Core.Type
 import GHC.Core.Ppr
-import GHC.Core.TyCon    ( TyConBinder, isTypeFamilyTyCon )
+import GHC.Core.TyCon    ( TyConBinder )
 
 import GHC.Types.Name
 import GHC.Types.Id
@@ -58,9 +59,11 @@ import GHC.Types.Var.Set
 import GHC.Types.Basic
 import GHC.Types.Error
 
-import GHC.Utils.Misc
+import GHC.Driver.DynFlags( DynFlags, xopt )
+import GHC.Driver.Flags( WarningFlag(..) )
 import GHC.Utils.Panic
 import GHC.Utils.Outputable
+import GHC.Utils.Misc( filterOut )
 
 import GHC.Data.Bag
 
@@ -882,7 +885,8 @@ instance Outputable InferMode where
   ppr EagerDefaulting = text "EagerDefaulting"
   ppr NoRestrictions  = text "NoRestrictions"
 
-simplifyInfer :: TcLevel               -- Used when generating the constraints
+simplifyInfer :: TopLevelFlag
+              -> TcLevel               -- Used when generating the constraints
               -> InferMode
               -> [TcIdSigInst]         -- Any signatures (possibly partial)
               -> [(Name, TcTauType)]   -- Variables to be generalised,
@@ -893,7 +897,7 @@ simplifyInfer :: TcLevel               -- Used when generating the constraints
                       TcEvBinds,    -- ... binding these evidence variables
                       Bool)         -- True <=> the residual constraints are insoluble
 
-simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
+simplifyInfer top_lvl rhs_tclvl infer_mode sigs name_taus wanteds
   | isEmptyWC wanteds
    = do { -- When quantifying, we want to preserve any order of variables as they
           -- appear in partial signatures. cf. decideQuantifiedTyVars
@@ -946,9 +950,8 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
        ; wanted_transformed <- TcM.liftZonkM $ TcM.zonkWC wanted_transformed
        ; let definite_error = insolubleWC wanted_transformed
                               -- See Note [Quantification with errors]
-             quant_pred_candidates
-               | definite_error = []
-               | otherwise      = ctsPreds (approximateWC False wanted_transformed)
+             wanted_dq | definite_error = emptyWC
+                       | otherwise      = wanted_transformed
 
        -- Decide what type variables and constraints to quantify
        -- NB: quant_pred_candidates is already fully zonked
@@ -957,9 +960,11 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
        -- NB: bound_theta are fully zonked
        -- rec {..}: see Note [Keeping SkolemInfo inside a SkolemTv]
        --           in GHC.Tc.Utils.TcType
-       ; rec { (qtvs, bound_theta, co_vars) <- decideQuantification skol_info infer_mode rhs_tclvl
-                                                     name_taus partial_sigs
-                                                     quant_pred_candidates
+       ; rec { (qtvs, bound_theta, co_vars) <- decideQuantification
+                                                     top_lvl rhs_tclvl infer_mode
+                                                     skol_info name_taus partial_sigs
+                                                     wanted_dq
+
              ; bound_theta_vars <- mapM TcM.newEvVar bound_theta
 
              ; let full_theta = map idType bound_theta_vars
@@ -975,7 +980,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
 
          -- All done!
        ; traceTc "} simplifyInfer/produced residual implication for quantification" $
-         vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates
+         vcat [ text "wanted_dq ="      <+> ppr wanted_dq
               , text "psig_theta ="     <+> ppr psig_theta
               , text "bound_theta ="    <+> pprCoreBinders bound_theta_vars
               , text "qtvs ="           <+> ppr qtvs
@@ -1278,20 +1283,21 @@ simplifyInfer.
 -}
 
 decideQuantification
-  :: SkolemInfo
-  -> InferMode
+  :: TopLevelFlag
   -> TcLevel
+  -> InferMode
+  -> SkolemInfo
   -> [(Name, TcTauType)]   -- Variables to be generalised
   -> [TcIdSigInst]         -- Partial type signatures (if any)
-  -> [PredType]            -- Candidate theta; already zonked
+  -> WantedConstraints     -- Candidate theta; already zonked
   -> TcM ( [TcTyVar]       -- Quantify over these (skolems)
          , [PredType]      -- and this context (fully zonked)
          , CoVarSet)
 -- See Note [Deciding quantification]
-decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs candidates
+decideQuantification top_lvl rhs_tclvl infer_mode skol_info name_taus psigs wanted
   = do { -- Step 1: find the mono_tvs
-       ; (candidates, co_vars, mono_tvs0)
-             <- decidePromotedTyVars infer_mode name_taus psigs candidates
+       ; (candidates, co_vars)
+             <- decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
 
        -- Step 2: default any non-mono tyvars, and re-simplify
        -- This step may do some unification, but result candidates is zonked
@@ -1308,11 +1314,11 @@ decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs candidates
           do { candidates <- TcM.zonkTcTypes candidates
              ; psig_theta <- TcM.zonkTcTypes (concatMap sig_inst_theta psigs)
              ; return (candidates, psig_theta) }
-       ; min_theta  <- pickQuantifiablePreds (mkVarSet qtvs) mono_tvs0 candidates
 
        -- Take account of partial type signatures
        -- See Note [Constraints in partial type signatures]
        ; let min_psig_theta = mkMinimalBySCs id psig_theta
+             min_theta      = pickQuantifiablePreds (mkVarSet qtvs) candidates
        ; theta <- if
            | null psigs -> return min_theta                 -- Case (P3)
            | not (all has_extra_constraints_wildcard psigs) -- Case (P2)
@@ -1396,147 +1402,376 @@ Some rationale and observations
     g :: forall b. Show b => F b -> _ -> b
     g x y = let _ = (f y, show x) in x
   But that's a battle for another day.
+
+Note [Generalising top-level bindings]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider
+  class C a b | a -> b where ..
+  f x = ...[W] C Int beta[1]...
+
+When generalising `f`, closeWrtFunDeps will promote beta[1] to beta[0].
+But we do NOT want to make a top level type
+  f :: C Int beta[0] => blah
+The danger is that beta[0] is defaulted to Any, and that then appears
+in a user error message.  Even if the type `blah` mentions beta[0], /and/
+there is a call that fixes beta[0] to (say) Bool, we'll end up with
+[W] C Int Bool, which is insoluble.  Why insoluble? If there was an
+   instance C Int Bool
+then fundeps would have fixed beta:=Bool in the first place.
+
+If the binding of `f` is nested, things are different: we can
+definitely see all the calls.
+
+For nested bindings, I think it just doesn't matter. No one cares what this
+variable ends up being; it seems silly to halt compilation around it. (Like in
+the length [] case.)
 -}
 
-decidePromotedTyVars :: InferMode
-                     -> [(Name,TcType)]
-                     -> [TcIdSigInst]
-                     -> [PredType]
-                     -> TcM ([PredType], CoVarSet, TcTyVarSet)
--- We are about to generalise over type variables at level N
--- Each must be either
---    (P) promoted
---    (D) defaulted
---    (Q) quantified
--- This function finds (P), the type variables that we are going to promote:
---   (a) Mentioned in a constraint we can't generalise (the MR)
---   (b) Mentioned in the kind of a CoVar; we can't quantify over a CoVar,
---       so we must not quantify over a type variable free in its kind
---   (c) Connected by an equality or fundep to
---          * a type variable at level < N, or
---          * A tyvar subject to (a), (b) or (c)
--- Having found all such level-N tyvars that we can't generalise,
--- promote them, to eliminate them from further consideration.
---
--- Also return CoVars that appear free in the final quantified types
---   we can't quantify over these, and we must make sure they are in scope
-decidePromotedTyVars infer_mode name_taus psigs candidates
-  = do { tc_lvl <- TcM.getTcLevel
-       ; (no_quant, maybe_quant) <- pick infer_mode candidates
+decideAndPromoteTyVars :: TopLevelFlag -> TcLevel
+                       -> InferMode
+                       -> [(Name,TcType)]
+                       -> [TcIdSigInst]
+                       -> WantedConstraints
+                       -> TcM ([PredType], CoVarSet)
+-- See Note [decideAndPromoteTyVars]
+decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
+  = do { dflags <- getDynFlags
 
        -- If possible, we quantify over partial-sig qtvs, so they are
        -- not mono. Need to zonk them because they are meta-tyvar TyVarTvs
-       ; (psig_qtvs, psig_theta, taus) <- TcM.liftZonkM $
-          do { psig_qtvs <- zonkTcTyVarsToTcTyVars $ binderVars $
-                            concatMap (map snd . sig_inst_skols) psigs
-             ; psig_theta <- mapM TcM.zonkTcType $
-                             concatMap sig_inst_theta psigs
-             ; taus <- mapM (TcM.zonkTcType . snd) name_taus
-             ; return (psig_qtvs, psig_theta, taus) }
+       ; (psig_qtvs, psig_theta, tau_tys) <- getSeedTys name_taus psigs
 
-       ; let psig_tys = mkTyVarTys psig_qtvs ++ psig_theta
+       ; let is_top_level = isTopLevel top_lvl  -- A syntactically top-level binding
 
-             -- (b) The co_var_tvs are tvs mentioned in the types of covars or
+             -- Step 1 of Note [decideAndPromoteTyVars]
+             -- Get candidate constraints, decide which we can potentially quantify
+             (can_quant_cts, no_quant_cts) = approximateWCX wanted
+             can_quant = ctsPreds can_quant_cts
+             no_quant  = ctsPreds no_quant_cts
+
+             -- Step 2 of Note [decideAndPromoteTyVars]
+             -- Apply the monomorphism restriction
+             (post_mr_quant, mr_no_quant) = applyMR dflags infer_mode can_quant
+
+             -- The co_var_tvs are tvs mentioned in the types of covars or
              -- coercion holes. We can't quantify over these covars, so we
              -- must include the variable in their types in the mono_tvs.
              -- E.g.  If we can't quantify over co :: k~Type, then we can't
              --       quantify over k either!  Hence closeOverKinds
              -- Recall that coVarsOfTypes also returns coercion holes
-             co_vars = coVarsOfTypes (psig_tys ++ taus ++ candidates)
+             co_vars    = coVarsOfTypes (mkTyVarTys psig_qtvs ++ psig_theta
+                                         ++ tau_tys ++ post_mr_quant)
              co_var_tvs = closeOverKinds co_vars
 
-             mono_tvs0 = filterVarSet (not . isQuantifiableTv tc_lvl) $
-                         tyCoVarsOfTypes candidates
-               -- We need to grab all the non-quantifiable tyvars in the
-               -- types so that we can grow this set to find other
-               -- non-quantifiable tyvars. This can happen with something like
-               --    f x y = ...
-               --      where z = x 3
-               -- The body of z tries to unify the type of x (call it alpha[1])
-               -- with (beta[2] -> gamma[2]). This unification fails because
-               -- alpha is untouchable, leaving [W] alpha[1] ~ (beta[2] -> gamma[2]).
-               -- We need to know not to quantify over beta or gamma, because they
-               -- are in the equality constraint with alpha. Actual test case:
-               -- typecheck/should_compile/tc213
-
-             mono_tvs1 = mono_tvs0 `unionVarSet` co_var_tvs
-
-               -- mono_tvs1 is now the set of variables from an outer scope
-               -- (that's mono_tvs0) and the set of covars, closed over kinds.
-               -- Given this set of variables we know we will not quantify,
-               -- we want to find any other variables that are determined by this
-               -- set, by functional dependencies or equalities. We thus use
-               -- closeWrtFunDeps to find all further variables determined by this root
-               -- set. See Note [growThetaTyVars vs closeWrtFunDeps]
-
-             non_ip_candidates = filterOut isIPLikePred candidates
-               -- implicit params don't really determine a type variable
-               -- (that is, we might have IP "c" Bool and IP "c" Int in different
-               -- places within the same program), and
-               -- skipping this causes implicit params to monomorphise too many
-               -- variables; see Note [Inheriting implicit parameters] in GHC.Tc.Solver.
-               -- Skipping causes typecheck/should_compile/tc219 to fail.
-
-             mono_tvs2 = closeWrtFunDeps non_ip_candidates mono_tvs1
-               -- mono_tvs2 now contains any variable determined by the "root
-               -- set" of monomorphic tyvars in mono_tvs1.
-
-             constrained_tvs = filterVarSet (isQuantifiableTv tc_lvl) $
-                               closeWrtFunDeps non_ip_candidates (tyCoVarsOfTypes no_quant)
-                                `minusVarSet` mono_tvs2
-             -- constrained_tvs: the tyvars that we are not going to
-             -- quantify /solely/ because of the monomorphism restriction
-             --
-             -- (`minusVarSet` mono_tvs2): a type variable is only
-             --   "constrained" (so that the MR bites) if it is not
-             --   free in the environment (#13785) or is determined
-             --   by some variable that is free in the env't
-
-             mono_tvs = (mono_tvs2 `unionVarSet` constrained_tvs)
-                        `delVarSetList` psig_qtvs
-             -- (`delVarSetList` psig_qtvs): if the user has explicitly
-             --   asked for quantification, then that request "wins"
-             --   over the MR.
-             --
-             -- What if a psig variable is also free in the environment
-             -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
-             -- in Step 2 of Note [Deciding quantification].
-
-           -- Warn about the monomorphism restriction
-       ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $ do
-           let dia = TcRnMonomorphicBindings (map fst name_taus)
-           diagnosticTc (constrained_tvs `intersectsVarSet` tyCoVarsOfTypes taus) dia
-
-       -- Promote the mono_tvs: see Note [Promote monomorphic tyvars]
-       ; _ <- promoteTyVarSet mono_tvs
-
-       ; traceTc "decidePromotedTyVars" $ vcat
-           [ text "infer_mode =" <+> ppr infer_mode
+             -- outer_tvs are mentioned in `wanted, and belong to some outer level.
+             -- We definitely can't quantify over them
+             outer_tvs = outerLevelTyVars rhs_tclvl $
+                         tyCoVarsOfTypes can_quant `unionVarSet` tyCoVarsOfTypes no_quant
+
+             -- Step 3 of Note [decideAndPromoteTyVars]
+             -- Identify mono_tvs: the type variables that we must not quantify over
+             mono_tvs_without_mr
+               | is_top_level = outer_tvs
+               | otherwise    = outer_tvs                                 -- (a)
+                                `unionVarSet` tyCoVarsOfTypes no_quant    -- (b)
+                                `unionVarSet` co_var_tvs                  -- (c)
+
+             mono_tvs_with_mr
+               = -- Even at top level, we don't quantify over type variables
+                 -- mentioned in constraints that the MR tells us not to quantify
+                 -- See Note [decideAndPromoteTyVars] (DP2)
+                 mono_tvs_without_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
+
+             --------------------------------------------------------------------
+             -- Step 4 of Note [decideAndPromoteTyVars]
+             -- Use closeWrtFunDeps to find any other variables that are determined by mono_tvs
+             add_determined tvs = closeWrtFunDeps post_mr_quant tvs
+                                  `delVarSetList` psig_qtvs
+                 -- Why delVarSetList psig_qtvs?
+                 -- If the user has explicitly asked for quantification, then that
+                 -- request "wins" over the MR.
+                 --
+                 -- What if a psig variable is also free in the environment
+                 -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
+                 -- in Step 2 of Note [Deciding quantification].
+
+             mono_tvs_with_mr_det    = add_determined mono_tvs_with_mr
+             mono_tvs_without_mr_det = add_determined mono_tvs_without_mr
+
+             --------------------------------------------------------------------
+             -- Step 5 of Note [decideAndPromoteTyVars]
+             -- Do not quantify over any constraint mentioning a "newly-mono" tyvar.
+             newly_mono_tvs = mono_tvs_with_mr_det `minusVarSet` mono_tvs_with_mr
+             final_quant
+               | is_top_level = filterOut (predMentions newly_mono_tvs) post_mr_quant
+               | otherwise    = post_mr_quant
+
+       --------------------------------------------------------------------
+       -- Check if the Monomorphism Restriction has bitten
+       ; warn_mr <- woptM Opt_WarnMonomorphism
+       ; when (warn_mr && case infer_mode of { ApplyMR -> True; _ -> False}) $
+         diagnosticTc (not (mono_tvs_with_mr_det `subVarSet` mono_tvs_without_mr_det)) $
+              TcRnMonomorphicBindings (map fst name_taus)
+             -- If there is a variable in mono_tvs, but not in mono_tvs_wo_mr
+             -- then the MR has "bitten" and reduced polymorphism.
+
+       --------------------------------------------------------------------
+       -- Step 6: Promote the mono_tvs: see Note [Promote monomorphic tyvars]
+       ; _ <- promoteTyVarSet mono_tvs_with_mr_det
+
+       ; traceTc "decideAndPromoteTyVars" $ vcat
+           [ text "rhs_tclvl =" <+> ppr rhs_tclvl
+           , text "top =" <+> ppr is_top_level
+           , text "infer_mode =" <+> ppr infer_mode
            , text "psigs =" <+> ppr psigs
            , text "psig_qtvs =" <+> ppr psig_qtvs
-           , text "mono_tvs0 =" <+> ppr mono_tvs0
+           , text "outer_tvs =" <+> ppr outer_tvs
+           , text "mono_tvs_with_mr =" <+> ppr mono_tvs_with_mr
+           , text "mono_tvs_without_mr =" <+> ppr mono_tvs_without_mr
+           , text "mono_tvs_with_mr_det =" <+> ppr mono_tvs_with_mr_det
+           , text "mono_tvs_without_mr_det =" <+> ppr mono_tvs_without_mr_det
+           , text "newly_mono_tvs =" <+> ppr newly_mono_tvs
+           , text "can_quant =" <+> ppr can_quant
+           , text "post_mr_quant =" <+> ppr post_mr_quant
            , text "no_quant =" <+> ppr no_quant
-           , text "maybe_quant =" <+> ppr maybe_quant
-           , text "mono_tvs =" <+> ppr mono_tvs
+           , text "mr_no_quant =" <+> ppr mr_no_quant
+           , text "final_quant =" <+> ppr final_quant
            , text "co_vars =" <+> ppr co_vars ]
 
-       ; return (maybe_quant, co_vars, mono_tvs0) }
+       ; return (final_quant, co_vars) }
+          -- We return `co_vars` that appear free in the final quantified types
+          -- we can't quantify over these, and we must make sure they are in scope
+
+-------------------
+applyMR :: DynFlags -> InferMode -> [PredType]
+        -> ( [PredType]   -- Quantify over these
+           , [PredType] ) -- But not over these
+-- Split the candidates into ones we definitely
+-- won't quantify, and ones that we might
+applyMR _      NoRestrictions  cand = (cand, [])
+applyMR _      ApplyMR         cand = ([], cand)
+applyMR dflags EagerDefaulting cand = partition not_int_ct cand
   where
-    pick :: InferMode -> [PredType] -> TcM ([PredType], [PredType])
-    -- Split the candidates into ones we definitely
-    -- won't quantify, and ones that we might
-    pick ApplyMR         cand = return (cand, [])
-    pick NoRestrictions  cand = return ([], cand)
-    pick EagerDefaulting cand = do { os <- xoptM LangExt.OverloadedStrings
-                                   ; return (partition (is_int_ct os) cand) }
-
-    -- is_int_ct returns True for a constraint we should /not/ quantify
+    ovl_strings = xopt LangExt.OverloadedStrings dflags
+
+    -- not_int_ct returns True for a constraint we /can/ quantify
     -- For EagerDefaulting, do not quantify over
     -- over any interactive class constraint
-    is_int_ct ovl_strings pred
+    not_int_ct pred
       = case classifyPredType pred of
-           ClassPred cls _ -> isInteractiveClass ovl_strings cls
-           _               -> False
+           ClassPred cls _ -> not (isInteractiveClass ovl_strings cls)
+           _               -> True
+
+-------------------
+outerLevelTyVars :: TcLevel -> TcTyVarSet -> TcTyVarSet
+-- Find just the tyvars that are bound outside rhs_tc_lvl
+outerLevelTyVars rhs_tclvl tvs
+  = filterVarSet is_outer_tv tvs
+  where
+    is_outer_tv tcv
+     | isTcTyVar tcv  -- Might be a CoVar; change this when gather covars separately
+     = rhs_tclvl `strictlyDeeperThan` tcTyVarLevel tcv
+     | otherwise
+     = False
+
+{- Note [decideAndPromoteTyVars]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We are about to generalise a let-binding at "outer level" N, where we have
+typechecked its RHS at "rhs level" N+1.  Each tyvar must be either
+  (P) promoted
+  (D) defaulted
+  (Q) quantified
+The function `decideAndPromoteTyVars` figures out (P), the type variables
+mentioned in constraints should definitely not be quantified, and promotes them
+to the outer level, namely (N-1).
+
+The plan
+
+* Step 1.  Use `approximateWCX` to extract, from the RHS `WantedConstraints`,
+  the PredTypes that we might quantify over; and also those that we can't.
+  Example: suppose the `wanted` is this:
+     (d1:Eq alpha, forall b. (F b ~ a) => (co:t1 ~ t2), (d:Show alpha))
+  Then
+     can_quant = [Eq alpha, Show alpha]
+     no_quant  = (t1 ~ t2)
+  We can't quantify over that (t1~t2) because of the enclosing equality (F b ~ a).
+
+  We also choose never to quantify over some forms of equality constraints.
+  Both this and the "given-equality" thing are described in
+  Note [Quantifying over equality constraints] in GHC.Tc.Types.Constraint.
+
+* Step 2. Further trim can_quant using the Monomorphism Restriction, yielding the
+  further `mr_no_quant` predicates that we won't quantify over; plus `post_mr_quant`,
+  which we can in principle quantify.
+
+* Step 3. Identify the type variables we definitely won't quantify, because they are:
+  a) From an outer level <=N anyway
+  b) Mentioned in a constraint we /can't/ quantify.  See Wrinkle (DP1).
+  c) Mentioned in the kind of a CoVar; we can't quantify over a CoVar,
+     so we must not quantify over a type variable free in its kind
+  d) Mentioned in a constraint that the MR says we should not quantify.
+
+  There is a special case for top-level bindings: see Wrinkle (DP2).
+
+* Step 4.  Close wrt functional dependencies and equalities.Example
+  Example
+           f x y = ...
+              where z = x 3
+  The body of z tries to unify the type of x (call it alpha[1]) with
+  (beta[2] -> gamma[2]). This unification fails because alpha is untouchable, leaving
+       [W] alpha[1] ~ (beta[2] -> gamma[2])
+  We need to know not to quantify over beta or gamma, because they are in the
+  equality constraint with alpha. Actual test case:   typecheck/should_compile/tc213
+
+  Another example. Suppose we have
+      class C a b | a -> b
+  and a constraint ([W] C alpha beta), if we promote alpha we should promote beta.
+
+  See also Note [growThetaTyVars vs closeWrtFunDeps]
+
+* Step 5. Further restrict the quantifiable constraints `post_mr_quant` to ones
+  that do not mention a "newly mono" tyvar. The "newly-mono" tyvars are the ones
+  not free in the envt, nor forced to be promoted by the MR; but are determined
+  (via fundeps) by them. Example:
+           class C a b | a -> b
+           [W] C Int beta[1],  tau = beta[1]->Int
+  We promote beta[1] to beta[0] since it is determined by fundep, but we do not
+  want to generate f :: (C Int beta[0]) => beta[0] -> Int Rather, we generate
+  f :: beta[0] -> Int, but leave [W] C Int beta[0] in the residual constraints,
+  which will probably cause a type error
+
+  See Note [Do not quantify over constraints that determine a variable]
+
+* Step 6: acutally promote the type variables we don't want to quantify.
+  We must do this: see Note [Promote monomorphic tyvars].
+
+We also add a warning that signals when the MR "bites".
+
+Wrinkles
+
+(DP1) In step 3, why (b)?  Consider the example given in Step 1.  we can't
+  quantify over the constraint (t1~t2).  But if we quantify over the /tyvars/ in
+  t1 or t2, we may simply make that constraint insoluble (#25266 was an example).
+
+(DP2) In Step 3, for top-level bindings, we do (a,d), but /not/ (b,c). Reason:
+  see Note [The top-level Any principle].  At top level we are very reluctant to
+  promote type variables.  But for bindings affected by the MR we have no choice
+  but to promote.
+
+Note [The top-level Any principle]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Key principle: we never want to show the programmer a type with `Any` in it.
+
+Most /top level/ bindings have a type signature, so none of this arises.  But
+where a top-level binding lacks a signature, we don't want to infer a type like
+    f :: alpha[0] -> Int
+and then subsequently default alpha[0]:=Any.  Exposing `Any` to the user is bad
+bad bad.  Better to report an error, which is what may well happen if we
+quantify over alpha instead.
+
+For /nested/ bindings, a monomorphic type like `f :: alpha[0] -> Int` is fine,
+because we can see all the call sites of `f`, and they will probably fix
+`alpha`.  In contrast, we can't see all of (or perhaps any of) the calls of
+top-level (exported) functions, reducing the worries about "spooky action at a
+distance".
+
+Note [Do not quantify over constraints that determine a variable]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider (typecheck/should_compile/tc231), where we're trying to infer
+the type of a top-level declaration. We have
+  class Zork s a b | a -> b
+and the candidate constraint at the end of simplifyInfer is
+  [W] Zork alpha[1] (Z [Char]) beta[1]
+We definitely want to quantify over `alpha` (which is mentioned in the
+tau-type).
+
+But we do *not* want to quantify over `beta`: it is determined by the
+functional dependency on Zork: note that the second argument to Zork
+in the Wanted is a variable-free `Z [Char]`.  Quantifying over it
+would be "Henry Ford polymorphism".  (Presumably we don't have an
+instance in scope that tells us what `beta` actually is.)  Instead
+we promote `beta[1]` to `beta[0]`, in `decidePromotedTyVars`.
+
+The question here: do we want to quantify over the constraint, to
+give the type
+   forall a. Zork a (Z [Char]) beta[0] => blah
+Definitely not: see Note [The top-level Any principle]
+
+What we really want (to catch the Zork example) is this:
+
+   Quantify over the constraint only if all its free variables are
+   (a) quantified, or
+   (b) appears in the type of something in the environment (mono_tvs0).
+
+To understand (b) consider
+
+  class C a b where { op :: a -> b -> () }
+
+  mr = 3                      -- mr :: alpha
+  f1 x = op x mr              -- f1 :: forall b. b -> (), plus [W] C b alpha
+  intify = mr + (4 :: Int)
+
+In `f1` should we quantify over that `(C b alpha)`?  Answer: since `alpha` is
+free in the type envt, yes we should.  After all, if we'd typechecked `intify`
+first, we'd have set `alpha := Int`, and /then/ we'd certainly quantify.  The
+delicate Zork situation applies when beta is completely unconstrained (not free
+in the environment) -- except by the fundep.  Hence `newly_mono`.
+
+Another way to put it: let's say `alpha` is in `outer_tvs`. It must be that
+some variable `x` has `alpha` free in its type. If we are at top-level (and we
+are, because nested decls don't go through this path all), then `x` must also
+be at top-level. And, by induction, `x` will not have Any in its type when all
+is said and done. The induction is well-founded because, if `x` is mutually
+recursive with the definition at hand, then their constraints get processed
+together (or `x` has a type signature, in which case the type doesn't have
+`Any`). So the key thing is that we must not introduce a new top-level
+unconstrained variable here.
+
+However this regrettably-subtle reasoning is needed only for /top-level/
+declarations.  For /nested/ decls we can see all the calls, so we'll instantiate
+that quantifed `Zork a (Z [Char]) beta` constraint at call sites, and either
+solve it or not (probably not).  We won't be left with a still-callable function
+with Any in its type.  So for nested definitions we don't make this tricky test.
+
+Historical note: we had a different, and more complicated test before, but it
+was utterly wrong: #23199.
+
+Note [Promote monomorphic tyvars]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Promote any type variables that are free in the environment.  Eg
+   f :: forall qtvs. bound_theta => zonked_tau
+The free vars of f's type become free in the envt, and hence will show
+up whenever 'f' is called.  They may currently at rhs_tclvl, but they
+had better be unifiable at the outer_tclvl!  Example: envt mentions
+alpha[1]
+           tau_ty = beta[2] -> beta[2]
+           constraints = alpha ~ [beta]
+we don't quantify over beta (since it is fixed by envt)
+so we must promote it!  The inferred type is just
+  f :: beta -> beta
+
+NB: promoteTyVarSet ignores coercion variables
+
+Note [Defaulting during simplifyInfer]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+When we are inferring a type, we simplify the constraint, and then use
+approximateWC to produce a list of candidate constraints.  Then we MUST
+
+  a) Promote any meta-tyvars that have been floated out by
+     approximateWC, to restore invariant (WantedInv) described in
+     Note [TcLevel invariants] in GHC.Tc.Utils.TcType.
+
+  b) Default the kind of any meta-tyvars that are not mentioned in
+     in the environment.
+
+To see (b), suppose the constraint is (C ((a :: OpenKind) -> Int)), and we
+have an instance (C ((x:*) -> Int)).  The instance doesn't match -- but it
+should!  If we don't solve the constraint, we'll stupidly quantify over
+(C (a->Int)) and, worse, in doing so skolemiseQuantifiedTyVar will quantify over
+(b:*) instead of (a:OpenKind), which can lead to disaster; see #7332.
+#7641 is a simpler example.
+
+-}
 
 -------------------
 defaultTyVarsAndSimplify :: TcLevel
@@ -1544,6 +1779,7 @@ defaultTyVarsAndSimplify :: TcLevel
                          -> TcM [PredType]      -- Guaranteed zonked
 -- Default any tyvar free in the constraints;
 -- and re-simplify in case the defaulting allows further simplification
+-- See Note [Defaulting during simplifyInfer]
 defaultTyVarsAndSimplify rhs_tclvl candidates
   = do {  -- Default any kind/levity vars
        ; DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs}
@@ -1592,118 +1828,87 @@ decideQuantifiedTyVars skol_info name_taus psigs candidates
   = do {     -- Why psig_tys? We try to quantify over everything free in here
              -- See Note [Quantification and partial signatures]
              --     Wrinkles 2 and 3
-       ; (psig_tv_tys, psig_theta, tau_tys) <- TcM.liftZonkM $
-         do { psig_tv_tys <- mapM TcM.zonkTcTyVar [ tv | sig <- psigs
-                                                       , (_,Bndr tv _) <- sig_inst_skols sig ]
-            ; psig_theta  <- mapM TcM.zonkTcType [ pred | sig <- psigs
-                                                        , pred <- sig_inst_theta sig ]
-            ; tau_tys     <- mapM (TcM.zonkTcType . snd) name_taus
-            ; return (psig_tv_tys, psig_theta, tau_tys) }
-
-       ; let -- Try to quantify over variables free in these types
-             psig_tys = psig_tv_tys ++ psig_theta
-             seed_tys = psig_tys ++ tau_tys
-
-             -- Now "grow" those seeds to find ones reachable via 'candidates'
+         (psig_qtvs, psig_theta, tau_tys) <- getSeedTys name_taus psigs
+
+       ; let psig_tys = mkTyVarTys psig_qtvs ++ psig_theta
+             seed_tvs = tyCoVarsOfTypes (psig_tys ++ tau_tys)
+
+               -- "Grow" those seeds to find ones reachable via 'candidates'
              -- See Note [growThetaTyVars vs closeWrtFunDeps]
-             grown_tcvs = growThetaTyVars candidates (tyCoVarsOfTypes seed_tys)
+             grown_tcvs = growThetaTyVars candidates seed_tvs
 
        -- Now we have to classify them into kind variables and type variables
        -- (sigh) just for the benefit of -XNoPolyKinds; see quantifyTyVars
        --
-       -- Keep the psig_tys first, so that candidateQTyVarsOfTypes produces
-       -- them in that order, so that the final qtvs quantifies in the same
-       -- order as the partial signatures do (#13524)
-       ; dv at DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs} <- candidateQTyVarsOfTypes $
-                                                         psig_tys ++ candidates ++ tau_tys
+       -- The psig_tys are first in seed_tys, then candidates, then tau_tvs.
+       -- This makes candidateQTyVarsOfTypes produces them in that order, so that the
+        -- final qtvs quantifies in the same- order as the partial signatures do (#13524)
+       ; dv at DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs}
+             <- candidateQTyVarsOfTypes $
+                psig_tys ++ candidates ++ tau_tys
        ; let pick     = (`dVarSetIntersectVarSet` grown_tcvs)
              dvs_plus = dv { dv_kvs = pick cand_kvs, dv_tvs = pick cand_tvs }
 
        ; traceTc "decideQuantifiedTyVars" (vcat
-           [ text "tau_tys =" <+> ppr tau_tys
-           , text "candidates =" <+> ppr candidates
+           [ text "candidates =" <+> ppr candidates
            , text "cand_kvs =" <+> ppr cand_kvs
            , text "cand_tvs =" <+> ppr cand_tvs
-           , text "tau_tys =" <+> ppr tau_tys
-           , text "seed_tys =" <+> ppr seed_tys
-           , text "seed_tcvs =" <+> ppr (tyCoVarsOfTypes seed_tys)
+           , text "seed_tys =" <+> ppr seed_tvs
            , text "grown_tcvs =" <+> ppr grown_tcvs
            , text "dvs =" <+> ppr dvs_plus])
 
        ; quantifyTyVars skol_info DefaultNonStandardTyVars dvs_plus }
 
 ------------------
+getSeedTys :: [(Name,TcType)]    -- The type of each RHS in the group
+           -> [TcIdSigInst]      -- Any partial type signatures
+           -> TcM ( [TcTyVar]    -- Zonked partial-sig quantified tyvars
+                  , ThetaType    -- Zonked partial signature thetas
+                  , [TcType] )   -- Zonked tau-tys from the bindings
+getSeedTys name_taus psigs
+  = TcM.liftZonkM $
+    do { psig_tv_tys <- mapM TcM.zonkTcTyVar [ tv | TISI{ sig_inst_skols = skols } <- psigs
+                                                  , (_, Bndr tv _) <- skols ]
+       ; psig_theta  <- mapM TcM.zonkTcType [ pred | TISI{ sig_inst_theta = theta } <- psigs
+                                                   , pred <- theta ]
+       ; tau_tys     <- mapM (TcM.zonkTcType . snd) name_taus
+       ; return ( map getTyVar psig_tv_tys
+                , psig_theta
+                , tau_tys ) }
+
+------------------
+predMentions :: TcTyVarSet -> TcPredType -> Bool
+predMentions qtvs pred = tyCoVarsOfType pred `intersectsVarSet` qtvs
+
 -- | When inferring types, should we quantify over a given predicate?
 -- See Note [pickQuantifiablePreds]
 pickQuantifiablePreds
   :: TyVarSet           -- Quantifying over these
-  -> TcTyVarSet         -- mono_tvs0: variables mentioned a candidate
-                        --   constraint that come from some outer level
   -> TcThetaType        -- Proposed constraints to quantify
-  -> TcM TcThetaType    -- A subset that we can actually quantify
+  -> TcThetaType        -- A subset that we can actually quantify
 -- This function decides whether a particular constraint should be
 -- quantified over, given the type variables that are being quantified
-pickQuantifiablePreds qtvs mono_tvs0 theta
-  = do { tc_lvl <- TcM.getTcLevel
-       ; let is_nested = not (isTopTcLevel tc_lvl)
-       ; return (mkMinimalBySCs id $  -- See Note [Minimize by Superclasses]
-                 mapMaybe (pick_me is_nested) theta) }
+pickQuantifiablePreds qtvs theta
+  = mkMinimalBySCs id $  -- See Note [Minimize by Superclasses]
+    mapMaybe pick_me theta
   where
-    pick_me is_nested pred
-      = let pred_tvs = tyCoVarsOfType pred
-            mentions_qtvs = pred_tvs `intersectsVarSet` qtvs
-        in case classifyPredType pred of
-
-          ClassPred cls tys
-            | Just {} <- isCallStackPred cls tys
-              -- NEVER infer a CallStack constraint.  Otherwise we let
-              -- the constraints bubble up to be solved from the outer
-              -- context, or be defaulted when we reach the top-level.
-              -- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
-            -> Nothing
-
+    pick_me pred
+      = case classifyPredType pred of
+          ClassPred cls _
             | isIPClass cls
-            -> Just pred -- See Note [Inheriting implicit parameters]
-
-            | not mentions_qtvs
-            -> Nothing   -- Don't quantify over predicates that don't
-                         -- mention any of the quantified type variables
-
-            | is_nested
-            -> Just pred
-
-            -- From here on, we are thinking about top-level defns only
-
-            | pred_tvs `subVarSet` (qtvs `unionVarSet` mono_tvs0)
-              -- See Note [Do not quantify over constraints that determine a variable]
-            -> Just pred
-
-            | otherwise
-            -> Nothing
+            -> Just pred -- Pick, say, (?x::Int) whether or not it mentions qtvs
+                         -- See Note [Inheriting implicit parameters]
 
           EqPred eq_rel ty1 ty2
-            | mentions_qtvs
-            , quantify_equality eq_rel ty1 ty2
+            | predMentions qtvs pred
             , Just (cls, tys) <- boxEqPred eq_rel ty1 ty2
               -- boxEqPred: See Note [Lift equality constraints when quantifying]
             -> Just (mkClassPred cls tys)
             | otherwise
             -> Nothing
 
-          IrredPred {} | mentions_qtvs -> Just pred
-                       | otherwise     -> Nothing
-
-          ForAllPred {} -> Nothing
-
-    -- See Note [Quantifying over equality constraints]
-    quantify_equality NomEq  ty1 ty2 = quant_fun ty1 || quant_fun ty2
-    quantify_equality ReprEq _   _   = True
-
-    quant_fun ty
-      = case tcSplitTyConApp_maybe ty of
-          Just (tc, tys) | isTypeFamilyTyCon tc
-                         -> tyCoVarsOfTypes tys `intersectsVarSet` qtvs
-          _ -> False
+          _ | predMentions qtvs pred -> Just pred
+            | otherwise              -> Nothing
 
 ------------------
 growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet
@@ -1725,24 +1930,8 @@ growThetaTyVars theta tcvs
          pred_tcvs = tyCoVarsOfType pred
 
 
-{- Note [Promote monomorphic tyvars]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Promote any type variables that are free in the environment.  Eg
-   f :: forall qtvs. bound_theta => zonked_tau
-The free vars of f's type become free in the envt, and hence will show
-up whenever 'f' is called.  They may currently at rhs_tclvl, but they
-had better be unifiable at the outer_tclvl!  Example: envt mentions
-alpha[1]
-           tau_ty = beta[2] -> beta[2]
-           constraints = alpha ~ [beta]
-we don't quantify over beta (since it is fixed by envt)
-so we must promote it!  The inferred type is just
-  f :: beta -> beta
-
-NB: promoteTyVarSet ignores coercion variables
-
-Note [pickQuantifiablePreds]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [pickQuantifiablePreds]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 When pickQuantifiablePreds is called we have decided what type
 variables to quantify over, `qtvs`. The only quesion is: which of the
 unsolved candidate predicates should we quantify over?  Call them
@@ -1754,58 +1943,37 @@ For the members of unsolved_constraints that we select for picked_theta
 it is easy to solve, by identity.  For the others we just hope that
 we can solve them.
 
-So which of the candidates should we pick to quantify over?  In some
-situations we distinguish top-level from nested bindings.  The point
-about nested binding is that
- (a) the types may mention type variables free in the environment
- (b) all of the call sites are statically visible, reducing the
-     worries about "spooky action at a distance".
-
-First, never pick a constraint that doesn't mention any of the quantified
-variables `qtvs`.  Picking such a constraint essentially moves the solving of
-the constraint from this function definition to call sites.  But because the
-constraint mentions no quantified variables, call sites have no advantage
-over the definition site. Well, not quite: there could be new constraints
-brought into scope by a pattern-match against a constrained (e.g. GADT)
-constructor.  Example
-
-      data T a where { T1 :: T1 Bool; ... }
-
-      f :: forall a. a -> T a -> blah
-      f x t = let g y = x&&y    -- This needs a~Bool
-            in case t of
-                  T1 -> g True
-                  ....
-
-At g's call site we have `a~Bool`, so we /could/ infer
-     g :: forall . (a~Bool) => Bool -> Bool  -- qtvs = {}
-
-This is all very contrived, and probably just postponse type errors to
-the call site.  If that's what you want, write a type signature.
-
-Actually, implicit parameters is an exception to the "no quantified vars"
-rule (see Note [Inheriting implicit parameters]) so we can't actually
-simply test this case first.
-
-Now we consider the different sorts of constraints:
+So which of the candidates should we pick to quantify over?  It's pretty easy:
 
-* For ClassPred constraints:
+* Never pick a constraint that doesn't mention any of the quantified
+  variables `qtvs`.  Picking such a constraint essentially moves the solving of
+  the constraint from this function definition to call sites.  But because the
+  constraint mentions no quantified variables, call sites have no advantage
+  over the definition site. Well, not quite: there could be new constraints
+  brought into scope by a pattern-match against a constrained (e.g. GADT)
+  constructor.  Example
 
-  * Never pick a CallStack constraint.
-    See Note [Overview of implicit CallStacks]
+        data T a where { T1 :: T1 Bool; ... }
 
-  * Always pick an implicit-parameter constraint.
-    Note [Inheriting implicit parameters]
+        f :: forall a. a -> T a -> blah
+        f x t = let g y = x&&y    -- This needs a~Bool
+              in case t of
+                    T1 -> g True
+                    ....
 
-  * For /top-level/ class constraints see
-    Note [Do not quantify over constraints that determine a variable]
+  At g's call site we have `a~Bool`, so we /could/ infer
+       g :: forall . (a~Bool) => Bool -> Bool  -- qtvs = {}
 
-* For EqPred constraints see Note [Quantifying over equality constraints]
+  This is all very contrived, and probably just postponse type errors to
+  the call site.  If that's what you want, write a type signature.
 
-* For IrredPred constraints, we allow anything that mentions the quantified
-  type variables.
+* Implicit parameters is an exception to the "no quantified vars"
+  rule (see Note [Inheriting implicit parameters]) so we can't actually
+  simply test this case first.
 
-* A ForAllPred should not appear: the candidates come from approximateWC.
+* Finally, we may need to "box" equality predicates: if we want to quantify
+  over `a ~# b`, we actually quantify over the boxed version, `a ~ b`.
+  See Note [Lift equality constraints when quantifying].
 
 Notice that we do /not/ consult -XFlexibleContexts here.  For example,
 we allow `pickQuantifiablePreds` to quantify over a constraint like
@@ -1852,102 +2020,6 @@ parameters, *even if* they don't mention the bound type variables.
 Reason: because implicit parameters, uniquely, have local instance
 declarations. See pickQuantifiablePreds.
 
-Note [Quantifying over equality constraints]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Should we quantify over an equality constraint (s ~ t)
-in pickQuantifiablePreds?
-
-* It is always /sound/ to quantify over a constraint -- those
-  quantified constraints will need to be proved at each call site.
-
-* We definitely don't want to quantify over (Maybe a ~ Bool), to get
-     f :: forall a. (Maybe a ~ Bool) => blah
-  That simply postpones a type error from the function definition site to
-  its call site.  Fortunately we have already filtered out insoluble
-  constraints: see `definite_error` in `simplifyInfer`.
-
-* What about (a ~ T alpha b), where we are about to quantify alpha, `a` and
-  `b` are in-scope skolems, and `T` is a data type.  It's pretty unlikely
-  that this will be soluble at a call site, so we don't quantify over it.
-
-* What about `(F beta ~ Int)` where we are going to quantify `beta`?
-  Should we quantify over the (F beta ~ Int), to get
-     f :: forall b. (F b ~ Int) => blah
-  Aha!  Perhaps yes, because at the call site we will instantiate `b`, and
-  perhaps we have `instance F Bool = Int`. So we *do* quantify over a
-  type-family equality where the arguments mention the quantified variables.
-
-This is all a bit ad-hoc.
-
-Note [Do not quantify over constraints that determine a variable]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider (typecheck/should_compile/tc231), where we're trying to infer
-the type of a top-level declaration. We have
-  class Zork s a b | a -> b
-and the candidate constraint at the end of simplifyInfer is
-  [W] Zork alpha[1] (Z [Char]) beta[1]
-We definitely want to quantify over `alpha` (which is mentioned in the
-tau-type).
-
-But we do *not* want to quantify over `beta`: it is determined by the
-functional dependency on Zork: note that the second argument to Zork
-in the Wanted is a variable-free `Z [Char]`.  Quantifying over it
-would be "Henry Ford polymorphism".  (Presumably we don't have an
-instance in scope that tells us what `beta` actually is.)  Instead
-we promote `beta[1]` to `beta[0]`, in `decidePromotedTyVars`.
-
-The question here: do we want to quantify over the constraint, to
-give the type
-   forall a. Zork a (Z [Char]) beta[0] => blah
-Definitely not.  Since we're not quantifying over beta, it has been
-promoted; and then will be zapped to Any in the final zonk.  So we end
-up with a (perhaps exported) type involving
-  forall a. Zork a (Z [Char]) Any => blah
-No no no:
-
-  Key principle: we never want to show the programmer
-                 a type with `Any` in it.
-
-What we really want (to catch the Zork example) is this:
-
-   Quantify over the constraint only if all its free variables are
-   (a) quantified, or
-   (b) appears in the type of something in the environment (mono_tvs0).
-
-To understand (b) consider
-
-  class C a b where { op :: a -> b -> () }
-
-  mr = 3                      -- mr :: alpha
-  f1 x = op x mr              -- f1 :: forall b. b -> (), plus [W] C b alpha
-  intify = mr + (4 :: Int)
-
-In `f1` should we quantify over that `(C b alpha)`?  Answer: since `alpha`
-is free in the type envt, yes we should.  After all, if we'd typechecked
-`intify` first, we'd have set `alpha := Int`, and /then/ we'd certainly
-quantify.  The delicate Zork situation applies when beta is completely
-unconstrained (not free in the environment) -- except by the fundep.
-
-Another way to put it: let's say `alpha` is in `mono_tvs0`. It must be that
-some variable `x` has `alpha` free in its type. If we are at top-level (and we
-are, because nested decls don't go through this path all), then `x` must also
-be at top-level. And, by induction, `x` will not have Any in its type when all
-is said and done. The induction is well-founded because, if `x` is mutually
-recursive with the definition at hand, then their constraints get processed
-together (or `x` has a type signature, in which case the type doesn't have
-`Any`). So the key thing is that we must not introduce a new top-level
-unconstrained variable here.
-
-However this regrettably-subtle reasoning is needed only for /top-level/
-declarations.  For /nested/ decls we can see all the calls, so we'll
-instantiate that quantifed `Zork a (Z [Char]) beta` constraint at call sites,
-and either solve it or not (probably not).  We won't be left with a
-still-callable function with Any in its type.  So for nested definitions we
-don't make this tricky test.
-
-Historical note: we had a different, and more complicated test
-before, but it was utterly wrong: #23199.
-
 Note [Quantification and partial signatures]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 When choosing type variables to quantify, the basic plan is to
@@ -2177,63 +2249,4 @@ whatever, because the type-class defaulting rules have yet to run.
 
 An alternate implementation would be to emit a Wanted constraint setting
 the RuntimeRep variable to LiftedRep, but this seems unnecessarily indirect.
-
-Note [Promote _and_ default when inferring]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When we are inferring a type, we simplify the constraint, and then use
-approximateWC to produce a list of candidate constraints.  Then we MUST
-
-  a) Promote any meta-tyvars that have been floated out by
-     approximateWC, to restore invariant (WantedInv) described in
-     Note [TcLevel invariants] in GHC.Tc.Utils.TcType.
-
-  b) Default the kind of any meta-tyvars that are not mentioned in
-     in the environment.
-
-To see (b), suppose the constraint is (C ((a :: OpenKind) -> Int)), and we
-have an instance (C ((x:*) -> Int)).  The instance doesn't match -- but it
-should!  If we don't solve the constraint, we'll stupidly quantify over
-(C (a->Int)) and, worse, in doing so skolemiseQuantifiedTyVar will quantify over
-(b:*) instead of (a:OpenKind), which can lead to disaster; see #7332.
-#7641 is a simpler example.
-
-Note [Promoting unification variables]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When we float an equality out of an implication we must "promote" free
-unification variables of the equality, in order to maintain Invariant
-(WantedInv) from Note [TcLevel invariants] in GHC.Tc.Types.TcType.
-
-This is absolutely necessary. Consider the following example. We start
-with two implications and a class with a functional dependency.
-
-    class C x y | x -> y
-    instance C [a] [a]
-
-    (I1)      [untch=beta]forall b. 0 => F Int ~ [beta]
-    (I2)      [untch=beta]forall c. 0 => F Int ~ [[alpha]] /\ C beta [c]
-
-We float (F Int ~ [beta]) out of I1, and we float (F Int ~ [[alpha]]) out of I2.
-They may react to yield that (beta := [alpha]) which can then be pushed inwards
-the leftover of I2 to get (C [alpha] [a]) which, using the FunDep, will mean that
-(alpha := a). In the end we will have the skolem 'b' escaping in the untouchable
-beta! Concrete example is in indexed_types/should_fail/ExtraTcsUntch.hs:
-
-    class C x y | x -> y where
-     op :: x -> y -> ()
-
-    instance C [a] [a]
-
-    type family F a :: *
-
-    h :: F Int -> ()
-    h = undefined
-
-    data TEx where
-      TEx :: a -> TEx
-
-    f (x::beta) =
-        let g1 :: forall b. b -> ()
-            g1 _ = h [x]
-            g2 z = case z of TEx y -> (h [[undefined]], op x [y])
-        in (g1 '3', g2 undefined)
 -}


=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -818,7 +818,11 @@ findDefaultableGroups (default_tys, extended_defaults) wanteds
     , defaultable_tyvar tv
     , defaultable_classes (map (classTyCon . sndOf3) group) ]
   where
-    simples                = approximateWC True wanteds
+    simples  = approximateWC True wanteds
+      -- True: for the purpose of defaulting we don't care
+      --       about shape or enclosing equalities
+      -- See (W3) in Note [ApproximateWC] in GHC.Tc.Types.Constraint
+
     (unaries, non_unaries) = partitionWith find_unary (bagToList simples)
     unary_groups           = equivClasses cmp_tv unaries
 


=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -73,9 +73,6 @@ simplifyWantedsTcM wanted
 
 solveWanteds :: WantedConstraints -> TcS WantedConstraints
 solveWanteds wc@(WC { wc_errors = errs })
-  | isEmptyWC wc  -- Fast path
-  = return wc
-  | otherwise
   = do { cur_lvl <- TcS.getTcLevel
        ; traceTcS "solveWanteds {" $
          vcat [ text "Level =" <+> ppr cur_lvl
@@ -106,6 +103,9 @@ simplify_loop :: Int -> IntWithInf -> Bool
 -- else, so we do them once, at the end in solveWanteds
 simplify_loop n limit definitely_redo_implications
               wc@(WC { wc_simple = simples, wc_impl = implics })
+  | isSolvedWC wc  -- Fast path
+  = return wc
+  | otherwise
   = do { csTraceTcS $
          text "simplify_loop iteration=" <> int n
          <+> (parens $ hsep [ text "definitely_redo =" <+> ppr definitely_redo_implications <> comma
@@ -145,7 +145,7 @@ maybe_simplify_again n limit unif_happened wc@(WC { wc_simple = simples })
   | unif_happened
   = simplify_loop n limit True wc
 
-  | superClassesMightHelp wc
+  | superClassesMightHelp wc    -- Returns False quickly if wc is solved
   = -- We still have unsolved goals, and apparently no way to solve them,
     -- so try expanding superclasses at this level, both Given and Wanted
     do { pending_given <- getPendingGivenScs


=====================================
compiler/GHC/Tc/TyCl/PatSyn.hs
=====================================
@@ -154,7 +154,7 @@ tcInferPatSynDecl (PSB { psb_id = lname@(L _ name), psb_args = details
 
        ; ((univ_tvs, req_dicts, ev_binds, _), residual)
                <- captureConstraints $
-                  simplifyInfer tclvl NoRestrictions [] named_taus wanted
+                  simplifyInfer TopLevel tclvl NoRestrictions [] named_taus wanted
        ; top_ev_binds <- checkNoErrs (simplifyTop residual)
        ; addTopEvBinds top_ev_binds $
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -61,7 +61,7 @@ module GHC.Tc.Types.Constraint (
         tyCoVarsOfWC, tyCoVarsOfWCList,
         insolubleWantedCt, insolubleCt, insolubleIrredCt,
         insolubleImplic, nonDefaultableTyVarsOfWC,
-        approximateWC,
+        approximateWCX, approximateWC,
 
         Implication(..), implicationPrototype, checkTelescopeSkol,
         ImplicStatus(..), isInsolubleStatus, isSolvedStatus,
@@ -1815,60 +1815,121 @@ At the end, we will hopefully have substituted uf1 := F alpha, and we
 will be able to report a more informative error:
     'Can't construct the infinite type beta ~ F alpha beta'
 
+
 ************************************************************************
 *                                                                      *
-            Invariant checking (debug only)
+                     approximateWC
 *                                                                      *
 ************************************************************************
 -}
 
-approximateWC :: Bool   -- See Wrinkle (W3) in Note [ApproximateWC]
-              -> WantedConstraints
-              -> Cts
--- Second return value is the depleted wc
--- Postcondition: Wanted Cts
+type ApproxWC = ( Bag Ct    -- Free quantifiable constraints
+                , Bag Ct )  -- Free non-quantifiable constraints
+                            -- due to shape, or enclosing equality
+
+approximateWC :: Bool -> WantedConstraints -> Bag Ct
+approximateWC include_non_quantifiable cts
+  | include_non_quantifiable = quant `unionBags` no_quant
+  | otherwise                = quant
+  where
+    (quant, no_quant) = approximateWCX cts
+
+approximateWCX :: WantedConstraints -> ApproxWC
+-- The "X" means "extended";
+--    we return both quantifiable and non-quantifiable constraints
 -- See Note [ApproximateWC]
 -- See Note [floatKindEqualities vs approximateWC]
-approximateWC float_past_equalities wc
-  = float_wc False emptyVarSet wc
+approximateWCX wc
+  = float_wc False emptyVarSet wc (emptyBag, emptyBag)
   where
     float_wc :: Bool           -- True <=> there are enclosing equalities
              -> TcTyCoVarSet   -- Enclosing skolem binders
-             -> WantedConstraints -> Cts
-    float_wc encl_eqs trapping_tvs (WC { wc_simple = simples, wc_impl = implics })
-      = filterBag (is_floatable encl_eqs trapping_tvs) simples `unionBags`
-        concatMapBag (float_implic encl_eqs trapping_tvs) implics
-
-    float_implic :: Bool -> TcTyCoVarSet -> Implication -> Cts
+             -> WantedConstraints
+             -> ApproxWC -> ApproxWC
+    float_wc encl_eqs trapping_tvs (WC { wc_simple = simples, wc_impl = implics }) acc
+      = foldBag_flip (float_ct     encl_eqs trapping_tvs) simples $
+        foldBag_flip (float_implic encl_eqs trapping_tvs) implics $
+        acc
+
+    float_implic :: Bool -> TcTyCoVarSet -> Implication
+                 -> ApproxWC -> ApproxWC
     float_implic encl_eqs trapping_tvs imp
       = float_wc new_encl_eqs new_trapping_tvs (ic_wanted imp)
       where
         new_trapping_tvs = trapping_tvs `extendVarSetList` ic_skols imp
         new_encl_eqs = encl_eqs || ic_given_eqs imp == MaybeGivenEqs
 
-    is_floatable encl_eqs skol_tvs ct
-       | isGivenCt ct                                = False
-       | insolubleCt ct                              = False
-       | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = False
+    float_ct :: Bool -> TcTyCoVarSet -> Ct
+             -> ApproxWC -> ApproxWC
+    float_ct encl_eqs skol_tvs ct acc@(quant, no_quant)
+       | isGivenCt ct                                = acc
+           -- There can be (insoluble) Given constraints in wc_simple,
+           -- there so that we get error reports for unreachable code
+           -- See `given_insols` in GHC.Tc.Solver.Solve.solveImplication
+       | insolubleCt ct                              = acc
+       | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
        | otherwise
        = case classifyPredType (ctPred ct) of
-           EqPred {}     -> float_past_equalities || not encl_eqs
-                                  -- See Wrinkle (W1)
-           ClassPred {}  -> True  -- See Wrinkle (W2)
-           IrredPred {}  -> True  -- ..both in Note [ApproximateWC]
-           ForAllPred {} -> False
+           -- See the classification in Note [ApproximateWC]
+           EqPred eq_rel ty1 ty2
+             | not encl_eqs      -- See Wrinkle (W1)
+             , quantify_equality eq_rel ty1 ty2
+             -> add_to_quant
+             | otherwise
+             -> add_to_no_quant
+
+           ClassPred cls tys
+             | Just {} <- isCallStackPred cls tys
+               -- NEVER infer a CallStack constraint.  Otherwise we let
+               -- the constraints bubble up to be solved from the outer
+               -- context, or be defaulted when we reach the top-level.
+               -- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
+             -> add_to_no_quant
+
+             | otherwise
+             -> add_to_quant  -- See Wrinkle (W2)
+
+           IrredPred {}  -> add_to_quant  -- See Wrinkle (W2)
+
+           ForAllPred {} -> add_to_no_quant  -- Never quantify these
+       where
+         add_to_quant    = (ct `consBag` quant, no_quant)
+         add_to_no_quant = (quant, ct `consBag` no_quant)
+
+    -- See Note [Quantifying over equality constraints]
+    quantify_equality NomEq  ty1 ty2 = quant_fun ty1 || quant_fun ty2
+    quantify_equality ReprEq _   _   = True
+
+    quant_fun ty
+      = case tcSplitTyConApp_maybe ty of
+          Just (tc, _) -> isTypeFamilyTyCon tc
+          _              -> False
 
 {- Note [ApproximateWC]
 ~~~~~~~~~~~~~~~~~~~~~~~
 approximateWC takes a constraint, typically arising from the RHS of a
-let-binding whose type we are *inferring*, and extracts from it some
-*simple* constraints that we might plausibly abstract over.  Of course
-the top-level simple constraints are plausible, but we also float constraints
-out from inside, if they are not captured by skolems.
+let-binding whose type we are *inferring*, and extracts from it some *simple*
+constraints that we might plausibly abstract over.  Of course the top-level
+simple constraints are plausible, but we also float constraints out from inside,
+if they are not captured by skolems.
 
 The same function is used when doing type-class defaulting (see the call
 to applyDefaultingRules) to extract constraints that might be defaulted.
 
+We proceed by classifying the constraint:
+  * ClassPred:
+    * Never pick a CallStack constraint.
+      See Note [Overview of implicit CallStacks]
+    * Always pick an implicit-parameter constraint.
+      Note [Inheriting implicit parameters]
+    See wrinkle (W2)
+
+  * EqPred: see Note [Quantifying over equality constraints]
+
+  * IrredPred: we allow anything.
+
+  * ForAllPred: never quantify over these
+
 Wrinkle (W1)
   When inferring most-general types (in simplifyInfer), we
   do *not* float an equality constraint if the implication binds
@@ -1884,22 +1945,19 @@ Wrinkle (W1)
   non-principal types.)
 
 Wrinkle (W2)
-  We do allow /class/ constraints to float, even if
-  the implication binds equalities.  This is a subtle point: see #23224.
-  In principle, a class constraint might ultimately be satisfiable from
-  a constraint bound by an implication (see #19106 for an example of this
-  kind), but it's extremely obscure and I was unable to construct a
-  concrete example.  In any case, in super-subtle cases where this might
-  make a difference, you would be much better advised to simply write a
-  type signature.
-
-  I included IrredPred here too, for good measure.  In general,
-  abstracting over more constraints does no harm.
+  We do allow /class/ constraints to float, even if the implication binds
+  equalities.  This is a subtle point: see #23224.  In principle, a class
+  constraint might ultimately be satisfiable from a constraint bound by an
+  implication (see #19106 for an example of this kind), but it's extremely
+  obscure and I was unable to construct a concrete example.  In any case, in
+  super-subtle cases where this might make a difference, you would be much
+  better advised to simply write a type signature.
 
 Wrinkle (W3)
-  In findDefaultableGroups we are not worried about the
-  most-general type; and we /do/ want to float out of equalities
-  (#12797).  Hence the boolean flag to approximateWC.
+  In findDefaultableGroups we are not worried about the most-general type; and
+  we /do/ want to float out of equalities (#12797).  Hence we just union the two
+  returned lists.
+
 
 ------ Historical note -----------
 There used to be a second caveat, driven by #8155
@@ -1926,6 +1984,33 @@ you want.  So I simply removed the extra code to implement the
 contamination stuff.  There was zero effect on the testsuite (not even #8155).
 ------ End of historical note -----------
 
+Note [Quantifying over equality constraints]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Should we quantify over an equality constraint (s ~ t)
+in pickQuantifiablePreds?
+
+* It is always /sound/ to quantify over a constraint -- those
+  quantified constraints will need to be proved at each call site.
+
+* We definitely don't want to quantify over (Maybe a ~ Bool), to get
+     f :: forall a. (Maybe a ~ Bool) => blah
+  That simply postpones a type error from the function definition site to
+  its call site.  Fortunately we have already filtered out insoluble
+  constraints: see `definite_error` in `simplifyInfer`.
+
+* What about (a ~ T alpha b), where we are about to quantify alpha, `a` and
+  `b` are in-scope skolems, and `T` is a data type.  It's pretty unlikely
+  that this will be soluble at a call site, so we don't quantify over it.
+
+* What about `(F beta ~ Int)` where we are going to quantify `beta`?
+  Should we quantify over the (F beta ~ Int), to get
+     f :: forall b. (F b ~ Int) => blah
+  Aha!  Perhaps yes, because at the call site we will instantiate `b`, and
+  perhaps we have `instance F Bool = Int`. So we *do* quantify over a
+  type-family equality where the arguments mention the quantified variables.
+
+This is all a bit ad-hoc.
+
 
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -78,9 +78,8 @@ module GHC.Tc.Utils.TcMType (
   ---------------------------------
   -- Promotion, defaulting, skolemisation
   defaultTyVar, promoteMetaTyVarTo, promoteTyVarSet,
-  quantifyTyVars, isQuantifiableTv,
+  quantifyTyVars, doNotQuantifyTyVars,
   zonkAndSkolemise, skolemiseQuantifiedTyVar,
-  doNotQuantifyTyVars,
 
   candidateQTyVarsOfType,  candidateQTyVarsOfKind,
   candidateQTyVarsOfTypes, candidateQTyVarsOfKinds,
@@ -1788,15 +1787,6 @@ quantifyTyVars skol_info ns_strat dvs
       | otherwise
       = Just <$> skolemiseQuantifiedTyVar skol_info tkv
 
-isQuantifiableTv :: TcLevel   -- Level of the context, outside the quantification
-                 -> TcTyVar
-                 -> Bool
-isQuantifiableTv outer_tclvl tcv
-  | isTcTyVar tcv  -- Might be a CoVar; change this when gather covars separately
-  = tcTyVarLevel tcv `strictlyDeeperThan` outer_tclvl
-  | otherwise
-  = False
-
 zonkAndSkolemise :: SkolemInfo -> TcTyCoVar -> ZonkM TcTyCoVar
 -- A tyvar binder is never a unification variable (TauTv),
 -- rather it is always a skolem. It *might* be a TyVarTv.
@@ -2414,7 +2404,7 @@ promoteMetaTyVarTo :: HasDebugCallStack => TcLevel -> TcTyVar -> TcM Bool
 -- invariant (WantedInv) in Note [TcLevel invariants] in GHC.Tc.Utils.TcType
 -- Return True <=> we did some promotion
 -- Also returns either the original tyvar (no promotion) or the new one
--- See Note [Promoting unification variables]
+-- See Note [Promote monomorphic tyvars] in GHC.Tc.Solver
 promoteMetaTyVarTo tclvl tv
   | assertPpr (isMetaTyVar tv) (ppr tv) $
     tcTyVarLevel tv `strictlyDeeperThan` tclvl


=====================================
testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
=====================================
@@ -1,12 +1,12 @@
 ExtraTcsUntch.hs:23:18: error: [GHC-83865]
     • Couldn't match expected type: F Int
-                  with actual type: [[a0]]
+                  with actual type: [p0]
     • In the first argument of ‘h’, namely ‘[x]’
       In the expression: h [x]
       In an equation for ‘g1’: g1 _ = h [x]
     • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
+        x :: p0 (bound at ExtraTcsUntch.hs:21:3)
+        f :: p0 -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 
 ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • Couldn't match expected type: F Int
@@ -14,7 +14,4 @@ ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • In the first argument of ‘h’, namely ‘[[undefined]]’
       In the expression: h [[undefined]]
       In the expression: (h [[undefined]], op x [y])
-    • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 


=====================================
testsuite/tests/partial-sigs/should_fail/T10615.stderr
=====================================
@@ -1,34 +1,39 @@
 
 T10615.hs:5:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w1’
-      Where: ‘w1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f1 :: w -> f
+               at T10615.hs:6:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f1 :: _ -> f
 
 T10615.hs:6:6: error: [GHC-25897]
-    • Couldn't match type ‘f’ with ‘b1 -> w1’
-      Expected: w1 -> f
-        Actual: w1 -> b1 -> w1
+    • Couldn't match type ‘f’ with ‘b1 -> w’
+      Expected: w -> f
+        Actual: w -> b1 -> w
       ‘f’ is a rigid type variable bound by
-        the inferred type of f1 :: w1 -> f
+        the inferred type of f1 :: w -> f
         at T10615.hs:5:1-12
     • In the expression: const
       In an equation for ‘f1’: f1 = const
-    • Relevant bindings include f1 :: w1 -> f (bound at T10615.hs:6:1)
+    • Relevant bindings include f1 :: w -> f (bound at T10615.hs:6:1)
 
 T10615.hs:8:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w0’
-      Where: ‘w0’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f2 :: w -> _f
+               at T10615.hs:9:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f2 :: _ -> _f
 
 T10615.hs:9:6: error: [GHC-25897]
-    • Couldn't match type ‘_f’ with ‘b0 -> w0’
-      Expected: w0 -> _f
-        Actual: w0 -> b0 -> w0
+    • Couldn't match type ‘_f’ with ‘b0 -> w’
+      Expected: w -> _f
+        Actual: w -> b0 -> w
       ‘_f’ is a rigid type variable bound by
-        the inferred type of f2 :: w0 -> _f
+        the inferred type of f2 :: w -> _f
         at T10615.hs:8:1-13
     • In the expression: const
       In an equation for ‘f2’: f2 = const
-    • Relevant bindings include f2 :: w0 -> _f (bound at T10615.hs:9:1)
+    • Relevant bindings include f2 :: w -> _f (bound at T10615.hs:9:1)
+


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,7 +1,9 @@
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
-      Where: ‘k0’ is an ambiguous type variable
-             ‘a'1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘a'’
+      Where: ‘a'’ is a rigid type variable bound by
+               the inferred type of
+                 traverseCompose :: (a -> f b) -> g a -> f (h a')
+               at T14172.hs:8:1-46
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -10,19 +12,18 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
-        Actual: (Unwrapped (Compose f'0 g'1 a'0)
-                 -> f (Unwrapped (h a'1)))
-                -> Compose f'0 g'1 a'0 -> f (h a'1)
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
+        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
+                -> Compose f'0 g'1 a'0 -> f (h a')
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+          traverseCompose :: (a -> f b) -> g a -> f (h a')
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+        traverseCompose :: (a -> f b) -> g a -> f (h a')
           (bound at T14172.hs:8:1)
 


=====================================
testsuite/tests/typecheck/should_compile/T13785.hs
=====================================
@@ -2,15 +2,20 @@
 {-# OPTIONS_GHC -Wmonomorphism-restriction #-}
 module Bug where
 
-class Monad m => C m where
-  c :: (m Char, m Char)
+class Monad x => C x where
+  c :: (x Char, x Char)
 
 foo :: forall m. C m => m Char
-foo = bar >> baz >> bar2
+foo = bar >> baz >> bar1 >> bar2
   where
     -- Should not get MR warning
     bar, baz :: m Char
     (bar, baz) = c
 
+    -- Should not get MR warning
+    (bar1, baz1) = c :: (m Char, m Char)
+
     -- Should get MR warning
+    -- Natural type for the "whole binding": forall x. C x => (x Char, x Char)
+    -- MR makes it less polymorphic => warning.
     (bar2, baz2) = c


=====================================
testsuite/tests/typecheck/should_compile/T13785.stderr
=====================================
@@ -1,12 +1,13 @@
-
-T13785.hs:16:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
+T13785.hs:21:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
     • The Monomorphism Restriction applies to the bindings
       for ‘bar2’, ‘baz2’
     • In an equation for ‘foo’:
           foo
-            = bar >> baz >> bar2
+            = bar >> baz >> bar1 >> bar2
             where
                 bar, baz :: m Char
                 (bar, baz) = c
+                (bar1, baz1) = c :: (m Char, m Char)
                 (bar2, baz2) = c
     Suggested fix: Consider giving ‘baz2’ and ‘bar2’ a type signature
+


=====================================
testsuite/tests/typecheck/should_compile/T25266.hs
=====================================
@@ -0,0 +1,127 @@
+{-# OPTIONS_GHC -Wno-missing-methods #-}
+{-# LANGUAGE GHC2021 #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE ImplicitPrelude #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module GHC25266 where
+
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Class (MonadTrans (lift))
+import Control.Monad.Trans.Reader (ReaderT, mapReaderT, runReaderT)
+import Data.Kind (Type)
+import Data.Void (Void)
+import GHC.Stack (HasCallStack, withFrozenCallStack)
+
+class MonadIO m => CanRunDB m where
+  unsafeUnlabelledRunDB :: HasCallStack => SqlPersistT m a -> m a
+
+type DBImpl backend env = ReaderT env (ReaderT backend IO)
+
+newtype DBWith backend env a = DB (DBImpl backend env a)
+  deriving newtype (Functor, Applicative, Monad)
+
+type DBEnv = ()
+
+type DB = DBWith SqlBackend DBEnv
+
+class Monad m => PersistentOperation m where
+  type PersistentBackend m
+  unsafeLiftPersistentOperation :: HasCallStack => ReaderT (PersistentBackend m) IO a -> m a
+
+instance PersistentOperation (DBWith backend env) where
+  type PersistentBackend (DBWith backend env) = backend
+  unsafeLiftPersistentOperation = DB . lift . checkpointCallStack
+
+toSqlPersistTIO :: env -> DBWith backend env a -> ReaderT backend IO a
+toSqlPersistTIO env (DB act) = runReaderT act env
+
+hoistIO :: MonadIO m => ReaderT backend IO a -> ReaderT backend m a
+hoistIO = mapReaderT liftIO
+
+liftToSqlPersistT :: forall m a backend. (CanRunDB m) => DBWith backend DBEnv a -> ReaderT backend m a
+liftToSqlPersistT action = do
+  let dbEnv = ()
+  hoistIO $ toSqlPersistTIO dbEnv action
+
+runDB :: (HasCallStack, CanRunDB m) => DB a -> m a
+runDB action = withFrozenCallStack unsafeUnlabelledRunDB $ liftToSqlPersistT action
+
+streamRows ::
+  forall m a.
+  (MonadUnliftIO m, CanRunDB m) =>
+  (forall n. (PersistentOperation n, PersistentBackend n ~ SqlBackend) => n [a]) ->
+  ConduitT () [a] m ()
+streamRows runQuery = go (10 :: Integer)
+  where
+    go n
+      | n < 0 = pure ()
+      | otherwise = do
+          rows <- lift . runDB $ runQuery
+          yield rows
+          go (n - 1)
+
+expectedList :: [Int]
+expectedList = [1, 2, 3]
+
+query :: forall n. (PersistentOperation n, PersistentBackend n ~ SqlBackend) => n [Int]
+query = pure expectedList
+
+test_success :: forall m. (MonadUnliftIO m, CanRunDB m) => m [[Int]]
+test_success = do
+  let conduit = streamRows query .| (sinkList @_ @[Int])
+  runConduit conduit
+
+test_fail :: forall m. (MonadUnliftIO m, CanRunDB m) => m [[Int]]
+test_fail = do
+  let conduit = streamRows query .| sinkList
+  runConduit conduit
+
+-----
+-- annotated-exception
+-----
+
+checkpointCallStack
+    -- :: (MonadCatch m, HasCallStack)
+    :: (Monad m, HasCallStack)
+    => m a
+    -> m a
+checkpointCallStack = id
+
+-----
+-- conduit
+-----
+
+data ConduitT i o (m :: Type -> Type) r
+instance Functor (ConduitT i o m)
+instance Applicative (ConduitT i o m)
+instance Monad (ConduitT i o m)
+instance MonadTrans (ConduitT i o)
+
+(.|) :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
+(.|) = undefined
+
+runConduit :: Monad m => ConduitT () Void m r -> m r
+runConduit = undefined
+
+sinkList :: Monad m => ConduitT a o m [a]
+sinkList = undefined
+
+yield :: Monad m => o -> ConduitT i o m ()
+yield = undefined
+
+-----
+-- persistent
+-----
+
+data SqlBackend
+
+type SqlPersistT = ReaderT SqlBackend
+
+-----
+-- unliftio
+-----
+
+class MonadIO m => MonadUnliftIO m where
+  withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b


=====================================
testsuite/tests/typecheck/should_compile/T25266a.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs #-}
+
+module T25266a where
+
+data T a where { T1 :: T Int; T2 :: a -> T a }
+
+-- Rejected, becuase there is no principal type,
+-- and the function is top level
+f x y t = (case t of
+                      T1   -> length [x,y]
+                      T2 _ -> 2)  :: Int
+
+


=====================================
testsuite/tests/typecheck/should_compile/T25266a.stderr
=====================================
@@ -0,0 +1,21 @@
+T25266a.hs:10:41: error: [GHC-25897]
+    • Could not deduce ‘p1 ~ p2’
+      from the context: a ~ Int
+        bound by a pattern with constructor: T1 :: T Int,
+                 in a case alternative
+        at T25266a.hs:10:23-24
+      ‘p1’ is a rigid type variable bound by
+        the inferred type of f :: p1 -> p2 -> T a -> Int
+        at T25266a.hs:(9,1)-(11,40)
+      ‘p2’ is a rigid type variable bound by
+        the inferred type of f :: p1 -> p2 -> T a -> Int
+        at T25266a.hs:(9,1)-(11,40)
+    • In the expression: y
+      In the first argument of ‘length’, namely ‘[x, y]’
+      In the expression: length [x, y]
+    • Relevant bindings include
+        y :: p2 (bound at T25266a.hs:9:5)
+        x :: p1 (bound at T25266a.hs:9:3)
+        f :: p1 -> p2 -> T a -> Int (bound at T25266a.hs:9:1)
+    Suggested fix: Consider giving ‘f’ a type signature
+


=====================================
testsuite/tests/typecheck/should_compile/T25266b.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE GADTs #-}
+
+module T25266b where
+
+data T a where { T1 :: T Int; T2 :: a -> T a }
+
+h :: Int -> (Int,Int)
+-- Binding for `f` is accepted; we do not generalise it
+--     f :: forall a. alpha -> beta -> T a -> Int
+-- We figure out alpha/beta from the call sites
+h p = let f x y t = (case t of
+                      T1   -> length [x,y]
+                      T2 _ -> 2)  :: Int
+      in (f p (4::Int) (T2 'c'), f 4 5 (T2 "oooh"))
+


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -934,4 +934,7 @@ test('T25125', normal, compile, [''])
 test('T24845a', normal, compile, [''])
 test('T23501a', normal, compile, [''])
 test('T23501b', normal, compile, [''])
+test('T25266', normal, compile, [''])
+test('T25266a', normal, compile_fail, [''])
+test('T25266b', normal, compile, [''])
 


=====================================
testsuite/tests/typecheck/should_fail/T18398.stderr
=====================================
@@ -6,7 +6,7 @@ T18398.hs:13:34: error: [GHC-39999]
       In the expression: case x of MkEx _ -> meth x y
 
 T18398.hs:13:70: error: [GHC-39999]
-    • No instance for ‘C Ex t0’ arising from a use of ‘meth’
+    • No instance for ‘C Ex t1’ arising from a use of ‘meth’
     • In the expression: meth x z
       In a case alternative: MkEx _ -> meth x z
       In the expression: case x of MkEx _ -> meth x z



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3fb9764f14acab1c3082cd98842eee6e6e110c44

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 22:04:26 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Thu, 17 Oct 2024 18:04:26 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-5
Message-ID: <671189ea19605_29d17e7c448075612@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-5 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 22:23:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 18:23:02 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 50 commits: ghci:
 mitigate host/target word size mismatch in BCOByteArray serialization
Message-ID: <67118e462c532_101b90192a5895a2@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
e9262761 by Cheng Shao at 2024-10-17T18:22:48-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
d6dbcd87 by Cheng Shao at 2024-10-17T18:22:48-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- + compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/ghc.cabal.in
- ghc/Main.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/doc/flavours.md
- hadrian/src/Base.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9b59b69a905bcbc7175e2c654614da47d8e6f3b...d6dbcd8718a8d1ad37b06806b7c14d3e90445464

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9b59b69a905bcbc7175e2c654614da47d8e6f3b...d6dbcd8718a8d1ad37b06806b7c14d3e90445464
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 17 22:40:24 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Thu, 17 Oct 2024 18:40:24 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-5] EPA: Remove [AddEpAnn]
 from StandaloneKindSig
Message-ID: <6711925821e4f_101b90311fdc233a5@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-5 at Glasgow Haskell Compiler / GHC


Commits:
395c02ad by Alan Zimmerman at 2024-10-17T23:39:55+01:00
EPA: Remove [AddEpAnn] from StandaloneKindSig

- - - - -


5 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -741,7 +741,7 @@ instance OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) where
   ppr (DctSingle _ ty) = ppr ty
   ppr (DctMulti _ tys) = parens (interpp'SP tys)
 
-type instance XStandaloneKindSig GhcPs = [AddEpAnn]
+type instance XStandaloneKindSig GhcPs = (EpToken "type", TokDcolon)
 type instance XStandaloneKindSig GhcRn = NoExtField
 type instance XStandaloneKindSig GhcTc = NoExtField
 
@@ -750,7 +750,7 @@ type instance XXStandaloneKindSig (GhcPass p) = DataConCantHappen
 standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
 standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname
 
-type instance XConDeclGADT GhcPs = (EpUniToken "::" "∷", [AddEpAnn])
+type instance XConDeclGADT GhcPs = (TokDcolon, [AddEpAnn])
 type instance XConDeclGADT GhcRn = NoExtField
 type instance XConDeclGADT GhcTc = NoExtField
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1366,7 +1366,7 @@ ty_decl :: { LTyClDecl GhcPs }
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
   : 'type' sks_vars '::' sigktype
       {% mkStandaloneKindSig (comb2 $1 $4) (L (gl $2) $ unLoc $2) $4
-               [mj AnnType $1,mu AnnDcolon $3]}
+               (epTok $1,epUniTok $3)}
 
 -- See also: sig_vars
 sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -283,7 +283,7 @@ mkStandaloneKindSig
   :: SrcSpan
   -> Located [LocatedN RdrName]   -- LHS
   -> LHsSigType GhcPs             -- RHS
-  -> [AddEpAnn]
+  -> (EpToken "type", TokDcolon)
   -> P (LStandaloneKindSig GhcPs)
 mkStandaloneKindSig loc lhs rhs anns =
   do { vs <- mapM check_lhs_name (unLoc lhs)


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -201,8 +201,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:9:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:9:13-14 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:9:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:9:13-14 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:9:6-11 })
@@ -885,8 +889,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:17:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:17:9-10 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:17:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:17:9-10 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:17:6-7 })


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2907,12 +2907,12 @@ instance ExactPrint (StandaloneKindSig GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StandaloneKindSig an vars sig) = do
-    an0 <- markEpAnnL an lidl AnnType
+  exact (StandaloneKindSig (tt,td) vars sig) = do
+    tt' <- markEpToken tt
     vars' <- markAnnotated vars
-    an1 <- markEpAnnL an0 lidl AnnDcolon
+    td' <- markEpUniToken td
     sig' <- markAnnotated sig
-    return (StandaloneKindSig an1 vars' sig')
+    return (StandaloneKindSig (tt',td') vars' sig')
 
 -- ---------------------------------------------------------------------
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/395c02ad803917d011050115cf9c152c05c0a58f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 03:03:28 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 23:03:28 -0400
Subject: [Git][ghc/ghc][master] 48 commits: ghci: mitigate host/target word
 size mismatch in BCOByteArray serialization
Message-ID: <6711d00053e9c_1115ad4aa84452489@gitlab.mail>



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


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- + compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/ghc.cabal.in
- ghc/Main.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/doc/flavours.md
- hadrian/src/Base.hs
- hadrian/src/Flavour.hs
- hadrian/src/Oracles/Flag.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/076c1a104f55750a49de03694786180bd78eb9b6...74a1f6818d1592ebceab8e0fbb6be1973f38fe78

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/076c1a104f55750a49de03694786180bd78eb9b6...74a1f6818d1592ebceab8e0fbb6be1973f38fe78
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 03:03:58 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 23:03:58 -0400
Subject: [Git][ghc/ghc][master] Revert "compiler: start deprecating
 cmmToRawCmmHook"
Message-ID: <6711d01ea33cc_1115ad4aa844554cb@gitlab.mail>



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


Commits:
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -


2 changed files:

- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs


Changes:

=====================================
compiler/GHC/Driver/Hooks.hs
=====================================
@@ -154,8 +154,6 @@ data Hooks = Hooks
                                  -> IO (CgStream RawCmmGroup a)))
   }
 
-{-# DEPRECATED cmmToRawCmmHook "cmmToRawCmmHook is being deprecated. If you do use it in your project, please raise a GHC issue!" #-}
-
 class HasHooks m where
     getHooks :: m Hooks
 


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -5,9 +5,6 @@
 
 {-# OPTIONS_GHC -fprof-auto-top #-}
 
--- Remove this after cmmToRawCmmHook removal
-{-# OPTIONS_GHC -Wno-deprecations #-}
-
 -------------------------------------------------------------------------------
 --
 -- | Main API for compiling plain Haskell source code.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/525d451e175c7d6acfa968ce99d8d3fc7a8af0c7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 03:04:29 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 17 Oct 2024 23:04:29 -0400
Subject: [Git][ghc/ghc][master] rts: fix pointer overflow undefined behavior
 in bytecode interpreter
Message-ID: <6711d03d80576_1115ad6c60385837d@gitlab.mail>



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


Commits:
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -


1 changed file:

- rts/Interpreter.c


Changes:

=====================================
rts/Interpreter.c
=====================================
@@ -157,11 +157,11 @@ tag functions as tag inference currently doesn't rely on those being properly ta
    cap->r.rRet = (retcode);                             \
    return cap;
 
-#define Sp_plusB(n)  ((void *)(((StgWord8*)Sp) + (n)))
-#define Sp_minusB(n) ((void *)(((StgWord8*)Sp) - (n)))
+#define Sp_plusB(n)  ((void *)((StgWord8*)Sp + (ptrdiff_t)(n)))
+#define Sp_minusB(n) ((void *)((StgWord8*)Sp - (ptrdiff_t)(n)))
 
-#define Sp_plusW(n)  (Sp_plusB((n) * sizeof(W_)))
-#define Sp_minusW(n) (Sp_minusB((n) * sizeof(W_)))
+#define Sp_plusW(n)  (Sp_plusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
+#define Sp_minusW(n) (Sp_minusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
 
 #define Sp_addB(n)   (Sp = Sp_plusB(n))
 #define Sp_subB(n)   (Sp = Sp_minusB(n))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5bcfefd5bb73c18a9bad63d1813968832b696f9a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 08:01:45 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 18 Oct 2024 04:01:45 -0400
Subject: [Git][ghc/ghc][wip/T25266] Improve the generalisation code in
 Solver.simplifyInfer
Message-ID: <671215e952862_222cf8c849c54528@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
c2694cb7 by Simon Peyton Jones at 2024-10-18T09:01:11+01:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


23 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/typecheck/should_compile/T13785.hs
- testsuite/tests/typecheck/should_compile/T13785.stderr
- + testsuite/tests/typecheck/should_compile/T25266.hs
- + testsuite/tests/typecheck/should_compile/T25266a.hs
- + testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T25266b.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T18398.stderr


Changes:

=====================================
compiler/GHC/Data/Bag.hs
=====================================
@@ -16,7 +16,7 @@ module GHC.Data.Bag (
         mapBag, pprBag,
         elemBag, lengthBag,
         filterBag, partitionBag, partitionBagWith,
-        concatBag, catBagMaybes, foldBag,
+        concatBag, catBagMaybes, foldBag_flip,
         isEmptyBag, isSingletonBag, consBag, snocBag, anyBag, allBag,
         listToBag, nonEmptyToBag, bagToList, headMaybe, mapAccumBagL,
         concatMapBag, concatMapBagPair, mapMaybeBag, mapMaybeBagM, unzipBag,
@@ -194,24 +194,10 @@ partitionBagWith pred (TwoBags b1 b2)
 partitionBagWith pred (ListBag vs) = (listToBag sats, listToBag fails)
   where (sats, fails) = partitionWith pred (toList vs)
 
-foldBag :: (r -> r -> r) -- Replace TwoBags with this; should be associative
-        -> (a -> r)      -- Replace UnitBag with this
-        -> r             -- Replace EmptyBag with this
-        -> Bag a
-        -> r
-
-{- Standard definition
-foldBag t u e EmptyBag        = e
-foldBag t u e (UnitBag x)     = u x
-foldBag t u e (TwoBags b1 b2) = (foldBag t u e b1) `t` (foldBag t u e b2)
-foldBag t u e (ListBag xs)    = foldr (t.u) e xs
--}
-
--- More tail-recursive definition, exploiting associativity of "t"
-foldBag _ _ e EmptyBag        = e
-foldBag t u e (UnitBag x)     = u x `t` e
-foldBag t u e (TwoBags b1 b2) = foldBag t u (foldBag t u e b2) b1
-foldBag t u e (ListBag xs)    = foldr (t.u) e xs
+foldBag_flip :: (a -> b -> b) -> Bag a -> b -> b
+-- Just foldr with flipped arguments,
+-- so it can be chained more nicely
+foldBag_flip k bag z = foldr k z bag
 
 mapBag :: (a -> b) -> Bag a -> Bag b
 mapBag = fmap


=====================================
compiler/GHC/Tc/Deriv/Infer.hs
=====================================
@@ -763,9 +763,11 @@ simplifyDeriv (DS { ds_loc = loc, ds_tvs = tvs
        -- See [STEP DAC HOIST]
        -- From the simplified constraints extract a subset 'good' that will
        -- become the context 'min_theta' for the derived instance.
-       ; let residual_simple = approximateWC True solved_wanteds
-             head_size       = pSizeClassPred clas inst_tys
-             good = mapMaybeBag get_good residual_simple
+       ; let residual_simple = approximateWC False solved_wanteds
+                -- False: ignore any non-quantifiable constraints,
+                --        including equalities hidden under Given equalities
+             head_size = pSizeClassPred clas inst_tys
+             good      = mapMaybeBag get_good residual_simple
 
              -- Returns @Just p@ (where @p@ is the type of the Ct) if a Ct is
              -- suitable to be inferred in the context of a derived instance.


=====================================
compiler/GHC/Tc/Gen/Bind.hs
=====================================
@@ -490,8 +490,8 @@ tcPolyBinds top_lvl sig_fn prag_fn rec_group rec_tc closed bind_list
     ; let plan = decideGeneralisationPlan dflags top_lvl closed sig_fn bind_list
     ; traceTc "Generalisation plan" (ppr plan)
     ; result@(_, scaled_poly_ids) <- case plan of
-         NoGen              -> tcPolyNoGen rec_tc prag_fn sig_fn bind_list
-         InferGen           -> tcPolyInfer rec_tc prag_fn sig_fn bind_list
+         NoGen              -> tcPolyNoGen         rec_tc prag_fn sig_fn bind_list
+         InferGen           -> tcPolyInfer top_lvl rec_tc prag_fn sig_fn bind_list
          CheckGen lbind sig -> tcPolyCheck prag_fn sig lbind
 
     ; let poly_ids = map scaledThing scaled_poly_ids
@@ -708,12 +708,13 @@ To address this we to do a few things
 -}
 
 tcPolyInfer
-  :: RecFlag       -- Whether it's recursive after breaking
+  :: TopLevelFlag
+  -> RecFlag       -- Whether it's recursive after breaking
                    -- dependencies based on type signatures
   -> TcPragEnv -> TcSigFun
   -> [LHsBind GhcRn]
   -> TcM (LHsBinds GhcTc, [Scaled TcId])
-tcPolyInfer rec_tc prag_fn tc_sig_fn bind_list
+tcPolyInfer top_lvl rec_tc prag_fn tc_sig_fn bind_list
   = do { (tclvl, wanted, (binds', mono_infos))
              <- pushLevelAndCaptureConstraints  $
                 tcMonoBinds rec_tc tc_sig_fn LetLclBndr bind_list
@@ -733,7 +734,7 @@ tcPolyInfer rec_tc prag_fn tc_sig_fn bind_list
 
        ; traceTc "simplifyInfer call" (ppr tclvl $$ ppr name_taus $$ ppr wanted)
        ; ((qtvs, givens, ev_binds, insoluble), residual)
-            <- captureConstraints $ simplifyInfer tclvl infer_mode sigs name_taus wanted
+            <- captureConstraints $ simplifyInfer top_lvl tclvl infer_mode sigs name_taus wanted
 
        ; let inferred_theta = map evVarPred givens
        ; scaled_exports <- checkNoErrs $


=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -696,7 +696,8 @@ tcExprSig expr sig@(TcPartialSig (PSig { psig_name = name, psig_loc = loc }))
                         | otherwise
                         = NoRestrictions
        ; ((qtvs, givens, ev_binds, _), residual)
-           <- captureConstraints $ simplifyInfer tclvl infer_mode [sig_inst] [(name, tau)] wanted
+           <- captureConstraints $
+              simplifyInfer NotTopLevel tclvl infer_mode [sig_inst] [(name, tau)] wanted
        ; emitConstraints residual
 
        ; tau <- liftZonkM $ zonkTcType tau


=====================================
compiler/GHC/Tc/Instance/FunDeps.hs
=====================================
@@ -578,11 +578,22 @@ closeWrtFunDeps preds fixed_tvs
        = case classifyPredType pred of
             EqPred NomEq t1 t2 -> [([t1],[t2]), ([t2],[t1])]
                -- See Note [Equality superclasses]
-            ClassPred cls tys  -> [ instFD fd cls_tvs tys
-                                  | let (cls_tvs, cls_fds) = classTvsFds cls
-                                  , fd <- cls_fds ]
+
+            ClassPred cls tys | not (isIPClass cls)
+               -- isIPClass: see Note [closeWrtFunDeps ignores implicit parameters]
+                              -> [ instFD fd cls_tvs tys
+                                 | let (cls_tvs, cls_fds) = classTvsFds cls
+                                 , fd <- cls_fds ]
             _ -> []
 
+{- Note [closeWrtFunDeps ignores implicit parameters]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Implicit params don't really determine a type variable (that is, we might have
+IP "c" Bool and IP "c" Int in different places within the same program), and
+skipping this causes implicit params to monomorphise too many variables; see
+Note [Inheriting implicit parameters] in GHC.Tc.Solver.  Skipping causes
+typecheck/should_compile/tc219 to fail.
+-}
 
 {- *********************************************************************
 *                                                                      *


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -2582,7 +2582,7 @@ tcRnExpr hsc_env mode rdr_expr
     let { fresh_it = itName uniq (getLocA rdr_expr) } ;
     ((qtvs, dicts, _, _), residual)
          <- captureConstraints $
-            simplifyInfer tclvl infer_mode
+            simplifyInfer TopLevel tclvl infer_mode
                           []    {- No sig vars -}
                           [(fresh_it, res_ty)]
                           lie ;


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -14,6 +14,7 @@ module GHC.Tc.Solver(
        tcCheckGivens,
        tcCheckWanteds,
        tcNormalise,
+       approximateWC,    -- Exported for plugins to use
 
        captureTopConstraints,
 
@@ -48,7 +49,7 @@ import GHC.Tc.Utils.TcType
 import GHC.Core.Predicate
 import GHC.Core.Type
 import GHC.Core.Ppr
-import GHC.Core.TyCon    ( TyConBinder, isTypeFamilyTyCon )
+import GHC.Core.TyCon    ( TyConBinder )
 
 import GHC.Types.Name
 import GHC.Types.Id
@@ -58,9 +59,11 @@ import GHC.Types.Var.Set
 import GHC.Types.Basic
 import GHC.Types.Error
 
-import GHC.Utils.Misc
+import GHC.Driver.DynFlags( DynFlags, xopt )
+import GHC.Driver.Flags( WarningFlag(..) )
 import GHC.Utils.Panic
 import GHC.Utils.Outputable
+import GHC.Utils.Misc( filterOut )
 
 import GHC.Data.Bag
 
@@ -882,7 +885,8 @@ instance Outputable InferMode where
   ppr EagerDefaulting = text "EagerDefaulting"
   ppr NoRestrictions  = text "NoRestrictions"
 
-simplifyInfer :: TcLevel               -- Used when generating the constraints
+simplifyInfer :: TopLevelFlag
+              -> TcLevel               -- Used when generating the constraints
               -> InferMode
               -> [TcIdSigInst]         -- Any signatures (possibly partial)
               -> [(Name, TcTauType)]   -- Variables to be generalised,
@@ -893,7 +897,7 @@ simplifyInfer :: TcLevel               -- Used when generating the constraints
                       TcEvBinds,    -- ... binding these evidence variables
                       Bool)         -- True <=> the residual constraints are insoluble
 
-simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
+simplifyInfer top_lvl rhs_tclvl infer_mode sigs name_taus wanteds
   | isEmptyWC wanteds
    = do { -- When quantifying, we want to preserve any order of variables as they
           -- appear in partial signatures. cf. decideQuantifiedTyVars
@@ -946,9 +950,8 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
        ; wanted_transformed <- TcM.liftZonkM $ TcM.zonkWC wanted_transformed
        ; let definite_error = insolubleWC wanted_transformed
                               -- See Note [Quantification with errors]
-             quant_pred_candidates
-               | definite_error = []
-               | otherwise      = ctsPreds (approximateWC False wanted_transformed)
+             wanted_dq | definite_error = emptyWC
+                       | otherwise      = wanted_transformed
 
        -- Decide what type variables and constraints to quantify
        -- NB: quant_pred_candidates is already fully zonked
@@ -957,9 +960,11 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
        -- NB: bound_theta are fully zonked
        -- rec {..}: see Note [Keeping SkolemInfo inside a SkolemTv]
        --           in GHC.Tc.Utils.TcType
-       ; rec { (qtvs, bound_theta, co_vars) <- decideQuantification skol_info infer_mode rhs_tclvl
-                                                     name_taus partial_sigs
-                                                     quant_pred_candidates
+       ; rec { (qtvs, bound_theta, co_vars) <- decideQuantification
+                                                     top_lvl rhs_tclvl infer_mode
+                                                     skol_info name_taus partial_sigs
+                                                     wanted_dq
+
              ; bound_theta_vars <- mapM TcM.newEvVar bound_theta
 
              ; let full_theta = map idType bound_theta_vars
@@ -975,7 +980,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds
 
          -- All done!
        ; traceTc "} simplifyInfer/produced residual implication for quantification" $
-         vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates
+         vcat [ text "wanted_dq ="      <+> ppr wanted_dq
               , text "psig_theta ="     <+> ppr psig_theta
               , text "bound_theta ="    <+> pprCoreBinders bound_theta_vars
               , text "qtvs ="           <+> ppr qtvs
@@ -1278,20 +1283,21 @@ simplifyInfer.
 -}
 
 decideQuantification
-  :: SkolemInfo
-  -> InferMode
+  :: TopLevelFlag
   -> TcLevel
+  -> InferMode
+  -> SkolemInfo
   -> [(Name, TcTauType)]   -- Variables to be generalised
   -> [TcIdSigInst]         -- Partial type signatures (if any)
-  -> [PredType]            -- Candidate theta; already zonked
+  -> WantedConstraints     -- Candidate theta; already zonked
   -> TcM ( [TcTyVar]       -- Quantify over these (skolems)
          , [PredType]      -- and this context (fully zonked)
          , CoVarSet)
 -- See Note [Deciding quantification]
-decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs candidates
+decideQuantification top_lvl rhs_tclvl infer_mode skol_info name_taus psigs wanted
   = do { -- Step 1: find the mono_tvs
-       ; (candidates, co_vars, mono_tvs0)
-             <- decidePromotedTyVars infer_mode name_taus psigs candidates
+       ; (candidates, co_vars)
+             <- decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
 
        -- Step 2: default any non-mono tyvars, and re-simplify
        -- This step may do some unification, but result candidates is zonked
@@ -1308,11 +1314,11 @@ decideQuantification skol_info infer_mode rhs_tclvl name_taus psigs candidates
           do { candidates <- TcM.zonkTcTypes candidates
              ; psig_theta <- TcM.zonkTcTypes (concatMap sig_inst_theta psigs)
              ; return (candidates, psig_theta) }
-       ; min_theta  <- pickQuantifiablePreds (mkVarSet qtvs) mono_tvs0 candidates
 
        -- Take account of partial type signatures
        -- See Note [Constraints in partial type signatures]
        ; let min_psig_theta = mkMinimalBySCs id psig_theta
+             min_theta      = pickQuantifiablePreds (mkVarSet qtvs) candidates
        ; theta <- if
            | null psigs -> return min_theta                 -- Case (P3)
            | not (all has_extra_constraints_wildcard psigs) -- Case (P2)
@@ -1396,147 +1402,376 @@ Some rationale and observations
     g :: forall b. Show b => F b -> _ -> b
     g x y = let _ = (f y, show x) in x
   But that's a battle for another day.
+
+Note [Generalising top-level bindings]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider
+  class C a b | a -> b where ..
+  f x = ...[W] C Int beta[1]...
+
+When generalising `f`, closeWrtFunDeps will promote beta[1] to beta[0].
+But we do NOT want to make a top level type
+  f :: C Int beta[0] => blah
+The danger is that beta[0] is defaulted to Any, and that then appears
+in a user error message.  Even if the type `blah` mentions beta[0], /and/
+there is a call that fixes beta[0] to (say) Bool, we'll end up with
+[W] C Int Bool, which is insoluble.  Why insoluble? If there was an
+   instance C Int Bool
+then fundeps would have fixed beta:=Bool in the first place.
+
+If the binding of `f` is nested, things are different: we can
+definitely see all the calls.
+
+For nested bindings, I think it just doesn't matter. No one cares what this
+variable ends up being; it seems silly to halt compilation around it. (Like in
+the length [] case.)
 -}
 
-decidePromotedTyVars :: InferMode
-                     -> [(Name,TcType)]
-                     -> [TcIdSigInst]
-                     -> [PredType]
-                     -> TcM ([PredType], CoVarSet, TcTyVarSet)
--- We are about to generalise over type variables at level N
--- Each must be either
---    (P) promoted
---    (D) defaulted
---    (Q) quantified
--- This function finds (P), the type variables that we are going to promote:
---   (a) Mentioned in a constraint we can't generalise (the MR)
---   (b) Mentioned in the kind of a CoVar; we can't quantify over a CoVar,
---       so we must not quantify over a type variable free in its kind
---   (c) Connected by an equality or fundep to
---          * a type variable at level < N, or
---          * A tyvar subject to (a), (b) or (c)
--- Having found all such level-N tyvars that we can't generalise,
--- promote them, to eliminate them from further consideration.
---
--- Also return CoVars that appear free in the final quantified types
---   we can't quantify over these, and we must make sure they are in scope
-decidePromotedTyVars infer_mode name_taus psigs candidates
-  = do { tc_lvl <- TcM.getTcLevel
-       ; (no_quant, maybe_quant) <- pick infer_mode candidates
+decideAndPromoteTyVars :: TopLevelFlag -> TcLevel
+                       -> InferMode
+                       -> [(Name,TcType)]
+                       -> [TcIdSigInst]
+                       -> WantedConstraints
+                       -> TcM ([PredType], CoVarSet)
+-- See Note [decideAndPromoteTyVars]
+decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
+  = do { dflags <- getDynFlags
 
        -- If possible, we quantify over partial-sig qtvs, so they are
        -- not mono. Need to zonk them because they are meta-tyvar TyVarTvs
-       ; (psig_qtvs, psig_theta, taus) <- TcM.liftZonkM $
-          do { psig_qtvs <- zonkTcTyVarsToTcTyVars $ binderVars $
-                            concatMap (map snd . sig_inst_skols) psigs
-             ; psig_theta <- mapM TcM.zonkTcType $
-                             concatMap sig_inst_theta psigs
-             ; taus <- mapM (TcM.zonkTcType . snd) name_taus
-             ; return (psig_qtvs, psig_theta, taus) }
+       ; (psig_qtvs, psig_theta, tau_tys) <- getSeedTys name_taus psigs
 
-       ; let psig_tys = mkTyVarTys psig_qtvs ++ psig_theta
+       ; let is_top_level = isTopLevel top_lvl  -- A syntactically top-level binding
 
-             -- (b) The co_var_tvs are tvs mentioned in the types of covars or
+             -- Step 1 of Note [decideAndPromoteTyVars]
+             -- Get candidate constraints, decide which we can potentially quantify
+             (can_quant_cts, no_quant_cts) = approximateWCX wanted
+             can_quant = ctsPreds can_quant_cts
+             no_quant  = ctsPreds no_quant_cts
+
+             -- Step 2 of Note [decideAndPromoteTyVars]
+             -- Apply the monomorphism restriction
+             (post_mr_quant, mr_no_quant) = applyMR dflags infer_mode can_quant
+
+             -- The co_var_tvs are tvs mentioned in the types of covars or
              -- coercion holes. We can't quantify over these covars, so we
              -- must include the variable in their types in the mono_tvs.
              -- E.g.  If we can't quantify over co :: k~Type, then we can't
              --       quantify over k either!  Hence closeOverKinds
              -- Recall that coVarsOfTypes also returns coercion holes
-             co_vars = coVarsOfTypes (psig_tys ++ taus ++ candidates)
+             co_vars    = coVarsOfTypes (mkTyVarTys psig_qtvs ++ psig_theta
+                                         ++ tau_tys ++ post_mr_quant)
              co_var_tvs = closeOverKinds co_vars
 
-             mono_tvs0 = filterVarSet (not . isQuantifiableTv tc_lvl) $
-                         tyCoVarsOfTypes candidates
-               -- We need to grab all the non-quantifiable tyvars in the
-               -- types so that we can grow this set to find other
-               -- non-quantifiable tyvars. This can happen with something like
-               --    f x y = ...
-               --      where z = x 3
-               -- The body of z tries to unify the type of x (call it alpha[1])
-               -- with (beta[2] -> gamma[2]). This unification fails because
-               -- alpha is untouchable, leaving [W] alpha[1] ~ (beta[2] -> gamma[2]).
-               -- We need to know not to quantify over beta or gamma, because they
-               -- are in the equality constraint with alpha. Actual test case:
-               -- typecheck/should_compile/tc213
-
-             mono_tvs1 = mono_tvs0 `unionVarSet` co_var_tvs
-
-               -- mono_tvs1 is now the set of variables from an outer scope
-               -- (that's mono_tvs0) and the set of covars, closed over kinds.
-               -- Given this set of variables we know we will not quantify,
-               -- we want to find any other variables that are determined by this
-               -- set, by functional dependencies or equalities. We thus use
-               -- closeWrtFunDeps to find all further variables determined by this root
-               -- set. See Note [growThetaTyVars vs closeWrtFunDeps]
-
-             non_ip_candidates = filterOut isIPLikePred candidates
-               -- implicit params don't really determine a type variable
-               -- (that is, we might have IP "c" Bool and IP "c" Int in different
-               -- places within the same program), and
-               -- skipping this causes implicit params to monomorphise too many
-               -- variables; see Note [Inheriting implicit parameters] in GHC.Tc.Solver.
-               -- Skipping causes typecheck/should_compile/tc219 to fail.
-
-             mono_tvs2 = closeWrtFunDeps non_ip_candidates mono_tvs1
-               -- mono_tvs2 now contains any variable determined by the "root
-               -- set" of monomorphic tyvars in mono_tvs1.
-
-             constrained_tvs = filterVarSet (isQuantifiableTv tc_lvl) $
-                               closeWrtFunDeps non_ip_candidates (tyCoVarsOfTypes no_quant)
-                                `minusVarSet` mono_tvs2
-             -- constrained_tvs: the tyvars that we are not going to
-             -- quantify /solely/ because of the monomorphism restriction
-             --
-             -- (`minusVarSet` mono_tvs2): a type variable is only
-             --   "constrained" (so that the MR bites) if it is not
-             --   free in the environment (#13785) or is determined
-             --   by some variable that is free in the env't
-
-             mono_tvs = (mono_tvs2 `unionVarSet` constrained_tvs)
-                        `delVarSetList` psig_qtvs
-             -- (`delVarSetList` psig_qtvs): if the user has explicitly
-             --   asked for quantification, then that request "wins"
-             --   over the MR.
-             --
-             -- What if a psig variable is also free in the environment
-             -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
-             -- in Step 2 of Note [Deciding quantification].
-
-           -- Warn about the monomorphism restriction
-       ; when (case infer_mode of { ApplyMR -> True; _ -> False}) $ do
-           let dia = TcRnMonomorphicBindings (map fst name_taus)
-           diagnosticTc (constrained_tvs `intersectsVarSet` tyCoVarsOfTypes taus) dia
-
-       -- Promote the mono_tvs: see Note [Promote monomorphic tyvars]
-       ; _ <- promoteTyVarSet mono_tvs
-
-       ; traceTc "decidePromotedTyVars" $ vcat
-           [ text "infer_mode =" <+> ppr infer_mode
+             -- outer_tvs are mentioned in `wanted, and belong to some outer level.
+             -- We definitely can't quantify over them
+             outer_tvs = outerLevelTyVars rhs_tclvl $
+                         tyCoVarsOfTypes can_quant `unionVarSet` tyCoVarsOfTypes no_quant
+
+             -- Step 3 of Note [decideAndPromoteTyVars]
+             -- Identify mono_tvs: the type variables that we must not quantify over
+             mono_tvs_without_mr
+               | is_top_level = outer_tvs
+               | otherwise    = outer_tvs                                 -- (a)
+                                `unionVarSet` tyCoVarsOfTypes no_quant    -- (b)
+                                `unionVarSet` co_var_tvs                  -- (c)
+
+             mono_tvs_with_mr
+               = -- Even at top level, we don't quantify over type variables
+                 -- mentioned in constraints that the MR tells us not to quantify
+                 -- See Note [decideAndPromoteTyVars] (DP2)
+                 mono_tvs_without_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
+
+             --------------------------------------------------------------------
+             -- Step 4 of Note [decideAndPromoteTyVars]
+             -- Use closeWrtFunDeps to find any other variables that are determined by mono_tvs
+             add_determined tvs = closeWrtFunDeps post_mr_quant tvs
+                                  `delVarSetList` psig_qtvs
+                 -- Why delVarSetList psig_qtvs?
+                 -- If the user has explicitly asked for quantification, then that
+                 -- request "wins" over the MR.
+                 --
+                 -- What if a psig variable is also free in the environment
+                 -- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
+                 -- in Step 2 of Note [Deciding quantification].
+
+             mono_tvs_with_mr_det    = add_determined mono_tvs_with_mr
+             mono_tvs_without_mr_det = add_determined mono_tvs_without_mr
+
+             --------------------------------------------------------------------
+             -- Step 5 of Note [decideAndPromoteTyVars]
+             -- Do not quantify over any constraint mentioning a "newly-mono" tyvar.
+             newly_mono_tvs = mono_tvs_with_mr_det `minusVarSet` mono_tvs_with_mr
+             final_quant
+               | is_top_level = filterOut (predMentions newly_mono_tvs) post_mr_quant
+               | otherwise    = post_mr_quant
+
+       --------------------------------------------------------------------
+       -- Check if the Monomorphism Restriction has bitten
+       ; warn_mr <- woptM Opt_WarnMonomorphism
+       ; when (warn_mr && case infer_mode of { ApplyMR -> True; _ -> False}) $
+         diagnosticTc (not (mono_tvs_with_mr_det `subVarSet` mono_tvs_without_mr_det)) $
+              TcRnMonomorphicBindings (map fst name_taus)
+             -- If there is a variable in mono_tvs, but not in mono_tvs_wo_mr
+             -- then the MR has "bitten" and reduced polymorphism.
+
+       --------------------------------------------------------------------
+       -- Step 6: Promote the mono_tvs: see Note [Promote monomorphic tyvars]
+       ; _ <- promoteTyVarSet mono_tvs_with_mr_det
+
+       ; traceTc "decideAndPromoteTyVars" $ vcat
+           [ text "rhs_tclvl =" <+> ppr rhs_tclvl
+           , text "top =" <+> ppr is_top_level
+           , text "infer_mode =" <+> ppr infer_mode
            , text "psigs =" <+> ppr psigs
            , text "psig_qtvs =" <+> ppr psig_qtvs
-           , text "mono_tvs0 =" <+> ppr mono_tvs0
+           , text "outer_tvs =" <+> ppr outer_tvs
+           , text "mono_tvs_with_mr =" <+> ppr mono_tvs_with_mr
+           , text "mono_tvs_without_mr =" <+> ppr mono_tvs_without_mr
+           , text "mono_tvs_with_mr_det =" <+> ppr mono_tvs_with_mr_det
+           , text "mono_tvs_without_mr_det =" <+> ppr mono_tvs_without_mr_det
+           , text "newly_mono_tvs =" <+> ppr newly_mono_tvs
+           , text "can_quant =" <+> ppr can_quant
+           , text "post_mr_quant =" <+> ppr post_mr_quant
            , text "no_quant =" <+> ppr no_quant
-           , text "maybe_quant =" <+> ppr maybe_quant
-           , text "mono_tvs =" <+> ppr mono_tvs
+           , text "mr_no_quant =" <+> ppr mr_no_quant
+           , text "final_quant =" <+> ppr final_quant
            , text "co_vars =" <+> ppr co_vars ]
 
-       ; return (maybe_quant, co_vars, mono_tvs0) }
+       ; return (final_quant, co_vars) }
+          -- We return `co_vars` that appear free in the final quantified types
+          -- we can't quantify over these, and we must make sure they are in scope
+
+-------------------
+applyMR :: DynFlags -> InferMode -> [PredType]
+        -> ( [PredType]   -- Quantify over these
+           , [PredType] ) -- But not over these
+-- Split the candidates into ones we definitely
+-- won't quantify, and ones that we might
+applyMR _      NoRestrictions  cand = (cand, [])
+applyMR _      ApplyMR         cand = ([], cand)
+applyMR dflags EagerDefaulting cand = partition not_int_ct cand
   where
-    pick :: InferMode -> [PredType] -> TcM ([PredType], [PredType])
-    -- Split the candidates into ones we definitely
-    -- won't quantify, and ones that we might
-    pick ApplyMR         cand = return (cand, [])
-    pick NoRestrictions  cand = return ([], cand)
-    pick EagerDefaulting cand = do { os <- xoptM LangExt.OverloadedStrings
-                                   ; return (partition (is_int_ct os) cand) }
-
-    -- is_int_ct returns True for a constraint we should /not/ quantify
+    ovl_strings = xopt LangExt.OverloadedStrings dflags
+
+    -- not_int_ct returns True for a constraint we /can/ quantify
     -- For EagerDefaulting, do not quantify over
     -- over any interactive class constraint
-    is_int_ct ovl_strings pred
+    not_int_ct pred
       = case classifyPredType pred of
-           ClassPred cls _ -> isInteractiveClass ovl_strings cls
-           _               -> False
+           ClassPred cls _ -> not (isInteractiveClass ovl_strings cls)
+           _               -> True
+
+-------------------
+outerLevelTyVars :: TcLevel -> TcTyVarSet -> TcTyVarSet
+-- Find just the tyvars that are bound outside rhs_tc_lvl
+outerLevelTyVars rhs_tclvl tvs
+  = filterVarSet is_outer_tv tvs
+  where
+    is_outer_tv tcv
+     | isTcTyVar tcv  -- Might be a CoVar; change this when gather covars separately
+     = rhs_tclvl `strictlyDeeperThan` tcTyVarLevel tcv
+     | otherwise
+     = False
+
+{- Note [decideAndPromoteTyVars]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We are about to generalise a let-binding at "outer level" N, where we have
+typechecked its RHS at "rhs level" N+1.  Each tyvar must be either
+  (P) promoted
+  (D) defaulted
+  (Q) quantified
+The function `decideAndPromoteTyVars` figures out (P), the type variables
+mentioned in constraints should definitely not be quantified, and promotes them
+to the outer level, namely N.
+
+The plan
+
+* Step 1.  Use `approximateWCX` to extract, from the RHS `WantedConstraints`,
+  the PredTypes that we might quantify over; and also those that we can't.
+  Example: suppose the `wanted` is this:
+     (d1:Eq alpha, forall b. (F b ~ a) => (co:t1 ~ t2), (d:Show alpha))
+  Then
+     can_quant = [Eq alpha, Show alpha]
+     no_quant  = (t1 ~ t2)
+  We can't quantify over that (t1~t2) because of the enclosing equality (F b ~ a).
+
+  We also choose never to quantify over some forms of equality constraints.
+  Both this and the "given-equality" thing are described in
+  Note [Quantifying over equality constraints] in GHC.Tc.Types.Constraint.
+
+* Step 2. Further trim can_quant using the Monomorphism Restriction, yielding the
+  further `mr_no_quant` predicates that we won't quantify over; plus `post_mr_quant`,
+  which we can in principle quantify.
+
+* Step 3. Identify the type variables we definitely won't quantify, because they are:
+  a) From an outer level <=N anyway
+  b) Mentioned in a constraint we /can't/ quantify.  See Wrinkle (DP1).
+  c) Mentioned in the kind of a CoVar; we can't quantify over a CoVar,
+     so we must not quantify over a type variable free in its kind
+  d) Mentioned in a constraint that the MR says we should not quantify.
+
+  There is a special case for top-level bindings: see Wrinkle (DP2).
+
+* Step 4.  Close wrt functional dependencies and equalities.Example
+  Example
+           f x y = ...
+              where z = x 3
+  The body of z tries to unify the type of x (call it alpha[1]) with
+  (beta[2] -> gamma[2]). This unification fails because alpha is untouchable, leaving
+       [W] alpha[1] ~ (beta[2] -> gamma[2])
+  We need to know not to quantify over beta or gamma, because they are in the
+  equality constraint with alpha. Actual test case:   typecheck/should_compile/tc213
+
+  Another example. Suppose we have
+      class C a b | a -> b
+  and a constraint ([W] C alpha beta), if we promote alpha we should promote beta.
+
+  See also Note [growThetaTyVars vs closeWrtFunDeps]
+
+* Step 5. Further restrict the quantifiable constraints `post_mr_quant` to ones
+  that do not mention a "newly mono" tyvar. The "newly-mono" tyvars are the ones
+  not free in the envt, nor forced to be promoted by the MR; but are determined
+  (via fundeps) by them. Example:
+           class C a b | a -> b
+           [W] C Int beta[1],  tau = beta[1]->Int
+  We promote beta[1] to beta[0] since it is determined by fundep, but we do not
+  want to generate f :: (C Int beta[0]) => beta[0] -> Int Rather, we generate
+  f :: beta[0] -> Int, but leave [W] C Int beta[0] in the residual constraints,
+  which will probably cause a type error
+
+  See Note [Do not quantify over constraints that determine a variable]
+
+* Step 6: actually promote the type variables we don't want to quantify.
+  We must do this: see Note [Promote monomorphic tyvars].
+
+We also add a warning that signals when the MR "bites".
+
+Wrinkles
+
+(DP1) In step 3, why (b)?  Consider the example given in Step 1.  we can't
+  quantify over the constraint (t1~t2).  But if we quantify over the /tyvars/ in
+  t1 or t2, we may simply make that constraint insoluble (#25266 was an example).
+
+(DP2) In Step 3, for top-level bindings, we do (a,d), but /not/ (b,c). Reason:
+  see Note [The top-level Any principle].  At top level we are very reluctant to
+  promote type variables.  But for bindings affected by the MR we have no choice
+  but to promote.
+
+Note [The top-level Any principle]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Key principle: we never want to show the programmer a type with `Any` in it.
+
+Most /top level/ bindings have a type signature, so none of this arises.  But
+where a top-level binding lacks a signature, we don't want to infer a type like
+    f :: alpha[0] -> Int
+and then subsequently default alpha[0]:=Any.  Exposing `Any` to the user is bad
+bad bad.  Better to report an error, which is what may well happen if we
+quantify over alpha instead.
+
+For /nested/ bindings, a monomorphic type like `f :: alpha[0] -> Int` is fine,
+because we can see all the call sites of `f`, and they will probably fix
+`alpha`.  In contrast, we can't see all of (or perhaps any of) the calls of
+top-level (exported) functions, reducing the worries about "spooky action at a
+distance".
+
+Note [Do not quantify over constraints that determine a variable]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Consider (typecheck/should_compile/tc231), where we're trying to infer
+the type of a top-level declaration. We have
+  class Zork s a b | a -> b
+and the candidate constraint at the end of simplifyInfer is
+  [W] Zork alpha[1] (Z [Char]) beta[1]
+We definitely want to quantify over `alpha` (which is mentioned in the
+tau-type).
+
+But we do *not* want to quantify over `beta`: it is determined by the
+functional dependency on Zork: note that the second argument to Zork
+in the Wanted is a variable-free `Z [Char]`.  Quantifying over it
+would be "Henry Ford polymorphism".  (Presumably we don't have an
+instance in scope that tells us what `beta` actually is.)  Instead
+we promote `beta[1]` to `beta[0]`, in `decidePromotedTyVars`.
+
+The question here: do we want to quantify over the constraint, to
+give the type
+   forall a. Zork a (Z [Char]) beta[0] => blah
+Definitely not: see Note [The top-level Any principle]
+
+What we really want (to catch the Zork example) is this:
+
+   Quantify over the constraint only if all its free variables are
+   (a) quantified, or
+   (b) appears in the type of something in the environment (mono_tvs0).
+
+To understand (b) consider
+
+  class C a b where { op :: a -> b -> () }
+
+  mr = 3                      -- mr :: alpha
+  f1 x = op x mr              -- f1 :: forall b. b -> (), plus [W] C b alpha
+  intify = mr + (4 :: Int)
+
+In `f1` should we quantify over that `(C b alpha)`?  Answer: since `alpha` is
+free in the type envt, yes we should.  After all, if we'd typechecked `intify`
+first, we'd have set `alpha := Int`, and /then/ we'd certainly quantify.  The
+delicate Zork situation applies when beta is completely unconstrained (not free
+in the environment) -- except by the fundep.  Hence `newly_mono`.
+
+Another way to put it: let's say `alpha` is in `outer_tvs`. It must be that
+some variable `x` has `alpha` free in its type. If we are at top-level (and we
+are, because nested decls don't go through this path all), then `x` must also
+be at top-level. And, by induction, `x` will not have Any in its type when all
+is said and done. The induction is well-founded because, if `x` is mutually
+recursive with the definition at hand, then their constraints get processed
+together (or `x` has a type signature, in which case the type doesn't have
+`Any`). So the key thing is that we must not introduce a new top-level
+unconstrained variable here.
+
+However this regrettably-subtle reasoning is needed only for /top-level/
+declarations.  For /nested/ decls we can see all the calls, so we'll instantiate
+that quantifed `Zork a (Z [Char]) beta` constraint at call sites, and either
+solve it or not (probably not).  We won't be left with a still-callable function
+with Any in its type.  So for nested definitions we don't make this tricky test.
+
+Historical note: we had a different, and more complicated test before, but it
+was utterly wrong: #23199.
+
+Note [Promote monomorphic tyvars]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Promote any type variables that are free in the environment.  Eg
+   f :: forall qtvs. bound_theta => zonked_tau
+The free vars of f's type become free in the envt, and hence will show
+up whenever 'f' is called.  They may currently at rhs_tclvl, but they
+had better be unifiable at the outer_tclvl!  Example: envt mentions
+alpha[1]
+           tau_ty = beta[2] -> beta[2]
+           constraints = alpha ~ [beta]
+we don't quantify over beta (since it is fixed by envt)
+so we must promote it!  The inferred type is just
+  f :: beta -> beta
+
+NB: promoteTyVarSet ignores coercion variables
+
+Note [Defaulting during simplifyInfer]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+When we are inferring a type, we simplify the constraint, and then use
+approximateWC to produce a list of candidate constraints.  Then we MUST
+
+  a) Promote any meta-tyvars that have been floated out by
+     approximateWC, to restore invariant (WantedInv) described in
+     Note [TcLevel invariants] in GHC.Tc.Utils.TcType.
+
+  b) Default the kind of any meta-tyvars that are not mentioned in
+     in the environment.
+
+To see (b), suppose the constraint is (C ((a :: OpenKind) -> Int)), and we
+have an instance (C ((x:*) -> Int)).  The instance doesn't match -- but it
+should!  If we don't solve the constraint, we'll stupidly quantify over
+(C (a->Int)) and, worse, in doing so skolemiseQuantifiedTyVar will quantify over
+(b:*) instead of (a:OpenKind), which can lead to disaster; see #7332.
+#7641 is a simpler example.
+
+-}
 
 -------------------
 defaultTyVarsAndSimplify :: TcLevel
@@ -1544,6 +1779,7 @@ defaultTyVarsAndSimplify :: TcLevel
                          -> TcM [PredType]      -- Guaranteed zonked
 -- Default any tyvar free in the constraints;
 -- and re-simplify in case the defaulting allows further simplification
+-- See Note [Defaulting during simplifyInfer]
 defaultTyVarsAndSimplify rhs_tclvl candidates
   = do {  -- Default any kind/levity vars
        ; DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs}
@@ -1592,118 +1828,87 @@ decideQuantifiedTyVars skol_info name_taus psigs candidates
   = do {     -- Why psig_tys? We try to quantify over everything free in here
              -- See Note [Quantification and partial signatures]
              --     Wrinkles 2 and 3
-       ; (psig_tv_tys, psig_theta, tau_tys) <- TcM.liftZonkM $
-         do { psig_tv_tys <- mapM TcM.zonkTcTyVar [ tv | sig <- psigs
-                                                       , (_,Bndr tv _) <- sig_inst_skols sig ]
-            ; psig_theta  <- mapM TcM.zonkTcType [ pred | sig <- psigs
-                                                        , pred <- sig_inst_theta sig ]
-            ; tau_tys     <- mapM (TcM.zonkTcType . snd) name_taus
-            ; return (psig_tv_tys, psig_theta, tau_tys) }
-
-       ; let -- Try to quantify over variables free in these types
-             psig_tys = psig_tv_tys ++ psig_theta
-             seed_tys = psig_tys ++ tau_tys
-
-             -- Now "grow" those seeds to find ones reachable via 'candidates'
+         (psig_qtvs, psig_theta, tau_tys) <- getSeedTys name_taus psigs
+
+       ; let psig_tys = mkTyVarTys psig_qtvs ++ psig_theta
+             seed_tvs = tyCoVarsOfTypes (psig_tys ++ tau_tys)
+
+               -- "Grow" those seeds to find ones reachable via 'candidates'
              -- See Note [growThetaTyVars vs closeWrtFunDeps]
-             grown_tcvs = growThetaTyVars candidates (tyCoVarsOfTypes seed_tys)
+             grown_tcvs = growThetaTyVars candidates seed_tvs
 
        -- Now we have to classify them into kind variables and type variables
        -- (sigh) just for the benefit of -XNoPolyKinds; see quantifyTyVars
        --
-       -- Keep the psig_tys first, so that candidateQTyVarsOfTypes produces
-       -- them in that order, so that the final qtvs quantifies in the same
-       -- order as the partial signatures do (#13524)
-       ; dv at DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs} <- candidateQTyVarsOfTypes $
-                                                         psig_tys ++ candidates ++ tau_tys
+       -- The psig_tys are first in seed_tys, then candidates, then tau_tvs.
+       -- This makes candidateQTyVarsOfTypes produces them in that order, so that the
+        -- final qtvs quantifies in the same- order as the partial signatures do (#13524)
+       ; dv at DV {dv_kvs = cand_kvs, dv_tvs = cand_tvs}
+             <- candidateQTyVarsOfTypes $
+                psig_tys ++ candidates ++ tau_tys
        ; let pick     = (`dVarSetIntersectVarSet` grown_tcvs)
              dvs_plus = dv { dv_kvs = pick cand_kvs, dv_tvs = pick cand_tvs }
 
        ; traceTc "decideQuantifiedTyVars" (vcat
-           [ text "tau_tys =" <+> ppr tau_tys
-           , text "candidates =" <+> ppr candidates
+           [ text "candidates =" <+> ppr candidates
            , text "cand_kvs =" <+> ppr cand_kvs
            , text "cand_tvs =" <+> ppr cand_tvs
-           , text "tau_tys =" <+> ppr tau_tys
-           , text "seed_tys =" <+> ppr seed_tys
-           , text "seed_tcvs =" <+> ppr (tyCoVarsOfTypes seed_tys)
+           , text "seed_tys =" <+> ppr seed_tvs
            , text "grown_tcvs =" <+> ppr grown_tcvs
            , text "dvs =" <+> ppr dvs_plus])
 
        ; quantifyTyVars skol_info DefaultNonStandardTyVars dvs_plus }
 
 ------------------
+getSeedTys :: [(Name,TcType)]    -- The type of each RHS in the group
+           -> [TcIdSigInst]      -- Any partial type signatures
+           -> TcM ( [TcTyVar]    -- Zonked partial-sig quantified tyvars
+                  , ThetaType    -- Zonked partial signature thetas
+                  , [TcType] )   -- Zonked tau-tys from the bindings
+getSeedTys name_taus psigs
+  = TcM.liftZonkM $
+    do { psig_tv_tys <- mapM TcM.zonkTcTyVar [ tv | TISI{ sig_inst_skols = skols } <- psigs
+                                                  , (_, Bndr tv _) <- skols ]
+       ; psig_theta  <- mapM TcM.zonkTcType [ pred | TISI{ sig_inst_theta = theta } <- psigs
+                                                   , pred <- theta ]
+       ; tau_tys     <- mapM (TcM.zonkTcType . snd) name_taus
+       ; return ( map getTyVar psig_tv_tys
+                , psig_theta
+                , tau_tys ) }
+
+------------------
+predMentions :: TcTyVarSet -> TcPredType -> Bool
+predMentions qtvs pred = tyCoVarsOfType pred `intersectsVarSet` qtvs
+
 -- | When inferring types, should we quantify over a given predicate?
 -- See Note [pickQuantifiablePreds]
 pickQuantifiablePreds
   :: TyVarSet           -- Quantifying over these
-  -> TcTyVarSet         -- mono_tvs0: variables mentioned a candidate
-                        --   constraint that come from some outer level
   -> TcThetaType        -- Proposed constraints to quantify
-  -> TcM TcThetaType    -- A subset that we can actually quantify
+  -> TcThetaType        -- A subset that we can actually quantify
 -- This function decides whether a particular constraint should be
 -- quantified over, given the type variables that are being quantified
-pickQuantifiablePreds qtvs mono_tvs0 theta
-  = do { tc_lvl <- TcM.getTcLevel
-       ; let is_nested = not (isTopTcLevel tc_lvl)
-       ; return (mkMinimalBySCs id $  -- See Note [Minimize by Superclasses]
-                 mapMaybe (pick_me is_nested) theta) }
+pickQuantifiablePreds qtvs theta
+  = mkMinimalBySCs id $  -- See Note [Minimize by Superclasses]
+    mapMaybe pick_me theta
   where
-    pick_me is_nested pred
-      = let pred_tvs = tyCoVarsOfType pred
-            mentions_qtvs = pred_tvs `intersectsVarSet` qtvs
-        in case classifyPredType pred of
-
-          ClassPred cls tys
-            | Just {} <- isCallStackPred cls tys
-              -- NEVER infer a CallStack constraint.  Otherwise we let
-              -- the constraints bubble up to be solved from the outer
-              -- context, or be defaulted when we reach the top-level.
-              -- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
-            -> Nothing
-
+    pick_me pred
+      = case classifyPredType pred of
+          ClassPred cls _
             | isIPClass cls
-            -> Just pred -- See Note [Inheriting implicit parameters]
-
-            | not mentions_qtvs
-            -> Nothing   -- Don't quantify over predicates that don't
-                         -- mention any of the quantified type variables
-
-            | is_nested
-            -> Just pred
-
-            -- From here on, we are thinking about top-level defns only
-
-            | pred_tvs `subVarSet` (qtvs `unionVarSet` mono_tvs0)
-              -- See Note [Do not quantify over constraints that determine a variable]
-            -> Just pred
-
-            | otherwise
-            -> Nothing
+            -> Just pred -- Pick, say, (?x::Int) whether or not it mentions qtvs
+                         -- See Note [Inheriting implicit parameters]
 
           EqPred eq_rel ty1 ty2
-            | mentions_qtvs
-            , quantify_equality eq_rel ty1 ty2
+            | predMentions qtvs pred
             , Just (cls, tys) <- boxEqPred eq_rel ty1 ty2
               -- boxEqPred: See Note [Lift equality constraints when quantifying]
             -> Just (mkClassPred cls tys)
             | otherwise
             -> Nothing
 
-          IrredPred {} | mentions_qtvs -> Just pred
-                       | otherwise     -> Nothing
-
-          ForAllPred {} -> Nothing
-
-    -- See Note [Quantifying over equality constraints]
-    quantify_equality NomEq  ty1 ty2 = quant_fun ty1 || quant_fun ty2
-    quantify_equality ReprEq _   _   = True
-
-    quant_fun ty
-      = case tcSplitTyConApp_maybe ty of
-          Just (tc, tys) | isTypeFamilyTyCon tc
-                         -> tyCoVarsOfTypes tys `intersectsVarSet` qtvs
-          _ -> False
+          _ | predMentions qtvs pred -> Just pred
+            | otherwise              -> Nothing
 
 ------------------
 growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet
@@ -1725,24 +1930,8 @@ growThetaTyVars theta tcvs
          pred_tcvs = tyCoVarsOfType pred
 
 
-{- Note [Promote monomorphic tyvars]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Promote any type variables that are free in the environment.  Eg
-   f :: forall qtvs. bound_theta => zonked_tau
-The free vars of f's type become free in the envt, and hence will show
-up whenever 'f' is called.  They may currently at rhs_tclvl, but they
-had better be unifiable at the outer_tclvl!  Example: envt mentions
-alpha[1]
-           tau_ty = beta[2] -> beta[2]
-           constraints = alpha ~ [beta]
-we don't quantify over beta (since it is fixed by envt)
-so we must promote it!  The inferred type is just
-  f :: beta -> beta
-
-NB: promoteTyVarSet ignores coercion variables
-
-Note [pickQuantifiablePreds]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [pickQuantifiablePreds]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 When pickQuantifiablePreds is called we have decided what type
 variables to quantify over, `qtvs`. The only quesion is: which of the
 unsolved candidate predicates should we quantify over?  Call them
@@ -1754,58 +1943,37 @@ For the members of unsolved_constraints that we select for picked_theta
 it is easy to solve, by identity.  For the others we just hope that
 we can solve them.
 
-So which of the candidates should we pick to quantify over?  In some
-situations we distinguish top-level from nested bindings.  The point
-about nested binding is that
- (a) the types may mention type variables free in the environment
- (b) all of the call sites are statically visible, reducing the
-     worries about "spooky action at a distance".
-
-First, never pick a constraint that doesn't mention any of the quantified
-variables `qtvs`.  Picking such a constraint essentially moves the solving of
-the constraint from this function definition to call sites.  But because the
-constraint mentions no quantified variables, call sites have no advantage
-over the definition site. Well, not quite: there could be new constraints
-brought into scope by a pattern-match against a constrained (e.g. GADT)
-constructor.  Example
-
-      data T a where { T1 :: T1 Bool; ... }
-
-      f :: forall a. a -> T a -> blah
-      f x t = let g y = x&&y    -- This needs a~Bool
-            in case t of
-                  T1 -> g True
-                  ....
-
-At g's call site we have `a~Bool`, so we /could/ infer
-     g :: forall . (a~Bool) => Bool -> Bool  -- qtvs = {}
-
-This is all very contrived, and probably just postponse type errors to
-the call site.  If that's what you want, write a type signature.
-
-Actually, implicit parameters is an exception to the "no quantified vars"
-rule (see Note [Inheriting implicit parameters]) so we can't actually
-simply test this case first.
-
-Now we consider the different sorts of constraints:
+So which of the candidates should we pick to quantify over?  It's pretty easy:
 
-* For ClassPred constraints:
+* Never pick a constraint that doesn't mention any of the quantified
+  variables `qtvs`.  Picking such a constraint essentially moves the solving of
+  the constraint from this function definition to call sites.  But because the
+  constraint mentions no quantified variables, call sites have no advantage
+  over the definition site. Well, not quite: there could be new constraints
+  brought into scope by a pattern-match against a constrained (e.g. GADT)
+  constructor.  Example
 
-  * Never pick a CallStack constraint.
-    See Note [Overview of implicit CallStacks]
+        data T a where { T1 :: T1 Bool; ... }
 
-  * Always pick an implicit-parameter constraint.
-    Note [Inheriting implicit parameters]
+        f :: forall a. a -> T a -> blah
+        f x t = let g y = x&&y    -- This needs a~Bool
+              in case t of
+                    T1 -> g True
+                    ....
 
-  * For /top-level/ class constraints see
-    Note [Do not quantify over constraints that determine a variable]
+  At g's call site we have `a~Bool`, so we /could/ infer
+       g :: forall . (a~Bool) => Bool -> Bool  -- qtvs = {}
 
-* For EqPred constraints see Note [Quantifying over equality constraints]
+  This is all very contrived, and probably just postponse type errors to
+  the call site.  If that's what you want, write a type signature.
 
-* For IrredPred constraints, we allow anything that mentions the quantified
-  type variables.
+* Implicit parameters is an exception to the "no quantified vars"
+  rule (see Note [Inheriting implicit parameters]) so we can't actually
+  simply test this case first.
 
-* A ForAllPred should not appear: the candidates come from approximateWC.
+* Finally, we may need to "box" equality predicates: if we want to quantify
+  over `a ~# b`, we actually quantify over the boxed version, `a ~ b`.
+  See Note [Lift equality constraints when quantifying].
 
 Notice that we do /not/ consult -XFlexibleContexts here.  For example,
 we allow `pickQuantifiablePreds` to quantify over a constraint like
@@ -1852,102 +2020,6 @@ parameters, *even if* they don't mention the bound type variables.
 Reason: because implicit parameters, uniquely, have local instance
 declarations. See pickQuantifiablePreds.
 
-Note [Quantifying over equality constraints]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Should we quantify over an equality constraint (s ~ t)
-in pickQuantifiablePreds?
-
-* It is always /sound/ to quantify over a constraint -- those
-  quantified constraints will need to be proved at each call site.
-
-* We definitely don't want to quantify over (Maybe a ~ Bool), to get
-     f :: forall a. (Maybe a ~ Bool) => blah
-  That simply postpones a type error from the function definition site to
-  its call site.  Fortunately we have already filtered out insoluble
-  constraints: see `definite_error` in `simplifyInfer`.
-
-* What about (a ~ T alpha b), where we are about to quantify alpha, `a` and
-  `b` are in-scope skolems, and `T` is a data type.  It's pretty unlikely
-  that this will be soluble at a call site, so we don't quantify over it.
-
-* What about `(F beta ~ Int)` where we are going to quantify `beta`?
-  Should we quantify over the (F beta ~ Int), to get
-     f :: forall b. (F b ~ Int) => blah
-  Aha!  Perhaps yes, because at the call site we will instantiate `b`, and
-  perhaps we have `instance F Bool = Int`. So we *do* quantify over a
-  type-family equality where the arguments mention the quantified variables.
-
-This is all a bit ad-hoc.
-
-Note [Do not quantify over constraints that determine a variable]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider (typecheck/should_compile/tc231), where we're trying to infer
-the type of a top-level declaration. We have
-  class Zork s a b | a -> b
-and the candidate constraint at the end of simplifyInfer is
-  [W] Zork alpha[1] (Z [Char]) beta[1]
-We definitely want to quantify over `alpha` (which is mentioned in the
-tau-type).
-
-But we do *not* want to quantify over `beta`: it is determined by the
-functional dependency on Zork: note that the second argument to Zork
-in the Wanted is a variable-free `Z [Char]`.  Quantifying over it
-would be "Henry Ford polymorphism".  (Presumably we don't have an
-instance in scope that tells us what `beta` actually is.)  Instead
-we promote `beta[1]` to `beta[0]`, in `decidePromotedTyVars`.
-
-The question here: do we want to quantify over the constraint, to
-give the type
-   forall a. Zork a (Z [Char]) beta[0] => blah
-Definitely not.  Since we're not quantifying over beta, it has been
-promoted; and then will be zapped to Any in the final zonk.  So we end
-up with a (perhaps exported) type involving
-  forall a. Zork a (Z [Char]) Any => blah
-No no no:
-
-  Key principle: we never want to show the programmer
-                 a type with `Any` in it.
-
-What we really want (to catch the Zork example) is this:
-
-   Quantify over the constraint only if all its free variables are
-   (a) quantified, or
-   (b) appears in the type of something in the environment (mono_tvs0).
-
-To understand (b) consider
-
-  class C a b where { op :: a -> b -> () }
-
-  mr = 3                      -- mr :: alpha
-  f1 x = op x mr              -- f1 :: forall b. b -> (), plus [W] C b alpha
-  intify = mr + (4 :: Int)
-
-In `f1` should we quantify over that `(C b alpha)`?  Answer: since `alpha`
-is free in the type envt, yes we should.  After all, if we'd typechecked
-`intify` first, we'd have set `alpha := Int`, and /then/ we'd certainly
-quantify.  The delicate Zork situation applies when beta is completely
-unconstrained (not free in the environment) -- except by the fundep.
-
-Another way to put it: let's say `alpha` is in `mono_tvs0`. It must be that
-some variable `x` has `alpha` free in its type. If we are at top-level (and we
-are, because nested decls don't go through this path all), then `x` must also
-be at top-level. And, by induction, `x` will not have Any in its type when all
-is said and done. The induction is well-founded because, if `x` is mutually
-recursive with the definition at hand, then their constraints get processed
-together (or `x` has a type signature, in which case the type doesn't have
-`Any`). So the key thing is that we must not introduce a new top-level
-unconstrained variable here.
-
-However this regrettably-subtle reasoning is needed only for /top-level/
-declarations.  For /nested/ decls we can see all the calls, so we'll
-instantiate that quantifed `Zork a (Z [Char]) beta` constraint at call sites,
-and either solve it or not (probably not).  We won't be left with a
-still-callable function with Any in its type.  So for nested definitions we
-don't make this tricky test.
-
-Historical note: we had a different, and more complicated test
-before, but it was utterly wrong: #23199.
-
 Note [Quantification and partial signatures]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 When choosing type variables to quantify, the basic plan is to
@@ -2177,63 +2249,4 @@ whatever, because the type-class defaulting rules have yet to run.
 
 An alternate implementation would be to emit a Wanted constraint setting
 the RuntimeRep variable to LiftedRep, but this seems unnecessarily indirect.
-
-Note [Promote _and_ default when inferring]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When we are inferring a type, we simplify the constraint, and then use
-approximateWC to produce a list of candidate constraints.  Then we MUST
-
-  a) Promote any meta-tyvars that have been floated out by
-     approximateWC, to restore invariant (WantedInv) described in
-     Note [TcLevel invariants] in GHC.Tc.Utils.TcType.
-
-  b) Default the kind of any meta-tyvars that are not mentioned in
-     in the environment.
-
-To see (b), suppose the constraint is (C ((a :: OpenKind) -> Int)), and we
-have an instance (C ((x:*) -> Int)).  The instance doesn't match -- but it
-should!  If we don't solve the constraint, we'll stupidly quantify over
-(C (a->Int)) and, worse, in doing so skolemiseQuantifiedTyVar will quantify over
-(b:*) instead of (a:OpenKind), which can lead to disaster; see #7332.
-#7641 is a simpler example.
-
-Note [Promoting unification variables]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When we float an equality out of an implication we must "promote" free
-unification variables of the equality, in order to maintain Invariant
-(WantedInv) from Note [TcLevel invariants] in GHC.Tc.Types.TcType.
-
-This is absolutely necessary. Consider the following example. We start
-with two implications and a class with a functional dependency.
-
-    class C x y | x -> y
-    instance C [a] [a]
-
-    (I1)      [untch=beta]forall b. 0 => F Int ~ [beta]
-    (I2)      [untch=beta]forall c. 0 => F Int ~ [[alpha]] /\ C beta [c]
-
-We float (F Int ~ [beta]) out of I1, and we float (F Int ~ [[alpha]]) out of I2.
-They may react to yield that (beta := [alpha]) which can then be pushed inwards
-the leftover of I2 to get (C [alpha] [a]) which, using the FunDep, will mean that
-(alpha := a). In the end we will have the skolem 'b' escaping in the untouchable
-beta! Concrete example is in indexed_types/should_fail/ExtraTcsUntch.hs:
-
-    class C x y | x -> y where
-     op :: x -> y -> ()
-
-    instance C [a] [a]
-
-    type family F a :: *
-
-    h :: F Int -> ()
-    h = undefined
-
-    data TEx where
-      TEx :: a -> TEx
-
-    f (x::beta) =
-        let g1 :: forall b. b -> ()
-            g1 _ = h [x]
-            g2 z = case z of TEx y -> (h [[undefined]], op x [y])
-        in (g1 '3', g2 undefined)
 -}


=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -818,7 +818,11 @@ findDefaultableGroups (default_tys, extended_defaults) wanteds
     , defaultable_tyvar tv
     , defaultable_classes (map (classTyCon . sndOf3) group) ]
   where
-    simples                = approximateWC True wanteds
+    simples  = approximateWC True wanteds
+      -- True: for the purpose of defaulting we don't care
+      --       about shape or enclosing equalities
+      -- See (W3) in Note [ApproximateWC] in GHC.Tc.Types.Constraint
+
     (unaries, non_unaries) = partitionWith find_unary (bagToList simples)
     unary_groups           = equivClasses cmp_tv unaries
 


=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -73,9 +73,6 @@ simplifyWantedsTcM wanted
 
 solveWanteds :: WantedConstraints -> TcS WantedConstraints
 solveWanteds wc@(WC { wc_errors = errs })
-  | isEmptyWC wc  -- Fast path
-  = return wc
-  | otherwise
   = do { cur_lvl <- TcS.getTcLevel
        ; traceTcS "solveWanteds {" $
          vcat [ text "Level =" <+> ppr cur_lvl
@@ -106,6 +103,9 @@ simplify_loop :: Int -> IntWithInf -> Bool
 -- else, so we do them once, at the end in solveWanteds
 simplify_loop n limit definitely_redo_implications
               wc@(WC { wc_simple = simples, wc_impl = implics })
+  | isSolvedWC wc  -- Fast path
+  = return wc
+  | otherwise
   = do { csTraceTcS $
          text "simplify_loop iteration=" <> int n
          <+> (parens $ hsep [ text "definitely_redo =" <+> ppr definitely_redo_implications <> comma
@@ -145,7 +145,7 @@ maybe_simplify_again n limit unif_happened wc@(WC { wc_simple = simples })
   | unif_happened
   = simplify_loop n limit True wc
 
-  | superClassesMightHelp wc
+  | superClassesMightHelp wc    -- Returns False quickly if wc is solved
   = -- We still have unsolved goals, and apparently no way to solve them,
     -- so try expanding superclasses at this level, both Given and Wanted
     do { pending_given <- getPendingGivenScs


=====================================
compiler/GHC/Tc/TyCl/PatSyn.hs
=====================================
@@ -154,7 +154,7 @@ tcInferPatSynDecl (PSB { psb_id = lname@(L _ name), psb_args = details
 
        ; ((univ_tvs, req_dicts, ev_binds, _), residual)
                <- captureConstraints $
-                  simplifyInfer tclvl NoRestrictions [] named_taus wanted
+                  simplifyInfer TopLevel tclvl NoRestrictions [] named_taus wanted
        ; top_ev_binds <- checkNoErrs (simplifyTop residual)
        ; addTopEvBinds top_ev_binds $
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -61,7 +61,7 @@ module GHC.Tc.Types.Constraint (
         tyCoVarsOfWC, tyCoVarsOfWCList,
         insolubleWantedCt, insolubleCt, insolubleIrredCt,
         insolubleImplic, nonDefaultableTyVarsOfWC,
-        approximateWC,
+        approximateWCX, approximateWC,
 
         Implication(..), implicationPrototype, checkTelescopeSkol,
         ImplicStatus(..), isInsolubleStatus, isSolvedStatus,
@@ -1815,60 +1815,121 @@ At the end, we will hopefully have substituted uf1 := F alpha, and we
 will be able to report a more informative error:
     'Can't construct the infinite type beta ~ F alpha beta'
 
+
 ************************************************************************
 *                                                                      *
-            Invariant checking (debug only)
+                     approximateWC
 *                                                                      *
 ************************************************************************
 -}
 
-approximateWC :: Bool   -- See Wrinkle (W3) in Note [ApproximateWC]
-              -> WantedConstraints
-              -> Cts
--- Second return value is the depleted wc
--- Postcondition: Wanted Cts
+type ApproxWC = ( Bag Ct    -- Free quantifiable constraints
+                , Bag Ct )  -- Free non-quantifiable constraints
+                            -- due to shape, or enclosing equality
+
+approximateWC :: Bool -> WantedConstraints -> Bag Ct
+approximateWC include_non_quantifiable cts
+  | include_non_quantifiable = quant `unionBags` no_quant
+  | otherwise                = quant
+  where
+    (quant, no_quant) = approximateWCX cts
+
+approximateWCX :: WantedConstraints -> ApproxWC
+-- The "X" means "extended";
+--    we return both quantifiable and non-quantifiable constraints
 -- See Note [ApproximateWC]
 -- See Note [floatKindEqualities vs approximateWC]
-approximateWC float_past_equalities wc
-  = float_wc False emptyVarSet wc
+approximateWCX wc
+  = float_wc False emptyVarSet wc (emptyBag, emptyBag)
   where
     float_wc :: Bool           -- True <=> there are enclosing equalities
              -> TcTyCoVarSet   -- Enclosing skolem binders
-             -> WantedConstraints -> Cts
-    float_wc encl_eqs trapping_tvs (WC { wc_simple = simples, wc_impl = implics })
-      = filterBag (is_floatable encl_eqs trapping_tvs) simples `unionBags`
-        concatMapBag (float_implic encl_eqs trapping_tvs) implics
-
-    float_implic :: Bool -> TcTyCoVarSet -> Implication -> Cts
+             -> WantedConstraints
+             -> ApproxWC -> ApproxWC
+    float_wc encl_eqs trapping_tvs (WC { wc_simple = simples, wc_impl = implics }) acc
+      = foldBag_flip (float_ct     encl_eqs trapping_tvs) simples $
+        foldBag_flip (float_implic encl_eqs trapping_tvs) implics $
+        acc
+
+    float_implic :: Bool -> TcTyCoVarSet -> Implication
+                 -> ApproxWC -> ApproxWC
     float_implic encl_eqs trapping_tvs imp
       = float_wc new_encl_eqs new_trapping_tvs (ic_wanted imp)
       where
         new_trapping_tvs = trapping_tvs `extendVarSetList` ic_skols imp
         new_encl_eqs = encl_eqs || ic_given_eqs imp == MaybeGivenEqs
 
-    is_floatable encl_eqs skol_tvs ct
-       | isGivenCt ct                                = False
-       | insolubleCt ct                              = False
-       | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = False
+    float_ct :: Bool -> TcTyCoVarSet -> Ct
+             -> ApproxWC -> ApproxWC
+    float_ct encl_eqs skol_tvs ct acc@(quant, no_quant)
+       | isGivenCt ct                                = acc
+           -- There can be (insoluble) Given constraints in wc_simple,
+           -- there so that we get error reports for unreachable code
+           -- See `given_insols` in GHC.Tc.Solver.Solve.solveImplication
+       | insolubleCt ct                              = acc
+       | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
        | otherwise
        = case classifyPredType (ctPred ct) of
-           EqPred {}     -> float_past_equalities || not encl_eqs
-                                  -- See Wrinkle (W1)
-           ClassPred {}  -> True  -- See Wrinkle (W2)
-           IrredPred {}  -> True  -- ..both in Note [ApproximateWC]
-           ForAllPred {} -> False
+           -- See the classification in Note [ApproximateWC]
+           EqPred eq_rel ty1 ty2
+             | not encl_eqs      -- See Wrinkle (W1)
+             , quantify_equality eq_rel ty1 ty2
+             -> add_to_quant
+             | otherwise
+             -> add_to_no_quant
+
+           ClassPred cls tys
+             | Just {} <- isCallStackPred cls tys
+               -- NEVER infer a CallStack constraint.  Otherwise we let
+               -- the constraints bubble up to be solved from the outer
+               -- context, or be defaulted when we reach the top-level.
+               -- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
+             -> add_to_no_quant
+
+             | otherwise
+             -> add_to_quant  -- See Wrinkle (W2)
+
+           IrredPred {}  -> add_to_quant  -- See Wrinkle (W2)
+
+           ForAllPred {} -> add_to_no_quant  -- Never quantify these
+       where
+         add_to_quant    = (ct `consBag` quant, no_quant)
+         add_to_no_quant = (quant, ct `consBag` no_quant)
+
+    -- See Note [Quantifying over equality constraints]
+    quantify_equality NomEq  ty1 ty2 = quant_fun ty1 || quant_fun ty2
+    quantify_equality ReprEq _   _   = True
+
+    quant_fun ty
+      = case tcSplitTyConApp_maybe ty of
+          Just (tc, _) -> isTypeFamilyTyCon tc
+          _              -> False
 
 {- Note [ApproximateWC]
 ~~~~~~~~~~~~~~~~~~~~~~~
 approximateWC takes a constraint, typically arising from the RHS of a
-let-binding whose type we are *inferring*, and extracts from it some
-*simple* constraints that we might plausibly abstract over.  Of course
-the top-level simple constraints are plausible, but we also float constraints
-out from inside, if they are not captured by skolems.
+let-binding whose type we are *inferring*, and extracts from it some *simple*
+constraints that we might plausibly abstract over.  Of course the top-level
+simple constraints are plausible, but we also float constraints out from inside,
+if they are not captured by skolems.
 
 The same function is used when doing type-class defaulting (see the call
 to applyDefaultingRules) to extract constraints that might be defaulted.
 
+We proceed by classifying the constraint:
+  * ClassPred:
+    * Never pick a CallStack constraint.
+      See Note [Overview of implicit CallStacks]
+    * Always pick an implicit-parameter constraint.
+      Note [Inheriting implicit parameters]
+    See wrinkle (W2)
+
+  * EqPred: see Note [Quantifying over equality constraints]
+
+  * IrredPred: we allow anything.
+
+  * ForAllPred: never quantify over these
+
 Wrinkle (W1)
   When inferring most-general types (in simplifyInfer), we
   do *not* float an equality constraint if the implication binds
@@ -1884,22 +1945,19 @@ Wrinkle (W1)
   non-principal types.)
 
 Wrinkle (W2)
-  We do allow /class/ constraints to float, even if
-  the implication binds equalities.  This is a subtle point: see #23224.
-  In principle, a class constraint might ultimately be satisfiable from
-  a constraint bound by an implication (see #19106 for an example of this
-  kind), but it's extremely obscure and I was unable to construct a
-  concrete example.  In any case, in super-subtle cases where this might
-  make a difference, you would be much better advised to simply write a
-  type signature.
-
-  I included IrredPred here too, for good measure.  In general,
-  abstracting over more constraints does no harm.
+  We do allow /class/ constraints to float, even if the implication binds
+  equalities.  This is a subtle point: see #23224.  In principle, a class
+  constraint might ultimately be satisfiable from a constraint bound by an
+  implication (see #19106 for an example of this kind), but it's extremely
+  obscure and I was unable to construct a concrete example.  In any case, in
+  super-subtle cases where this might make a difference, you would be much
+  better advised to simply write a type signature.
 
 Wrinkle (W3)
-  In findDefaultableGroups we are not worried about the
-  most-general type; and we /do/ want to float out of equalities
-  (#12797).  Hence the boolean flag to approximateWC.
+  In findDefaultableGroups we are not worried about the most-general type; and
+  we /do/ want to float out of equalities (#12797).  Hence we just union the two
+  returned lists.
+
 
 ------ Historical note -----------
 There used to be a second caveat, driven by #8155
@@ -1926,6 +1984,33 @@ you want.  So I simply removed the extra code to implement the
 contamination stuff.  There was zero effect on the testsuite (not even #8155).
 ------ End of historical note -----------
 
+Note [Quantifying over equality constraints]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Should we quantify over an equality constraint (s ~ t)
+in pickQuantifiablePreds?
+
+* It is always /sound/ to quantify over a constraint -- those
+  quantified constraints will need to be proved at each call site.
+
+* We definitely don't want to quantify over (Maybe a ~ Bool), to get
+     f :: forall a. (Maybe a ~ Bool) => blah
+  That simply postpones a type error from the function definition site to
+  its call site.  Fortunately we have already filtered out insoluble
+  constraints: see `definite_error` in `simplifyInfer`.
+
+* What about (a ~ T alpha b), where we are about to quantify alpha, `a` and
+  `b` are in-scope skolems, and `T` is a data type.  It's pretty unlikely
+  that this will be soluble at a call site, so we don't quantify over it.
+
+* What about `(F beta ~ Int)` where we are going to quantify `beta`?
+  Should we quantify over the (F beta ~ Int), to get
+     f :: forall b. (F b ~ Int) => blah
+  Aha!  Perhaps yes, because at the call site we will instantiate `b`, and
+  perhaps we have `instance F Bool = Int`. So we *do* quantify over a
+  type-family equality where the arguments mention the quantified variables.
+
+This is all a bit ad-hoc.
+
 
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -78,9 +78,8 @@ module GHC.Tc.Utils.TcMType (
   ---------------------------------
   -- Promotion, defaulting, skolemisation
   defaultTyVar, promoteMetaTyVarTo, promoteTyVarSet,
-  quantifyTyVars, isQuantifiableTv,
+  quantifyTyVars, doNotQuantifyTyVars,
   zonkAndSkolemise, skolemiseQuantifiedTyVar,
-  doNotQuantifyTyVars,
 
   candidateQTyVarsOfType,  candidateQTyVarsOfKind,
   candidateQTyVarsOfTypes, candidateQTyVarsOfKinds,
@@ -1788,15 +1787,6 @@ quantifyTyVars skol_info ns_strat dvs
       | otherwise
       = Just <$> skolemiseQuantifiedTyVar skol_info tkv
 
-isQuantifiableTv :: TcLevel   -- Level of the context, outside the quantification
-                 -> TcTyVar
-                 -> Bool
-isQuantifiableTv outer_tclvl tcv
-  | isTcTyVar tcv  -- Might be a CoVar; change this when gather covars separately
-  = tcTyVarLevel tcv `strictlyDeeperThan` outer_tclvl
-  | otherwise
-  = False
-
 zonkAndSkolemise :: SkolemInfo -> TcTyCoVar -> ZonkM TcTyCoVar
 -- A tyvar binder is never a unification variable (TauTv),
 -- rather it is always a skolem. It *might* be a TyVarTv.
@@ -2414,7 +2404,7 @@ promoteMetaTyVarTo :: HasDebugCallStack => TcLevel -> TcTyVar -> TcM Bool
 -- invariant (WantedInv) in Note [TcLevel invariants] in GHC.Tc.Utils.TcType
 -- Return True <=> we did some promotion
 -- Also returns either the original tyvar (no promotion) or the new one
--- See Note [Promoting unification variables]
+-- See Note [Promote monomorphic tyvars] in GHC.Tc.Solver
 promoteMetaTyVarTo tclvl tv
   | assertPpr (isMetaTyVar tv) (ppr tv) $
     tcTyVarLevel tv `strictlyDeeperThan` tclvl


=====================================
testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.stderr
=====================================
@@ -1,12 +1,12 @@
 ExtraTcsUntch.hs:23:18: error: [GHC-83865]
     • Couldn't match expected type: F Int
-                  with actual type: [[a0]]
+                  with actual type: [p0]
     • In the first argument of ‘h’, namely ‘[x]’
       In the expression: h [x]
       In an equation for ‘g1’: g1 _ = h [x]
     • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
+        x :: p0 (bound at ExtraTcsUntch.hs:21:3)
+        f :: p0 -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 
 ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • Couldn't match expected type: F Int
@@ -14,7 +14,4 @@ ExtraTcsUntch.hs:25:38: error: [GHC-83865]
     • In the first argument of ‘h’, namely ‘[[undefined]]’
       In the expression: h [[undefined]]
       In the expression: (h [[undefined]], op x [y])
-    • Relevant bindings include
-        x :: [a0] (bound at ExtraTcsUntch.hs:21:3)
-        f :: [a0] -> ((), ((), ())) (bound at ExtraTcsUntch.hs:21:1)
 


=====================================
testsuite/tests/partial-sigs/should_fail/T10615.stderr
=====================================
@@ -1,34 +1,39 @@
 
 T10615.hs:5:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w1’
-      Where: ‘w1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f1 :: w -> f
+               at T10615.hs:6:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f1 :: _ -> f
 
 T10615.hs:6:6: error: [GHC-25897]
-    • Couldn't match type ‘f’ with ‘b1 -> w1’
-      Expected: w1 -> f
-        Actual: w1 -> b1 -> w1
+    • Couldn't match type ‘f’ with ‘b1 -> w’
+      Expected: w -> f
+        Actual: w -> b1 -> w
       ‘f’ is a rigid type variable bound by
-        the inferred type of f1 :: w1 -> f
+        the inferred type of f1 :: w -> f
         at T10615.hs:5:1-12
     • In the expression: const
       In an equation for ‘f1’: f1 = const
-    • Relevant bindings include f1 :: w1 -> f (bound at T10615.hs:6:1)
+    • Relevant bindings include f1 :: w -> f (bound at T10615.hs:6:1)
 
 T10615.hs:8:7: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘w0’
-      Where: ‘w0’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘w’
+      Where: ‘w’ is a rigid type variable bound by
+               the inferred type of f2 :: w -> _f
+               at T10615.hs:9:1-10
       To use the inferred type, enable PartialTypeSignatures
     • In the type signature: f2 :: _ -> _f
 
 T10615.hs:9:6: error: [GHC-25897]
-    • Couldn't match type ‘_f’ with ‘b0 -> w0’
-      Expected: w0 -> _f
-        Actual: w0 -> b0 -> w0
+    • Couldn't match type ‘_f’ with ‘b0 -> w’
+      Expected: w -> _f
+        Actual: w -> b0 -> w
       ‘_f’ is a rigid type variable bound by
-        the inferred type of f2 :: w0 -> _f
+        the inferred type of f2 :: w -> _f
         at T10615.hs:8:1-13
     • In the expression: const
       In an equation for ‘f2’: f2 = const
-    • Relevant bindings include f2 :: w0 -> _f (bound at T10615.hs:9:1)
+    • Relevant bindings include f2 :: w -> _f (bound at T10615.hs:9:1)
+


=====================================
testsuite/tests/polykinds/T14172.stderr
=====================================
@@ -1,7 +1,9 @@
 T14172.hs:7:46: error: [GHC-88464]
-    • Found type wildcard ‘_’ standing for ‘a'1 :: k0’
-      Where: ‘k0’ is an ambiguous type variable
-             ‘a'1’ is an ambiguous type variable
+    • Found type wildcard ‘_’ standing for ‘a'’
+      Where: ‘a'’ is a rigid type variable bound by
+               the inferred type of
+                 traverseCompose :: (a -> f b) -> g a -> f (h a')
+               at T14172.hs:8:1-46
       To use the inferred type, enable PartialTypeSignatures
     • In the first argument of ‘h’, namely ‘_’
       In the first argument of ‘f’, namely ‘(h _)’
@@ -10,19 +12,18 @@ T14172.hs:7:46: error: [GHC-88464]
 
 T14172.hs:8:19: error: [GHC-25897]
     • Couldn't match type ‘a’ with ‘g'1 a'0’
-      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a'1)
-        Actual: (Unwrapped (Compose f'0 g'1 a'0)
-                 -> f (Unwrapped (h a'1)))
-                -> Compose f'0 g'1 a'0 -> f (h a'1)
+      Expected: (f'0 a -> f (f'0 b)) -> g a -> f (h a')
+        Actual: (Unwrapped (Compose f'0 g'1 a'0) -> f (Unwrapped (h a')))
+                -> Compose f'0 g'1 a'0 -> f (h a')
       ‘a’ is a rigid type variable bound by
         the inferred type of
-          traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+          traverseCompose :: (a -> f b) -> g a -> f (h a')
         at T14172.hs:7:1-47
     • In the first argument of ‘(.)’, namely ‘_Wrapping Compose’
       In the expression: _Wrapping Compose . traverse
       In an equation for ‘traverseCompose’:
           traverseCompose = _Wrapping Compose . traverse
     • Relevant bindings include
-        traverseCompose :: (a -> f b) -> g a -> f (h a'1)
+        traverseCompose :: (a -> f b) -> g a -> f (h a')
           (bound at T14172.hs:8:1)
 


=====================================
testsuite/tests/typecheck/should_compile/T13785.hs
=====================================
@@ -2,15 +2,20 @@
 {-# OPTIONS_GHC -Wmonomorphism-restriction #-}
 module Bug where
 
-class Monad m => C m where
-  c :: (m Char, m Char)
+class Monad x => C x where
+  c :: (x Char, x Char)
 
 foo :: forall m. C m => m Char
-foo = bar >> baz >> bar2
+foo = bar >> baz >> bar1 >> bar2
   where
     -- Should not get MR warning
     bar, baz :: m Char
     (bar, baz) = c
 
+    -- Should not get MR warning
+    (bar1, baz1) = c :: (m Char, m Char)
+
     -- Should get MR warning
+    -- Natural type for the "whole binding": forall x. C x => (x Char, x Char)
+    -- MR makes it less polymorphic => warning.
     (bar2, baz2) = c


=====================================
testsuite/tests/typecheck/should_compile/T13785.stderr
=====================================
@@ -1,12 +1,13 @@
-
-T13785.hs:16:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
+T13785.hs:21:5: warning: [GHC-55524] [-Wmonomorphism-restriction]
     • The Monomorphism Restriction applies to the bindings
       for ‘bar2’, ‘baz2’
     • In an equation for ‘foo’:
           foo
-            = bar >> baz >> bar2
+            = bar >> baz >> bar1 >> bar2
             where
                 bar, baz :: m Char
                 (bar, baz) = c
+                (bar1, baz1) = c :: (m Char, m Char)
                 (bar2, baz2) = c
     Suggested fix: Consider giving ‘baz2’ and ‘bar2’ a type signature
+


=====================================
testsuite/tests/typecheck/should_compile/T25266.hs
=====================================
@@ -0,0 +1,127 @@
+{-# OPTIONS_GHC -Wno-missing-methods #-}
+{-# LANGUAGE GHC2021 #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE ImplicitPrelude #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module GHC25266 where
+
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Class (MonadTrans (lift))
+import Control.Monad.Trans.Reader (ReaderT, mapReaderT, runReaderT)
+import Data.Kind (Type)
+import Data.Void (Void)
+import GHC.Stack (HasCallStack, withFrozenCallStack)
+
+class MonadIO m => CanRunDB m where
+  unsafeUnlabelledRunDB :: HasCallStack => SqlPersistT m a -> m a
+
+type DBImpl backend env = ReaderT env (ReaderT backend IO)
+
+newtype DBWith backend env a = DB (DBImpl backend env a)
+  deriving newtype (Functor, Applicative, Monad)
+
+type DBEnv = ()
+
+type DB = DBWith SqlBackend DBEnv
+
+class Monad m => PersistentOperation m where
+  type PersistentBackend m
+  unsafeLiftPersistentOperation :: HasCallStack => ReaderT (PersistentBackend m) IO a -> m a
+
+instance PersistentOperation (DBWith backend env) where
+  type PersistentBackend (DBWith backend env) = backend
+  unsafeLiftPersistentOperation = DB . lift . checkpointCallStack
+
+toSqlPersistTIO :: env -> DBWith backend env a -> ReaderT backend IO a
+toSqlPersistTIO env (DB act) = runReaderT act env
+
+hoistIO :: MonadIO m => ReaderT backend IO a -> ReaderT backend m a
+hoistIO = mapReaderT liftIO
+
+liftToSqlPersistT :: forall m a backend. (CanRunDB m) => DBWith backend DBEnv a -> ReaderT backend m a
+liftToSqlPersistT action = do
+  let dbEnv = ()
+  hoistIO $ toSqlPersistTIO dbEnv action
+
+runDB :: (HasCallStack, CanRunDB m) => DB a -> m a
+runDB action = withFrozenCallStack unsafeUnlabelledRunDB $ liftToSqlPersistT action
+
+streamRows ::
+  forall m a.
+  (MonadUnliftIO m, CanRunDB m) =>
+  (forall n. (PersistentOperation n, PersistentBackend n ~ SqlBackend) => n [a]) ->
+  ConduitT () [a] m ()
+streamRows runQuery = go (10 :: Integer)
+  where
+    go n
+      | n < 0 = pure ()
+      | otherwise = do
+          rows <- lift . runDB $ runQuery
+          yield rows
+          go (n - 1)
+
+expectedList :: [Int]
+expectedList = [1, 2, 3]
+
+query :: forall n. (PersistentOperation n, PersistentBackend n ~ SqlBackend) => n [Int]
+query = pure expectedList
+
+test_success :: forall m. (MonadUnliftIO m, CanRunDB m) => m [[Int]]
+test_success = do
+  let conduit = streamRows query .| (sinkList @_ @[Int])
+  runConduit conduit
+
+test_fail :: forall m. (MonadUnliftIO m, CanRunDB m) => m [[Int]]
+test_fail = do
+  let conduit = streamRows query .| sinkList
+  runConduit conduit
+
+-----
+-- annotated-exception
+-----
+
+checkpointCallStack
+    -- :: (MonadCatch m, HasCallStack)
+    :: (Monad m, HasCallStack)
+    => m a
+    -> m a
+checkpointCallStack = id
+
+-----
+-- conduit
+-----
+
+data ConduitT i o (m :: Type -> Type) r
+instance Functor (ConduitT i o m)
+instance Applicative (ConduitT i o m)
+instance Monad (ConduitT i o m)
+instance MonadTrans (ConduitT i o)
+
+(.|) :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
+(.|) = undefined
+
+runConduit :: Monad m => ConduitT () Void m r -> m r
+runConduit = undefined
+
+sinkList :: Monad m => ConduitT a o m [a]
+sinkList = undefined
+
+yield :: Monad m => o -> ConduitT i o m ()
+yield = undefined
+
+-----
+-- persistent
+-----
+
+data SqlBackend
+
+type SqlPersistT = ReaderT SqlBackend
+
+-----
+-- unliftio
+-----
+
+class MonadIO m => MonadUnliftIO m where
+  withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b


=====================================
testsuite/tests/typecheck/should_compile/T25266a.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs #-}
+
+module T25266a where
+
+data T a where { T1 :: T Int; T2 :: a -> T a }
+
+-- Rejected, becuase there is no principal type,
+-- and the function is top level
+f x y t = (case t of
+                      T1   -> length [x,y]
+                      T2 _ -> 2)  :: Int
+
+


=====================================
testsuite/tests/typecheck/should_compile/T25266a.stderr
=====================================
@@ -0,0 +1,21 @@
+T25266a.hs:10:41: error: [GHC-25897]
+    • Could not deduce ‘p1 ~ p2’
+      from the context: a ~ Int
+        bound by a pattern with constructor: T1 :: T Int,
+                 in a case alternative
+        at T25266a.hs:10:23-24
+      ‘p1’ is a rigid type variable bound by
+        the inferred type of f :: p1 -> p2 -> T a -> Int
+        at T25266a.hs:(9,1)-(11,40)
+      ‘p2’ is a rigid type variable bound by
+        the inferred type of f :: p1 -> p2 -> T a -> Int
+        at T25266a.hs:(9,1)-(11,40)
+    • In the expression: y
+      In the first argument of ‘length’, namely ‘[x, y]’
+      In the expression: length [x, y]
+    • Relevant bindings include
+        y :: p2 (bound at T25266a.hs:9:5)
+        x :: p1 (bound at T25266a.hs:9:3)
+        f :: p1 -> p2 -> T a -> Int (bound at T25266a.hs:9:1)
+    Suggested fix: Consider giving ‘f’ a type signature
+


=====================================
testsuite/tests/typecheck/should_compile/T25266b.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE GADTs #-}
+
+module T25266b where
+
+data T a where { T1 :: T Int; T2 :: a -> T a }
+
+h :: Int -> (Int,Int)
+-- Binding for `f` is accepted; we do not generalise it
+--     f :: forall a. alpha -> beta -> T a -> Int
+-- We figure out alpha/beta from the call sites
+h p = let f x y t = (case t of
+                      T1   -> length [x,y]
+                      T2 _ -> 2)  :: Int
+      in (f p (4::Int) (T2 'c'), f 4 5 (T2 "oooh"))
+


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -934,4 +934,7 @@ test('T25125', normal, compile, [''])
 test('T24845a', normal, compile, [''])
 test('T23501a', normal, compile, [''])
 test('T23501b', normal, compile, [''])
+test('T25266', normal, compile, [''])
+test('T25266a', normal, compile_fail, [''])
+test('T25266b', normal, compile, [''])
 


=====================================
testsuite/tests/typecheck/should_fail/T18398.stderr
=====================================
@@ -6,7 +6,7 @@ T18398.hs:13:34: error: [GHC-39999]
       In the expression: case x of MkEx _ -> meth x y
 
 T18398.hs:13:70: error: [GHC-39999]
-    • No instance for ‘C Ex t0’ arising from a use of ‘meth’
+    • No instance for ‘C Ex t1’ arising from a use of ‘meth’
     • In the expression: meth x z
       In a case alternative: MkEx _ -> meth x z
       In the expression: case x of MkEx _ -> meth x z



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 08:02:36 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 18 Oct 2024 04:02:36 -0400
Subject: [Git][ghc/ghc][wip/T25266] 52 commits: ghci: mitigate host/target
 word size mismatch in BCOByteArray serialization
Message-ID: <6712161c275e6_222cf8c83e854918@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
5fa6709b by Simon Peyton Jones at 2024-10-18T09:01:57+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
8cf7cb14 by Simon Peyton Jones at 2024-10-18T09:02:24+01:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- + compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2694cb71a1b9e2e193040fd1951f01477bfbc5a...8cf7cb14086b4322c3b4b0511c341e0ab69301b9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c2694cb71a1b9e2e193040fd1951f01477bfbc5a...8cf7cb14086b4322c3b4b0511c341e0ab69301b9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 11:05:06 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Fri, 18 Oct 2024 07:05:06 -0400
Subject: [Git][ghc/ghc][wip/T20749] 30 commits: JS: add basic support for
 POSIX *at functions (#25190)
Message-ID: <671240e24236e_2460fe26ea44427e3@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
27dceb42 by Sylvain Henry at 2024-08-26T11:05:11-04:00
JS: add basic support for POSIX *at functions (#25190)

openat/fstatat/unlinkat/dup are now used in the recent release of the
`directory` and `file-io` packages.

As such, these functions are (indirectly) used in the following tests
one we'll bump the `directory` submodule (see !13122):
- openFile008
- jsOptimizer
- T20509
- bkpcabal02
- bkpcabal03
- bkpcabal04

- - - - -
c68be356 by Matthew Pickering at 2024-08-26T11:05:11-04:00
Update directory submodule to latest master

The primary reason for this bump is to fix the warning from `ghc-pkg
check`:

```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```

This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)

Fixes #23594 #25145

- - - - -
4ee094d4 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Fix aarch64-alpine target platform description

We are producing bindists where the target triple is

aarch64-alpine-linux

when it should be

aarch64-unknown-linux

This is because the bootstrapped compiler originally set the target
triple to `aarch64-alpine-linux` which is when propagated forwards by
setting `bootstrap_target` from the bootstrap compiler target.

In order to break this chain we explicitly specify build/host/target for
aarch64-alpine.

This requires a new configure flag `--enable-ignore-` which just
switches off a validation check that the target platform of the
bootstrap compiler is the same as the build platform. It is the same,
but the name is just wrong.

These commits can be removed when the bootstrap compiler has the correct
target triple (I looked into patching this on ci-images, but it looked
hard to do correctly as the build/host platform is not in the settings
file).

Fixes #25200

- - - - -
e0e0f2b2 by Matthew Pickering at 2024-08-26T11:05:47-04:00
Bump nixpkgs commit for gen_ci script

- - - - -
63a27091 by doyougnu at 2024-08-26T20:39:30-04:00
rts: win32: emit additional debugging information

-- migration from haskell.nix

- - - - -
aaab3d10 by Vladislav Zavialov at 2024-08-26T20:40:06-04:00
Only export defaults when NamedDefaults are enabled (#25206)

This is a reinterpretation of GHC Proposal #409 that avoids a breaking
change introduced in fa0dbaca6c "Implements the Exportable Named Default proposal"

Consider a module M that has no explicit export list:

	module M where
	default (Rational)

Should it export the default (Rational)?

The proposal says "yes", and there's a test case for that:

	default/DefaultImport04.hs

However, as it turns out, this change in behavior breaks existing
programs, e.g. the colour-2.3.6 package can no longer be compiled,
as reported in #25206.

In this patch, we make implicit exports of defaults conditional on
the NamedDefaults extension. This fix is unintrusive and compliant
with the existing proposal text (i.e. it does not require a proposal
amendment). Should the proposal be amended, we can go for a simpler
solution, such as requiring all defaults to be exported explicitly.

Test case: testsuite/tests/default/T25206.hs

- - - - -
3a5bebf8 by Matthew Pickering at 2024-08-28T14:16:42-04:00
simplifier: Fix space leak during demand analysis

The lazy structure (a list) in a strict field in `DmdType` is not fully
forced which leads to a very large thunk build-up.

It seems there is likely still more work to be done here as it seems we
may be trading space usage for work done. For now, this is the right
choice as rather than using all the memory on my computer, compilation
just takes a little bit longer.

See #25196

- - - - -
c2525e9e by Ryan Scott at 2024-08-28T14:17:17-04:00
Add missing parenthesizeHsType in cvtp's InvisP case

We need to ensure that when we convert an `InvisP` (invisible type pattern) to
a `Pat`, we parenthesize it (at precedence `appPrec`) so that patterns such as
`@(a :: k)` will parse correctly when roundtripped back through the parser.

Fixes #25209.

- - - - -
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.

- - - - -
768fe644 by Andreas Klebinger at 2024-09-03T13:15:20-04:00
Add functions to check for weakly pinned arrays.

This commit adds `isByteArrayWeaklyPinned#` and `isMutableByteArrayWeaklyPinned#` primops.
These check if a bytearray is *weakly* pinned. Which means it can still be explicitly moved
by the user via compaction but won't be moved by the RTS.

This moves us one more stop closer to nailing down #22255.

- - - - -
b16605e7 by Arsen Arsenović at 2024-09-03T13:16:05-04:00
ghc-toolchain: Don't leave stranded a.outs when testing for -g0

This happened because, when ghc-toolchain tests for -g0, it does so by
compiling an empty program.  This compilation creates an a.out.

Since we create a temporary directory, lets place the test program
compilation in it also, so that it gets cleaned up.

Fixes: 25b0b40467d0a12601497117c0ad14e1fcab0b74
Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/25203

- - - - -
83e70b14 by Torsten Schmits at 2024-09-03T13:16:41-04:00
Build foreign objects for TH with interpreter's way when loading from iface

Fixes #25211

When linking bytecode for TH from interface core bindings with
`-fprefer-byte-code`, foreign sources are loaded from the interface as
well and compiled to object code in an ad-hoc manner.

The results are then loaded by the interpreter, whose way may differ
from the current build's target way.

This patch ensures that foreign objects are compiled with the
interpreter's way.

- - - - -
0d3bc2fa by Cheng Shao at 2024-09-04T07:20:06-04:00
rts: fix checkClosure error message

This patch fixes an error message in checkClosure() when the closure
has already been evacuated. The previous logic was meant to print the
evacuated closure's type in the error message, but it was completely
wrong, given info was not really an info table, but a tagged pointer
that points to the closure's new address.

- - - - -
fb0a4e5c by Sven Tennie at 2024-09-04T07:20:43-04:00
MO_AcquireFence: Less restrictive barrier

GCC and CLang translate the built-in `atomic_thread_fence(memory_order_acquire)`
to `dmb ishld`, which is a bit less restrictive than `dmb ish` (which
also implies stores.)

- - - - -
a45f1488 by Fendor at 2024-09-04T20:22:00-04:00
testsuite: Add support to capture performance metrics via 'perf'

Performance metrics collected via 'perf' can be more accurate for
run-time performance than GHC's rts, due to the usage of hardware
counters.

We allow performance tests to also record PMU events according to 'perf
list'.

- - - - -
ce61fca5 by Fendor at 2024-09-04T20:22:00-04:00
gitlab-ci: Add nightly job for running the testsuite with perf profiling support

- - - - -
6dfb9471 by Fendor at 2024-09-04T20:22:00-04:00
Enable perf profiling for compiler performance tests

- - - - -
da306610 by sheaf at 2024-09-04T20:22:41-04:00
RecordCon lookup: don't allow a TyCon

This commit adds extra logic when looking up a record constructor.
If GHC.Rename.Env.lookupOccRnConstr returns a TyCon (as it may, due to
the logic explained in Note [Pattern to type (P2T) conversion]),
we emit an error saying that the data constructor is not in scope.

This avoids the compiler falling over shortly thereafter, in the call to
'lookupConstructorInfo' inside 'GHC.Rename.Env.lookupRecFieldOcc',
because the record constructor would not have been a ConLike.

Fixes #25056

- - - - -
9c354beb by Matthew Pickering at 2024-09-04T20:23:16-04:00
Use deterministic names for temporary files

When there are multiple threads they can race to create a temporary
file, in some situations the thread will create ghc_1.c and in some it
will create ghc_2.c. This filename ends up in the debug info for object
files after compiling a C file, therefore contributes to object
nondeterminism.

In order to fix this we store a prefix in `TmpFs` which serves to
namespace temporary files. The prefix is populated from the counter in
TmpFs when the TmpFs is forked. Therefore the TmpFs must be forked
outside the thread which consumes it, in a deterministic order, so each
thread always receives a TmpFs with the same prefix.

This assumes that after the initial TmpFs is created, all other TmpFs
are created from forking the original TmpFs. Which should have been try
anyway as otherwise there would be file collisions and non-determinism.

Fixes #25224

- - - - -
59906975 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
Silence x-partial in Haddock.Backends.Xhtml

This is an unfortunate consequence of two mechanisms:
  * GHC provides (possibly-empty) lists of names
  * The functions that retrieve those names are not equipped to do error
    reporting, and thus accept these lists at face value. They will have
    to be attached an effect for error reporting in a later refactoring

- - - - -
8afbab62 by Hécate Kleidukos at 2024-09-05T10:57:15-04:00
hadrian: Support loading haddock in ghci

There is one tricky aspect with wired-in packages where the boot package
is built with `-this-unit-id ghc` but the dependency is reported as
`-package-id ghc-9.6...`. This has never been fixed in GHC as the
situation of loading wired-in packages into the multi-repl seems like
quite a niche feature that is always just easier to workaround.

- - - - -
6cac9eb8 by Matthew Pickering at 2024-09-05T10:57:15-04:00
hadrian/multi: Load all targets when ./hadrian/ghci-multi is called

This seems to make a bit more sense than just loading `ghc` component
(and dependencies).

- - - - -
7d84df86 by Matthew Pickering at 2024-09-05T10:57:51-04:00
ci: Beef up determinism interface test

There have recently been some determinism issues with the simplifier and
documentation. We enable more things to test in the ABI test to check
that we produce interface files deterministically.

- - - - -
5456e02e by Sylvain Henry at 2024-09-06T11:57:01+02:00
Transform some StgRhsClosure into StgRhsCon after unarisation (#25166)

Before unarisation we may have code like:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      \u []
          case (# |_| #) [GHC.Types.(##)] of sat_sAw [Occ=Once1] {
          __DEFAULT -> Test.D [GHC.Types.True sat_sAw];
          };

After unarisation we get:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      {} \u [] Test.D [GHC.Types.True 2#];

Notice that it's still an Updatable closure for no reason anymore. This
patch transforms appropriate StgRhsClosures into StgRhsCons after
unarisation, allowing these closures to be statically allocated. Now we
get the expected:

  Test.foo :: Test.D
  [GblId, Unf=OtherCon []] =
      Test.D! [GHC.Types.True 2#];

Fix #25166

To avoid duplicating code, this patch refactors the mk(Top)StgRhs
functions and put them in a GHC.Stg.Make module alongside the new
mk(Top)StgRhsCon_maybe functions.

- - - - -
958b4518 by Hécate Kleidukos at 2024-09-06T16:40:56-04:00
haddock: Add missing requirements.txt for the online manual

- - - - -
573f9833 by Sven Tennie at 2024-09-08T09:58:21+00:00
AArch64: Implement takeRegRegMoveInstr

This has likely been forgotten.

- - - - -
20b0de7d by Hécate Kleidukos at 2024-09-08T14:19:28-04:00
haddock: Configuration fix for ReadTheDocs

- - - - -
87aba1a5 by Sebastian Graf at 2024-09-09T11:19:03+02:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
99924024 by Sebastian Graf at 2024-10-17T17:27:09+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                          Baseline
                      Test    Metric          value      New value Change
--------------------------------------------------------------------------------
  ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
            T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
            T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
            T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
           T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
            T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
            T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
             T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
             T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                 geo. mean                                          -0.7%
                 minimum                                           -33.9%
                 maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors

- - - - -
291a7edf by Sebastian Graf at 2024-10-18T13:04:55+02:00
WIP

- - - - -


30 changed files:

- .gitlab/ci.sh
- .gitlab/generate-ci/flake.lock
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitmodules
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Config/Stg/Pipeline.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/333b1c5338e8d39c2bafd0860b74e9a64723580f...291a7edf66cf331b61339f4019fac1a84fca2d49

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/333b1c5338e8d39c2bafd0860b74e9a64723580f...291a7edf66cf331b61339f4019fac1a84fca2d49
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 11:53:00 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Fri, 18 Oct 2024 07:53:00 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <67124c1c5c3b8_1ebe89ca45471544@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
112fe1c8 by Sebastian Graf at 2024-10-18T13:52:37+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                          Baseline
                      Test    Metric          value      New value Change
--------------------------------------------------------------------------------
  ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
            T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
            T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
            T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
           T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
            T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
            T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
             T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
             T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                 geo. mean                                          -0.7%
                 minimum                                           -33.9%
                 maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/112fe1c8d5a1ee9c905baf197df8c23c3f356ad7

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 12:13:26 2024
From: gitlab at gitlab.haskell.org (jeffrey young (@doyougnu))
Date: Fri, 18 Oct 2024 08:13:26 -0400
Subject: [Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef]
 206 commits: RTS: expose closure_sizeW_ (#25252)
Message-ID: <671250e6a4f0b_1ebe8927c360842e2@gitlab.mail>



jeffrey young pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
5f98e4bd by doyougnu at 2024-10-18T08:12:07-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
9ee0bee9 by doyougnu at 2024-10-18T08:12:15-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -


20 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types/Literals.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/BlockId.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/Dataflow/Graph.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/979407b14e93aa903606d22fc9cd1cddf443bc60...9ee0bee9ac3becdf2f2b27b2786fdfa3ae024d8a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/979407b14e93aa903606d22fc9cd1cddf443bc60...9ee0bee9ac3becdf2f2b27b2786fdfa3ae024d8a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 12:19:12 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Fri, 18 Oct 2024 08:19:12 -0400
Subject: [Git][ghc/ghc][wip/T23490-part2] 59 commits: GHCi: fix improper
 location of ghci_history file
Message-ID: <671252401079a_1ebe8973a34886258@gitlab.mail>



Cheng Shao pushed to branch wip/T23490-part2 at Glasgow Haskell Compiler / GHC


Commits:
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Platform.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42ad05c0ad423eb99fcfdd5269cf2bb3a57a4f4c...b3c00c62d76b873f20ebfbf124853ba2b248a397

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42ad05c0ad423eb99fcfdd5269cf2bb3a57a4f4c...b3c00c62d76b873f20ebfbf124853ba2b248a397
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 12:20:25 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Fri, 18 Oct 2024 08:20:25 -0400
Subject: [Git][ghc/ghc][wip/only_job] 77 commits: testsuite: Normalise
 trailing digits from hole fits output
Message-ID: <67125289abd5e_1ebe89806678910da@gitlab.mail>



Cheng Shao pushed to branch wip/only_job at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
0e1f72e1 by Matthew Pickering at 2024-10-18T12:20:09+00:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cca59600f31f2b3e59bd5f8eeca99901a879d007...0e1f72e1754ab198fa0744772c0ceedbd63cf37a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cca59600f31f2b3e59bd5f8eeca99901a879d007...0e1f72e1754ab198fa0744772c0ceedbd63cf37a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 13:22:38 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Fri, 18 Oct 2024 09:22:38 -0400
Subject: [Git][ghc/ghc][wip/andreask/mkTickUnsafeCoerce] 51 commits: ghci:
 mitigate host/target word size mismatch in BCOByteArray serialization
Message-ID: <6712611ec28_dbd7d316f3c907cb@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/mkTickUnsafeCoerce at Glasgow Haskell Compiler / GHC


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
9c28ea87 by Andreas Klebinger at 2024-10-18T15:03:11+02:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- + compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Types/Tickish.hs
- compiler/ghc.cabal.in
- ghc/Main.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1328fe354923e2cbf84a5cd34bf1e47215f25141...9c28ea87b6ecaa54d895abd91dabcfaa38d25223

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1328fe354923e2cbf84a5cd34bf1e47215f25141...9c28ea87b6ecaa54d895abd91dabcfaa38d25223
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 13:25:33 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Fri, 18 Oct 2024 09:25:33 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-9.12-wasm-th
Message-ID: <671261cd9a84d_dbd7d42b2c492643@gitlab.mail>



Cheng Shao pushed new branch wip/ghc-9.12-wasm-th at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-9.12-wasm-th
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 15:33:36 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Fri, 18 Oct 2024 11:33:36 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 18 commits: users-guide:
 Document GHCi :where command
Message-ID: <67127fd0995bc_18606e2301f41131@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
da545574 by Apoorv Ingle at 2024-10-17T16:39:10-05:00
Make ApplicativeDo work with HsExpansions
testcase added: T24406
Issues Fixed: #24406, #16135

Code Changes:
- Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc`
- The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide
  if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr`

Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail

- - - - -
ad024a7b by Apoorv Ingle at 2024-10-17T16:39:28-05:00
simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts

- - - - -
b9eaac97 by Simon Peyton Jones at 2024-10-17T16:39:29-05:00
Remove special cases

... to see what breaks

- - - - -
337e488c by Simon Peyton Jones at 2024-10-17T16:39:29-05:00
Don't use a user SrcSpan on a Stmt expansoin

- - - - -
06dec751 by Apoorv Ingle at 2024-10-18T10:32:19-05:00
make caller wrap the pop err ctxt

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb2a76c55fbead298474d442b6578cd2b83de316...06dec75140ca23f0df316c88ec2da93acb76d397

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb2a76c55fbead298474d442b6578cd2b83de316...06dec75140ca23f0df316c88ec2da93acb76d397
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 15:35:48 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Fri, 18 Oct 2024 11:35:48 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] 55 commits: ghci: mitigate
 host/target word size mismatch in BCOByteArray serialization
Message-ID: <67128054d49ca_18606e2155d4115aa@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
1b36ade3 by Apoorv Ingle at 2024-10-18T10:35:34-05:00
Make ApplicativeDo work with HsExpansions
testcase added: T24406
Issues Fixed: #24406, #16135

Code Changes:
- Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc`
- The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide
  if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr`

Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail

- - - - -
ed23ec9c by Apoorv Ingle at 2024-10-18T10:35:35-05:00
simplify data structures. remove doTcApp and applicative stmt fail blocks do not refer stmts

- - - - -
4cabbc7a by Simon Peyton Jones at 2024-10-18T10:35:35-05:00
Remove special cases

... to see what breaks

- - - - -
4f454596 by Simon Peyton Jones at 2024-10-18T10:35:35-05:00
Don't use a user SrcSpan on a Stmt expansoin

- - - - -
5c504100 by Apoorv Ingle at 2024-10-18T10:35:35-05:00
make caller wrap the pop err ctxt

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/GuardedRHSs.hs
- compiler/GHC/HsToCore/ListComp.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06dec75140ca23f0df316c88ec2da93acb76d397...5c50410028b87ec1b7b624003fefac09ee04867f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06dec75140ca23f0df316c88ec2da93acb76d397...5c50410028b87ec1b7b624003fefac09ee04867f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 16:23:56 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Fri, 18 Oct 2024 12:23:56 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/base-9.12-notes
Message-ID: <67128b9c31bf7_18606e55599c19766@gitlab.mail>



Andreas Klebinger pushed new branch wip/andreask/base-9.12-notes at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/base-9.12-notes
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 16:28:33 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 12:28:33 -0400
Subject: [Git][ghc/ghc] Pushed new tag ghc-9.8.3-release
Message-ID: <67128cb120075_18606e64a62c25214@gitlab.mail>



Ben Gamari pushed new tag ghc-9.8.3-release at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/ghc-9.8.3-release
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:12:26 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Fri, 18 Oct 2024 13:12:26 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-4] EPA: Remove [AddEpAnn]
 Commit 4
Message-ID: <671296f9f2fea_18606eb68dd4331be@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-4 at Glasgow Haskell Compiler / GHC


Commits:
d783489b by Alan Zimmerman at 2024-10-18T18:11:33+01:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -


22 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,8 +31,10 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnDataDefn(..),
   AnnClassDecl(..),
   AnnSynDecl(..),
+  AnnFamilyDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -359,7 +361,7 @@ type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
-type instance XDataDecl     GhcPs = [AddEpAnn]
+type instance XDataDecl     GhcPs = NoExtField
 type instance XDataDecl     GhcRn = DataDeclRn
 type instance XDataDecl     GhcTc = DataDeclRn
 
@@ -379,9 +381,27 @@ type instance XClassDecl    GhcTc = NameSet -- FVs
 
 type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 
-type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
+type instance XCTyFamInstDecl (GhcPass _) = (EpToken "type", EpToken "instance")
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnDataDefn
+  = AnnDataDefn {
+      andd_openp    :: [EpToken "("],
+      andd_closep   :: [EpToken ")"],
+      andd_type     :: EpToken "type",
+      andd_newtype  :: EpToken "newtype",
+      andd_data     :: EpToken "data",
+      andd_instance :: EpToken "instance",
+      andd_dcolon   :: TokDcolon,
+      andd_where    :: EpToken "where",
+      andd_openc    :: EpToken "{",
+      andd_closec   :: EpToken "}",
+      andd_equal    :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnDataDefn where
+  noAnn = AnnDataDefn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
 data AnnClassDecl
   = AnnClassDecl {
       acd_class  :: EpToken "class",
@@ -559,7 +579,7 @@ pprTyClDeclFlavour (DataDecl { tcdDataDefn = HsDataDefn { dd_cons = nd } })
 instance OutputableBndrId p => Outputable (FunDep (GhcPass p)) where
   ppr = pprFunDep
 
-type instance XCFunDep    (GhcPass _) = [AddEpAnn]
+type instance XCFunDep    (GhcPass _) = TokRarrow
 type instance XXFunDep    (GhcPass _) = DataConCantHappen
 
 pprFundeps :: OutputableBndrId p => [FunDep (GhcPass p)] -> SDoc
@@ -593,9 +613,27 @@ type instance XCKindSig         (GhcPass _) = NoExtField
 type instance XTyVarSig         (GhcPass _) = NoExtField
 type instance XXFamilyResultSig (GhcPass _) = DataConCantHappen
 
-type instance XCFamilyDecl    (GhcPass _) = [AddEpAnn]
+type instance XCFamilyDecl    (GhcPass _) = AnnFamilyDecl
 type instance XXFamilyDecl    (GhcPass _) = DataConCantHappen
 
+data AnnFamilyDecl
+  = AnnFamilyDecl {
+      afd_openp  :: [EpToken "("],
+      afd_closep :: [EpToken ")"],
+      afd_type   :: EpToken "type",
+      afd_data   :: EpToken "data",
+      afd_family :: EpToken "family",
+      afd_dcolon :: TokDcolon,
+      afd_equal  :: EpToken "=",
+      afd_vbar   :: EpToken "|",
+      afd_where  :: EpToken "where",
+      afd_openc  :: EpToken "{",
+      afd_dotdot :: EpToken "..",
+      afd_closec :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnFamilyDecl where
+  noAnn = AnnFamilyDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 ------------- Functions over FamilyDecls -----------
 
@@ -620,7 +658,7 @@ resultVariableName _                = Nothing
 
 ------------- Pretty printing FamilyDecls -----------
 
-type instance XCInjectivityAnn  (GhcPass _) = [AddEpAnn]
+type instance XCInjectivityAnn  (GhcPass _) = TokRarrow
 type instance XXInjectivityAnn  (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -664,7 +702,7 @@ instance OutputableBndrId p
 *                                                                      *
 ********************************************************************* -}
 
-type instance XCHsDataDefn    (GhcPass _) = NoExtField
+type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
 type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
@@ -854,7 +892,7 @@ ppr_con_names = pprWithCommas (pprPrefixOcc . unLoc)
 ************************************************************************
 -}
 
-type instance XCFamEqn    (GhcPass _) r = [AddEpAnn]
+type instance XCFamEqn    (GhcPass _) r = ([EpToken "("], [EpToken ")"], EpToken "=")
 type instance XXFamEqn    (GhcPass _) r = DataConCantHappen
 
 ----------------- Class instances -------------
@@ -1145,7 +1183,7 @@ mapDerivStrategy f ds = foldDerivStrategy ds (ViaStrategy . f) ds
 ************************************************************************
 -}
 
-type instance XCDefaultDecl    GhcPs = [AddEpAnn]
+type instance XCDefaultDecl    GhcPs = (EpToken "default", EpToken "(", EpToken ")")
 type instance XCDefaultDecl    GhcRn = NoExtField
 type instance XCDefaultDecl    GhcTc = NoExtField
 
@@ -1233,7 +1271,7 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XCRuleDecls    GhcPs = ([AddEpAnn], SourceText)
+type instance XCRuleDecls    GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XCRuleDecls    GhcRn = SourceText
 type instance XCRuleDecls    GhcTc = SourceText
 
@@ -1318,7 +1356,7 @@ pprFullRuleName st (L _ n) = pprWithSourceText st (doubleQuotes $ ftext n)
 ************************************************************************
 -}
 
-type instance XWarnings      GhcPs = ([AddEpAnn], SourceText)
+type instance XWarnings      GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XWarnings      GhcRn = SourceText
 type instance XWarnings      GhcTc = SourceText
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -61,6 +61,8 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `ext1Q` list
               `extQ` list_addEpAnn
               `extQ` list_epaLocation
+              `extQ` list_epTokenOpenP
+              `extQ` list_epTokenCloseP
               `extQ` string `extQ` fastString `extQ` srcSpan `extQ` realSrcSpan
               `extQ` annotationModule
               `extQ` annotationGrhsAnn
@@ -72,9 +74,13 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
+              `extQ` epTokenInstance
+              `extQ` epTokenForall
               `extQ` annParen
               `extQ` annClassDecl
               `extQ` annSynDecl
+              `extQ` annDataDefn
+              `extQ` annFamilyDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -118,6 +124,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                        $ text "blanked:" <+> text "[EpaLocation]"
               NoBlankEpAnnotations -> list ls
 
+            list_epTokenOpenP :: [EpToken "("] -> SDoc
+            list_epTokenOpenP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
+            list_epTokenCloseP :: [EpToken ")"] -> SDoc
+            list_epTokenCloseP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
             list []    = brackets empty
             list [x]   = brackets (showAstData' x)
             list (x1 : x2 : xs) =  (text "[" <> showAstData' x1)
@@ -224,6 +242,26 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                         $$ vcat [showAstData' ops, showAstData' cps,
                                  showAstData' t, showAstData' e]
 
+            annDataDefn :: AnnDataDefn -> SDoc
+            annDataDefn (AnnDataDefn a b c d e f g h i j k) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnDataDefn"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnDataDefn"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k]
+
+            annFamilyDecl :: AnnFamilyDecl -> SDoc
+            annFamilyDecl (AnnFamilyDecl a b c d e f g h i j k l) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnFamilyDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k, showAstData' l]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -253,6 +291,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenCC :: EpToken "}" -> SDoc
             epTokenCC = epToken'
 
+            epTokenInstance :: EpToken "instance" -> SDoc
+            epTokenInstance = epToken'
+
+            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall = epUniToken'
+
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc
             epToken' (EpTok s) = case ba of
              BlankEpAnnotations -> parens
@@ -265,6 +309,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "NoEpTok"
 
+            epUniToken' :: EpUniToken sym1 sym2 -> SDoc
+            epUniToken' (EpUniTok s f) = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "EpUniTok" <+> epaLocation s <+> ppr f
+            epUniToken' NoEpUniTok = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "NoEpUniTok"
+
 
             var  :: Var -> SDoc
             var v      = braces $ text "Var:" <+> ppr v


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.Hs.Type (
         pprHsArrow,
 
         HsType(..), HsCoreTy, LHsType, HsKind, LHsKind,
-        HsForAllTelescope(..), EpAnnForallTy,
+        HsForAllTelescope(..), EpAnnForallVis, EpAnnForallInvis,
         HsTyVarBndr(..), LHsTyVarBndr, AnnTyVarBndr(..),
         HsBndrKind(..),
         HsBndrVar(..),
@@ -163,16 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnnForallTy
+type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnnForallTy
+type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallTy = EpAnn (AddEpAnn, AddEpAnn)
-  -- ^ Location of 'forall' and '->' for HsForAllVis
-  -- Location of 'forall' and '.' for HsForAllInvis
+type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -184,12 +183,12 @@ type instance XHsQTvs GhcTc = HsQTvsRn
 
 type instance XXLHsQTyVars  (GhcPass _) = DataConCantHappen
 
-mkHsForAllVisTele ::EpAnnForallTy ->
+mkHsForAllVisTele ::EpAnnForallVis ->
   [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllVisTele an vis_bndrs =
   HsForAllVis { hsf_xvis = an, hsf_vis_bndrs = vis_bndrs }
 
-mkHsForAllInvisTele :: EpAnnForallTy
+mkHsForAllInvisTele :: EpAnnForallInvis
   -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllInvisTele an invis_bndrs =
   HsForAllInvis { hsf_xinvis = an, hsf_invis_bndrs = invis_bndrs }
@@ -207,7 +206,7 @@ type instance XHsOuterImplicit GhcPs = NoExtField
 type instance XHsOuterImplicit GhcRn = [Name]
 type instance XHsOuterImplicit GhcTc = [TyVar]
 
-type instance XHsOuterExplicit GhcPs _    = EpAnnForallTy
+type instance XHsOuterExplicit GhcPs _    = EpAnnForallInvis
 type instance XHsOuterExplicit GhcRn _    = NoExtField
 type instance XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag]
 
@@ -323,7 +322,7 @@ hsOuterExplicitBndrs (HsOuterImplicit{})                  = []
 mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs
 mkHsOuterImplicit = HsOuterImplicit{hso_ximplicit = noExtField}
 
-mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs]
+mkHsOuterExplicit :: EpAnnForallInvis -> [LHsTyVarBndr flag GhcPs]
                   -> HsOuterTyVarBndrs flag GhcPs
 mkHsOuterExplicit an bndrs = HsOuterExplicit { hso_xexplicit = an
                                              , hso_bndrs     = bndrs }
@@ -333,7 +332,7 @@ mkHsImplicitSigType body =
   HsSig { sig_ext   = noExtField
         , sig_bndrs = mkHsOuterImplicit, sig_body = body }
 
-mkHsExplicitSigType :: EpAnnForallTy
+mkHsExplicitSigType :: EpAnnForallInvis
                     -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs
                     -> HsSigType GhcPs
 mkHsExplicitSigType an bndrs body =


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1275,9 +1275,9 @@ topdecl :: { LHsDecl GhcPs }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
         | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
-        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
-        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getWARNING_PRAGs $1)) (fromOL $2))) }
-        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ([mo $1,mc $3], (getRULES_PRAGs $1)) (reverse $2))) }
+        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
+        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
+        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
         | annotation { $1 }
         | decl_no_th                            { $1 }
 
@@ -1300,7 +1300,7 @@ cl_decl :: { LTyClDecl GhcPs }
 --
 default_decl :: { LDefaultDecl GhcPs }
              : 'default' opt_class '(' comma_types0 ')'
-               {% amsA' (sLL $1 $> (DefaultDecl [mj AnnDefault $1,mop $3,mcp $5] $2 $4)) }
+               {% amsA' (sLL $1 $> (DefaultDecl (epTok $1,epTok $3,epTok $5) $2 $4)) }
 
 
 -- Type declarations (toplevel)
@@ -1322,17 +1322,22 @@ ty_decl :: { LTyClDecl GhcPs }
                           where_type_family
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
+             {% do { let { (tdcolon, tequal) = fst $ unLoc $4 }
+                   ; let { tvbar = fst $ unLoc $5 }
+                   ; let { (twhere, (toc, tdd, tcc)) = fst $ unLoc $6  }
+                   ; mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
                                    (snd $ unLoc $4) (snd $ unLoc $5)
-                           (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)
-                           ++ (fst $ unLoc $5) ++ (fst $ unLoc $6))  }
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar twhere toc tdd tcc) }}
 
           -- ordinary data type or newtype declaration
         | type_data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings
-                {% mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tequal = fst $ unLoc $4 }
+                  ; mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                            Nothing (reverse (snd $ unLoc $4))
                                    (fmap reverse $5)
-                           ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)) }
+                           (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)
+                             }}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
@@ -1340,18 +1345,22 @@ ty_decl :: { LTyClDecl GhcPs }
         | type_data_or_newtype capi_ctype tycl_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tdcolon = fst $ unLoc $4 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $5 }
+                  ; mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                             (snd $ unLoc $4) (snd $ unLoc $5)
                             (fmap reverse $6)
-                            ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)++(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok tdcolon twhere oc cc NoEpTok)}}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
           -- data/newtype family
         | 'data' 'family' type opt_datafam_kind_sig
-                {% mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
                                    (snd $ unLoc $4) Nothing
-                          (mj AnnData $1:mj AnnFamily $2:(fst $ unLoc $4)) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) (epTok $2) tdcolon noAnn noAnn noAnn noAnn noAnn noAnn) }}
 
 -- standalone kind signature
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
@@ -1386,25 +1395,29 @@ inst_decl :: { LInstDecl GhcPs }
            -- type instance declarations
         | 'type' 'instance' ty_fam_inst_eqn
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                        (mj AnnType $1:mj AnnInstance $2:[]) }
+                        (epTok $1) (epTok $2) }
 
           -- data/newtype instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr constrs
                           maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                       Nothing (reverse (snd  $ unLoc $5))
                                               (fmap reverse $6)
-                      ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
           -- GADT instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { dcolon = fst $ unLoc $5 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                  ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
                                    (snd $ unLoc $5) (snd $ unLoc $6)
                                    (fmap reverse $7)
-                     ((fst $ unLoc $1):mj AnnInstance $2
-                       :(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) dcolon twhere oc cc NoEpTok)}}
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
@@ -1439,14 +1452,14 @@ opt_class :: { Maybe (LIdP GhcPs) }
 
 -- Injective type families
 
-opt_injective_info :: { Located ([AddEpAnn], Maybe (LInjectivityAnn GhcPs)) }
-        : {- empty -}               { noLoc ([], Nothing) }
-        | '|' injectivity_cond      { sLL $1 $> ([mj AnnVbar $1]
+opt_injective_info :: { Located (EpToken "|", Maybe (LInjectivityAnn GhcPs)) }
+        : {- empty -}               { noLoc (noAnn, Nothing) }
+        | '|' injectivity_cond      { sLL $1 $> ((epTok $1)
                                                 , Just ($2)) }
 
 injectivity_cond :: { LInjectivityAnn GhcPs }
         : tyvarid '->' inj_varids
-           {% amsA' (sLL $1 $> (InjectivityAnn [mu AnnRarrow $2] $1 (reverse (unLoc $3)))) }
+           {% amsA' (sLL $1 $> (InjectivityAnn (epUniTok $2) $1 (reverse (unLoc $3)))) }
 
 inj_varids :: { Located [LocatedN RdrName] }
         : inj_varids tyvarid  { sLL $1 $> ($2 : unLoc $1) }
@@ -1454,21 +1467,20 @@ inj_varids :: { Located [LocatedN RdrName] }
 
 -- Closed type families
 
-where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
-        : {- empty -}                      { noLoc ([],OpenTypeFamily) }
+where_type_family :: { Located ((EpToken "where", (EpToken "{", EpToken "..", EpToken "}")),FamilyInfo GhcPs) }
+        : {- empty -}                      { noLoc (noAnn,OpenTypeFamily) }
         | 'where' ty_fam_inst_eqn_list
-               { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
+               { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
                     ,ClosedTypeFamily (fmap reverse $ snd $ unLoc $2)) }
 
-ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
-        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
+ty_fam_inst_eqn_list :: { Located ((EpToken "{", EpToken "..", EpToken "}"),Maybe [LTyFamInstEqn GhcPs]) }
+        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ((epTok $1,noAnn, epTok $3)
                                                 ,Just (unLoc $2)) }
         | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
-                                             L loc ([],Just (unLoc $2)) }
-        |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
-                                                 ,mcc $3],Nothing) }
+                                             L loc (noAnn,Just (unLoc $2)) }
+        |     '{' '..' '}'                 { sLL $1 $> ((epTok $1,epTok $2 ,epTok $3),Nothing) }
         | vocurly '..' close               { let (L loc _) = $2 in
-                                             L loc ([mj AnnDotdot $2],Nothing) }
+                                             L loc ((noAnn,epTok $2, noAnn),Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
         : ty_fam_inst_eqns ';' ty_fam_inst_eqn
@@ -1492,9 +1504,9 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
                     ; tvbs <- fromSpecTyVarBndrs $2
                     ; let loc = comb2 $1 $>
                     ; !cs <- getCommentsFor loc
-                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs) $4 $6 [mj AnnEqual $5] }}
+                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs) $4 $6 (epTok $5) }}
         | type '=' ktype
-              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (mj AnnEqual $2:[]) }
+              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (epTok $2) }
               -- Note the use of type for the head; this allows
               -- infix type constructors and type patterns
 
@@ -1510,40 +1522,42 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
 at_decl_cls :: { LHsDecl GhcPs }
         :  -- data family declarations, with optional 'family' keyword
           'data' opt_family type opt_datafam_kind_sig
-                {% liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
                                                   (snd $ unLoc $4) Nothing
-                        (mj AnnData $1:$2++(fst $ unLoc $4))) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) $2 tdcolon noAnn noAnn noAnn noAnn noAnn noAnn)) }}
 
            -- type family declarations, with optional 'family' keyword
            -- (can't use opt_instance because you get shift/reduce errors
         | 'type' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $3 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $2 $3) OpenTypeFamily NotTopLevel $2
                                    (fst . snd $ unLoc $3)
                                    (snd . snd $ unLoc $3)
-                         (mj AnnType $1:(fst $ unLoc $3)) )}
+                         (AnnFamilyDecl [] [] (epTok $1) noAnn noAnn tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
         | 'type' 'family' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $4 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $3 $4) OpenTypeFamily NotTopLevel $3
                                    (fst . snd $ unLoc $4)
                                    (snd . snd $ unLoc $4)
-                         (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)))}
-
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
            -- default type instances, with optional 'instance' keyword
         | 'type' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $2) (unLoc $2)
-                          [mj AnnType $1]) }
+                          (epTok $1) NoEpTok) }
         | 'type' 'instance' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                              (mj AnnType $1:mj AnnInstance $2:[]) )}
+                              (epTok $1) (epTok $2) )}
 
-opt_family   :: { [AddEpAnn] }
-              : {- empty -}   { [] }
-              | 'family'      { [mj AnnFamily $1] }
+opt_family   :: { EpToken "family" }
+              : {- empty -}   { noAnn }
+              | 'family'      { (epTok $1) }
 
-opt_instance :: { [AddEpAnn] }
-              : {- empty -} { [] }
-              | 'instance'  { [mj AnnInstance $1] }
+opt_instance :: { EpToken "instance" }
+              : {- empty -} { NoEpTok }
+              | 'instance'  { epTok $1 }
 
 -- Associated type instances
 --
@@ -1553,57 +1567,63 @@ at_decl_inst :: { LInstDecl GhcPs }
                 -- Note the use of type for the head; this allows
                 -- infix type constructors and type patterns
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                          (mj AnnType $1:$2) }
+                          (epTok $1) $2 }
 
         -- data/newtype instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr constrs maybe_derivings
-               {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                     Nothing (reverse (snd $ unLoc $5))
-                                            (fmap reverse $6)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)) }
+                                             (fmap reverse $6)
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
         -- GADT instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-                {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
+             {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                   ; let { dcolon = fst $ unLoc $5 }
+                   ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                   ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
                                 (unLoc $4) (snd $ unLoc $5) (snd $ unLoc $6)
                                 (fmap reverse $7)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 dcolon twhere oc cc NoEpTok)}}
 
-type_data_or_newtype :: { Located ([AddEpAnn], Bool, NewOrData) }
-        : 'data'        { sL1 $1 ([mj AnnData    $1],            False,DataType) }
-        | 'newtype'     { sL1 $1 ([mj AnnNewtype $1],            False,NewType) }
-        | 'type' 'data' { sL1 $1 ([mj AnnType $1, mj AnnData $2],True ,DataType) }
+type_data_or_newtype :: { Located ((EpToken "data", EpToken "newtype", EpToken "type")
+                                   , Bool, NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok,  NoEpTok),  False,DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1, NoEpTok),  False,NewType) }
+        | 'type' 'data' { sL1 $1 ((epTok $2, NoEpTok,  epTok $1), True ,DataType) }
 
-data_or_newtype :: { Located (AddEpAnn, NewOrData) }
-        : 'data'        { sL1 $1 (mj AnnData    $1,DataType) }
-        | 'newtype'     { sL1 $1 (mj AnnNewtype $1,NewType) }
+data_or_newtype :: { Located ((EpToken "data", EpToken "newtype"), NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok), DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1),NewType) }
 
 -- Family result/return kind signatures
 
-opt_kind_sig :: { Located ([AddEpAnn], Maybe (LHsKind GhcPs)) }
-        :               { noLoc     ([]               , Nothing) }
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], Just $2) }
+opt_kind_sig :: { Located (TokDcolon, Maybe (LHsKind GhcPs)) }
+        :               { noLoc     (NoEpUniTok , Nothing) }
+        | '::' kind     { sLL $1 $> (epUniTok $1, Just $2) }
 
-opt_datafam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :               { noLoc     ([]               , noLocA (NoSig noExtField)         )}
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig noExtField $2))}
+opt_datafam_kind_sig :: { Located (TokDcolon, LFamilyResultSig GhcPs) }
+        :               { noLoc     (noAnn,       noLocA (NoSig noExtField)         )}
+        | '::' kind     { sLL $1 $> (epUniTok $1, sLLa $1 $> (KindSig noExtField $2))}
 
-opt_tyfam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :              { noLoc     ([]               , noLocA     (NoSig    noExtField)   )}
-        | '::' kind    { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig  noExtField $2))}
+opt_tyfam_kind_sig :: { Located ((TokDcolon, EpToken "="), LFamilyResultSig GhcPs) }
+        :              { noLoc     (noAnn               , noLocA     (NoSig    noExtField)   )}
+        | '::' kind    { sLL $1 $> ((epUniTok $1, noAnn), sLLa $1 $> (KindSig  noExtField $2))}
         | '='  tv_bndr {% do { tvb <- fromSpecTyVarBndr $2
-                             ; return $ sLL $1 $> ([mj AnnEqual $1], sLLa $1 $> (TyVarSig noExtField tvb))} }
+                             ; return $ sLL $1 $> ((noAnn, epTok $1), sLLa $1 $> (TyVarSig noExtField tvb))} }
 
-opt_at_kind_inj_sig :: { Located ([AddEpAnn], ( LFamilyResultSig GhcPs
+opt_at_kind_inj_sig :: { Located ((TokDcolon, EpToken "=", EpToken "|"), ( LFamilyResultSig GhcPs
                                             , Maybe (LInjectivityAnn GhcPs)))}
-        :            { noLoc ([], (noLocA (NoSig noExtField), Nothing)) }
-        | '::' kind  { sLL $1 $> ( [mu AnnDcolon $1]
+        :            { noLoc (noAnn, (noLocA (NoSig noExtField), Nothing)) }
+        | '::' kind  { sLL $1 $> ( (epUniTok $1, noAnn, noAnn)
                                  , (sL1a $> (KindSig noExtField $2), Nothing)) }
         | '='  tv_bndr_no_braces '|' injectivity_cond
                 {% do { tvb <- fromSpecTyVarBndr $2
-                      ; return $ sLL $1 $> ([mj AnnEqual $1, mj AnnVbar $3]
+                      ; return $ sLL $1 $> ((noAnn, epTok $1, epTok $3)
                                            , (sLLa $1 $2 (TyVarSig noExtField tvb), Just $4))} }
 
 -- tycl_hdr parses the header of a class or data type decl,
@@ -1623,13 +1643,13 @@ datafam_inst_hdr :: { Located (Maybe (LHsContext GhcPs), HsOuterFamEqnTyVarBndrs
                                                          >>= \tvbs ->
                                                              (acs (comb2 $1 $>) (\loc cs -> (L loc
                                                                                   (Just ( addTrailingDarrowC $4 $5 cs)
-                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) emptyComments) tvbs, $6))))
+                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) emptyComments) tvbs, $6))))
                                                     }
         | 'forall' tv_bndrs '.' type   {% do { hintExplicitForall $1
                                              ; tvbs <- fromSpecTyVarBndrs $2
                                              ; let loc = comb2 $1 $>
                                              ; !cs <- getCommentsFor loc
-                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs, $4))
+                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs, $4))
                                        } }
         | context '=>' type         {% acs (comb2 $1 $>) (\loc cs -> (L loc (Just (addTrailingDarrowC $1 $2 cs), mkHsOuterImplicit, $3))) }
         | type                      { sL1 $1 (Nothing, mkHsOuterImplicit, $1) }
@@ -2184,11 +2204,11 @@ unpackedness :: { Located UnpackednessPragma }
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnDot $3) cs) $2 )) }}
+                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (epUniTok $1,epTok $3) cs) $2 )) }}
         | 'forall' tv_bndrs '->' {% do { hintExplicitForall $1
                                        ; req_tvbs <- fromSpecTyVarBndrs $2
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnRarrow $3) cs) req_tvbs )) }}
+                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (epUniTok $1,epUniTok $3) cs) req_tvbs )) }}
 
 -- A ktype is a ctype, possibly with a kind annotation
 ktype :: { LHsType GhcPs }
@@ -2434,7 +2454,7 @@ fds1 :: { Located [LHsFunDep GhcPs] }
 
 fd :: { LHsFunDep GhcPs }
         : varids0 '->' varids0  {% amsA' (L (comb3 $1 $2 $3)
-                                       (FunDep [mu AnnRarrow $2]
+                                       (FunDep (epUniTok $2)
                                                (reverse (unLoc $1))
                                                (reverse (unLoc $3)))) }
 
@@ -2478,20 +2498,20 @@ constructors.
 -----------------------------------------------------------------------------
 -- Datatype declarations
 
-gadt_constrlist :: { Located ([AddEpAnn]
+gadt_constrlist :: { Located ((EpToken "where", EpToken "{", EpToken "}")
                           ,[LConDecl GhcPs]) } -- Returned in order
 
         : 'where' '{'        gadt_constrs '}'    {% checkEmptyGADTs $
                                                       L (comb2 $1 $4)
-                                                        ([mj AnnWhere $1
-                                                         ,moc $2
-                                                         ,mcc $4]
+                                                        ((epTok $1
+                                                         ,epTok $2
+                                                         ,epTok $4)
                                                         , unLoc $3) }
         | 'where' vocurly    gadt_constrs close  {% checkEmptyGADTs $
                                                       L (comb2 $1 $3)
-                                                        ([mj AnnWhere $1]
+                                                        ((epTok $1, NoEpTok, NoEpTok)
                                                         , unLoc $3) }
-        | {- empty -}                            { noLoc ([],[]) }
+        | {- empty -}                            { noLoc (noAnn,[]) }
 
 gadt_constrs :: { Located [LConDecl GhcPs] }
         : gadt_constr ';' gadt_constrs
@@ -2525,8 +2545,8 @@ consequence, GADT constructor names are restricted (names like '(*)' are
 allowed in usual data constructors, but not in GADTs).
 -}
 
-constrs :: { Located ([AddEpAnn],[LConDecl GhcPs]) }
-        : '=' constrs1    { sLL $1 $2 ([mj AnnEqual $1],unLoc $2)}
+constrs :: { Located (EpToken "=",[LConDecl GhcPs]) }
+        : '=' constrs1    { sLL $1 $2 (epTok $1,unLoc $2)}
 
 constrs1 :: { Located [LConDecl GhcPs] }
         : constrs1 '|' constr


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon,
+  TokDcolon, TokRarrow,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -411,6 +411,7 @@ getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
 type TokDcolon = EpUniToken "::" "∷"
+type TokRarrow = EpUniToken "->" "→"
 
 -- | Layout information for declarations.
 data EpLayout =


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -231,41 +231,32 @@ mkTyData :: SrcSpan
          -> Maybe (LHsKind GhcPs)
          -> [LConDecl GhcPs]
          -> Located (HsDeriving GhcPs)
-         -> [AddEpAnn]
+         -> AnnDataDefn
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns = annsIn {andd_openp = ops, andd_closep = cps}
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
        ; !cs' <- getCommentsFor loc'
        ; let loc = EpAnn (spanAsAnchor loc') noAnn (cs' Semi.<> cs)
-       ; return (L loc (DataDecl { tcdDExt = anns',
+       ; return (L loc (DataDecl { tcdDExt = noExtField,
                                    tcdLName = tc, tcdTyVars = tyvars,
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
--- TODO:AZ:temporary
-openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
-openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
-openParen2AddEpAnn NoEpTok = []
-
-closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
-closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
-closeParen2AddEpAnn NoEpTok = []
-
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
            -> DataDefnCons (LConDecl GhcPs)
            -> HsDeriving GhcPs
+           -> AnnDataDefn
            -> P (HsDataDefn GhcPs)
-mkDataDefn cType mcxt ksig data_cons maybe_deriv
+mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
   = do { checkDatatypeContext mcxt
-       ; return (HsDataDefn { dd_ext = noExtField
+       ; return (HsDataDefn { dd_ext = anns
                             , dd_cType = cType
                             , dd_ctxt = mcxt
                             , dd_cons = data_cons
@@ -316,15 +307,13 @@ mkTyFamInstEqn :: SrcSpan
                -> HsOuterFamEqnTyVarBndrs GhcPs
                -> LHsType GhcPs
                -> LHsType GhcPs
-               -> [AddEpAnn]
+               -> EpToken "="
                -> P (LTyFamInstEqn GhcPs)
-mkTyFamInstEqn loc bndrs lhs rhs anns
+mkTyFamInstEqn loc bndrs lhs rhs annEq
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns'
+                        { feqn_ext    = (ops, cps, annEq)
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -339,18 +328,17 @@ mkDataFamInst :: SrcSpan
               -> Maybe (LHsKind GhcPs)
               -> [LConDecl GhcPs]
               -> Located (HsDeriving GhcPs)
-              -> [AddEpAnn]
+              -> AnnDataDefn
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; let anns' = anns {andd_openp = ops, andd_closep = cps}
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns'
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = anns'
+                  (FamEqn { feqn_ext    = ([], [], NoEpTok)
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
@@ -361,11 +349,12 @@ mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
 
 mkTyFamInst :: SrcSpan
             -> TyFamInstEqn GhcPs
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "instance"
             -> P (LInstDecl GhcPs)
-mkTyFamInst loc eqn anns = do
+mkTyFamInst loc eqn t i = do
   return (L (noAnnSrcSpan loc) (TyFamInstD noExtField
-              (TyFamInstDecl anns eqn)))
+              (TyFamInstDecl (t,i) eqn)))
 
 mkFamDecl :: SrcSpan
           -> FamilyInfo GhcPs
@@ -373,14 +362,13 @@ mkFamDecl :: SrcSpan
           -> LHsType GhcPs                   -- LHS
           -> LFamilyResultSig GhcPs          -- Optional result signature
           -> Maybe (LInjectivityAnn GhcPs)   -- Injectivity annotation
-          -> [AddEpAnn]
+          -> AnnFamilyDecl
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns' = annsIn { afd_openp = ops, afd_closep = cps }
        ; return (L loc' (FamDecl noExtField (FamilyDecl
                                            { fdExt       = anns'
                                            , fdTopLevel  = topLevel
@@ -1050,8 +1038,8 @@ checkRecordSyntax lr@(L loc r)
 
 -- | Check if the gadt_constrlist is empty. Only raise parse error for
 -- `data T where` to avoid affecting existing error message, see #8258.
-checkEmptyGADTs :: Located ([AddEpAnn], [LConDecl GhcPs])
-                -> P (Located ([AddEpAnn], [LConDecl GhcPs]))
+checkEmptyGADTs :: Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs])
+                -> P (Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs]))
 checkEmptyGADTs gadts@(L span (_, []))           -- Empty GADT declaration.
     = do gadtSyntax <- getBit GadtSyntaxBit   -- GADTs implies GADTSyntax
          unless gadtSyntax $ addError $ mkPlainErrorMsgEnvelope span $


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -1883,7 +1883,7 @@ rnDataDefn doc (HsDataDefn { dd_cType = cType, dd_ctxt = context, dd_cons = cond
 
         ; let all_fvs = fvs1 `plusFV` fvs3 `plusFV`
                         con_fvs `plusFV` sig_fvs
-        ; return ( HsDataDefn { dd_ext = noExtField, dd_cType = cType
+        ; return ( HsDataDefn { dd_ext = noAnn, dd_cType = cType
                               , dd_ctxt = context', dd_kindSig = m_sig'
                               , dd_cons = condecls'
                               , dd_derivs = derivs' }


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -291,14 +291,14 @@ cvtDec (NewtypeD ctxt tc tvs ksig constr derivs)
         ; ksig' <- cvtKind `traverse` ksig
         ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = con'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }
@@ -363,7 +363,7 @@ cvtDec (DataInstD ctxt bndrs tys ksig constrs derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; cons' <- cvtDataDefnCons False ksig $ DataTypeCons False constrs
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -385,7 +385,7 @@ cvtDec (NewtypeInstD ctxt bndrs tys ksig constr derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -504,14 +504,14 @@ cvtGenDataDec type_data ctxt tc tvs ksig constrs derivs
         ; cons' <- cvtDataDefnCons type_data ksig $
                    DataTypeCons type_data constrs
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = cons'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -76,9 +76,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnData (EpaSpan { Test20239.hs:5:1-4 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { Test20239.hs:5:6-13 }))
-        ,(AddEpAnn AnnEqual (EpaSpan { Test20239.hs:5:34 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { Test20239.hs:5:15-20 })
@@ -113,7 +114,20 @@
               {OccName: PGMigration})))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:1-4 }))
+          (EpTok (EpaSpan { Test20239.hs:5:6-13 }))
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:34 })))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -891,7 +891,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:22:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:22:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1032,8 +1045,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:24:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:24:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:24:8-9 })
@@ -1068,7 +1083,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1239,7 +1267,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:28:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:28:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1380,8 +1421,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:30:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:30:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:30:8-9 })
@@ -1416,7 +1459,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1587,7 +1643,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:34:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:34:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1728,8 +1797,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:36:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:36:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:36:8-9 })
@@ -1764,7 +1835,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1935,7 +2019,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:40:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:40:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2076,8 +2173,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:42:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:42:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:42:8-9 })
@@ -2112,7 +2211,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2283,7 +2395,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:46:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:46:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2424,8 +2549,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:48:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:48:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:48:8-9 })
@@ -2460,7 +2587,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2631,7 +2771,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:52:21-24 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:52:21-24 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2772,8 +2925,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:54:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:54:16-20 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:54:8-10 })
@@ -2808,7 +2963,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:16-20 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -59,8 +59,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T17544_kw.hs:15:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:16:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:15:6-8 })
@@ -75,7 +74,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:16:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -161,8 +173,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnNewtype (EpaSpan { T17544_kw.hs:18:1-7 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:19:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:18:9-11 })
@@ -177,7 +188,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:18:1-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:19:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:3:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:5:3 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:3:6-9 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:3:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:5:3 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -285,8 +297,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:11:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:11:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:11:6-9 })
@@ -301,7 +312,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -401,8 +425,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:14:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:14:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:14:6-9 })
@@ -417,7 +440,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -559,8 +595,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:19:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:19:6-9 })
@@ -575,7 +610,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -717,8 +765,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:27:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:27:6-9 })
@@ -733,7 +780,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -906,8 +966,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:31:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:31:6-9 })
@@ -922,7 +981,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1107,8 +1179,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:36:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:36:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:36:6-9 })
@@ -1123,7 +1194,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:11 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -82,8 +82,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:7:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:7:12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:7:6-10 })
@@ -98,7 +97,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:12 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -286,10 +298,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:10:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:10:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:10:32-33 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:10:41-45 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:10:32-33 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:41-45 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -300,7 +326,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:11:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:11:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:11:3-8 })
@@ -479,7 +509,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:12:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:12:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:12:3-8 })
@@ -642,8 +676,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:15:19 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:15:6 })
@@ -734,7 +767,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:19 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1000,10 +1046,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:18:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:18:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:18:42-43 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:18:50-54 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:18:42-43 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:50-54 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1014,7 +1074,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:19:17 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:19:17 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:19:3-4 })
@@ -1378,9 +1442,23 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:21:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:21:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:21:17-18 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:1-4 }))
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:21:17-18 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (DataFamily)
        (TopLevel)
        (L
@@ -1501,10 +1579,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnNewtype (EpaSpan { DumpParsedAst.hs:22:1-7 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { DumpParsedAst.hs:22:9-16 }))
-        ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:22:39-40 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:22:62-66 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { DumpParsedAst.hs:22:18-20 })
@@ -1613,7 +1691,22 @@
                     {OccName: Type})))))))))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:1-7 }))
+          (NoEpTok)
+          (EpTok (EpaSpan { DumpParsedAst.hs:22:9-16 }))
+          (EpUniTok
+           (EpaSpan { DumpParsedAst.hs:22:39-40 })
+           (NormalSyntax))
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:62-66 }))
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Just
@@ -1779,8 +1872,9 @@
                     (EpAnn
                      (EpaSpan { DumpParsedAst.hs:23:11-20 })
                      ((,)
-                      (AddEpAnn AnnForall (EpaSpan { DumpParsedAst.hs:23:11-16 }))
-                      (AddEpAnn AnnDot (EpaSpan { DumpParsedAst.hs:23:20 })))
+                      (EpUniTok (EpaSpan { DumpParsedAst.hs:23:11-16 }) NormalSyntax)
+                      (EpTok
+                       (EpaSpan { DumpParsedAst.hs:23:20 })))
                      (EpaComments
                       []))
                     [(L


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -154,7 +154,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -245,7 +256,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -256,7 +279,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:13:3-8 })
@@ -429,7 +455,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:14:3-8 })
@@ -671,7 +700,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (TopLevel)
          (L
@@ -784,7 +825,10 @@
         (NoExtField)
         (DataFamInstDecl
          (FamEqn
-          []
+          ((,,)
+           []
+           []
+           (NoEpTok))
           (L
            (EpAnn
             (EpaSpan { DumpRenamedAst.hs:19:18-20 })
@@ -888,7 +932,18 @@
                      {Name: GHC.Types.Type}))))))))))]
           (Prefix)
           (HsDataDefn
-           (NoExtField)
+           (AnnDataDefn
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (Nothing)
            (Nothing)
            (Just
@@ -1041,8 +1096,8 @@
                       (EpAnn
                        (EpaDelta {  } (SameLine 0) [])
                        ((,)
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) []))
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) [])))
+                        (NoEpUniTok)
+                        (NoEpTok))
                        (EpaComments
                         []))
                       [(L
@@ -1347,7 +1402,18 @@
                 {Name: k}))))))])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -1452,7 +1518,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -1463,7 +1541,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:26:3-4 })
@@ -2006,7 +2087,19 @@
            (EpaComments
             []))
           (FamilyDecl
-           []
+           (AnnFamilyDecl
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (OpenTypeFamily)
            (NotTopLevel)
            (L
@@ -2176,9 +2269,15 @@
             (EpaComments
              []))
            (TyFamInstDecl
-            [(AddEpAnn AnnType (EpaSpan { DumpRenamedAst.hs:32:3-6 }))]
+            ((,)
+             (EpTok
+              (EpaSpan { DumpRenamedAst.hs:32:3-6 }))
+             (NoEpTok))
             (FamEqn
-             []
+             ((,,)
+              []
+              []
+              (NoEpTok))
              (L
               (EpAnn
                (EpaSpan { DumpRenamedAst.hs:32:8 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -84,9 +84,22 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:11:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { KindSigs.hs:11:6-11 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { KindSigs.hs:11:19-23 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:6-11 }))
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:19-23 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -97,7 +110,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:12:9 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { KindSigs.hs:12:9 })))
             (L
              (EpAnn
               (EpaSpan { KindSigs.hs:12:3-5 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -37,7 +37,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T15323.hs:5:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T15323.hs:5:21-25 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T15323.hs:5:6-17 })
@@ -90,7 +89,20 @@
            (NoExtField))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:21-25 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -131,8 +143,9 @@
              (EpAnn
               (EpaSpan { T15323.hs:6:20-29 })
               ((,)
-               (AddEpAnn AnnForall (EpaSpan { T15323.hs:6:20-25 }))
-               (AddEpAnn AnnDot (EpaSpan { T15323.hs:6:29 })))
+               (EpUniTok (EpaSpan { T15323.hs:6:20-25 }) NormalSyntax)
+               (EpTok
+                (EpaSpan { T15323.hs:6:29 })))
               (EpaComments
                []))
              [(L


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:5:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:5:6-11 })
@@ -111,7 +110,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:24 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -153,8 +165,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:6:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:6:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:6:6-11 })
@@ -219,7 +230,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:24 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T18791.hs:4:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T18791.hs:4:8-12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T18791.hs:4:6 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:8-12 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -363,6 +363,14 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
+instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+  trailing _ = []
+  setTrailing a _ = a
+
+instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+  trailing _ = []
+  setTrailing a _ = a
+
 -- ---------------------------------------------------------------------
 
 fromAnn' :: (HasEntry a) => a -> Entry
@@ -918,10 +926,6 @@ markAnnOpenP' :: (Monad m, Monoid w) => AnnPragma -> SourceText -> String -> EP
 markAnnOpenP' an NoSourceText txt   = markEpAnnLMS0 an lapr_open AnnOpen (Just txt)
 markAnnOpenP' an (SourceText txt) _ = markEpAnnLMS0 an lapr_open AnnOpen (Just $ unpackFS txt)
 
-markAnnOpen :: (Monad m, Monoid w) => [AddEpAnn] -> SourceText -> String -> EP w m [AddEpAnn]
-markAnnOpen an NoSourceText txt   = markEpAnnLMS'' an lidl AnnOpen (Just txt)
-markAnnOpen an (SourceText txt) _ = markEpAnnLMS'' an lidl AnnOpen (Just $ unpackFS txt)
-
 markAnnOpen' :: (Monad m, Monoid w)
   => Maybe EpaLocation -> SourceText -> String -> EP w m (Maybe EpaLocation)
 markAnnOpen' ms NoSourceText txt   = printStringAtMLoc' ms txt
@@ -2004,17 +2008,17 @@ exactDataFamInstDecl :: (Monad m, Monoid w)
                      => [AddEpAnn] -> TopLevelFlag -> DataFamInstDecl GhcPs
                      -> EP w m ([AddEpAnn], DataFamInstDecl GhcPs)
 exactDataFamInstDecl an top_lvl
-  (DataFamInstDecl (FamEqn { feqn_ext    = an2
+  (DataFamInstDecl (FamEqn { feqn_ext    = (ops, cps, eq)
                            , feqn_tycon  = tycon
                            , feqn_bndrs  = bndrs
                            , feqn_pats   = pats
                            , feqn_fixity = fixity
                            , feqn_rhs    = defn })) = do
-    (an', an2', tycon', bndrs', pats', defn') <- exactDataDefn an2 pp_hdr defn
+    ((ops', cps', an'), tycon', bndrs', pats', defn') <- exactDataDefn pp_hdr defn
                                           -- See Note [an and an2 in exactDataFamInstDecl]
     return
       (an',
-       DataFamInstDecl ( FamEqn { feqn_ext    = an2'
+       DataFamInstDecl ( FamEqn { feqn_ext    = (ops', cps', eq)
                                 , feqn_tycon  = tycon'
                                 , feqn_bndrs  = bndrs'
                                 , feqn_pats   = pats'
@@ -2024,7 +2028,7 @@ exactDataFamInstDecl an top_lvl
   where
     pp_hdr :: (Monad m, Monoid w)
            => Maybe (LHsContext GhcPs)
-           -> EP w m ( [AddEpAnn]
+           -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
                      , LocatedN RdrName
                      , HsOuterTyVarBndrs () GhcPs
                      , HsFamEqnPats GhcPs
@@ -2033,7 +2037,7 @@ exactDataFamInstDecl an top_lvl
       an0 <- case top_lvl of
                TopLevel -> markEpAnnL an lidl AnnInstance -- TODO: maybe in toplevel
                NotTopLevel -> return an
-      exactHsFamInstLHS an0 tycon bndrs pats fixity mctxt
+      exactHsFamInstLHS ops cps an0 tycon bndrs pats fixity mctxt
 
 {-
 Note [an and an2 in exactDataFamInstDecl]
@@ -2146,11 +2150,11 @@ instance ExactPrint (WarnDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warnings (an,src) warns) = do
-    an0 <- markAnnOpen an src "{-# WARNING" -- Note: might be {-# DEPRECATED
+  exact (Warnings ((o,c),src) warns) = do
+    o' <- markAnnOpen'' o src "{-# WARNING" -- Note: might be {-# DEPRECATED
     warns' <- markAnnotated warns
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (Warnings (an1,src) warns')
+    c' <- printStringAtAA c "#-}"
+    return (Warnings ((o',c'),src) warns')
 
 -- ---------------------------------------------------------------------
 
@@ -2212,14 +2216,14 @@ instance ExactPrint FastString where
 instance ExactPrint (RuleDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (HsRules (an, src) rules) = do
-    an0 <-
+  exact (HsRules ((o,c), src) rules) = do
+    o' <-
       case src of
-        NoSourceText      -> markEpAnnLMS'' an lidl AnnOpen  (Just "{-# RULES")
-        SourceText srcTxt -> markEpAnnLMS'' an lidl AnnOpen  (Just $ unpackFS srcTxt)
+        NoSourceText      -> printStringAtAA o "{-# RULES"
+        SourceText srcTxt -> printStringAtAA o (unpackFS srcTxt)
     rules' <- markAnnotated rules
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (HsRules (an1,src) rules')
+    c' <- printStringAtAA c "#-}"
+    return (HsRules ((o',c'),src) rules')
 
 -- ---------------------------------------------------------------------
 
@@ -2344,16 +2348,16 @@ instance ExactPrint (RuleBndr GhcPs) where
 instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor fe _ _ _s = fe
-  exact (FamEqn { feqn_ext = an
+  exact (FamEqn { feqn_ext    = (ops, cps, eq)
                 , feqn_tycon  = tycon
                 , feqn_bndrs  = bndrs
                 , feqn_pats   = pats
                 , feqn_fixity = fixity
                 , feqn_rhs    = rhs }) = do
-    (an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS an tycon bndrs pats fixity Nothing
-    an1 <- markEpAnnL an0 lidl AnnEqual
+    (_an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (FamEqn { feqn_ext = an1
+    return (FamEqn { feqn_ext    = ([], [], eq')
                    , feqn_tycon  = tycon'
                    , feqn_bndrs  = bndrs'
                    , feqn_pats   = pats'
@@ -2364,48 +2368,52 @@ instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
 
 exactHsFamInstLHS ::
       (Monad m, Monoid w)
-   => [AddEpAnn]
+   => [EpToken "("]
+   -> [EpToken ")"]
+   -> [AddEpAnn]
    -> LocatedN RdrName
    -> HsOuterTyVarBndrs () GhcPs
    -> HsFamEqnPats GhcPs
    -> LexicalFixity
    -> Maybe (LHsContext GhcPs)
-   -> EP w m ( [AddEpAnn]
+   -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
              , LocatedN RdrName
              , HsOuterTyVarBndrs () GhcPs
              , HsFamEqnPats GhcPs, Maybe (LHsContext GhcPs))
-exactHsFamInstLHS an thing bndrs typats fixity mb_ctxt = do
+exactHsFamInstLHS ops cps an thing bndrs typats fixity mb_ctxt = do
+  -- TODO:AZ: do these ans exist? They are in the binders now
   an0 <- markEpAnnL an lidl AnnForall
   bndrs' <- markAnnotated bndrs
   an1 <- markEpAnnL an0 lidl AnnDot
   mb_ctxt' <- mapM markAnnotated mb_ctxt
-  (an2, thing', typats') <- exact_pats an1 typats
-  return (an2, thing', bndrs', typats', mb_ctxt')
+  (ops', cps', thing', typats') <- exact_pats ops cps typats
+  return ((ops', cps', an1), thing', bndrs', typats', mb_ctxt')
   where
     exact_pats :: (Monad m, Monoid w)
-      => [AddEpAnn] -> HsFamEqnPats GhcPs -> EP w m ([AddEpAnn], LocatedN RdrName, HsFamEqnPats GhcPs)
-    exact_pats an' (patl:patr:pats)
+      => [EpToken "("] -> [EpToken ")"] -> HsFamEqnPats GhcPs
+      -> EP w m ([EpToken "("], [EpToken ")"], LocatedN RdrName, HsFamEqnPats GhcPs)
+    exact_pats ops1 cps1 (patl:patr:pats)
       | Infix <- fixity
       = let exact_op_app = do
-              an0 <- markEpAnnAllL' an' lidl AnnOpenP
+              ops' <- mapM markEpToken ops1
               patl' <- markAnnotated patl
               thing' <- markAnnotated thing
               patr' <- markAnnotated patr
-              an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-              return (an1, thing', [patl',patr'])
+              cps' <- mapM markEpToken cps1
+              return (ops', cps', thing', [patl',patr'])
         in case pats of
              [] -> exact_op_app
              _  -> do
-               (an0, thing', p) <- exact_op_app
+               (ops', cps', thing', p) <- exact_op_app
                pats' <- mapM markAnnotated pats
-               return (an0, thing', p++pats')
+               return (ops', cps', thing', p++pats')
 
-    exact_pats an' pats = do
-      an0 <- markEpAnnAllL' an' lidl AnnOpenP
+    exact_pats ops0 cps0 pats = do
+      ops' <- mapM markEpToken ops0
       thing' <- markAnnotated thing
       pats' <- markAnnotated pats
-      an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-      return (an1, thing', pats')
+      cps' <- mapM markEpToken cps0
+      return (ops', cps', thing', pats')
 
 -- ---------------------------------------------------------------------
 
@@ -2471,11 +2479,11 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact d@(TyFamInstDecl { tfid_xtn = an, tfid_eqn = eqn }) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnInstance
+  exact d@(TyFamInstDecl { tfid_xtn = (tt,ti), tfid_eqn = eqn }) = do
+    tt' <- markEpToken tt
+    ti' <- markEpToken ti
     eqn' <- markAnnotated eqn
-    return (d { tfid_xtn = an1, tfid_eqn = eqn' })
+    return (d { tfid_xtn = (tt',ti'), tfid_eqn = eqn' })
 
 -- ---------------------------------------------------------------------
 
@@ -2967,13 +2975,13 @@ instance ExactPrint (DefaultDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DefaultDecl an cl tys) = do
-    an0 <- markEpAnnL an lidl AnnDefault
-    an1 <- markEpAnnL an0 lidl AnnOpenP
+  exact (DefaultDecl (d,op,cp) cl tys) = do
+    d' <- markEpToken d
+    op' <- markEpToken op
     cl' <- markAnnotated cl
     tys' <- markAnnotated tys
-    an2 <- markEpAnnL an1 lidl AnnCloseP
-    return (DefaultDecl an2 cl' tys')
+    cp' <- markEpToken cp
+    return (DefaultDecl (d',op',cp') cl' tys')
 
 -- ---------------------------------------------------------------------
 
@@ -3773,11 +3781,11 @@ instance ExactPrint (TyClDecl GhcPs) where
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
+  exact (DataDecl { tcdDExt = x, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
-    (_, an', ltycon', tyvars', _, defn') <-
-      exactDataDefn an (exactVanillaDeclHead ltycon tyvars fixity) defn
-    return (DataDecl { tcdDExt = an', tcdLName = ltycon', tcdTyVars = tyvars'
+    (_, ltycon', tyvars', _, defn') <-
+      exactDataDefn (exactVanillaDeclHead ltycon tyvars fixity) defn
+    return (DataDecl { tcdDExt = x, tcdLName = ltycon', tcdTyVars = tyvars'
                      , tcdFixity = fixity, tcdDataDefn = defn' })
 
   -- -----------------------------------
@@ -3852,7 +3860,7 @@ instance ExactPrint (FunDep GhcPs) where
 
   exact (FunDep an ls rs') = do
     ls' <- markAnnotated ls
-    an0 <- markEpAnnL an lidl AnnRarrow
+    an0 <- markEpUniToken an
     rs'' <- markAnnotated rs'
     return (FunDep an0 ls' rs'')
 
@@ -3862,7 +3870,7 @@ instance ExactPrint (FamilyDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (FamilyDecl { fdExt = an
+  exact (FamilyDecl { fdExt = AnnFamilyDecl ops cps t d f dc eq vb w oc dd cc
                     , fdInfo = info
                     , fdTopLevel = top_level
                     , fdLName = ltycon
@@ -3870,35 +3878,37 @@ instance ExactPrint (FamilyDecl GhcPs) where
                     , fdFixity = fixity
                     , fdResultSig = L lr result
                     , fdInjectivityAnn = mb_inj }) = do
-    an0 <- exactFlavour an info
-    an1 <- exact_top_level an0
-    an2 <- annotationsToComments an1 lidl [AnnOpenP,AnnCloseP]
+    (d',t') <- exactFlavour (d,t) info
+    f' <- exact_top_level f
+
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
     (_, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    (an3, result') <- exact_kind an2
-    (an4, mb_inj') <-
+    (dc', eq', result') <- exact_kind (dc, eq)
+    (vb', mb_inj') <-
       case mb_inj of
-        Nothing -> return (an3, mb_inj)
+        Nothing -> return (vb, mb_inj)
         Just inj -> do
-          an4 <- markEpAnnL an3 lidl AnnVbar
+          vb' <- markEpToken vb
           inj' <- markAnnotated inj
-          return (an4, Just inj')
-    (an5, info') <-
+          return (vb', Just inj')
+    (w', oc', dd', cc', info') <-
              case info of
                ClosedTypeFamily mb_eqns -> do
-                 an5 <- markEpAnnL an4 lidl AnnWhere
-                 an6 <- markEpAnnL an5 lidl AnnOpenC
-                 (an7, mb_eqns') <-
+                 w' <- markEpToken w
+                 oc' <- markEpToken oc
+                 (dd', mb_eqns') <-
                    case mb_eqns of
                      Nothing -> do
-                       an7 <- markEpAnnL an6 lidl AnnDotdot
-                       return (an7, mb_eqns)
+                       dd' <- markEpToken dd
+                       return (dd', mb_eqns)
                      Just eqns -> do
                        eqns' <- markAnnotated eqns
-                       return (an6, Just eqns')
-                 an8 <- markEpAnnL an7 lidl AnnCloseC
-                 return (an8, ClosedTypeFamily mb_eqns')
-               _ -> return (an4, info)
-    return (FamilyDecl { fdExt = an5
+                       return (dd, Just eqns')
+                 cc' <- markEpToken cc
+                 return (w',oc',dd',cc', ClosedTypeFamily mb_eqns')
+               _ -> return (w,oc,dd,cc, info)
+    return (FamilyDecl { fdExt = AnnFamilyDecl [] [] t' d' f' dc' eq' vb' w' oc' dd' cc'
                        , fdInfo = info'
                        , fdTopLevel = top_level
                        , fdLName = ltycon'
@@ -3907,86 +3917,91 @@ instance ExactPrint (FamilyDecl GhcPs) where
                        , fdResultSig = L lr result'
                        , fdInjectivityAnn = mb_inj' })
     where
-      exact_top_level an' =
+      exact_top_level tfamily =
         case top_level of
-          TopLevel    -> markEpAnnL an' lidl AnnFamily
+          TopLevel    -> markEpToken tfamily
           NotTopLevel -> do
             -- It seems that in some kind of legacy
             -- mode the 'family' keyword is still
             -- accepted.
-            markEpAnnL an' lidl AnnFamily
+            markEpToken tfamily
 
-      exact_kind an' =
+      exact_kind (tdcolon, tequal) =
         case result of
-          NoSig    _         -> return (an', result)
+          NoSig    _         -> return (tdcolon, tequal, result)
           KindSig  x kind    -> do
-            an0 <- markEpAnnL an' lidl AnnDcolon
+            tdcolon' <- markEpUniToken tdcolon
             kind' <- markAnnotated kind
-            return (an0, KindSig  x kind')
+            return (tdcolon', tequal, KindSig  x kind')
           TyVarSig x tv_bndr -> do
-            an0 <- markEpAnnL an' lidl AnnEqual
+            tequal' <- markEpToken tequal
             tv_bndr' <- markAnnotated tv_bndr
-            return (an0, TyVarSig x tv_bndr')
+            return (tdcolon, tequal', TyVarSig x tv_bndr')
 
 
-exactFlavour :: (Monad m, Monoid w) => [AddEpAnn] -> FamilyInfo GhcPs -> EP w m [AddEpAnn]
-exactFlavour an DataFamily            = markEpAnnL an lidl AnnData
-exactFlavour an OpenTypeFamily        = markEpAnnL an lidl AnnType
-exactFlavour an (ClosedTypeFamily {}) = markEpAnnL an lidl AnnType
+exactFlavour :: (Monad m, Monoid w) => (EpToken "data", EpToken "type") -> FamilyInfo GhcPs -> EP w m (EpToken "data", EpToken "type")
+exactFlavour (td,tt) DataFamily            = (\td' -> (td',tt)) <$> markEpToken td
+exactFlavour (td,tt) OpenTypeFamily        = (td,)              <$> markEpToken tt
+exactFlavour (td,tt) (ClosedTypeFamily {}) = (td,)              <$> markEpToken tt
 
 -- ---------------------------------------------------------------------
 
 exactDataDefn
   :: (Monad m, Monoid w)
-  => [AddEpAnn]
-  -> (Maybe (LHsContext GhcPs) -> EP w m ([AddEpAnn]
+  => (Maybe (LHsContext GhcPs) -> EP w m (r
                                          , LocatedN RdrName
                                          , a
                                          , b
                                          , Maybe (LHsContext GhcPs))) -- Printing the header
   -> HsDataDefn GhcPs
-  -> EP w m ( [AddEpAnn] -- ^ from exactHdr
-            , [AddEpAnn] -- ^ updated one passed in
+  -> EP w m ( r -- ^ from exactHdr
             , LocatedN RdrName, a, b, HsDataDefn GhcPs)
-exactDataDefn an exactHdr
-                 (HsDataDefn { dd_ext = x, dd_ctxt = context
+exactDataDefn exactHdr
+                 (HsDataDefn { dd_ext = AnnDataDefn ops cps t nt d i dc w oc cc eq
+                             , dd_ctxt = context
                              , dd_cType = mb_ct
                              , dd_kindSig = mb_sig
                              , dd_cons = condecls, dd_derivs = derivings }) = do
 
-  an' <- annotationsToComments an lidl [AnnOpenP, AnnCloseP]
 
-  an0 <- case condecls of
-    DataTypeCons is_type_data _ -> do
-      an0' <- if is_type_data
-                then markEpAnnL an' lidl AnnType
-                else return an'
-      markEpAnnL an0' lidl AnnData
-    NewTypeCon   _ -> markEpAnnL an' lidl AnnNewtype
+  epTokensToComments AnnOpenP ops
+  epTokensToComments AnnCloseP cps
 
-  an1 <- markEpAnnL an0 lidl AnnInstance -- optional
+  (t',nt',d') <- case condecls of
+    DataTypeCons is_type_data _ -> do
+      t' <- if is_type_data
+                then markEpToken t
+                else return t
+      d' <- markEpToken d
+      return (t',nt,d')
+    NewTypeCon   _ -> do
+      nt' <- markEpToken nt
+      return (t, nt', d)
+
+  i' <- markEpToken i -- optional
   mb_ct' <- mapM markAnnotated mb_ct
   (anx, ln', tvs', b, mctxt') <- exactHdr context
-  (an2, mb_sig') <- case mb_sig of
-    Nothing -> return (an1, Nothing)
+  (dc', mb_sig') <- case mb_sig of
+    Nothing -> return (dc, Nothing)
     Just kind -> do
-      an2 <- markEpAnnL an1 lidl AnnDcolon
+      dc' <- markEpUniToken dc
       kind' <- markAnnotated kind
-      return (an2, Just kind')
-  an3 <- if (needsWhere condecls)
-    then markEpAnnL an2 lidl AnnWhere
-    else return an2
-  an4 <- markEpAnnL an3 lidl AnnOpenC
-  (an5, condecls') <- exact_condecls an4 (toList condecls)
+      return (dc', Just kind')
+  w' <- if (needsWhere condecls)
+    then markEpToken w
+    else return w
+  oc' <- markEpToken oc
+  (eq', condecls') <- exact_condecls eq (toList condecls)
   let condecls'' = case condecls of
-        DataTypeCons d _ -> DataTypeCons d condecls'
+        DataTypeCons td _ -> DataTypeCons td condecls'
         NewTypeCon _     -> case condecls' of
           [decl] -> NewTypeCon decl
           _ -> panic "exacprint NewTypeCon"
-  an6 <- markEpAnnL an5 lidl AnnCloseC
+  cc' <- markEpToken cc
   derivings' <- mapM markAnnotated derivings
-  return (anx, an6, ln', tvs', b,
-                 (HsDataDefn { dd_ext = x, dd_ctxt = mctxt'
+  return (anx, ln', tvs', b,
+                 (HsDataDefn { dd_ext = AnnDataDefn [] [] t' nt' d' i' dc' w' oc' cc' eq'
+                             , dd_ctxt = mctxt'
                              , dd_cType = mb_ct'
                              , dd_kindSig = mb_sig'
                              , dd_cons = condecls'', dd_derivs = derivings' }))
@@ -4032,12 +4047,11 @@ exactVanillaDeclHead thing tvs@(HsQTvs { hsq_explicit = tyvars }) fixity context
 instance ExactPrint (InjectivityAnn GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (InjectivityAnn an lhs rhs) = do
-    an0 <- markEpAnnL an lidl AnnVbar
+  exact (InjectivityAnn rarrow lhs rhs) = do
     lhs' <- markAnnotated lhs
-    an1 <- markEpAnnL an0 lidl AnnRarrow
+    rarrow' <- markEpUniToken rarrow
     rhs' <- mapM markAnnotated rhs
-    return (InjectivityAnn an1 lhs' rhs')
+    return (InjectivityAnn rarrow' lhs' rhs')
 
 -- ---------------------------------------------------------------------
 
@@ -4238,17 +4252,17 @@ instance ExactPrint (HsForAllTelescope GhcPs) where
   setAnnotationAnchor (HsForAllVis an a) anc ts cs = HsForAllVis (setAnchorEpa an anc ts cs) a
   setAnnotationAnchor (HsForAllInvis an a) anc ts cs = HsForAllInvis (setAnchorEpa an anc ts cs) a
 
-  exact (HsForAllVis an bndrs)   = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllVis (EpAnn l (f,r) cs) bndrs)   = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnRarrow
-    return (HsForAllVis an1 bndrs')
+    r' <- markEpUniToken r
+    return (HsForAllVis (EpAnn l (f',r') cs) bndrs')
 
-  exact (HsForAllInvis an bndrs) = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllInvis (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnDot
-    return (HsForAllInvis an1 bndrs')
+    d' <- markEpToken d
+    return (HsForAllInvis (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 
@@ -4430,17 +4444,17 @@ markTrailing ts = do
 
 -- based on pp_condecls in Decls.hs
 exact_condecls :: (Monad m, Monoid w)
-  => [AddEpAnn] -> [LConDecl GhcPs] -> EP w m ([AddEpAnn],[LConDecl GhcPs])
-exact_condecls an cs
+  => EpToken "=" -> [LConDecl GhcPs] -> EP w m (EpToken "=",[LConDecl GhcPs])
+exact_condecls eq cs
   | gadt_syntax                  -- In GADT syntax
   = do
       cs' <- mapM markAnnotated cs
-      return (an, cs')
+      return (eq, cs')
   | otherwise                    -- In H98 syntax
   = do
-      an0 <- markEpAnnL an lidl AnnEqual
+      eq0 <- markEpToken eq
       cs' <- mapM markAnnotated cs
-      return (an0, cs')
+      return (eq0, cs')
   where
     gadt_syntax = case cs of
       []                      -> False
@@ -4553,11 +4567,11 @@ instance ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) wher
   setAnnotationAnchor (HsOuterExplicit an a) anc ts cs = HsOuterExplicit (setAnchorEpa an anc ts cs) a
 
   exact b@(HsOuterImplicit _) = pure b
-  exact (HsOuterExplicit an bndrs) = do
-    an0 <- markLensAA an lfst -- "forall"
+  exact (HsOuterExplicit (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- "."
-    return (HsOuterExplicit an1 bndrs')
+    d' <- markEpToken d
+    return (HsOuterExplicit (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -209,10 +209,10 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
- "../../testsuite/tests/printer/Test21355.hs" Nothing
+ -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- -- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -269,7 +269,7 @@ synifyTyCon prr _coax tc
           , tcdFixity = synifyFixity tc
           , tcdDataDefn =
               HsDataDefn
-                { dd_ext = noExtField
+                { dd_ext = noAnn
                 , dd_cons = DataTypeCons False [] -- No constructors; arbitrary lie, they are neither
                 -- algebraic data nor newtype:
                 , dd_ctxt = Nothing
@@ -401,7 +401,7 @@ synifyTyCon _prr coax tc
         alg_deriv = []
         defn =
           HsDataDefn
-            { dd_ext = noExtField
+            { dd_ext = noAnn
             , dd_ctxt = alg_ctx
             , dd_cType = Nothing
             , dd_kindSig = kindSig



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:22:57 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:22:57 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25390
Message-ID: <671299712cd0b_1895e9bc4a8687bb@gitlab.mail>



Ben Gamari pushed new branch wip/T25390 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25390
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:25:18 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:25:18 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <671299fe70316_1895e9bc50c70526@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
e184100d by Ben Gamari at 2024-10-18T13:23:56-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

   version=9.13   while    RELEASE=YES
   version=9.12   while    RELEASE=YES
   version=9.12   while    RELEASE=NO

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,26 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$RELEASE" = "NO"; then
+        if test "$NumVersionComponents" != "2"; then
+            AC_MSG_ERROR([Version numbers on unstable branches must have two components])
+        else
+            AC_MSG_RESULT([okay unstable version])
+        fi
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        if test "$NumVersionComponents" != "3"; then
+            AC_MSG_ERROR([Version numbers on stable branches must have three components])
+        else
+            AC_MSG_RESULT([okay stable version])
+        fi
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:25:34 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:25:34 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <67129a0e2ff37_1895e9bcb9c709d5@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
cf8e5633 by Ben Gamari at 2024-10-18T13:25:17-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

   version=9.13   while    RELEASE=YES
   version=9.12   while    RELEASE=YES
   version=9.12   while    RELEASE=NO

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,26 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$RELEASE" = "NO"; then
+        if test "$NumVersionComponents" != "2"; then
+            AC_MSG_ERROR([Version numbers on unstable branches must have two components])
+        else
+            AC_MSG_RESULT([okay unstable version])
+        fi
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        if test "$NumVersionComponents" != "3"; then
+            AC_MSG_ERROR([Version numbers on stable branches must have three components])
+        else
+            AC_MSG_RESULT([okay stable version])
+        fi
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:26:06 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:26:06 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <67129a2ee20a0_1895e9bc520713d7@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
86d8a668 by Ben Gamari at 2024-10-18T13:25:43-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

 * `version=9.13`   while    `RELEASE=YES`
 * `version=9.12`   while    `RELEASE=YES`
 * `version=9.12`   while    `RELEASE=NO`

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,26 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$RELEASE" = "NO"; then
+        if test "$NumVersionComponents" != "2"; then
+            AC_MSG_ERROR([Version numbers on unstable branches must have two components])
+        else
+            AC_MSG_RESULT([okay unstable version])
+        fi
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        if test "$NumVersionComponents" != "3"; then
+            AC_MSG_ERROR([Version numbers on stable branches must have three components])
+        else
+            AC_MSG_RESULT([okay stable version])
+        fi
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/86d8a668289082ff70c98fc587d03f049c9b178a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:28:40 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:28:40 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <67129ac8b9d4f_1895e94398d871735@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
279a5d2b by Ben Gamari at 2024-10-18T13:28:10-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

 * `version=9.13` while `RELEASE=YES` since this would imply a
   release made from an unstable branch
 * `version=9.13.0` since unstable versions should only have two
   components
 * `version=9.12` since this has the wrong number of version components
   for a stable branch

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,26 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$RELEASE" = "NO"; then
+        if test "$NumVersionComponents" != "2"; then
+            AC_MSG_ERROR([Version numbers on unstable branches must have two components])
+        else
+            AC_MSG_RESULT([okay unstable version])
+        fi
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        if test "$NumVersionComponents" != "3"; then
+            AC_MSG_ERROR([Version numbers on stable branches must have three components])
+        else
+            AC_MSG_RESULT([okay stable version])
+        fi
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/279a5d2b56f90a841dbad958704e81257f306ead

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:35:34 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Fri, 18 Oct 2024 13:35:34 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] make caller wrap the pop err ctxt
Message-ID: <67129c66add4f_1895e954450c721d1@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
f697c26c by Apoorv Ingle at 2024-10-18T12:35:02-05:00
make caller wrap the pop err ctxt

- - - - -


3 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -586,22 +586,6 @@ mkExpandedPatRn
 mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav
                                                          , xrn_expanded = eExpr })
 
--- | Build an expression using the extension constructor `XExpr`,
---   and the two components of the expansion: original do stmt and
---   expanded expression and associate it with a provided location
-mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
-  -> HsDoFlavour          -- ^ the flavour of the statement
-  -> HsExpr GhcRn         -- ^ expanded expression
-  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
-  = L loc $ mkExpandedStmt oStmt flav eExpr
-
 data XXExprGhcTc
   = WrapExpr        -- Type and evidence application and abstractions
       HsWrapper (HsExpr GhcTc)


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -2258,7 +2258,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
              -- Need 'pureAName' and not 'returnMName' here, so that it requires
              -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed).
              (pure_name, _) <- lookupQualifiedDoName (HsDoStmt ctxt) pureAName
-             let expr = noLocA (HsApp noExtField (noLocA ret) tup)
+             let expr = noLocA (HsApp noExtField (noLocA pure_name) tup)
              return (expr, emptyFVs)
      return ( ApplicativeArgMany
               { xarg_app_arg_many = noExtField


=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -47,7 +47,7 @@ import Data.List ((\\))
 *                                                                      *
 ************************************************************************
 -}
-
+-- TODO: make caller add the pop error context
 -- | Expand the `do`-statments into expressions right after renaming
 --   so that they can be typechecked.
 --   See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary
@@ -63,8 +63,6 @@ expand_do_stmts _ ListComp _ =
   pprPanic "expand_do_stmts: impossible happened. ListComp" empty
         -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
-
 expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) =
   pprPanic "expand_do_stmts: TransStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
@@ -73,13 +71,15 @@ expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) =
   pprPanic "expand_do_stmts: ParStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
+expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
+
+expand_do_stmts _addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (5) below
 -- last statement of a list comprehension, needs to explicitly return it
 -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
    | NoSyntaxExprRn <- ret_expr
    -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
-   = return $ mkExpandedStmtAt addPop loc stmt flav body
+   = return $ mkExpandedStmtAt False loc stmt flav body
 
    | SyntaxExprRn ret <- ret_expr
    --
@@ -87,18 +87,18 @@ expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_exp
    --               return e  ~~> return e
    -- to make T18324 work
    = do let expansion = genHsApp ret (L body_loc body)
-        return $ mkExpandedStmtAt addPop loc stmt flav expansion
+        return $ mkExpandedStmtAt False loc stmt flav expansion
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
+expand_do_stmts _addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
 --                      stmts ~~> stmts'
 --    ------------------------------------------------
 --       let x = e ; stmts ~~> let x = e in stmts'
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
-     let expansion = genHsLet bs expand_stmts
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+  do expand_stmts <- expand_do_stmts False doFlavour lstmts
+     let expansion = genPopErrCtxtExpr (wrapGenSpan $ genHsLet bs expand_stmts)
+     return $ mkExpandedStmtAt False loc stmt doFlavour (unLoc expansion)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
+expand_do_stmts _addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
   | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn
   , fail_op              <- xbsrn_failOp xbsrn
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (2) below
@@ -107,27 +107,27 @@ expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
 --                                   _   -> fail "Pattern match failure .."
 --    -------------------------------------------------------
 --       pat <- e ; stmts   ~~> (>>=) e f
-  = do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  = do expand_stmts <- genPopErrCtxtExpr <$> expand_do_stmts False doFlavour lstmts
        failable_expr <- mk_failable_expr False doFlavour pat expand_stmts fail_op
        let expansion = genHsExpApps bind_op  -- (>>=)
                        [ e
                        , failable_expr ]
-       return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+       return $ mkExpandedStmtAt False loc stmt doFlavour expansion
 
   | otherwise
   = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr  stmt)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
+expand_do_stmts _addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
 -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (1) below
 --              stmts ~~> stmts'
 --    ----------------------------------------------
 --      e ; stmts ~~> (>>) e stmts'
-  do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts_expr <- expand_do_stmts False doFlavour lstmts
      let expansion = genHsExpApps then_op  -- (>>)
-                                  [ e
-                                  , expand_stmts_expr ]
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+                     [ e
+                     , wrapGenSpan (mkPopErrCtxtExpr expand_stmts_expr) ]
+     return $ mkExpandedStmtAt False loc stmt doFlavour expansion
 
 expand_do_stmts _ doFlavour
        ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts
@@ -149,7 +149,7 @@ expand_do_stmts _ doFlavour
 --                                           -> do { rec_stmts
 --                                                 ; return (local_only_ids ++ later_ids) } ))
 --                              (\ [ local_only_ids ++ later_ids ] -> stmts')
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts <- expand_do_stmts False doFlavour lstmts
      -- NB: No need to wrap the expansion with an ExpandedStmt
      -- as we want to flatten the rec block statements into its parent do block anyway
      return $ mkHsApps (wrapGenSpan bind_fun)                                           -- (>>=)
@@ -177,7 +177,7 @@ expand_do_stmts _ doFlavour
                              -- NB: LazyPat because we do not want to eagerly evaluate the pattern
                              -- and potentially loop forever
 
-expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
+expand_do_stmts _addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
 -- See Note [Applicative BodyStmt]
 --
 --                  stmts ~~> stmts'
@@ -216,7 +216,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
             { xarg_app_arg_one = mb_fail_op
             , app_arg_pattern = pat
             , arg_expr        = (L rhs_loc rhs) }) =
-      do let xx_expr = mkExpandedStmtAt addPop (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
+      do let xx_expr = mkExpandedStmtAt False (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
          traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr])
          return ((pat, mb_fail_op)
                 , xx_expr)
@@ -225,13 +225,13 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
                                , final_expr = ret@(L ret_loc _)
                                , bv_pattern = pat
                                , stmt_context = ctxt }) =
-      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts addPop ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
-         ; traceTc "do_arg" (text "ManyArg" <+> ppr addPop <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
+      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts False ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
+         ; traceTc "do_arg" (text "ManyArg" <+> ppr False <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
          ; return ((pat, Nothing)
                   , xx_expr) }
 
     match_args :: (LPat GhcRn, FailOperator GhcRn)  -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn)
-    match_args (pat, fail_op) body = mk_failable_expr addPop doFlavour pat body fail_op
+    match_args (pat, fail_op) body = mk_failable_expr False doFlavour pat body fail_op
 
     mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn
     mk_apps l_expr (op, r_expr) =
@@ -243,7 +243,7 @@ expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (p
 
 -- checks the pattern `pat` for irrefutability which decides if we need to wrap it with a fail block
 mk_failable_expr :: Bool -> HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
-mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
+mk_failable_expr _addPop doFlav lpat@(L loc pat) expr@(L _exprloc _) fail_op =
   do { is_strict <- xoptM LangExt.Strict
      ; hscEnv <- getTopEnv
      ; rdrEnv <- getGlobalRdrEnv
@@ -252,13 +252,11 @@ mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
      ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat
                                         , text "isIrrefutable:" <+> ppr irrf_pat
                                         ])
-     ; let xexpr | addPop = mkPopErrCtxtExprAt exprloc expr
-                 | otherwise = expr
      ; if irrf_pat -- don't wrap with fail block if
                    -- the pattern is irrefutable
        then case pat of
-              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] xexpr
-              _ -> return $ genHsLamDoExp doFlav [lpat] xexpr
+              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr
+              _ -> return $ genHsLamDoExp doFlav [lpat] expr
 
        else L loc <$> mk_fail_block doFlav lpat expr fail_op
      }
@@ -343,10 +341,10 @@ They capture the essence of statement expansions as implemented in `expand_do_st
 
           (2) DO【 p <- e; ss 】 = if p is irrefutable
                                    then ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\ p -> DO【 ss 】))
+                                          (>>=) s ((\ p -> ‹PopExprCtxt› DO【 ss 】))
                                    else ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\case p -> DO【 ss 】
-                                                                       _ -> fail "pattern p failure"))
+                                          (>>=) s ((\case p -> ‹PopExprCtxt› DO【 ss 】
+                                                          _ -> fail "pattern p failure"))
 
           (3) DO【 let x = e; ss 】
                                  = ‹ExpansionStmt (let x = e)› (let x = e in (‹PopErrCtxt›DO【 ss 】))
@@ -573,7 +571,6 @@ mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
 mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
 mkPopErrCtxtExprAt _loc a = wrapGenSpan $ mkPopErrCtxtExpr a
 
-
 genPopErrCtxtExpr :: LHsExpr GhcRn -> LHsExpr GhcRn
 genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:43:24 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 18 Oct 2024 13:43:24 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Revert
 "compiler: start deprecating cmmToRawCmmHook"
Message-ID: <67129e3c9338f_1895e961f1ac74478@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
147f8f01 by Daneel Yaitskov at 2024-10-18T13:43:12-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


23 changed files:

- .gitlab-ci.yml
- cabal.project-reinstall
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/Setup.hs
- compiler/ghc.cabal.in
- libraries/base/changelog.md
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- + libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
- libraries/transformers
- rts/Interpreter.c
- + testsuite/tests/perf/should_run/T17949.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/profiling/should_run/callstack002.stderr
- testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
- testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
- testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
- testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
- testsuite/tests/tcplugins/all.T
- testsuite/tests/typecheck/should_compile/all.T
- utils/haddock/haddock.cabal


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -494,21 +494,16 @@ stack-hadrian-build:
 # Testing reinstallable ghc codepath
 ####################################
 
-# As documented on the original ticket #19896, this feature already has a long
-# way to go before it can actually be used. Meanwhile, parts of it have
-# bit-rotted, possibly related to some Cabal change. The job is disabled for
-# now.
-#
-# test-cabal-reinstall-x86_64-linux-deb10:
-#   extends: nightly-x86_64-linux-deb10-validate
-#   stage: full-build
-#   variables:
-#     REINSTALL_GHC: "yes"
-#     BUILD_FLAVOUR: validate
-#     TEST_ENV: "x86_64-linux-deb10-cabal-install"
-#   rules:
-#     - if: $NIGHTLY
-#     - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
+test-cabal-reinstall-x86_64-linux-deb10:
+  extends: nightly-x86_64-linux-deb10-validate
+  stage: full-build
+  variables:
+    REINSTALL_GHC: "yes"
+    BUILD_FLAVOUR: validate
+    TEST_ENV: "x86_64-linux-deb10-cabal-install"
+  rules:
+    - if: $NIGHTLY
+    - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
 
 ########################################
 # Testing ABI is invariant across builds


=====================================
cabal.project-reinstall
=====================================
@@ -12,11 +12,13 @@ packages: ./compiler
           -- ./libraries/deepseq/
           ./libraries/directory/
           ./libraries/exceptions/
+          ./libraries/file-io/
           ./libraries/filepath/
           -- ./libraries/ghc-bignum/
            ./libraries/ghc-boot/
           -- ./libraries/ghc-boot-th/
           ./libraries/ghc-compact
+          ./libraries/ghc-experimental
           ./libraries/ghc-heap
           ./libraries/ghci
           -- ./libraries/ghc-prim
@@ -25,6 +27,7 @@ packages: ./compiler
           ./libraries/hpc
           -- ./libraries/integer-gmp
           ./libraries/mtl/
+          ./libraries/os-string/
           ./libraries/parsec/
           -- ./libraries/pretty/
           ./libraries/process/
@@ -39,7 +42,11 @@ packages: ./compiler
           ./libraries/Win32/
           ./libraries/xhtml/
           ./utils/ghc-pkg
+          ./utils/ghc-toolchain
+          ./utils/ghc-toolchain/exe
           ./utils/haddock
+          ./utils/haddock/haddock-api
+          ./utils/haddock/haddock-library
           ./utils/hp2ps
           ./utils/hpc
           ./utils/hsc2hs
@@ -61,15 +68,10 @@ constraints: ghc +internal-interpreter +dynamic-system-linke,
              any.pretty installed,
              any.template-haskell installed
 
-allow-newer:
-  ghc-paths:Cabal,
-  *:base,
-  *:ghc-prim,
-  tree-diff:time
 
 benchmarks: False
 tests: False
-allow-boot-library-installs: False
+allow-boot-library-installs: True
 
 -- Workaround for https://github.com/haskell/cabal/issues/7297
 package *


=====================================
compiler/GHC/Driver/Hooks.hs
=====================================
@@ -154,8 +154,6 @@ data Hooks = Hooks
                                  -> IO (CgStream RawCmmGroup a)))
   }
 
-{-# DEPRECATED cmmToRawCmmHook "cmmToRawCmmHook is being deprecated. If you do use it in your project, please raise a GHC issue!" #-}
-
 class HasHooks m where
     getHooks :: m Hooks
 


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -5,9 +5,6 @@
 
 {-# OPTIONS_GHC -fprof-auto-top #-}
 
--- Remove this after cmmToRawCmmHook removal
-{-# OPTIONS_GHC -Wno-deprecations #-}
-
 -------------------------------------------------------------------------------
 --
 -- | Main API for compiling plain Haskell source code.


=====================================
compiler/Setup.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE NamedFieldPuns #-}
 module Main where
 
 import Distribution.Simple
@@ -52,10 +52,12 @@ primopIncls =
     , ("primop-vector-tys-exports.hs-incl", "--primop-vector-tys-exports")
     , ("primop-vector-tycons.hs-incl"     , "--primop-vector-tycons")
     , ("primop-docs.hs-incl"              , "--wired-in-docs")
+    , ("primop-deprecations.hs-incl"      , "--wired-in-deprecations")
     ]
 
 ghcAutogen :: Verbosity -> LocalBuildInfo -> IO ()
-ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
+ghcAutogen verbosity lbi at LocalBuildInfo{pkgDescrFile,withPrograms,componentNameMap}
+  = do
   -- Get compiler/ root directory from the cabal file
   let Just compilerRoot = takeDirectory <$> pkgDescrFile
 
@@ -77,7 +79,7 @@ ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
   -- Call genprimopcode to generate *.hs-incl
   forM_ primopIncls $ \(file,command) -> do
     contents <- readProcess "genprimopcode" [command] primopsStr
-    rewriteFileEx verbosity (buildDir  file) contents
+    rewriteFileEx verbosity (buildDir lbi  file) contents
 
   -- Write GHC.Platform.Constants
   let platformConstantsPath = autogenPackageModulesDir lbi  "GHC/Platform/Constants.hs"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -50,7 +50,7 @@ extra-source-files:
 
 
 custom-setup
-    setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.10, directory, process, filepath, containers
+    setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.14, directory, process, filepath, containers
 
 Flag internal-interpreter
     Description: Build with internal interpreter support.


=====================================
libraries/base/changelog.md
=====================================
@@ -37,6 +37,7 @@
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
   * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
+  * Make `Debug.Trace.{traceEventIO,traceMarkerIO}` faster when tracing is disabled. See [CLC proposal #291](https://github.com/haskell/core-libraries-committee/issues/291).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -253,6 +253,7 @@ Library
         GHC.Internal.Records
         GHC.Internal.ResponseFile
         GHC.Internal.RTS.Flags
+        GHC.Internal.RTS.Flags.Test
         GHC.Internal.ST
         GHC.Internal.Stack.CloneStack
         GHC.Internal.StaticPtr


=====================================
libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE Unsafe #-}
+{-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE UnboxedTuples #-}
@@ -54,6 +55,11 @@ import GHC.Internal.Ptr
 import GHC.Internal.Show
 import GHC.Internal.Stack
 import GHC.Internal.Data.List (null, partition)
+import GHC.Internal.RTS.Flags.Test
+
+-- | 'userEventTracingEnabled' is True if event logging for user events (@+RTS -l@) is enabled.
+userEventTracingEnabled :: IO Bool
+userEventTracingEnabled = getUserEventTracingEnabled
 
 -- | The 'traceIO' function outputs the trace message from the IO monad.
 -- This sequences the output with respect to other IO actions.
@@ -239,8 +245,8 @@ traceStack str expr = unsafePerformIO $ do
 
 {-# NOINLINE traceEvent #-}
 -- | The 'traceEvent' function behaves like 'trace' with the difference that
--- the message is emitted to the eventlog, if eventlog profiling is available
--- and enabled at runtime.
+-- the message is emitted to the eventlog, if eventlog tracing is available
+-- and user event tracing is enabled at runtime.
 --
 -- It is suitable for use in pure code. In an IO context use 'traceEventIO'
 -- instead.
@@ -256,16 +262,19 @@ traceEvent msg expr = unsafeDupablePerformIO $ do
     return expr
 
 -- | The 'traceEventIO' function emits a message to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
 --
 -- Compared to 'traceEvent', 'traceEventIO' sequences the event with respect to
 -- other IO actions.
 --
 -- @since base-4.5.0.0
 traceEventIO :: String -> IO ()
-traceEventIO msg =
-  Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
-    case traceEvent# p s of s' -> (# s', () #)
+{-# INLINE traceEventIO #-}
+traceEventIO msg = do
+  enabled <- userEventTracingEnabled
+  when enabled $
+    Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+      case traceEvent# p s of s' -> (# s', () #)
 
 -- | Like 'traceEvent', but emits the result of calling a function on its
 -- argument.
@@ -276,7 +285,7 @@ traceEventWith f a = traceEvent (f a) a
 
 {-# NOINLINE traceMarker #-}
 -- | The 'traceMarker' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime. The @String@ is the name of
+-- tracing is available and enabled at runtime. The @String@ is the name of
 -- the marker. The name is just used in the profiling tools to help you keep
 -- clear which marker is which.
 --
@@ -294,16 +303,19 @@ traceMarker msg expr = unsafeDupablePerformIO $ do
     return expr
 
 -- | The 'traceMarkerIO' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
 --
 -- Compared to 'traceMarker', 'traceMarkerIO' sequences the event with respect to
 -- other IO actions.
 --
 -- @since base-4.7.0.0
 traceMarkerIO :: String -> IO ()
-traceMarkerIO msg =
-  Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
-    case traceMarker# p s of s' -> (# s', () #)
+{-# INLINE traceMarkerIO #-}
+traceMarkerIO msg = do
+  enabled <- userEventTracingEnabled
+  when enabled $
+    Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+      case traceMarker# p s of s' -> (# s', () #)
 
 -- | Immediately flush the event log, if enabled.
 --


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -613,6 +613,10 @@ getProfFlags = do
 
 getTraceFlags :: IO TraceFlags
 getTraceFlags = do
+#if defined(javascript_HOST_ARCH)
+  -- The JS backend does not currently have trace flags
+  pure (TraceFlags TraceNone False False False False False False False)
+#else
   let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
   TraceFlags <$> (toEnum . fromIntegral
                    <$> (#{peek TRACE_FLAGS, tracing} ptr :: IO CInt))
@@ -630,6 +634,7 @@ getTraceFlags = do
                    (#{peek TRACE_FLAGS, sparks_full} ptr :: IO CBool))
              <*> (toBool <$>
                    (#{peek TRACE_FLAGS, user} ptr :: IO CBool))
+#endif
 
 getTickyFlags :: IO TickyFlags
 getTickyFlags = do


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-- | Module with fewer dependencies than GHC.Internal.RTS.Flags
+-- that allows to quickly test if some flag is set.
+module GHC.Internal.RTS.Flags.Test
+  ( getUserEventTracingEnabled
+  )
+where
+
+import GHC.Internal.Base
+
+#if !defined(javascript_HOST_ARCH)
+
+import GHC.Internal.Ptr
+import GHC.Internal.Foreign.C.Types
+import GHC.Internal.Foreign.Marshal.Utils
+import GHC.Internal.Foreign.Storable
+import GHC.Internal.Data.Functor ((<$>))
+
+#include "Rts.h"
+#include "rts/Flags.h"
+
+foreign import ccall "&RtsFlags" rtsFlagsPtr :: Ptr ()
+#endif
+
+-- | Specialized version of 'getTraceFlags' for just checking if user
+-- event tracing is enabled.
+getUserEventTracingEnabled :: IO Bool
+getUserEventTracingEnabled = do
+#if defined(javascript_HOST_ARCH)
+  -- The JS backend does not currently have trace flags
+  pure False
+#else
+  let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
+  toBool <$> (#{peek TRACE_FLAGS, user} ptr :: IO CBool)
+#endif


=====================================
libraries/transformers
=====================================
@@ -1 +1 @@
-Subproject commit ba3503905dec072acc6515323c884706efd4dbb4
+Subproject commit b3eaaae9b6c986aaac84f0f05a137eef65ccfab3


=====================================
rts/Interpreter.c
=====================================
@@ -157,11 +157,11 @@ tag functions as tag inference currently doesn't rely on those being properly ta
    cap->r.rRet = (retcode);                             \
    return cap;
 
-#define Sp_plusB(n)  ((void *)(((StgWord8*)Sp) + (n)))
-#define Sp_minusB(n) ((void *)(((StgWord8*)Sp) - (n)))
+#define Sp_plusB(n)  ((void *)((StgWord8*)Sp + (ptrdiff_t)(n)))
+#define Sp_minusB(n) ((void *)((StgWord8*)Sp - (ptrdiff_t)(n)))
 
-#define Sp_plusW(n)  (Sp_plusB((n) * sizeof(W_)))
-#define Sp_minusW(n) (Sp_minusB((n) * sizeof(W_)))
+#define Sp_plusW(n)  (Sp_plusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
+#define Sp_minusW(n) (Sp_minusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
 
 #define Sp_addB(n)   (Sp = Sp_plusB(n))
 #define Sp_subB(n)   (Sp = Sp_minusB(n))


=====================================
testsuite/tests/perf/should_run/T17949.hs
=====================================
@@ -0,0 +1,7 @@
+module Main where
+
+import Debug.Trace
+
+main :: IO ()
+main = do
+  traceEventIO (show [0..1234567])


=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -414,3 +414,4 @@ test('T21839r',
 test('T18964', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O'])
 test('T23021', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])
 test('T25055', [collect_stats('bytes allocated', 2), only_ways(['normal'])], compile_and_run, ['-O2'])
+test('T17949', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])


=====================================
testsuite/tests/profiling/should_run/callstack002.stderr
=====================================
@@ -1,6 +1,6 @@
 f: 42
 CallStack (from -prof):
-  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
   Main.f (callstack002.hs:10:7-43)
   Main.map.go (callstack002.hs:15:21-23)
   Main.map.go (callstack002.hs:15:21-34)
@@ -9,7 +9,7 @@ CallStack (from -prof):
   Main.CAF ()
 f: 43
 CallStack (from -prof):
-  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
   Main.f (callstack002.hs:10:7-43)
   Main.map.go (callstack002.hs:15:21-23)
   Main.map.go (callstack002.hs:15:21-34)


=====================================
testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
=====================================


=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -109,3 +109,10 @@ test('TcPlugin_CtId'
     , [ 'TcPlugin_CtId.hs'
       , '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
     )
+
+test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
+     [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
+      '-dynamic' if have_dynamic() else ''])
+test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
+     [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
+      '-dynamic' if have_dynamic() else ''])


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -500,9 +500,6 @@ test('T10592', normal, compile, [''])
 test('T11305', normal, compile, [''])
 test('T11254', normal, compile, [''])
 test('T11379', normal, compile, [''])
-test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
-     [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
-      '-dynamic' if have_dynamic() else ''])
 test('T11480', normal, compile, [''])
 test('RebindHR', normal, compile, [''])
 test('RebindNegate', normal, compile, [''])
@@ -568,9 +565,6 @@ test('T11723', normal, compile, [''])
 test('T12987', normal, compile, [''])
 test('T11736', normal, compile, [''])
 test('T13248', expect_broken(13248), compile, [''])
-test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
-     [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
-      '-dynamic' if have_dynamic() else ''])
 test('T12923_1', normal, compile, [''])
 test('T21208', normal, compile, [''])
 test('T12923_2', normal, compile, [''])


=====================================
utils/haddock/haddock.cabal
=====================================
@@ -43,7 +43,6 @@ extra-source-files:
   doc/README.md
   doc/*.rst
   doc/conf.py
-  haddock-api/src/haddock.sh
   html-test/src/*.hs
   html-test/ref/*.html
   hypsrc-test/src/*.hs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6dbcd8718a8d1ad37b06806b7c14d3e90445464...147f8f0176db0d777955648dd5fc6ecd32e82576

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6dbcd8718a8d1ad37b06806b7c14d3e90445464...147f8f0176db0d777955648dd5fc6ecd32e82576
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:44:21 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:44:21 -0400
Subject: [Git][ghc/ghc] Deleted tag ghc-9.8.3-release
Message-ID: <67129e75ce1fe_1895e965a61c81351@gitlab.mail>



Ben Gamari deleted tag ghc-9.8.3-release at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 17:44:54 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 13:44:54 -0400
Subject: [Git][ghc/ghc][ghc-9.8] Bump base version to 4.19.2.0
Message-ID: <67129e961f263_1895e9666cb4815d8@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
24e765b4 by Ben Gamari at 2024-10-18T13:39:14-04:00
Bump base version to 4.19.2.0

- - - - -


7 changed files:

- docs/users_guide/9.8.3-notes.rst
- libraries/base/base.cabal
- libraries/base/changelog.md
- testsuite/tests/backpack/should_fail/bkpfail16.stderr
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- testsuite/tests/gadt/T19847a.stderr


Changes:

=====================================
docs/users_guide/9.8.3-notes.rst
=====================================
@@ -50,6 +50,7 @@ JavaScript backend
 ``base``
 --------
 
+- Bump version to 4.19.2.0
 - Fix spurious closing of file descriptors after ``fork`` on platforms using the KQueue event manager backend (:ghc-ticket:`24672`)
 
 Haddock


=====================================
libraries/base/base.cabal
=====================================
@@ -1,6 +1,6 @@
 cabal-version:  3.0
 name:           base
-version:        4.19.1.0
+version:        4.19.2.0
 -- NOTE: Don't forget to update ./changelog.md
 
 license:        BSD-3-Clause


=====================================
libraries/base/changelog.md
=====================================
@@ -1,5 +1,10 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
+## 4.19.2.0 *October 2024*
+  * Shipped with GHC 9.8.3
+  * Improve documentation of various functions
+  * Fix interaction between `fork` and the `kqueue`-based IO manager ([#24672](https://gitlab.haskell.org/ghc/ghc/-/issues/24672))
+
 ## 4.19.1.0 *October 2023*
   * Shipped with GHC 9.8.2
   * Improve documentation of various functions


=====================================
testsuite/tests/backpack/should_fail/bkpfail16.stderr
=====================================
@@ -1,11 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Data.Bool]
-    Instantiating p[ShouldFail=base-4.18.0.0:Data.Bool]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail16.out\p\p-1OqLaT7dAn947wScQQKCw5\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.Bool]
+    Instantiating p[ShouldFail=base-4.19.1.0:Data.Bool]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail16.out/p/p-IWIH695NuFKHfA9JCzN8tU/ShouldFail.o )
 
-bkpfail16.out\p\p-1OqLaT7dAn947wScQQKCw5\..\ShouldFail.hi:1:1: error: [GHC-93011]
-    • ‘Booly’ is exported by the hsig file, but not exported by the implementing module ‘Data.Bool’
-    • While checking that ‘Data.Bool’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.Bool]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Data.Bool differs from name found in the interface file base:Data.Bool (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,18 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Prelude]
-    Instantiating p[ShouldFail=base-4.18.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail17.out\p\p-2W6J7O3LvroH97zGxbPEGF\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Prelude]
+    Instantiating p[ShouldFail=base-4.19.1.0:Prelude]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9af3lmxJNZa50ZueXSR02Y/ShouldFail.o )
 
-: error: [GHC-15843]
-    • Type constructor ‘Either’ has conflicting definitions in the module
-      and its hsig file.
-      Main module: type Either :: * -> * -> *
-                   data Either a b = Left a | Right b
-        Hsig file: type role Either representational phantom phantom
-                   type Either :: * -> * -> * -> *
-                   data Either a b c = Left a
-      The types have different kinds.
-    • While checking that ‘Prelude’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Prelude]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Prelude differs from name found in the interface file base:Prelude (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,12 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Data.STRef]
-    Instantiating p[ShouldFail=base-4.18.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail19.out\p\p-CfyUIAu1JTRCDuXEyGszXN\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.STRef]
+    Instantiating p[ShouldFail=base-4.19.1.0:Data.STRef]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Ak3HDozWrn3BPHIdYYNht5/ShouldFail.o )
 
-: error: [GHC-12424]
-    • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
-      but the implementing module exports a different identifier ‘GHC.STRef.newSTRef’
-    • While checking that ‘Data.STRef’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.STRef]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Data.STRef differs from name found in the interface file base:Data.STRef (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/gadt/T19847a.stderr
=====================================
@@ -9,4 +9,4 @@ DATA CONSTRUCTORS
          (x ~ y, c ~ [x], Ord x) =>
          x -> y -> T (x, y) b c
 Dependent modules: []
-Dependent packages: [base-4.19.1.0]
+Dependent packages: [base-4.19.2.0]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24e765b4be020c6c3c9641d7c9a2d3da347d45a6

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 18 20:10:31 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Fri, 18 Oct 2024 16:10:31 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] make caller wrap the pop err ctxt
Message-ID: <6712c0b716c92_3ce97cfcdc819425@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
d13b6338 by Apoorv Ingle at 2024-10-18T15:09:38-05:00
make caller wrap the pop err ctxt

- - - - -


3 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -586,22 +586,6 @@ mkExpandedPatRn
 mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav
                                                          , xrn_expanded = eExpr })
 
--- | Build an expression using the extension constructor `XExpr`,
---   and the two components of the expansion: original do stmt and
---   expanded expression and associate it with a provided location
-mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
-  -> HsDoFlavour          -- ^ the flavour of the statement
-  -> HsExpr GhcRn         -- ^ expanded expression
-  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
-  = L loc $ mkExpandedStmt oStmt flav eExpr
-
 data XXExprGhcTc
   = WrapExpr        -- Type and evidence application and abstractions
       HsWrapper (HsExpr GhcTc)


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -2258,7 +2258,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
              -- Need 'pureAName' and not 'returnMName' here, so that it requires
              -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed).
              (pure_name, _) <- lookupQualifiedDoName (HsDoStmt ctxt) pureAName
-             let expr = noLocA (HsApp noExtField (noLocA ret) tup)
+             let expr = noLocA (genHsApps pure_name [tup])
              return (expr, emptyFVs)
      return ( ApplicativeArgMany
               { xarg_app_arg_many = noExtField


=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -47,7 +47,7 @@ import Data.List ((\\))
 *                                                                      *
 ************************************************************************
 -}
-
+-- TODO: make caller add the pop error context
 -- | Expand the `do`-statments into expressions right after renaming
 --   so that they can be typechecked.
 --   See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary
@@ -63,8 +63,6 @@ expand_do_stmts _ ListComp _ =
   pprPanic "expand_do_stmts: impossible happened. ListComp" empty
         -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
-
 expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) =
   pprPanic "expand_do_stmts: TransStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
@@ -73,13 +71,15 @@ expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) =
   pprPanic "expand_do_stmts: ParStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
+expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
+
+expand_do_stmts _addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (5) below
 -- last statement of a list comprehension, needs to explicitly return it
 -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
    | NoSyntaxExprRn <- ret_expr
    -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
-   = return $ mkExpandedStmtAt addPop loc stmt flav body
+   = return $ mkExpandedStmtAt False loc stmt flav body
 
    | SyntaxExprRn ret <- ret_expr
    --
@@ -87,18 +87,18 @@ expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_exp
    --               return e  ~~> return e
    -- to make T18324 work
    = do let expansion = genHsApp ret (L body_loc body)
-        return $ mkExpandedStmtAt addPop loc stmt flav expansion
+        return $ mkExpandedStmtAt False loc stmt flav expansion
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
+expand_do_stmts _addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
 --                      stmts ~~> stmts'
 --    ------------------------------------------------
 --       let x = e ; stmts ~~> let x = e in stmts'
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
-     let expansion = genHsLet bs expand_stmts
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+  do expand_stmts <- expand_do_stmts False doFlavour lstmts
+     let expansion = genPopErrCtxtExpr (wrapGenSpan $ genHsLet bs expand_stmts)
+     return $ mkExpandedStmtAt False loc stmt doFlavour (unLoc expansion)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
+expand_do_stmts _addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
   | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn
   , fail_op              <- xbsrn_failOp xbsrn
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (2) below
@@ -107,27 +107,27 @@ expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
 --                                   _   -> fail "Pattern match failure .."
 --    -------------------------------------------------------
 --       pat <- e ; stmts   ~~> (>>=) e f
-  = do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  = do expand_stmts <- genPopErrCtxtExpr <$> expand_do_stmts False doFlavour lstmts
        failable_expr <- mk_failable_expr False doFlavour pat expand_stmts fail_op
        let expansion = genHsExpApps bind_op  -- (>>=)
                        [ e
                        , failable_expr ]
-       return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+       return $ mkExpandedStmtAt False loc stmt doFlavour expansion
 
   | otherwise
   = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr  stmt)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
+expand_do_stmts _addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
 -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (1) below
 --              stmts ~~> stmts'
 --    ----------------------------------------------
 --      e ; stmts ~~> (>>) e stmts'
-  do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts_expr <- expand_do_stmts False doFlavour lstmts
      let expansion = genHsExpApps then_op  -- (>>)
-                                  [ e
-                                  , expand_stmts_expr ]
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+                     [ e
+                     , wrapGenSpan (mkPopErrCtxtExpr expand_stmts_expr) ]
+     return $ mkExpandedStmtAt False loc stmt doFlavour expansion
 
 expand_do_stmts _ doFlavour
        ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts
@@ -149,7 +149,7 @@ expand_do_stmts _ doFlavour
 --                                           -> do { rec_stmts
 --                                                 ; return (local_only_ids ++ later_ids) } ))
 --                              (\ [ local_only_ids ++ later_ids ] -> stmts')
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts <- expand_do_stmts False doFlavour lstmts
      -- NB: No need to wrap the expansion with an ExpandedStmt
      -- as we want to flatten the rec block statements into its parent do block anyway
      return $ mkHsApps (wrapGenSpan bind_fun)                                           -- (>>=)
@@ -177,7 +177,7 @@ expand_do_stmts _ doFlavour
                              -- NB: LazyPat because we do not want to eagerly evaluate the pattern
                              -- and potentially loop forever
 
-expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
+expand_do_stmts _addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
 -- See Note [Applicative BodyStmt]
 --
 --                  stmts ~~> stmts'
@@ -216,7 +216,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
             { xarg_app_arg_one = mb_fail_op
             , app_arg_pattern = pat
             , arg_expr        = (L rhs_loc rhs) }) =
-      do let xx_expr = mkExpandedStmtAt addPop (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
+      do let xx_expr = mkExpandedStmtAt False (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
          traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr])
          return ((pat, mb_fail_op)
                 , xx_expr)
@@ -225,13 +225,13 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
                                , final_expr = ret@(L ret_loc _)
                                , bv_pattern = pat
                                , stmt_context = ctxt }) =
-      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts addPop ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
-         ; traceTc "do_arg" (text "ManyArg" <+> ppr addPop <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
+      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts False ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
+         ; traceTc "do_arg" (text "ManyArg" <+> ppr False <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
          ; return ((pat, Nothing)
                   , xx_expr) }
 
     match_args :: (LPat GhcRn, FailOperator GhcRn)  -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn)
-    match_args (pat, fail_op) body = mk_failable_expr addPop doFlavour pat body fail_op
+    match_args (pat, fail_op) body = mk_failable_expr False doFlavour pat body fail_op
 
     mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn
     mk_apps l_expr (op, r_expr) =
@@ -243,7 +243,7 @@ expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (p
 
 -- checks the pattern `pat` for irrefutability which decides if we need to wrap it with a fail block
 mk_failable_expr :: Bool -> HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
-mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
+mk_failable_expr _addPop doFlav lpat@(L loc pat) expr@(L _exprloc _) fail_op =
   do { is_strict <- xoptM LangExt.Strict
      ; hscEnv <- getTopEnv
      ; rdrEnv <- getGlobalRdrEnv
@@ -252,13 +252,11 @@ mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
      ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat
                                         , text "isIrrefutable:" <+> ppr irrf_pat
                                         ])
-     ; let xexpr | addPop = mkPopErrCtxtExprAt exprloc expr
-                 | otherwise = expr
      ; if irrf_pat -- don't wrap with fail block if
                    -- the pattern is irrefutable
        then case pat of
-              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] xexpr
-              _ -> return $ genHsLamDoExp doFlav [lpat] xexpr
+              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr
+              _ -> return $ genHsLamDoExp doFlav [lpat] expr
 
        else L loc <$> mk_fail_block doFlav lpat expr fail_op
      }
@@ -343,10 +341,10 @@ They capture the essence of statement expansions as implemented in `expand_do_st
 
           (2) DO【 p <- e; ss 】 = if p is irrefutable
                                    then ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\ p -> DO【 ss 】))
+                                          (>>=) s ((\ p -> ‹PopExprCtxt› DO【 ss 】))
                                    else ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\case p -> DO【 ss 】
-                                                                       _ -> fail "pattern p failure"))
+                                          (>>=) s ((\case p -> ‹PopExprCtxt› DO【 ss 】
+                                                          _ -> fail "pattern p failure"))
 
           (3) DO【 let x = e; ss 】
                                  = ‹ExpansionStmt (let x = e)› (let x = e in (‹PopErrCtxt›DO【 ss 】))
@@ -573,7 +571,6 @@ mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
 mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
 mkPopErrCtxtExprAt _loc a = wrapGenSpan $ mkPopErrCtxtExpr a
 
-
 genPopErrCtxtExpr :: LHsExpr GhcRn -> LHsExpr GhcRn
 genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 01:51:24 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Fri, 18 Oct 2024 21:51:24 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/expose-base
Message-ID: <6713109cd448c_1920cc44b8d0326ee@gitlab.mail>



Ben Gamari pushed new branch wip/expose-base at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/expose-base
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 12:48:29 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sat, 19 Oct 2024 08:48:29 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] 11 commits: Bump version to 9.8.3
Message-ID: <6713aa9d294a_d0cd452bc3c774e2@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
8f7adb8a by Ben Gamari at 2024-10-15T08:58:56-04:00
Bump version to 9.8.3

- - - - -
c3dedd00 by Ben Gamari at 2024-10-15T12:51:53-04:00
Bump semaphore-compat submodule back to 1.0.0

This only drops a one-sentence change in Haddocks.

- - - - -
4a9f4d76 by Ben Gamari at 2024-10-15T13:28:36-04:00
docs: Drop Included Libraries from old release notes

- - - - -
6cc77976 by Ben Gamari at 2024-10-15T13:29:18-04:00
Update autoconf scripts

Scripts taken from autoconf 00b15927496058d23e6258a28d8996f87cf1f191

- - - - -
c332cb09 by Ben Gamari at 2024-10-15T13:32:31-04:00
gitlab-ci: Update bootstrap_matrix

- - - - -
bb8f9dc0 by Ben Gamari at 2024-10-15T13:46:09-04:00
Revert "finder: Add `IsBootInterface` to finder cache keys"

There are objections raised on the MR (!13237) and the interface change
makes me rather uncomfortable.

This reverts commit fb82ee70d9f7fe43cd1cd2aa7263e9aef6cf9238.

- - - - -
036044df by Ben Gamari at 2024-10-15T17:30:09-04:00
Revert "gitlab-ci: Update bootstrap_matrix"

This reverts commit c332cb09f1bc767536bd2afd12c9ccbcf0a34289.

- - - - -
e9aabcf5 by Matthew Pickering at 2024-10-17T13:10:09-04:00
bindist: Use complete relative paths when cding to directories

If a user has configured CDPATH on their system then `cd lib` may change
into an unexpected directory during the installation process.

If you write `cd ./lib` then it will not consult `CDPATH` to determine
what you mean.

I have added a check on ghcup-ci to verify that the bindist installation
works in this situation.

Fixes #24951

(cherry picked from commit 383c01a8928779920b4edea2f9d886ff303b8bd3)

- - - - -
24e765b4 by Ben Gamari at 2024-10-18T13:39:14-04:00
Bump base version to 4.19.2.0

- - - - -
f41b0bda by Brandon Chinn at 2024-10-19T08:13:42-04:00
Simplify regexes with raw strings

(cherry picked from commit c91946f994ad8b734b09cf3023f1fc9671a7475a)

- - - - -
72e04175 by Ben Gamari at 2024-10-19T08:41:21-04:00
testsuite: More aggressive version number normalization

Component names can sometimes have hashes.

- - - - -


27 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Types.hs
- config.guess
- config.sub
- configure.ac
- docs/users_guide/9.8.1-notes.rst
- docs/users_guide/9.8.2-notes.rst
- docs/users_guide/9.8.3-notes.rst
- hadrian/bindist/Makefile
- libraries/base/base.cabal
- libraries/base/changelog.md
- libraries/semaphore-compat
- testsuite/driver/testlib.py
- testsuite/tests/backpack/should_fail/bkpfail16.stderr
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr
- − testsuite/tests/driver/boot-target/A.hs
- − testsuite/tests/driver/boot-target/A.hs-boot
- − testsuite/tests/driver/boot-target/B.hs
- − testsuite/tests/driver/boot-target/Makefile
- − testsuite/tests/driver/boot-target/all.T
- testsuite/tests/gadt/T19847a.stderr


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -893,7 +893,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2055,43 +2055,25 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = src_fn
-
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+
+        -- Make a ModLocation for this file
+        let location = mkHomeModLocation fopts pi_mod_name src_fn
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
             , nms_src_hash = src_hash
-            , nms_hsc_src = hsc_src
+            , nms_is_boot = NotBoot
+            , nms_hsc_src =
+                if isHaskellSigFilename src_fn
+                   then HsigFile
+                   else HsSrcFile
             , nms_location = location
             , nms_mod = mod
             , nms_preimps = preimps
@@ -2119,10 +2101,9 @@ checkSummaryHash
            -- Also, only add to finder cache for non-boot modules as the finder cache
            -- makes sure to add a boot suffix for boot files.
            _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
+              let fc        = hsc_FC hsc_env
               case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
+                HsSrcFile -> addModuleToFinder fc (ms_mod old_summary) location
                 _ -> return ()
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
@@ -2260,6 +2241,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
             , nms_src_hash = src_hash
+            , nms_is_boot = is_boot
             , nms_hsc_src = hsc_src
             , nms_location = location
             , nms_mod = mod
@@ -2272,6 +2254,7 @@ data MakeNewModSummary
   = MakeNewModSummary
       { nms_src_fn :: FilePath
       , nms_src_hash :: Fingerprint
+      , nms_is_boot :: IsBootInterface
       , nms_hsc_src :: HscSource
       , nms_location :: ModLocation
       , nms_mod :: Module


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -743,7 +743,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location
 
   -- Make the ModSummary to hand to hscMain
   let


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -89,7 +89,7 @@ type BaseName = String  -- Basename of file
 
 
 initFinderCache :: IO FinderCache
-initFinderCache = FinderCache <$> newIORef emptyInstalledModuleWithIsBootEnv
+initFinderCache = FinderCache <$> newIORef emptyInstalledModuleEnv
                               <*> newIORef M.empty
 
 -- remove all the home modules from the cache; package modules are
@@ -97,23 +97,23 @@ initFinderCache = FinderCache <$> newIORef emptyInstalledModuleWithIsBootEnv
 -- cache
 flushFinderCaches :: FinderCache -> UnitEnv -> IO ()
 flushFinderCaches (FinderCache ref file_ref) ue = do
-  atomicModifyIORef' ref $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+  atomicModifyIORef' ref $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
   atomicModifyIORef' file_ref $ \_ -> (M.empty, ())
  where
-  is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+  is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-addToFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+addToFinderCache :: FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
 addToFinderCache (FinderCache ref _) key val =
-  atomicModifyIORef' ref $ \c -> (extendInstalledModuleWithIsBootEnv c key val, ())
+  atomicModifyIORef' ref $ \c -> (extendInstalledModuleEnv c key val, ())
 
-removeFromFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> IO ()
+removeFromFinderCache :: FinderCache -> InstalledModule -> IO ()
 removeFromFinderCache (FinderCache ref _) key =
-  atomicModifyIORef' ref $ \c -> (delInstalledModuleWithIsBootEnv c key, ())
+  atomicModifyIORef' ref $ \c -> (delInstalledModuleEnv c key, ())
 
-lookupFinderCache :: FinderCache -> InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+lookupFinderCache :: FinderCache -> InstalledModule -> IO (Maybe InstalledFindResult)
 lookupFinderCache (FinderCache ref _) key = do
    c <- readIORef ref
-   return $! lookupInstalledModuleWithIsBootEnv c key
+   return $! lookupInstalledModuleEnv c key
 
 lookupFileCache :: FinderCache -> FilePath -> IO Fingerprint
 lookupFileCache (FinderCache _ ref) key = do
@@ -262,7 +262,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -319,7 +319,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -329,23 +329,22 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  let imod = toUnitId <$> mod
+  addToFinderCache fc imod (InstalledFound loc imod)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+  let mod = mkHomeInstalledModule home_unit mod_name
+  addToFinderCache fc mod (InstalledFound loc mod)
+  return (mkHomeModule home_unit mod_name)
 
-uncacheModule :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> IO ()
+uncacheModule :: FinderCache -> HomeUnit -> ModuleName -> IO ()
 uncacheModule fc home_unit mod_name = do
-  let mod = mkHomeInstalledModule home_unit (gwib_mod mod_name)
-  removeFromFinderCache fc (GWIB mod (gwib_isBoot mod_name))
-
+  let mod = mkHomeInstalledModule home_unit mod_name
+  removeFromFinderCache fc mod
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -478,7 +477,7 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -22,7 +22,7 @@ import qualified Data.Set as Set
 -- modules along the search path. On @:load@, we flush the entire
 -- contents of this cache.
 --
-type FinderCacheState = InstalledModuleWithIsBootEnv InstalledFindResult
+type FinderCacheState = InstalledModuleEnv InstalledFindResult
 type FileCacheState   = M.Map FilePath Fingerprint
 data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState)
                                , fcFileCache   :: (IORef FileCacheState)


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -86,8 +86,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -715,8 +713,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -730,6 +726,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}


=====================================
config.guess
=====================================
@@ -1,10 +1,10 @@
 #! /bin/sh
 # Attempt to guess a canonical system name.
-#   Copyright 1992-2022 Free Software Foundation, Inc.
+#   Copyright 1992-2024 Free Software Foundation, Inc.
 
 # shellcheck disable=SC2006,SC2268 # see below for rationale
 
-timestamp='2022-05-25'
+timestamp='2024-07-27'
 
 # This file is free software; you can redistribute it and/or modify it
 # under the terms of the GNU General Public License as published by
@@ -47,7 +47,7 @@ me=`echo "$0" | sed -e 's,.*/,,'`
 usage="\
 Usage: $0 [OPTION]
 
-Output the configuration name of the system \`$me' is run on.
+Output the configuration name of the system '$me' is run on.
 
 Options:
   -h, --help         print this help, then exit
@@ -60,13 +60,13 @@ version="\
 GNU config.guess ($timestamp)
 
 Originally written by Per Bothner.
-Copyright 1992-2022 Free Software Foundation, Inc.
+Copyright 1992-2024 Free Software Foundation, Inc.
 
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE."
 
 help="
-Try \`$me --help' for more information."
+Try '$me --help' for more information."
 
 # Parse command line
 while test $# -gt 0 ; do
@@ -102,8 +102,8 @@ GUESS=
 # temporary files to be created and, as you can see below, it is a
 # headache to deal with in a portable fashion.
 
-# Historically, `CC_FOR_BUILD' used to be named `HOST_CC'. We still
-# use `HOST_CC' if defined, but it is deprecated.
+# Historically, 'CC_FOR_BUILD' used to be named 'HOST_CC'. We still
+# use 'HOST_CC' if defined, but it is deprecated.
 
 # Portable tmp directory creation inspired by the Autoconf team.
 
@@ -123,7 +123,7 @@ set_cc_for_build() {
     dummy=$tmp/dummy
     case ${CC_FOR_BUILD-},${HOST_CC-},${CC-} in
 	,,)    echo "int x;" > "$dummy.c"
-	       for driver in cc gcc c89 c99 ; do
+	       for driver in cc gcc c17 c99 c89 ; do
 		   if ($driver -c -o "$dummy.o" "$dummy.c") >/dev/null 2>&1 ; then
 		       CC_FOR_BUILD=$driver
 		       break
@@ -155,6 +155,9 @@ Linux|GNU|GNU/*)
 
 	set_cc_for_build
 	cat <<-EOF > "$dummy.c"
+	#if defined(__ANDROID__)
+	LIBC=android
+	#else
 	#include 
 	#if defined(__UCLIBC__)
 	LIBC=uclibc
@@ -162,6 +165,8 @@ Linux|GNU|GNU/*)
 	LIBC=dietlibc
 	#elif defined(__GLIBC__)
 	LIBC=gnu
+	#elif defined(__LLVM_LIBC__)
+	LIBC=llvm
 	#else
 	#include 
 	/* First heuristic to detect musl libc.  */
@@ -169,6 +174,7 @@ Linux|GNU|GNU/*)
 	LIBC=musl
 	#endif
 	#endif
+	#endif
 	EOF
 	cc_set_libc=`$CC_FOR_BUILD -E "$dummy.c" 2>/dev/null | grep '^LIBC' | sed 's, ,,g'`
 	eval "$cc_set_libc"
@@ -459,7 +465,7 @@ case $UNAME_MACHINE:$UNAME_SYSTEM:$UNAME_RELEASE:$UNAME_VERSION in
 		UNAME_RELEASE=`uname -v`
 		;;
 	esac
-	# Japanese Language versions have a version number like `4.1.3-JL'.
+	# Japanese Language versions have a version number like '4.1.3-JL'.
 	SUN_REL=`echo "$UNAME_RELEASE" | sed -e 's/-/_/'`
 	GUESS=sparc-sun-sunos$SUN_REL
 	;;
@@ -628,7 +634,8 @@ EOF
 		sed 's/^		//' << EOF > "$dummy.c"
 		#include 
 
-		main()
+		int
+		main ()
 			{
 			if (!__power_pc())
 				exit(1);
@@ -712,7 +719,8 @@ EOF
 		#include 
 		#include 
 
-		int main ()
+		int
+		main ()
 		{
 		#if defined(_SC_KERNEL_BITS)
 		    long bits = sysconf(_SC_KERNEL_BITS);
@@ -904,7 +912,7 @@ EOF
 	fi
 	;;
     *:FreeBSD:*:*)
-	UNAME_PROCESSOR=`/usr/bin/uname -p`
+	UNAME_PROCESSOR=`uname -p`
 	case $UNAME_PROCESSOR in
 	    amd64)
 		UNAME_PROCESSOR=x86_64 ;;
@@ -966,11 +974,37 @@ EOF
 	GNU_REL=`echo "$UNAME_RELEASE" | sed -e 's/[-(].*//'`
 	GUESS=$UNAME_MACHINE-unknown-$GNU_SYS$GNU_REL-$LIBC
 	;;
+    x86_64:[Mm]anagarm:*:*|i?86:[Mm]anagarm:*:*)
+	GUESS="$UNAME_MACHINE-pc-managarm-mlibc"
+	;;
+    *:[Mm]anagarm:*:*)
+	GUESS="$UNAME_MACHINE-unknown-managarm-mlibc"
+	;;
     *:Minix:*:*)
 	GUESS=$UNAME_MACHINE-unknown-minix
 	;;
     aarch64:Linux:*:*)
-	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
+	set_cc_for_build
+	CPU=$UNAME_MACHINE
+	LIBCABI=$LIBC
+	if test "$CC_FOR_BUILD" != no_compiler_found; then
+	    ABI=64
+	    sed 's/^	    //' << EOF > "$dummy.c"
+	    #ifdef __ARM_EABI__
+	    #ifdef __ARM_PCS_VFP
+	    ABI=eabihf
+	    #else
+	    ABI=eabi
+	    #endif
+	    #endif
+EOF
+	    cc_set_abi=`$CC_FOR_BUILD -E "$dummy.c" 2>/dev/null | grep '^ABI' | sed 's, ,,g'`
+	    eval "$cc_set_abi"
+	    case $ABI in
+		eabi | eabihf) CPU=armv8l; LIBCABI=$LIBC$ABI ;;
+	    esac
+	fi
+	GUESS=$CPU-unknown-linux-$LIBCABI
 	;;
     aarch64_be:Linux:*:*)
 	UNAME_MACHINE=aarch64_be
@@ -1036,7 +1070,16 @@ EOF
     k1om:Linux:*:*)
 	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
 	;;
-    loongarch32:Linux:*:* | loongarch64:Linux:*:* | loongarchx32:Linux:*:*)
+    kvx:Linux:*:*)
+	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
+	;;
+    kvx:cos:*:*)
+	GUESS=$UNAME_MACHINE-unknown-cos
+	;;
+    kvx:mbr:*:*)
+	GUESS=$UNAME_MACHINE-unknown-mbr
+	;;
+    loongarch32:Linux:*:* | loongarch64:Linux:*:*)
 	GUESS=$UNAME_MACHINE-unknown-linux-$LIBC
 	;;
     m32r*:Linux:*:*)
@@ -1191,7 +1234,7 @@ EOF
 	GUESS=$UNAME_MACHINE-pc-sysv4.2uw$UNAME_VERSION
 	;;
     i*86:OS/2:*:*)
-	# If we were able to find `uname', then EMX Unix compatibility
+	# If we were able to find 'uname', then EMX Unix compatibility
 	# is probably installed.
 	GUESS=$UNAME_MACHINE-pc-os2-emx
 	;;
@@ -1332,7 +1375,7 @@ EOF
 		GUESS=ns32k-sni-sysv
 	fi
 	;;
-    PENTIUM:*:4.0*:*)	# Unisys `ClearPath HMP IX 4000' SVR4/MP effort
+    PENTIUM:*:4.0*:*)	# Unisys 'ClearPath HMP IX 4000' SVR4/MP effort
 			# says 
 	GUESS=i586-unisys-sysv4
 	;;
@@ -1554,6 +1597,9 @@ EOF
     *:Unleashed:*:*)
 	GUESS=$UNAME_MACHINE-unknown-unleashed$UNAME_RELEASE
 	;;
+    *:Ironclad:*:*)
+	GUESS=$UNAME_MACHINE-unknown-ironclad
+	;;
 esac
 
 # Do we have a guess based on uname results?
@@ -1577,6 +1623,7 @@ cat > "$dummy.c" <."
 version="\
 GNU config.sub ($timestamp)
 
-Copyright 1992-2022 Free Software Foundation, Inc.
+Copyright 1992-2024 Free Software Foundation, Inc.
 
 This is free software; see the source for copying conditions.  There is NO
 warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE."
 
 help="
-Try \`$me --help' for more information."
+Try '$me --help' for more information."
 
 # Parse command line
 while test $# -gt 0 ; do
@@ -120,7 +120,6 @@ case $# in
 esac
 
 # Split fields of configuration type
-# shellcheck disable=SC2162
 saved_IFS=$IFS
 IFS="-" read field1 field2 field3 field4 <&2
+		echo "Invalid configuration '$1': more than four components" >&2
 		exit 1
 		;;
 	*-*-*-*)
@@ -142,10 +141,21 @@ case $1 in
 		# parts
 		maybe_os=$field2-$field3
 		case $maybe_os in
-			nto-qnx* | linux-* | uclinux-uclibc* \
-			| uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \
-			| netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \
-			| storm-chaos* | os2-emx* | rtmk-nova*)
+			  cloudabi*-eabi* \
+			| kfreebsd*-gnu* \
+			| knetbsd*-gnu* \
+			| kopensolaris*-gnu* \
+			| linux-* \
+			| managarm-* \
+			| netbsd*-eabi* \
+			| netbsd*-gnu* \
+			| nto-qnx* \
+			| os2-emx* \
+			| rtmk-nova* \
+			| storm-chaos* \
+			| uclinux-gnu* \
+			| uclinux-uclibc* \
+			| windows-* )
 				basic_machine=$field1
 				basic_os=$maybe_os
 				;;
@@ -160,8 +170,12 @@ case $1 in
 		esac
 		;;
 	*-*)
-		# A lone config we happen to match not fitting any pattern
 		case $field1-$field2 in
+			# Shorthands that happen to contain a single dash
+			convex-c[12] | convex-c3[248])
+				basic_machine=$field2-convex
+				basic_os=
+				;;
 			decstation-3100)
 				basic_machine=mips-dec
 				basic_os=
@@ -169,28 +183,88 @@ case $1 in
 			*-*)
 				# Second component is usually, but not always the OS
 				case $field2 in
-					# Prevent following clause from handling this valid os
+					# Do not treat sunos as a manufacturer
 					sun*os*)
 						basic_machine=$field1
 						basic_os=$field2
 						;;
-					zephyr*)
-						basic_machine=$field1-unknown
-						basic_os=$field2
-						;;
 					# Manufacturers
-					dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \
-					| att* | 7300* | 3300* | delta* | motorola* | sun[234]* \
-					| unicom* | ibm* | next | hp | isi* | apollo | altos* \
-					| convergent* | ncr* | news | 32* | 3600* | 3100* \
-					| hitachi* | c[123]* | convex* | sun | crds | omron* | dg \
-					| ultra | tti* | harris | dolphin | highlevel | gould \
-					| cbm | ns | masscomp | apple | axis | knuth | cray \
-					| microblaze* | sim | cisco \
-					| oki | wec | wrs | winbond)
+					  3100* \
+					| 32* \
+					| 3300* \
+					| 3600* \
+					| 7300* \
+					| acorn \
+					| altos* \
+					| apollo \
+					| apple \
+					| atari \
+					| att* \
+					| axis \
+					| be \
+					| bull \
+					| cbm \
+					| ccur \
+					| cisco \
+					| commodore \
+					| convergent* \
+					| convex* \
+					| cray \
+					| crds \
+					| dec* \
+					| delta* \
+					| dg \
+					| digital \
+					| dolphin \
+					| encore* \
+					| gould \
+					| harris \
+					| highlevel \
+					| hitachi* \
+					| hp \
+					| ibm* \
+					| intergraph \
+					| isi* \
+					| knuth \
+					| masscomp \
+					| microblaze* \
+					| mips* \
+					| motorola* \
+					| ncr* \
+					| news \
+					| next \
+					| ns \
+					| oki \
+					| omron* \
+					| pc533* \
+					| rebel \
+					| rom68k \
+					| rombug \
+					| semi \
+					| sequent* \
+					| siemens \
+					| sgi* \
+					| siemens \
+					| sim \
+					| sni \
+					| sony* \
+					| stratus \
+					| sun \
+					| sun[234]* \
+					| tektronix \
+					| tti* \
+					| ultra \
+					| unicom* \
+					| wec \
+					| winbond \
+					| wrs)
 						basic_machine=$field1-$field2
 						basic_os=
 						;;
+					zephyr*)
+						basic_machine=$field1-unknown
+						basic_os=$field2
+						;;
 					*)
 						basic_machine=$field1
 						basic_os=$field2
@@ -271,26 +345,6 @@ case $1 in
 				basic_machine=arm-unknown
 				basic_os=cegcc
 				;;
-			convex-c1)
-				basic_machine=c1-convex
-				basic_os=bsd
-				;;
-			convex-c2)
-				basic_machine=c2-convex
-				basic_os=bsd
-				;;
-			convex-c32)
-				basic_machine=c32-convex
-				basic_os=bsd
-				;;
-			convex-c34)
-				basic_machine=c34-convex
-				basic_os=bsd
-				;;
-			convex-c38)
-				basic_machine=c38-convex
-				basic_os=bsd
-				;;
 			cray)
 				basic_machine=j90-cray
 				basic_os=unicos
@@ -713,15 +767,26 @@ case $basic_machine in
 		vendor=dec
 		basic_os=tops20
 		;;
-	delta | 3300 | motorola-3300 | motorola-delta \
-	      | 3300-motorola | delta-motorola)
+	delta | 3300 | delta-motorola | 3300-motorola | motorola-delta | motorola-3300)
 		cpu=m68k
 		vendor=motorola
 		;;
-	dpx2*)
+	# This used to be dpx2*, but that gets the RS6000-based
+	# DPX/20 and the x86-based DPX/2-100 wrong.  See
+	# https://oldskool.silicium.org/stations/bull_dpx20.htm
+	# https://www.feb-patrimoine.com/english/bull_dpx2.htm
+	# https://www.feb-patrimoine.com/english/unix_and_bull.htm
+	dpx2 | dpx2[23]00 | dpx2[23]xx)
 		cpu=m68k
 		vendor=bull
-		basic_os=sysv3
+		;;
+	dpx2100 | dpx21xx)
+		cpu=i386
+		vendor=bull
+		;;
+	dpx20)
+		cpu=rs6000
+		vendor=bull
 		;;
 	encore | umax | mmax)
 		cpu=ns32k
@@ -836,18 +901,6 @@ case $basic_machine in
 	next | m*-next)
 		cpu=m68k
 		vendor=next
-		case $basic_os in
-		    openstep*)
-		        ;;
-		    nextstep*)
-			;;
-		    ns2*)
-		      basic_os=nextstep2
-			;;
-		    *)
-		      basic_os=nextstep3
-			;;
-		esac
 		;;
 	np1)
 		cpu=np1
@@ -936,14 +989,13 @@ case $basic_machine in
 		;;
 
 	*-*)
-		# shellcheck disable=SC2162
 		saved_IFS=$IFS
 		IFS="-" read cpu vendor <&2
+				echo "Invalid configuration '$1': machine '$cpu-$vendor' not recognized" 1>&2
 				exit 1
 				;;
 		esac
@@ -1306,11 +1491,12 @@ esac
 
 # Decode manufacturer-specific aliases for certain operating systems.
 
-if test x$basic_os != x
+if test x"$basic_os" != x
 then
 
 # First recognize some ad-hoc cases, or perhaps split kernel-os, or else just
 # set os.
+obj=
 case $basic_os in
 	gnu/linux*)
 		kernel=linux
@@ -1325,7 +1511,6 @@ case $basic_os in
 		os=`echo "$basic_os" | sed -e 's|nto-qnx|qnx|'`
 		;;
 	*-*)
-		# shellcheck disable=SC2162
 		saved_IFS=$IFS
 		IFS="-" read kernel os <&2
+		fi
+		;;
+	*)
+		echo "Invalid configuration '$1': OS '$os' not recognized" 1>&2
+		exit 1
+		;;
+esac
+
+case $obj in
+	aout* | coff* | elf* | pe*)
+		;;
+	'')
+		# empty is fine
+		;;
 	*)
-		echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2
+		echo "Invalid configuration '$1': Machine code format '$obj' not recognized" 1>&2
+		exit 1
+		;;
+esac
+
+# Here we handle the constraint that a (synthetic) cpu and os are
+# valid only in combination with each other and nowhere else.
+case $cpu-$os in
+	# The "javascript-unknown-ghcjs" triple is used by GHC; we
+	# accept it here in order to tolerate that, but reject any
+	# variations.
+	javascript-ghcjs)
+		;;
+	javascript-* | *-ghcjs)
+		echo "Invalid configuration '$1': cpu '$cpu' is not valid with os '$os$obj'" 1>&2
 		exit 1
 		;;
 esac
 
 # As a final step for OS-related things, validate the OS-kernel combination
 # (given a valid OS), if there is a kernel.
-case $kernel-$os in
-	linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* \
-		   | linux-musl* | linux-relibc* | linux-uclibc* )
+case $kernel-$os-$obj in
+	linux-gnu*- | linux-android*- | linux-dietlibc*- | linux-llvm*- \
+		    | linux-mlibc*- | linux-musl*- | linux-newlib*- \
+		    | linux-relibc*- | linux-uclibc*- | linux-ohos*- )
+		;;
+	uclinux-uclibc*- | uclinux-gnu*- )
+		;;
+	managarm-mlibc*- | managarm-kernel*- )
 		;;
-	uclinux-uclibc* )
+	windows*-msvc*-)
 		;;
-	-dietlibc* | -newlib* | -musl* | -relibc* | -uclibc* )
+	-dietlibc*- | -llvm*- | -mlibc*- | -musl*- | -newlib*- | -relibc*- \
+		    | -uclibc*- )
 		# These are just libc implementations, not actual OSes, and thus
 		# require a kernel.
-		echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2
+		echo "Invalid configuration '$1': libc '$os' needs explicit kernel." 1>&2
 		exit 1
 		;;
-	kfreebsd*-gnu* | kopensolaris*-gnu*)
+	-kernel*- )
+		echo "Invalid configuration '$1': '$os' needs explicit kernel." 1>&2
+		exit 1
 		;;
-	vxworks-simlinux | vxworks-simwindows | vxworks-spe)
+	*-kernel*- )
+		echo "Invalid configuration '$1': '$kernel' does not support '$os'." 1>&2
+		exit 1
 		;;
-	nto-qnx*)
+	*-msvc*- )
+		echo "Invalid configuration '$1': '$os' needs 'windows'." 1>&2
+		exit 1
 		;;
-	os2-emx)
+	kfreebsd*-gnu*- | knetbsd*-gnu*- | netbsd*-gnu*- | kopensolaris*-gnu*-)
+		;;
+	vxworks-simlinux- | vxworks-simwindows- | vxworks-spe-)
+		;;
+	nto-qnx*-)
 		;;
-	*-eabi* | *-gnueabi*)
+	os2-emx-)
 		;;
-	-*)
+	rtmk-nova-)
+		;;
+	*-eabi*- | *-gnueabi*-)
+		;;
+	none--*)
+		# None (no kernel, i.e. freestanding / bare metal),
+		# can be paired with an machine code file format
+		;;
+	-*-)
 		# Blank kernel with real OS is always fine.
 		;;
-	*-*)
-		echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2
+	--*)
+		# Blank kernel and OS with real machine code file format is always fine.
+		;;
+	*-*-*)
+		echo "Invalid configuration '$1': Kernel '$kernel' not known to work with OS '$os'." 1>&2
 		exit 1
 		;;
 esac
@@ -1813,7 +2273,7 @@ case $vendor in
 			*-riscix*)
 				vendor=acorn
 				;;
-			*-sunos*)
+			*-sunos* | *-solaris*)
 				vendor=sun
 				;;
 			*-cnk* | *-aix*)
@@ -1883,7 +2343,7 @@ case $vendor in
 		;;
 esac
 
-echo "$cpu-$vendor-${kernel:+$kernel-}$os"
+echo "$cpu-$vendor${kernel:+-$kernel}${os:+-$os}${obj:+-$obj}"
 exit
 
 # Local variables:


=====================================
configure.ac
=====================================
@@ -13,7 +13,7 @@ dnl
 # see what flags are available. (Better yet, read the documentation!)
 #
 
-AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.8.2], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION])
+AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.8.3], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION])
     # Version on master must be X.Y (not X.Y.Z) for ProjectVersionMunged variable
     # to be useful (cf #19058). However, the version must have three components
     # (X.Y.Z) on stable branches (e.g. ghc-9.2) to ensure that pre-releases are


=====================================
docs/users_guide/9.8.1-notes.rst
=====================================
@@ -334,48 +334,3 @@ will need to avoid using a bundled import (e.g. by qualification): ::
 
     import Data.Text.Array as A
 
-
-Included libraries
-~~~~~~~~~~~~~~~~~~
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/semaphore-compat/semaphore-compat.cabal: Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable


=====================================
docs/users_guide/9.8.2-notes.rst
=====================================
@@ -121,48 +121,3 @@ Core libraries
 - Bump ``unix`` to 2.8.4.0
 - Bump ``bytestring`` to 0.12.1.0
 - Bump ``text`` to 2.1.1
-
-Included libraries
-------------------
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/semaphore-compat/semaphore-compat.cabal: Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable


=====================================
docs/users_guide/9.8.3-notes.rst
=====================================
@@ -50,6 +50,7 @@ JavaScript backend
 ``base``
 --------
 
+- Bump version to 4.19.2.0
 - Fix spurious closing of file descriptors after ``fork`` on platforms using the KQueue event manager backend (:ghc-ticket:`24672`)
 
 Haddock


=====================================
hadrian/bindist/Makefile
=====================================
@@ -165,7 +165,7 @@ install_lib: lib/settings
 	$(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)"
 	
 	@dest="$(DESTDIR)$(ActualLibsDir)"; \
-	cd lib; \
+	cd ./lib; \
 	for i in `$(FIND) . -type f`; do \
 		$(INSTALL_DIR) "$$dest/`dirname $$i`" ; \
 		case $$i in \
@@ -195,7 +195,7 @@ install_docs:
 	$(INSTALL_DIR) "$(DESTDIR)$(docdir)"
 
 	if [ -d doc ]; then \
-		cd doc; $(FIND) . -type f -exec sh -c \
+		cd ./doc; $(FIND) . -type f -exec sh -c \
 			'$(INSTALL_DIR) "$(DESTDIR)$(docdir)/`dirname $$1`" && $(INSTALL_DATA) "$$1" "$(DESTDIR)$(docdir)/`dirname $$1`"' \
 			sh '{}' ';'; \
 	fi
@@ -210,7 +210,7 @@ install_docs:
 install_data:
 	@echo "Copying data to $(DESTDIR)share"
 	$(INSTALL_DIR) "$(DESTDIR)$(datadir)"
-	cd share; $(FIND) . -type f -exec sh -c \
+	cd ./share; $(FIND) . -type f -exec sh -c \
 		'$(INSTALL_DIR) "$(DESTDIR)$(datadir)/`dirname $$1`" && \
 		$(INSTALL_DATA) "$$1" "$(DESTDIR)$(datadir)/`dirname $$1`"' \
 		sh '{}' ';';
@@ -231,7 +231,7 @@ export SHELL
 install_wrappers: install_bin_libdir install_hsc2hs_wrapper
 	@echo "Installing wrapper scripts"
 	$(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)"
-	for p in `cd wrappers; $(FIND) . ! -type d`; do \
+	for p in `cd ./wrappers; $(FIND) . ! -type d`; do \
 	    mk/install_script.sh "$$p" "$(DESTDIR)/$(WrapperBinsDir)/$$p" "$(WrapperBinsDir)" "$(ActualBinsDir)" "$(ActualBinsDir)/$$p" "$(ActualLibsDir)" "$(docdir)" "$(includedir)"; \
 	done
 


=====================================
libraries/base/base.cabal
=====================================
@@ -1,6 +1,6 @@
 cabal-version:  3.0
 name:           base
-version:        4.19.1.0
+version:        4.19.2.0
 -- NOTE: Don't forget to update ./changelog.md
 
 license:        BSD-3-Clause


=====================================
libraries/base/changelog.md
=====================================
@@ -1,5 +1,10 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
+## 4.19.2.0 *October 2024*
+  * Shipped with GHC 9.8.3
+  * Improve documentation of various functions
+  * Fix interaction between `fork` and the `kqueue`-based IO manager ([#24672](https://gitlab.haskell.org/ghc/ghc/-/issues/24672))
+
 ## 4.19.1.0 *October 2023*
   * Shipped with GHC 9.8.2
   * Improve documentation of various functions


=====================================
libraries/semaphore-compat
=====================================
@@ -1 +1 @@
-Subproject commit c8fc7b1757b4eecbd10239038fbc6602340105b1
+Subproject commit ec34791e402e9e6d01623eba90284e8129eb8dba


=====================================
testsuite/driver/testlib.py
=====================================
@@ -1019,8 +1019,12 @@ def normalise_win32_io_errors(name, opts):
 def normalise_version_( *pkgs ):
     def normalise_version__( str ):
         # (name)(-version)(-hash)(-components)
-        return re.sub('(' + '|'.join(map(re.escape,pkgs)) + ')-[0-9.]+(-[0-9a-zA-Z\+]+)?(-[0-9a-zA-Z]+)?',
-                      '\\1--', str)
+        pkg_names = '(' + '|'.join(map(re.escape,pkgs)) + ')'
+        version = r'[0-9\.]+'
+        pkg_hash = r'(-[0-9a-zA-Z\+]+)'
+        component = r'(-[0-9a-zA-Z]+(\+[0-9a-zA-Z]+)?)'
+        return re.sub(f'{pkg_names}-{version}{pkg_hash}?{component}?',
+                      r'\1--', str)
     return normalise_version__
 
 def normalise_version( *pkgs ):
@@ -1393,7 +1397,7 @@ async def do_test(name: TestName,
     if opts.expect not in ['pass', 'fail', 'missing-lib']:
         framework_fail(name, way, 'bad expected ' + opts.expect)
 
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
 
     if way in opts.fragile_ways:
         if_verbose(1, '*** fragile test %s resulted in %s' % (full_name, 'pass' if result.passed else 'fail'))
@@ -1440,7 +1444,7 @@ def override_options(pre_cmd):
 
 def framework_fail(name: Optional[TestName], way: Optional[WayName], reason: str) -> None:
     opts = getTestOpts()
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
     full_name = '%s(%s)' % (name, way)
     if_verbose(1, '*** framework failure for %s %s ' % (full_name, reason))
     name2 = name if name is not None else TestName('none')
@@ -1451,7 +1455,7 @@ def framework_fail(name: Optional[TestName], way: Optional[WayName], reason: str
 
 def framework_warn(name: TestName, way: WayName, reason: str) -> None:
     opts = getTestOpts()
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
     full_name = name + '(' + way + ')'
     if_verbose(1, '*** framework warning for %s %s ' % (full_name, reason))
     t.framework_warnings.append(TestResult(directory, name, reason, way))
@@ -2476,7 +2480,7 @@ def normalise_errmsg(s: str) -> str:
     s = normalise_type_reps(s)
 
     # normalise slashes, minimise Windows/Unix filename differences
-    s = re.sub('\\\\', '/', s)
+    s = re.sub(r'\\', '/', s)
 
     # Normalize the name of the GHC executable. Specifically,
     # this catches the cases that:
@@ -2491,11 +2495,11 @@ def normalise_errmsg(s: str) -> str:
     #    the colon is there because it appears in error messages; this
     #    hacky solution is used in place of more sophisticated filename
     #    mangling
-    s = re.sub('([^\\s])\\.exe', '\\1', s)
+    s = re.sub(r'([^\s])\.exe', r'\1', s)
     # Same thing for .wasm modules generated by the Wasm backend
-    s = re.sub('([^\\s])\\.wasm', '\\1', s)
+    s = re.sub(r'([^\s])\.wasm', r'\1', s)
     # Same thing for .jsexe directories generated by the JS backend
-    s = re.sub('([^\\s])\\.jsexe', '\\1', s)
+    s = re.sub(r'([^\s])\.jsexe', r'\1', s)
 
     # normalise slashes, minimise Windows/Unix filename differences
     s = re.sub('\\\\', '/', s)
@@ -2508,8 +2512,8 @@ def normalise_errmsg(s: str) -> str:
     s = re.sub('ghc-stage[123]', 'ghc', s)
     # Remove platform prefix (e.g. javascript-unknown-ghcjs) for cross-compiled tools
     # (ghc, ghc-pkg, unlit, etc.)
-    s = re.sub('\\w+(-\\w+)*-ghc', 'ghc', s)
-    s = re.sub('\\w+(-\\w+)*-unlit', 'unlit', s)
+    s = re.sub(r'\w+(-\w+)*-ghc', 'ghc', s)
+    s = re.sub(r'\w+(-\w+)*-unlit', 'unlit', s)
 
     # On windows error messages can mention versioned executables
     s = re.sub('ghc-[0-9.]+', 'ghc', s)
@@ -2610,8 +2614,8 @@ def normalise_prof (s: str) -> str:
     return s
 
 def normalise_slashes_( s: str ) -> str:
-    s = re.sub('\\\\', '/', s)
-    s = re.sub('//', '/', s)
+    s = re.sub(r'\\', '/', s)
+    s = re.sub(r'//', '/', s)
     return s
 
 def normalise_exe_( s: str ) -> str:
@@ -2629,9 +2633,9 @@ def normalise_output( s: str ) -> str:
     # and .wasm extension (for the Wasm backend)
     # and .jsexe extension (for the JS backend)
     # This can occur in error messages generated by the program.
-    s = re.sub('([^\\s])\\.exe', '\\1', s)
-    s = re.sub('([^\\s])\\.wasm', '\\1', s)
-    s = re.sub('([^\\s])\\.jsexe', '\\1', s)
+    s = re.sub(r'([^\s])\.exe', r'\1', s)
+    s = re.sub(r'([^\s])\.wasm', r'\1', s)
+    s = re.sub(r'([^\s])\.jsexe', r'\1', s)
     s = normalise_callstacks(s)
     s = normalise_type_reps(s)
     # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is
@@ -2651,7 +2655,7 @@ def normalise_output( s: str ) -> str:
     s = re.sub('.*warning: argument unused during compilation:.*\n', '', s)
 
     # strip the cross prefix if any
-    s = re.sub('\\w+(-\\w+)*-ghc', 'ghc', s)
+    s = re.sub(r'\w+(-\w+)*-ghc', 'ghc', s)
 
     return s
 


=====================================
testsuite/tests/backpack/should_fail/bkpfail16.stderr
=====================================
@@ -1,11 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Data.Bool]
-    Instantiating p[ShouldFail=base-4.18.0.0:Data.Bool]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail16.out\p\p-1OqLaT7dAn947wScQQKCw5\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.Bool]
+    Instantiating p[ShouldFail=base-4.19.1.0:Data.Bool]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail16.out/p/p-IWIH695NuFKHfA9JCzN8tU/ShouldFail.o )
 
-bkpfail16.out\p\p-1OqLaT7dAn947wScQQKCw5\..\ShouldFail.hi:1:1: error: [GHC-93011]
-    • ‘Booly’ is exported by the hsig file, but not exported by the implementing module ‘Data.Bool’
-    • While checking that ‘Data.Bool’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.Bool]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Data.Bool differs from name found in the interface file base:Data.Bool (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,18 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Prelude]
-    Instantiating p[ShouldFail=base-4.18.0.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail17.out\p\p-2W6J7O3LvroH97zGxbPEGF\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Prelude]
+    Instantiating p[ShouldFail=base-4.19.1.0:Prelude]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9af3lmxJNZa50ZueXSR02Y/ShouldFail.o )
 
-: error: [GHC-15843]
-    • Type constructor ‘Either’ has conflicting definitions in the module
-      and its hsig file.
-      Main module: type Either :: * -> * -> *
-                   data Either a b = Left a | Right b
-        Hsig file: type role Either representational phantom phantom
-                   type Either :: * -> * -> * -> *
-                   data Either a b c = Left a
-      The types have different kinds.
-    • While checking that ‘Prelude’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Prelude]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Prelude differs from name found in the interface file base:Prelude (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,12 +1,10 @@
 [1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, nothing )
+  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
 [2 of 2] Processing q
   Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.18.0.0:Data.STRef]
-    Instantiating p[ShouldFail=base-4.18.0.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p\ShouldFail.hsig, bkpfail19.out\p\p-CfyUIAu1JTRCDuXEyGszXN\ShouldFail.o )
+  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.STRef]
+    Instantiating p[ShouldFail=base-4.19.1.0:Data.STRef]
+    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Ak3HDozWrn3BPHIdYYNht5/ShouldFail.o )
 
-: error: [GHC-12424]
-    • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
-      but the implementing module exports a different identifier ‘GHC.STRef.newSTRef’
-    • While checking that ‘Data.STRef’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.STRef]’.
+: error:
+    Something is amiss; requested module  base-4.19.1.0-inplace:Data.STRef differs from name found in the interface file base:Data.STRef (if these names look the same, try again with -dppr-debug)


=====================================
testsuite/tests/driver/boot-target/A.hs deleted
=====================================
@@ -1,5 +0,0 @@
-module A where
-
-import B
-
-data A = A B


=====================================
testsuite/tests/driver/boot-target/A.hs-boot deleted
=====================================
@@ -1,3 +0,0 @@
-module A where
-
-data A


=====================================
testsuite/tests/driver/boot-target/B.hs deleted
=====================================
@@ -1,5 +0,0 @@
-module B where
-
-import {-# source #-} A
-
-data B = B A


=====================================
testsuite/tests/driver/boot-target/Makefile deleted
=====================================
@@ -1,8 +0,0 @@
-boot1:
-	$(TEST_HC) -c A.hs-boot B.hs
-
-boot2:
-	$(TEST_HC) A.hs-boot A.hs B.hs -v0
-
-boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/all.T deleted
=====================================
@@ -1,10 +0,0 @@
-def test_boot(name):
-    return test(name,
-     [extra_files(['A.hs', 'A.hs-boot', 'B.hs']),
-      ],
-     makefile_test,
-     [])
-
-test_boot('boot1')
-test_boot('boot2')
-test_boot('boot3')


=====================================
testsuite/tests/gadt/T19847a.stderr
=====================================
@@ -9,4 +9,4 @@ DATA CONSTRUCTORS
          (x ~ y, c ~ [x], Ord x) =>
          x -> y -> T (x, y) b c
 Dependent modules: []
-Dependent packages: [base-4.19.1.0]
+Dependent packages: [base-4.19.2.0]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f43950e3e5198a1119441f7e3677a7cd20226ea...72e041753f8d2c5b1fae0465277b187c61f17634

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f43950e3e5198a1119441f7e3677a7cd20226ea...72e041753f8d2c5b1fae0465277b187c61f17634
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 13:34:06 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 09:34:06 -0400
Subject: [Git][ghc/ghc][master] 5 commits: Bump transformers submodule
Message-ID: <6713b54e72df2_d0cd482da4891581@gitlab.mail>



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


Commits:
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -


12 changed files:

- .gitlab-ci.yml
- cabal.project-reinstall
- compiler/Setup.hs
- compiler/ghc.cabal.in
- libraries/transformers
- testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
- testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
- testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
- testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
- testsuite/tests/tcplugins/all.T
- testsuite/tests/typecheck/should_compile/all.T
- utils/haddock/haddock.cabal


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -494,21 +494,16 @@ stack-hadrian-build:
 # Testing reinstallable ghc codepath
 ####################################
 
-# As documented on the original ticket #19896, this feature already has a long
-# way to go before it can actually be used. Meanwhile, parts of it have
-# bit-rotted, possibly related to some Cabal change. The job is disabled for
-# now.
-#
-# test-cabal-reinstall-x86_64-linux-deb10:
-#   extends: nightly-x86_64-linux-deb10-validate
-#   stage: full-build
-#   variables:
-#     REINSTALL_GHC: "yes"
-#     BUILD_FLAVOUR: validate
-#     TEST_ENV: "x86_64-linux-deb10-cabal-install"
-#   rules:
-#     - if: $NIGHTLY
-#     - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
+test-cabal-reinstall-x86_64-linux-deb10:
+  extends: nightly-x86_64-linux-deb10-validate
+  stage: full-build
+  variables:
+    REINSTALL_GHC: "yes"
+    BUILD_FLAVOUR: validate
+    TEST_ENV: "x86_64-linux-deb10-cabal-install"
+  rules:
+    - if: $NIGHTLY
+    - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
 
 ########################################
 # Testing ABI is invariant across builds


=====================================
cabal.project-reinstall
=====================================
@@ -12,11 +12,13 @@ packages: ./compiler
           -- ./libraries/deepseq/
           ./libraries/directory/
           ./libraries/exceptions/
+          ./libraries/file-io/
           ./libraries/filepath/
           -- ./libraries/ghc-bignum/
            ./libraries/ghc-boot/
           -- ./libraries/ghc-boot-th/
           ./libraries/ghc-compact
+          ./libraries/ghc-experimental
           ./libraries/ghc-heap
           ./libraries/ghci
           -- ./libraries/ghc-prim
@@ -25,6 +27,7 @@ packages: ./compiler
           ./libraries/hpc
           -- ./libraries/integer-gmp
           ./libraries/mtl/
+          ./libraries/os-string/
           ./libraries/parsec/
           -- ./libraries/pretty/
           ./libraries/process/
@@ -39,7 +42,11 @@ packages: ./compiler
           ./libraries/Win32/
           ./libraries/xhtml/
           ./utils/ghc-pkg
+          ./utils/ghc-toolchain
+          ./utils/ghc-toolchain/exe
           ./utils/haddock
+          ./utils/haddock/haddock-api
+          ./utils/haddock/haddock-library
           ./utils/hp2ps
           ./utils/hpc
           ./utils/hsc2hs
@@ -61,15 +68,10 @@ constraints: ghc +internal-interpreter +dynamic-system-linke,
              any.pretty installed,
              any.template-haskell installed
 
-allow-newer:
-  ghc-paths:Cabal,
-  *:base,
-  *:ghc-prim,
-  tree-diff:time
 
 benchmarks: False
 tests: False
-allow-boot-library-installs: False
+allow-boot-library-installs: True
 
 -- Workaround for https://github.com/haskell/cabal/issues/7297
 package *


=====================================
compiler/Setup.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE NamedFieldPuns #-}
 module Main where
 
 import Distribution.Simple
@@ -52,10 +52,12 @@ primopIncls =
     , ("primop-vector-tys-exports.hs-incl", "--primop-vector-tys-exports")
     , ("primop-vector-tycons.hs-incl"     , "--primop-vector-tycons")
     , ("primop-docs.hs-incl"              , "--wired-in-docs")
+    , ("primop-deprecations.hs-incl"      , "--wired-in-deprecations")
     ]
 
 ghcAutogen :: Verbosity -> LocalBuildInfo -> IO ()
-ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
+ghcAutogen verbosity lbi at LocalBuildInfo{pkgDescrFile,withPrograms,componentNameMap}
+  = do
   -- Get compiler/ root directory from the cabal file
   let Just compilerRoot = takeDirectory <$> pkgDescrFile
 
@@ -77,7 +79,7 @@ ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
   -- Call genprimopcode to generate *.hs-incl
   forM_ primopIncls $ \(file,command) -> do
     contents <- readProcess "genprimopcode" [command] primopsStr
-    rewriteFileEx verbosity (buildDir  file) contents
+    rewriteFileEx verbosity (buildDir lbi  file) contents
 
   -- Write GHC.Platform.Constants
   let platformConstantsPath = autogenPackageModulesDir lbi  "GHC/Platform/Constants.hs"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -50,7 +50,7 @@ extra-source-files:
 
 
 custom-setup
-    setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.10, directory, process, filepath, containers
+    setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.14, directory, process, filepath, containers
 
 Flag internal-interpreter
     Description: Build with internal interpreter support.


=====================================
libraries/transformers
=====================================
@@ -1 +1 @@
-Subproject commit ba3503905dec072acc6515323c884706efd4dbb4
+Subproject commit b3eaaae9b6c986aaac84f0f05a137eef65ccfab3


=====================================
testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
=====================================


=====================================
testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
=====================================


=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -109,3 +109,10 @@ test('TcPlugin_CtId'
     , [ 'TcPlugin_CtId.hs'
       , '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
     )
+
+test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
+     [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
+      '-dynamic' if have_dynamic() else ''])
+test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
+     [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
+      '-dynamic' if have_dynamic() else ''])


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -500,9 +500,6 @@ test('T10592', normal, compile, [''])
 test('T11305', normal, compile, [''])
 test('T11254', normal, compile, [''])
 test('T11379', normal, compile, [''])
-test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
-     [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
-      '-dynamic' if have_dynamic() else ''])
 test('T11480', normal, compile, [''])
 test('RebindHR', normal, compile, [''])
 test('RebindNegate', normal, compile, [''])
@@ -568,9 +565,6 @@ test('T11723', normal, compile, [''])
 test('T12987', normal, compile, [''])
 test('T11736', normal, compile, [''])
 test('T13248', expect_broken(13248), compile, [''])
-test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
-     [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
-      '-dynamic' if have_dynamic() else ''])
 test('T12923_1', normal, compile, [''])
 test('T21208', normal, compile, [''])
 test('T12923_2', normal, compile, [''])


=====================================
utils/haddock/haddock.cabal
=====================================
@@ -43,7 +43,6 @@ extra-source-files:
   doc/README.md
   doc/*.rst
   doc/conf.py
-  haddock-api/src/haddock.sh
   html-test/src/*.hs
   html-test/ref/*.html
   hypsrc-test/src/*.hs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5bcfefd5bb73c18a9bad63d1813968832b696f9a...b3c00c62d76b873f20ebfbf124853ba2b248a397

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5bcfefd5bb73c18a9bad63d1813968832b696f9a...b3c00c62d76b873f20ebfbf124853ba2b248a397
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 13:34:52 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 09:34:52 -0400
Subject: [Git][ghc/ghc][master] base: speed up traceEventIO and friends when
 eventlogging is turned off #17949
Message-ID: <6713b57c5dbf7_d0cd4838bf0963c4@gitlab.mail>



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


Commits:
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


8 changed files:

- libraries/base/changelog.md
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- + libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
- + testsuite/tests/perf/should_run/T17949.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/profiling/should_run/callstack002.stderr


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -37,6 +37,7 @@
       for libraries that define exception-handling combinators like `catch` and
       `onException`, such as `base`, or the `exceptions` package.
   * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
+  * Make `Debug.Trace.{traceEventIO,traceMarkerIO}` faster when tracing is disabled. See [CLC proposal #291](https://github.com/haskell/core-libraries-committee/issues/291).
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -253,6 +253,7 @@ Library
         GHC.Internal.Records
         GHC.Internal.ResponseFile
         GHC.Internal.RTS.Flags
+        GHC.Internal.RTS.Flags.Test
         GHC.Internal.ST
         GHC.Internal.Stack.CloneStack
         GHC.Internal.StaticPtr


=====================================
libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE Unsafe #-}
+{-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE UnboxedTuples #-}
@@ -54,6 +55,11 @@ import GHC.Internal.Ptr
 import GHC.Internal.Show
 import GHC.Internal.Stack
 import GHC.Internal.Data.List (null, partition)
+import GHC.Internal.RTS.Flags.Test
+
+-- | 'userEventTracingEnabled' is True if event logging for user events (@+RTS -l@) is enabled.
+userEventTracingEnabled :: IO Bool
+userEventTracingEnabled = getUserEventTracingEnabled
 
 -- | The 'traceIO' function outputs the trace message from the IO monad.
 -- This sequences the output with respect to other IO actions.
@@ -239,8 +245,8 @@ traceStack str expr = unsafePerformIO $ do
 
 {-# NOINLINE traceEvent #-}
 -- | The 'traceEvent' function behaves like 'trace' with the difference that
--- the message is emitted to the eventlog, if eventlog profiling is available
--- and enabled at runtime.
+-- the message is emitted to the eventlog, if eventlog tracing is available
+-- and user event tracing is enabled at runtime.
 --
 -- It is suitable for use in pure code. In an IO context use 'traceEventIO'
 -- instead.
@@ -256,16 +262,19 @@ traceEvent msg expr = unsafeDupablePerformIO $ do
     return expr
 
 -- | The 'traceEventIO' function emits a message to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
 --
 -- Compared to 'traceEvent', 'traceEventIO' sequences the event with respect to
 -- other IO actions.
 --
 -- @since base-4.5.0.0
 traceEventIO :: String -> IO ()
-traceEventIO msg =
-  Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
-    case traceEvent# p s of s' -> (# s', () #)
+{-# INLINE traceEventIO #-}
+traceEventIO msg = do
+  enabled <- userEventTracingEnabled
+  when enabled $
+    Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+      case traceEvent# p s of s' -> (# s', () #)
 
 -- | Like 'traceEvent', but emits the result of calling a function on its
 -- argument.
@@ -276,7 +285,7 @@ traceEventWith f a = traceEvent (f a) a
 
 {-# NOINLINE traceMarker #-}
 -- | The 'traceMarker' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime. The @String@ is the name of
+-- tracing is available and enabled at runtime. The @String@ is the name of
 -- the marker. The name is just used in the profiling tools to help you keep
 -- clear which marker is which.
 --
@@ -294,16 +303,19 @@ traceMarker msg expr = unsafeDupablePerformIO $ do
     return expr
 
 -- | The 'traceMarkerIO' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
 --
 -- Compared to 'traceMarker', 'traceMarkerIO' sequences the event with respect to
 -- other IO actions.
 --
 -- @since base-4.7.0.0
 traceMarkerIO :: String -> IO ()
-traceMarkerIO msg =
-  Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
-    case traceMarker# p s of s' -> (# s', () #)
+{-# INLINE traceMarkerIO #-}
+traceMarkerIO msg = do
+  enabled <- userEventTracingEnabled
+  when enabled $
+    Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+      case traceMarker# p s of s' -> (# s', () #)
 
 -- | Immediately flush the event log, if enabled.
 --


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -613,6 +613,10 @@ getProfFlags = do
 
 getTraceFlags :: IO TraceFlags
 getTraceFlags = do
+#if defined(javascript_HOST_ARCH)
+  -- The JS backend does not currently have trace flags
+  pure (TraceFlags TraceNone False False False False False False False)
+#else
   let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
   TraceFlags <$> (toEnum . fromIntegral
                    <$> (#{peek TRACE_FLAGS, tracing} ptr :: IO CInt))
@@ -630,6 +634,7 @@ getTraceFlags = do
                    (#{peek TRACE_FLAGS, sparks_full} ptr :: IO CBool))
              <*> (toBool <$>
                    (#{peek TRACE_FLAGS, user} ptr :: IO CBool))
+#endif
 
 getTickyFlags :: IO TickyFlags
 getTickyFlags = do


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-- | Module with fewer dependencies than GHC.Internal.RTS.Flags
+-- that allows to quickly test if some flag is set.
+module GHC.Internal.RTS.Flags.Test
+  ( getUserEventTracingEnabled
+  )
+where
+
+import GHC.Internal.Base
+
+#if !defined(javascript_HOST_ARCH)
+
+import GHC.Internal.Ptr
+import GHC.Internal.Foreign.C.Types
+import GHC.Internal.Foreign.Marshal.Utils
+import GHC.Internal.Foreign.Storable
+import GHC.Internal.Data.Functor ((<$>))
+
+#include "Rts.h"
+#include "rts/Flags.h"
+
+foreign import ccall "&RtsFlags" rtsFlagsPtr :: Ptr ()
+#endif
+
+-- | Specialized version of 'getTraceFlags' for just checking if user
+-- event tracing is enabled.
+getUserEventTracingEnabled :: IO Bool
+getUserEventTracingEnabled = do
+#if defined(javascript_HOST_ARCH)
+  -- The JS backend does not currently have trace flags
+  pure False
+#else
+  let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
+  toBool <$> (#{peek TRACE_FLAGS, user} ptr :: IO CBool)
+#endif


=====================================
testsuite/tests/perf/should_run/T17949.hs
=====================================
@@ -0,0 +1,7 @@
+module Main where
+
+import Debug.Trace
+
+main :: IO ()
+main = do
+  traceEventIO (show [0..1234567])


=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -414,3 +414,4 @@ test('T21839r',
 test('T18964', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O'])
 test('T23021', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])
 test('T25055', [collect_stats('bytes allocated', 2), only_ways(['normal'])], compile_and_run, ['-O2'])
+test('T17949', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])


=====================================
testsuite/tests/profiling/should_run/callstack002.stderr
=====================================
@@ -1,6 +1,6 @@
 f: 42
 CallStack (from -prof):
-  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
   Main.f (callstack002.hs:10:7-43)
   Main.map.go (callstack002.hs:15:21-23)
   Main.map.go (callstack002.hs:15:21-34)
@@ -9,7 +9,7 @@ CallStack (from -prof):
   Main.CAF ()
 f: 43
 CallStack (from -prof):
-  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+  GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
   Main.f (callstack002.hs:10:7-43)
   Main.map.go (callstack002.hs:15:21-23)
   Main.map.go (callstack002.hs:15:21-34)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 14:05:46 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 10:05:46 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: base: speed
 up traceEventIO and friends when eventlogging is turned off #17949
Message-ID: <6713bcbaa70dd_d0cd4cf43c497944@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
3ce9419d by Matthew Pickering at 2024-10-19T10:05:39-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
5705095c by Zubin Duggal at 2024-10-19T10:05:40-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
d01a62a9 by Alan Zimmerman at 2024-10-19T10:05:40-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -


18 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/ThToHs.hs
- libraries/base/changelog.md
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- + libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/147f8f0176db0d777955648dd5fc6ecd32e82576...d01a62a97b38f3f4de971ad9813a7269eac1da0a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/147f8f0176db0d777955648dd5fc6ecd32e82576...d01a62a97b38f3f4de971ad9813a7269eac1da0a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 14:41:54 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 19 Oct 2024 10:41:54 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-5] 4 commits: EPA: Remove
 [AddEpAnn] From HsDeriving
Message-ID: <6713c53265e24_d0cd4f5d6601068bb@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-5 at Glasgow Haskell Compiler / GHC


Commits:
1e096aed by Alan Zimmerman at 2024-10-19T10:33:32+01:00
EPA: Remove [AddEpAnn] From HsDeriving

- - - - -
557387a2 by Alan Zimmerman at 2024-10-19T11:08:56+01:00
EPA: Remove [AddEpAnn] from ConDeclField

- - - - -
78c5782b by Alan Zimmerman at 2024-10-19T14:40:02+01:00
EPA: Remove [AddEpAnn] from ConDeclGADT

- - - - -
e44633ef by Alan Zimmerman at 2024-10-19T15:41:07+01:00
EPA: Remove [AddEpAnn] from ConDeclH98

- - - - -


20 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -59,7 +59,7 @@ module GHC.Hs.Decls (
   LClsInstDecl, ClsInstDecl(..),
 
   -- ** Standalone deriving declarations
-  DerivDecl(..), LDerivDecl,
+  DerivDecl(..), LDerivDecl, AnnDerivDecl,
   -- ** Deriving strategies
   DerivStrategy(..), LDerivStrategy,
   derivStrategyName, foldDerivStrategy, mapDerivStrategy,
@@ -80,7 +80,9 @@ module GHC.Hs.Decls (
   CImportSpec(..),
   -- ** Data-constructor declarations
   ConDecl(..), LConDecl,
-  HsConDeclH98Details, HsConDeclGADTDetails(..), hsConDeclTheta,
+  HsConDeclH98Details, HsConDeclGADTDetails(..),
+  AnnConDeclH98(..), AnnConDeclGADT(..),
+  hsConDeclTheta,
   getConNames, getRecConArgs_maybe,
   -- ** Document comments
   DocDecl(..), LDocDecl, docDeclDoc,
@@ -705,7 +707,7 @@ instance OutputableBndrId p
 type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
-type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
+type instance XCHsDerivingClause    (GhcPass _) = EpToken "deriving"
 type instance XXHsDerivingClause    (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -750,11 +752,11 @@ type instance XXStandaloneKindSig (GhcPass p) = DataConCantHappen
 standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
 standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname
 
-type instance XConDeclGADT GhcPs = (TokDcolon, [AddEpAnn])
+type instance XConDeclGADT GhcPs = AnnConDeclGADT
 type instance XConDeclGADT GhcRn = NoExtField
 type instance XConDeclGADT GhcTc = NoExtField
 
-type instance XConDeclH98  GhcPs = [AddEpAnn]
+type instance XConDeclH98  GhcPs = AnnConDeclH98
 type instance XConDeclH98  GhcRn = NoExtField
 type instance XConDeclH98  GhcTc = NoExtField
 
@@ -768,6 +770,26 @@ type instance XRecConGADT          GhcTc = NoExtField
 
 type instance XXConDeclGADTDetails (GhcPass _) = DataConCantHappen
 
+data AnnConDeclH98
+  = AnnConDeclH98 {
+    acdh_forall  :: TokForall,
+    acdh_dot :: EpToken ".",
+    acdh_darrow :: TokDarrow
+  } deriving Data
+
+instance NoAnn AnnConDeclH98 where
+  noAnn = AnnConDeclH98 noAnn noAnn noAnn
+
+data AnnConDeclGADT
+  = AnnConDeclGADT {
+    acdg_openp  :: [EpToken "("],
+    acdg_closep :: [EpToken ")"],
+    acdg_dcolon :: TokDcolon
+  } deriving Data
+
+instance NoAnn AnnConDeclGADT where
+  noAnn = AnnConDeclGADT noAnn noAnn noAnn
+
 -- Codomain could be 'NonEmpty', but at the moment all users need a list.
 getConNames :: ConDecl GhcRn -> [LocatedN Name]
 getConNames ConDeclH98  {con_name  = name}  = [name]
@@ -1086,15 +1108,17 @@ type instance XCDerivDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
+                                     , AnnDerivDecl )
 type instance XCDerivDecl    GhcRn = ( Maybe (LWarningTxt GhcRn)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
-type instance XCDerivDecl    GhcTc = [AddEpAnn]
+                                     , AnnDerivDecl )
+type instance XCDerivDecl    GhcTc = AnnDerivDecl
 type instance XXDerivDecl    (GhcPass _) = DataConCantHappen
 
+type AnnDerivDecl = (EpToken "deriving", EpToken "instance")
+
 derivDeprecation :: forall p. IsPass p
                => DerivDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1128,15 +1152,15 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XStockStrategy    GhcPs = [AddEpAnn]
+type instance XStockStrategy    GhcPs = EpToken "stock"
 type instance XStockStrategy    GhcRn = NoExtField
 type instance XStockStrategy    GhcTc = NoExtField
 
-type instance XAnyClassStrategy GhcPs = [AddEpAnn]
+type instance XAnyClassStrategy GhcPs = EpToken "anyclass"
 type instance XAnyClassStrategy GhcRn = NoExtField
 type instance XAnyClassStrategy GhcTc = NoExtField
 
-type instance XNewtypeStrategy  GhcPs = [AddEpAnn]
+type instance XNewtypeStrategy  GhcPs = EpToken "newtype"
 type instance XNewtypeStrategy  GhcRn = NoExtField
 type instance XNewtypeStrategy  GhcTc = NoExtField
 
@@ -1144,7 +1168,7 @@ type instance XViaStrategy GhcPs = XViaStrategyPs
 type instance XViaStrategy GhcRn = LHsSigType GhcRn
 type instance XViaStrategy GhcTc = Type
 
-data XViaStrategyPs = XViaStrategyPs [AddEpAnn] (LHsSigType GhcPs)
+data XViaStrategyPs = XViaStrategyPs (EpToken "via") (LHsSigType GhcPs)
 
 instance OutputableBndrId p
         => Outputable (DerivStrategy (GhcPass p)) where


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -294,7 +294,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenInstance :: EpToken "instance" -> SDoc
             epTokenInstance = epToken'
 
-            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall :: TokForall -> SDoc
             epTokenForall = epUniToken'
 
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -163,15 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type instance XHsForAllVis   (GhcPass _) = EpAnn (TokForall, EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type instance XHsForAllInvis (GhcPass _) = EpAnn (TokForall, EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
-type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type EpAnnForallVis   = EpAnn (TokForall, TokRarrow)
+type EpAnnForallInvis = EpAnn (TokForall, EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -461,7 +461,7 @@ type instance XListTy          (GhcPass _) = AnnParen
 type instance XTupleTy         (GhcPass _) = AnnParen
 type instance XSumTy           (GhcPass _) = AnnParen
 type instance XOpTy            (GhcPass _) = NoExtField
-type instance XParTy           (GhcPass _) = AnnParen
+type instance XParTy           (GhcPass _) = (EpToken "(", EpToken ")")
 type instance XIParamTy        (GhcPass _) = TokDcolon
 type instance XStarTy          (GhcPass _) = NoExtField
 type instance XKindSig         (GhcPass _) = TokDcolon
@@ -572,7 +572,7 @@ pprHsArrow (HsUnrestrictedArrow _) = pprArrowWithMultiplicity visArgTypeLike (Le
 pprHsArrow (HsLinearArrow _)       = pprArrowWithMultiplicity visArgTypeLike (Left True)
 pprHsArrow (HsExplicitMult _ p)    = pprArrowWithMultiplicity visArgTypeLike (Right (ppr p))
 
-type instance XConDeclField  (GhcPass _) = [AddEpAnn]
+type instance XConDeclField  (GhcPass _) = TokDcolon
 type instance XXConDeclField (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -710,23 +710,22 @@ mkHsAppKindTy at ty k = addCLocA ty k (HsAppKindTy at ty k)
 -- It returns API Annotations for any parens removed
 splitHsFunType ::
      LHsType (GhcPass p)
-  -> ( [AddEpAnn], EpAnnComments -- The locations of any parens and
+  -> ( ([EpToken "("], [EpToken ")"]) , EpAnnComments -- The locations of any parens and
                                   -- comments discarded
      , [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p))
 splitHsFunType ty = go ty
   where
-    go (L l (HsParTy an ty))
+    go (L l (HsParTy (op,cp) ty))
       = let
-          (anns, cs, args, res) = splitHsFunType ty
-          anns' = anns ++ annParen2AddEpAnn an
+          ((ops, cps), cs, args, res) = splitHsFunType ty
           cs' = cs S.<> epAnnComments l
-        in (anns', cs', args, res)
+        in ((ops++[op], cps ++ [cp]), cs', args, res)
 
     go (L ll (HsFunTy _ mult x y))
       | (anns, csy, args, res) <- splitHsFunType y
       = (anns, csy S.<> epAnnComments ll, HsScaled mult x:args, res)
 
-    go other = ([], emptyComments, [], other)
+    go other = (noAnn, emptyComments, [], other)
 
 -- | Retrieve the name of the \"head\" of a nested type application.
 -- This is somewhat like @GHC.Tc.Gen.HsType.splitHsAppTys@, but a little more


=====================================
compiler/GHC/JS/Ppr.hs
=====================================
@@ -33,7 +33,7 @@
 -- * Design
 --
 --     This module follows the architecture and style of the other backends in
---     GHC: it intances Outputable for the relevant types, creates a class that
+--     GHC: it instances Outputable for the relevant types, creates a class that
 --     describes a morphism from the IR domain to JavaScript concrete Syntax and
 --     then generates that syntax on a case by case basis.
 --


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1431,17 +1431,17 @@ overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   | {- empty -}                 { Nothing }
 
 deriv_strategy_no_via :: { LDerivStrategy GhcPs }
-  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
 
 deriv_strategy_via :: { LDerivStrategy GhcPs }
-  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs [mj AnnVia $1] $2))) }
+  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs (epTok $1) $2))) }
 
 deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) }
-  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
   | deriv_strategy_via          { Just $1 }
   | {- empty -}                 { Nothing }
 
@@ -1676,7 +1676,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
                 {% do { let { err = text "in the stand-alone deriving instance"
                                     <> colon <+> quotes (ppr $6) }
                       ; amsA' (sLL $1 $>
-                                 (DerivDecl ($4, [mj AnnDeriving $1, mj AnnInstance $3]) (mkHsWildCardBndrs $6) $2 $5)) }}
+                                 (DerivDecl ($4, (epTok $1, epTok $3)) (mkHsWildCardBndrs $6) $2 $5)) }}
 
 -----------------------------------------------------------------------------
 -- Role annotations
@@ -2343,7 +2343,7 @@ atype :: { LHsType GhcPs }
         | '(#' bar_types2 '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsA' (sLL $1 $> $ HsSumTy (AnnParen AnnParensHash (glR $1) (glR $3)) $2) } }
         | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (glR $1) $2 (glR $3)) }
-        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
+        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy (epTok $1, epTok $3) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                             ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
@@ -2559,22 +2559,22 @@ constr :: { LConDecl GhcPs }
         : forall context '=>' constr_stuff
                 {% amsA' (let (con,details) = unLoc $4 in
                   (L (comb4 $1 $2 $3 $4) (mkConDeclH98
-                                                       (mu AnnDarrow $3:(fst $ unLoc $1))
+                                                       (epUniTok $3,(fst $ unLoc $1))
                                                        con
                                                        (snd $ unLoc $1)
                                                        (Just $2)
                                                        details))) }
         | forall constr_stuff
                 {% amsA' (let (con,details) = unLoc $2 in
-                  (L (comb2 $1 $2) (mkConDeclH98 (fst $ unLoc $1)
+                  (L (comb2 $1 $2) (mkConDeclH98 (noAnn, fst $ unLoc $1)
                                                       con
                                                       (snd $ unLoc $1)
                                                       Nothing   -- No context
                                                       details))) }
 
-forall :: { Located ([AddEpAnn], Maybe [LHsTyVarBndr Specificity GhcPs]) }
-        : 'forall' tv_bndrs '.'       { sLL $1 $> ([mu AnnForall $1,mj AnnDot $3], Just $2) }
-        | {- empty -}                 { noLoc ([], Nothing) }
+forall :: { Located ((TokForall, EpToken "."), Maybe [LHsTyVarBndr Specificity GhcPs]) }
+        : 'forall' tv_bndrs '.'       { sLL $1 $> ((epUniTok $1,epTok $3), Just $2) }
+        | {- empty -}                 { noLoc (noAnn, Nothing) }
 
 constr_stuff :: { Located (LocatedN RdrName, HsConDeclH98Details GhcPs) }
         : infixtype       {% do { b <- runPV $1
@@ -2599,7 +2599,7 @@ fielddecl :: { LConDeclField GhcPs }
                                               -- A list because of   f,g :: Int
         : sig_vars '::' ctype
             {% amsA' (L (comb2 $1 $3)
-                      (ConDeclField [mu AnnDcolon $2]
+                      (ConDeclField (epUniTok $2)
                                     (reverse (map (\ln@(L l n)
                                                -> L (fromTrailingN l) $ FieldOcc noExtField (L (noTrailingN l) n)) (unLoc $1))) $3 Nothing))}
 
@@ -2618,15 +2618,15 @@ derivings :: { Located (HsDeriving GhcPs) }
 deriving :: { LHsDerivingClause GhcPs }
         : 'deriving' deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] Nothing $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) Nothing $2) }
 
         | 'deriving' deriv_strategy_no_via deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $2) $3) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $2) $3) }
 
         | 'deriving' deriv_clause_types deriv_strategy_via
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $3) $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $3) $2) }
 
 deriv_clause_types :: { LDerivClauseTys GhcPs }
         : qtycon              { let { tc = sL1a $1 $ mkHsImplicitSigType $


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon, TokRarrow,
+  TokDcolon, TokDarrow, TokRarrow, TokForall,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -410,8 +410,11 @@ getEpTokenLoc :: EpToken tok -> EpaLocation
 getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
+-- TODO:AZ: check we have all of the unicode tokens
 type TokDcolon = EpUniToken "::" "∷"
+type TokDarrow = EpUniToken "=>"  "⇒"
 type TokRarrow = EpUniToken "->" "→"
+type TokForall = EpUniToken "forall" "∀"
 
 -- | Layout information for declarations.
 data EpLayout =


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -773,12 +773,12 @@ recordPatSynErr loc pat =
     addFatalError $ mkPlainErrorMsgEnvelope loc $
       (PsErrRecordSyntaxInPatSynDecl pat)
 
-mkConDeclH98 :: [AddEpAnn] -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
+mkConDeclH98 :: (TokDarrow, (TokForall, EpToken ".")) -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
                 -> Maybe (LHsContext GhcPs) -> HsConDeclH98Details GhcPs
                 -> ConDecl GhcPs
 
-mkConDeclH98 ann name mb_forall mb_cxt args
-  = ConDeclH98 { con_ext    = ann
+mkConDeclH98 (tdarrow, (tforall,tdot)) name mb_forall mb_cxt args
+  = ConDeclH98 { con_ext    = AnnConDeclH98 tforall tdot tdarrow
                , con_name   = name
                , con_forall = isJust mb_forall
                , con_ex_tvs = mb_forall `orElse` []
@@ -795,12 +795,12 @@ mkConDeclH98 ann name mb_forall mb_cxt args
 --   Note [GADT abstract syntax] in "GHC.Hs.Decls" for more details.
 mkGadtDecl :: SrcSpan
            -> NonEmpty (LocatedN RdrName)
-           -> EpUniToken "::" "∷"
+           -> TokDcolon
            -> LHsSigType GhcPs
            -> P (LConDecl GhcPs)
 mkGadtDecl loc names dcol ty = do
 
-  (args, res_ty, annsa, csa) <-
+  (args, res_ty, (ops, cps), csa) <-
     case body_ty of
      L ll (HsFunTy _ hsArr (L (EpAnn anc _ cs) (HsRecTy an rf)) res_ty) -> do
        arr <- case hsArr of
@@ -810,10 +810,10 @@ mkGadtDecl loc names dcol ty = do
                  return noAnn
 
        return ( RecConGADT arr (L (EpAnn anc an cs) rf), res_ty
-              , [], epAnnComments ll)
+              , ([], []), epAnnComments ll)
      _ -> do
-       let (anns, cs, arg_types, res_type) = splitHsFunType body_ty
-       return (PrefixConGADT noExtField arg_types, res_type, anns, cs)
+       let ((ops, cps), cs, arg_types, res_type) = splitHsFunType body_ty
+       return (PrefixConGADT noExtField arg_types, res_type, (ops,cps), cs)
 
   let bndrs_loc = case outer_bndrs of
         HsOuterImplicit{} -> getLoc ty
@@ -822,7 +822,7 @@ mkGadtDecl loc names dcol ty = do
   let l = EpAnn (spanAsAnchor loc) noAnn csa
 
   pure $ L l ConDeclGADT
-                     { con_g_ext  = (dcol, annsa)
+                     { con_g_ext  = AnnConDeclGADT ops cps dcol
                      , con_names  = names
                      , con_bndrs  = L bndrs_loc outer_bndrs
                      , con_mb_cxt = mcxt
@@ -1079,9 +1079,7 @@ checkTyClHdr is_cls ty
       | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
-    go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
-      where
-        (o,c) = mkParensEpToks (realSrcSpan (locA l))
+    go cs l (HsParTy (o,c) ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
@@ -1098,12 +1096,12 @@ checkTyClHdr is_cls ty
 
     -- Combine the annotations from the HsParTy and HsStarTy into a
     -- new one for the LocatedN RdrName
-    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> AnnParen -> SrcSpanAnnN
-    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (AnnParen _ o c) =
+    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> (EpToken "(", EpToken ")") -> SrcSpanAnnN
+    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (o,c) =
       let
         lr = combineSrcSpans (locA l1) (locA l)
       in
-        EpAnn (EpaSpan lr) (NameAnn NameParens o ap c ta) (csp0 Semi.<> csp)
+        EpAnn (EpaSpan lr) (NameAnn NameParens (getEpTokenLoc o) ap (getEpTokenLoc c) ta) (csp0 Semi.<> csp)
 
 -- | Yield a parse error if we have a function applied directly to a do block
 -- etc. and BlockArguments is not enabled.
@@ -1171,9 +1169,9 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
             EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
             _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
-  check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
-                                  -- to be sure HsParTy doesn't get into the way
-    = check (ap_open ann':opi, ap_close ann':cpi, csi) ty
+  check (opi,cpi,csi) (L _lp1 (HsParTy (o,c) ty))
+                                             -- to be sure HsParTy doesn't get into the way
+    = check (getEpTokenLoc o:opi, getEpTokenLoc c:cpi, csi) ty
 
   -- No need for anns, returning original
   check (_opi,_cpi,_csi) _t = unprocessed


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -142,7 +142,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:5:36-49 })
@@ -190,7 +193,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:7:36-48 })
@@ -218,10 +224,11 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaSpan { Test20239.hs:7:50 })
-                   (EpaSpan { Test20239.hs:7:86 }))
+                  ((,)
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:50 }))
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:86 })))
                   (L
                    (EpAnn
                     (EpaSpan { Test20239.hs:7:51-85 })
@@ -290,10 +297,11 @@
                         (EpaComments
                          []))
                        (HsParTy
-                        (AnnParen
-                         AnnParens
-                         (EpaSpan { Test20239.hs:7:68 })
-                         (EpaSpan { Test20239.hs:7:85 }))
+                        ((,)
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:68 }))
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:85 })))
                         (L
                          (EpAnn
                           (EpaSpan { Test20239.hs:7:69-84 })


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -1110,11 +1110,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:25:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1486,11 +1487,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:31:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1862,11 +1864,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:37:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2238,11 +2241,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:43:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2614,11 +2618,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:49:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2990,11 +2995,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:55:11-12 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -101,11 +101,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T17544_kw.hs:16:15-16 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -214,11 +215,12 @@
           (EpaComments
            []))
          (ConDeclGADT
-          ((,)
+          (AnnConDeclGADT
+           []
+           []
            (EpUniTok
             (EpaSpan { T17544_kw.hs:19:15-16 })
-            (NormalSyntax))
-           [])
+            (NormalSyntax)))
           (:|
            (L
             (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -90,7 +90,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:5:5-8 })
@@ -151,7 +154,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:7:5-8 })
@@ -211,7 +217,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:9:9-10 })
@@ -339,7 +348,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:12:7-8 })
@@ -467,7 +479,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:16:3-4 })
@@ -637,7 +652,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:23:3-4 })
@@ -807,7 +825,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:28:3-8 })
@@ -844,7 +865,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:28:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:28:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:28:12-13 })
@@ -903,7 +926,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:29:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:29:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:29:12-13 })
@@ -1008,7 +1033,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:32:3-8 })
@@ -1045,7 +1073,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:33:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:33:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:33:7-8 })
@@ -1104,7 +1134,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:34:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:34:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:34:7-8 })
@@ -1221,7 +1253,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:38:3-8 })
@@ -1258,7 +1293,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:40:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:40:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:40:5-6 })
@@ -1317,7 +1354,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:42:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:42:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:42:5-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -125,7 +125,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:14-17 })
@@ -150,7 +153,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:21-24 })
@@ -356,10 +362,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:10 })
-                 (EpaSpan { DumpParsedAst.hs:11:17 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:17 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:11-16 })
@@ -454,10 +461,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:26 })
-                 (EpaSpan { DumpParsedAst.hs:11:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:26 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:27-35 })
@@ -798,7 +806,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:15:21-23 })
@@ -826,10 +837,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:15:25 })
-                 (EpaSpan { DumpParsedAst.hs:15:29 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:25 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:29 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:15:26-28 })
@@ -968,10 +980,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:17:17 })
-               (EpaSpan { DumpParsedAst.hs:17:27 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:17 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:27 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:17:18-26 })
@@ -1612,10 +1625,11 @@
             (EpaComments
              []))
            (HsParTy
-            (AnnParen
-             AnnParens
-             (EpaSpan { DumpParsedAst.hs:22:22 })
-             (EpaSpan { DumpParsedAst.hs:22:37 }))
+            ((,)
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:22 }))
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:37 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:22:23-36 })
@@ -1739,10 +1753,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:22:42 })
-               (EpaSpan { DumpParsedAst.hs:22:52 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:42 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:52 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:22:43-51 })
@@ -1822,11 +1837,12 @@
             (EpaComments
              []))
            (ConDeclGADT
-            ((,)
+            (AnnConDeclGADT
+             []
+             []
              (EpUniTok
               (EpaSpan { DumpParsedAst.hs:23:7-8 })
-              (NormalSyntax))
-             [])
+              (NormalSyntax)))
             (:|
              (L
               (EpAnn
@@ -1863,10 +1879,11 @@
                  (EpaComments
                   []))
                 (HsParTy
-                 (AnnParen
-                  AnnParens
-                  (EpaSpan { DumpParsedAst.hs:23:10 })
-                  (EpaSpan { DumpParsedAst.hs:23:34 }))
+                 ((,)
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:10 }))
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:34 })))
                  (L
                   (EpAnn
                    (EpaSpan { DumpParsedAst.hs:23:11-33 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -304,10 +304,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:11-16 })
@@ -398,10 +397,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:27-35 })
@@ -850,10 +848,9 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaDelta {  } (SameLine 0) [])
-               (EpaDelta {  } (SameLine 0) []))
+              ((,)
+               (NoEpTok)
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:19:23-36 })
@@ -966,10 +963,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:19:43-51 })
@@ -1079,10 +1075,9 @@
                    (EpaComments
                     []))
                   (HsParTy
-                   (AnnParen
-                    AnnParens
-                    (EpaDelta {  } (SameLine 0) [])
-                    (EpaDelta {  } (SameLine 0) []))
+                   ((,)
+                    (NoEpTok)
+                    (NoEpTok))
                    (L
                     (EpAnn
                      (EpaSpan { DumpRenamedAst.hs:20:11-33 })
@@ -1452,10 +1447,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:22:26-28 })
@@ -1955,10 +1949,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:24:18-26 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -831,10 +831,11 @@
              (EpaComments
               []))
             (HsParTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { KindSigs.hs:22:8 })
-              (EpaSpan { KindSigs.hs:22:20 }))
+             ((,)
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:8 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:20 })))
              (L
               (EpAnn
                (EpaSpan { KindSigs.hs:22:9-19 })
@@ -924,10 +925,11 @@
                (EpaComments
                 []))
               (HsParTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { KindSigs.hs:22:33 })
-                (EpaSpan { KindSigs.hs:22:44 }))
+               ((,)
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:33 }))
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:44 })))
                (L
                 (EpAnn
                  (EpaSpan { KindSigs.hs:22:34-43 })
@@ -1643,10 +1645,11 @@
            (EpaComments
             []))
           (HsParTy
-           (AnnParen
-            AnnParens
-            (EpaSpan { KindSigs.hs:34:9 })
-            (EpaSpan { KindSigs.hs:34:22 }))
+           ((,)
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:9 }))
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:22 })))
            (L
             (EpAnn
              (EpaSpan { KindSigs.hs:34:10-21 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -167,7 +167,7 @@
                   (EpaComments
                    []))
                  (ConDeclField
-                  []
+                  (NoEpUniTok)
                   [(L
                     (EpAnn
                      (EpaSpan { T14189.hs:6:33 })


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -116,11 +116,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T15323.hs:6:17-18 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -196,10 +197,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { T15323.hs:6:31 })
-                 (EpaSpan { T15323.hs:6:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:31 }))
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { T15323.hs:6:32-35 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -137,7 +137,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:5:26-31 })
@@ -257,7 +260,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:6:26-31 })


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -89,11 +89,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T18791.hs:5:7-8 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -63,7 +63,6 @@ import Data.Data ( Data )
 import Data.Dynamic
 import Data.Foldable
 import Data.Functor.Const
-import qualified Data.Set as Set
 import Data.Typeable
 import Data.List ( partition, sort, sortBy)
 import qualified Data.List.NonEmpty as NE
@@ -363,11 +362,11 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+instance HasTrailing (TokForall, EpUniToken "->" "→") where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+instance HasTrailing (TokForall, EpToken ".") where
   trailing _ = []
   setTrailing a _ = a
 
@@ -646,23 +645,6 @@ flushComments !trailing_anns = do
 
 -- ---------------------------------------------------------------------
 
--- |In order to interleave annotations into the stream, we turn them into
--- comments. They are removed from the annotation to avoid duplication.
-annotationsToComments :: (Monad m, Monoid w)
-  => a -> Lens a [AddEpAnn] -> [AnnKeywordId] -> EP w m a
-annotationsToComments a l kws = do
-  let (newComments, newAnns) = go ([],[]) (view l a)
-  addComments True newComments
-  return (set l (reverse newAnns) a)
-  where
-    keywords = Set.fromList kws
-
-    go :: ([Comment], [AddEpAnn]) -> [AddEpAnn] -> ([Comment], [AddEpAnn])
-    go acc [] = acc
-    go (cs',ans) ((AddEpAnn k ss) : ls)
-      | Set.member k keywords = go ((mkKWComment k (epaToNoCommentsLocation ss)):cs', ans) ls
-      | otherwise             = go (cs', (AddEpAnn k ss):ans)    ls
-
 epTokensToComments :: (Monad m, Monoid w)
   => AnnKeywordId -> [EpToken tok] -> EP w m ()
 epTokensToComments kw toks
@@ -2004,14 +1986,14 @@ instance ExactPrint (DerivDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DerivDecl (mw, an) typ ms mov) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+  exact (DerivDecl (mw, (td,ti)) typ ms mov) = do
+    td' <- markEpToken td
     ms' <- mapM markAnnotated ms
-    an1 <- markEpAnnL an0 lidl AnnInstance
+    ti' <- markEpToken ti
     mw' <- mapM markAnnotated mw
     mov' <- mapM markAnnotated mov
     typ' <- markAnnotated typ
-    return (DerivDecl (mw', an1) typ' ms' mov')
+    return (DerivDecl (mw', (td',ti')) typ' ms' mov')
 
 -- ---------------------------------------------------------------------
 
@@ -2299,7 +2281,7 @@ instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
                 , feqn_pats   = pats
                 , feqn_fixity = fixity
                 , feqn_rhs    = rhs }) = do
-    (an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
+    (_an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
     eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
     return (FamEqn { feqn_ext    = ([], [], eq')
@@ -2337,14 +2319,14 @@ exactHsFamInstLHS ops cps an thing bndrs typats fixity mb_ctxt = do
     exact_pats :: (Monad m, Monoid w)
       => [EpToken "("] -> [EpToken ")"] -> HsFamEqnPats GhcPs
       -> EP w m ([EpToken "("], [EpToken ")"], LocatedN RdrName, HsFamEqnPats GhcPs)
-    exact_pats ops cps (patl:patr:pats)
+    exact_pats ops1 cps1 (patl:patr:pats)
       | Infix <- fixity
       = let exact_op_app = do
-              ops' <- mapM markEpToken ops
+              ops' <- mapM markEpToken ops1
               patl' <- markAnnotated patl
               thing' <- markAnnotated thing
               patr' <- markAnnotated patr
-              cps' <- mapM markEpToken cps
+              cps' <- mapM markEpToken cps1
               return (ops', cps', thing', [patl',patr'])
         in case pats of
              [] -> exact_op_app
@@ -4121,11 +4103,11 @@ instance ExactPrint (HsType GhcPs) where
     lo' <- markAnnotated lo
     t2' <- markAnnotated t2
     return (HsOpTy x promoted t1' lo' t2')
-  exact (HsParTy an ty) = do
-    an0 <- markOpeningParen an
+  exact (HsParTy (o,c) ty) = do
+    o' <- markEpToken o
     ty' <- markAnnotated ty
-    an1 <- markClosingParen an0
-    return (HsParTy an1 ty')
+    c' <- markEpToken c
+    return (HsParTy (o',c') ty')
   exact (HsIParamTy an n t) = do
     n' <- markAnnotated n
     an0 <- markEpUniToken an
@@ -4216,7 +4198,7 @@ instance ExactPrint (HsDerivingClause GhcPs) where
   exact (HsDerivingClause { deriv_clause_ext      = an
                           , deriv_clause_strategy = dcs
                           , deriv_clause_tys      = dct }) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+    an0 <- markEpToken an
     dcs0 <- case dcs of
             Just (L _ ViaStrategy{}) -> return dcs
             _ -> mapM markAnnotated dcs
@@ -4235,16 +4217,16 @@ instance ExactPrint (DerivStrategy GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
   exact (StockStrategy an)    = do
-    an0 <- markEpAnnL an lid AnnStock
+    an0 <- markEpToken an
     return (StockStrategy an0)
   exact (AnyclassStrategy an) = do
-    an0 <- markEpAnnL an lid AnnAnyclass
+    an0 <- markEpToken an
     return (AnyclassStrategy an0)
   exact (NewtypeStrategy an)  = do
-    an0 <- markEpAnnL an lid AnnNewtype
+    an0 <- markEpToken an
     return (NewtypeStrategy an0)
   exact (ViaStrategy (XViaStrategyPs an ty)) = do
-    an0 <- markEpAnnL an lid AnnVia
+    an0 <- markEpToken an
     ty' <- markAnnotated ty
     return (ViaStrategy (XViaStrategyPs an0 ty'))
 
@@ -4411,27 +4393,27 @@ instance ExactPrint (ConDecl GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
 -- based on pprConDecl
-  exact (ConDeclH98 { con_ext = an
+  exact (ConDeclH98 { con_ext = AnnConDeclH98 tforall tdot tdarrow
                     , con_name = con
                     , con_forall = has_forall
                     , con_ex_tvs = ex_tvs
                     , con_mb_cxt = mcxt
                     , con_args = args
                     , con_doc = doc }) = do
-    an0 <- if has_forall
-      then markEpAnnL an lidl AnnForall
-      else return an
+    tforall' <- if has_forall
+      then markEpUniToken tforall
+      else return tforall
     ex_tvs' <- mapM markAnnotated ex_tvs
-    an1 <- if has_forall
-      then markEpAnnL an0 lidl AnnDot
-      else return an0
+    tdot' <- if has_forall
+      then markEpToken tdot
+      else return tdot
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
+    tdarrow' <- if (isJust mcxt)
+      then markEpUniToken tdarrow
+      else return tdarrow
 
     (con', args') <- exact_details args
-    return (ConDeclH98 { con_ext = an2
+    return (ConDeclH98 { con_ext = AnnConDeclH98 tforall' tdot' tdarrow'
                        , con_name = con'
                        , con_forall = has_forall
                        , con_ex_tvs = ex_tvs'
@@ -4459,14 +4441,15 @@ instance ExactPrint (ConDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ConDeclGADT { con_g_ext = (dcol, an)
+  exact (ConDeclGADT { con_g_ext = AnnConDeclGADT ops cps dcol
                      , con_names = cons
                      , con_bndrs = bndrs
                      , con_mb_cxt = mcxt, con_g_args = args
                      , con_res_ty = res_ty, con_doc = doc }) = do
     cons' <- mapM markAnnotated cons
     dcol' <- markEpUniToken dcol
-    an1 <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
 
     -- Work around https://gitlab.haskell.org/ghc/ghc/-/issues/20558
     bndrs' <- case bndrs of
@@ -4474,9 +4457,6 @@ instance ExactPrint (ConDecl GhcPs) where
       _ -> markAnnotated bndrs
 
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
     args' <-
       case args of
           (PrefixConGADT x args0) -> do
@@ -4487,7 +4467,7 @@ instance ExactPrint (ConDecl GhcPs) where
             rarr' <- markEpUniToken rarr
             return (RecConGADT rarr' fields')
     res_ty' <- markAnnotated res_ty
-    return (ConDeclGADT { con_g_ext = (dcol', an2)
+    return (ConDeclGADT { con_g_ext = AnnConDeclGADT [] [] dcol'
                         , con_names = cons'
                         , con_bndrs = bndrs'
                         , con_mb_cxt = mcxt', con_g_args = args'
@@ -4522,11 +4502,11 @@ instance ExactPrint (ConDeclField GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ConDeclField an names ftype mdoc) = do
+  exact (ConDeclField td names ftype mdoc) = do
     names' <- markAnnotated names
-    an0 <- markEpAnnL an lidl AnnDcolon
+    td' <- markEpUniToken td
     ftype' <- markAnnotated ftype
-    return (ConDeclField an0 names' ftype' mdoc)
+    return (ConDeclField td' names' ftype' mdoc)
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
 {-# LANGUAGE DerivingStrategies #-}
@@ -820,7 +821,7 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
 
 type XRecCond a =
-  ( XParTy a ~ AnnParen
+  ( XParTy a ~ (EpToken "(", EpToken ")")
   , NoGhcTc a ~ a
   , MapXRec a
   , UnXRec a
@@ -852,7 +853,7 @@ type instance XListTy DocNameI = EpAnn AnnParen
 type instance XTupleTy DocNameI = EpAnn AnnParen
 type instance XSumTy DocNameI = EpAnn AnnParen
 type instance XOpTy DocNameI = EpAnn [AddEpAnn]
-type instance XParTy DocNameI = AnnParen
+type instance XParTy DocNameI = (EpToken "(", EpToken ")")
 type instance XIParamTy DocNameI = EpAnn [AddEpAnn]
 type instance XKindSig DocNameI = EpAnn [AddEpAnn]
 type instance XSpliceTy DocNameI = DataConCantHappen



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/395c02ad803917d011050115cf9c152c05c0a58f...e44633ef60d86e33784e8198373f768d89e1882a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/395c02ad803917d011050115cf9c152c05c0a58f...e44633ef60d86e33784e8198373f768d89e1882a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 19 18:45:24 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sat, 19 Oct 2024 14:45:24 -0400
Subject: [Git][ghc/ghc][wip/backports-9.8] testsuite: Elide progress output
 from bkpfail{16,18,19}
Message-ID: <6713fe4428d67_185c05146fcc3829c@gitlab.mail>



Ben Gamari pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
b6639a64 by Ben Gamari at 2024-10-19T14:22:45-04:00
testsuite: Elide progress output from bkpfail{16,18,19}

These tests are seemingly testing the error message, not the progress
output and the latter contains filenames with unstable hashes.

- - - - -


4 changed files:

- testsuite/tests/backpack/should_fail/all.T
- testsuite/tests/backpack/should_fail/bkpfail16.stderr
- testsuite/tests/backpack/should_fail/bkpfail17.stderr
- testsuite/tests/backpack/should_fail/bkpfail19.stderr


Changes:

=====================================
testsuite/tests/backpack/should_fail/all.T
=====================================
@@ -11,10 +11,10 @@ test('bkpfail12', normal, backpack_compile_fail, [''])
 test('bkpfail13', normal, backpack_compile_fail, [''])
 test('bkpfail14', normal, backpack_compile_fail, [''])
 test('bkpfail15', normal, backpack_compile_fail, [''])
-test('bkpfail16', normalise_version('base'), backpack_compile_fail, [''])
-test('bkpfail17', normalise_version('base'), backpack_compile_fail, [''])
+test('bkpfail16', normalise_version('base'), backpack_compile_fail, ['-v0'])
+test('bkpfail17', normalise_version('base'), backpack_compile_fail, ['-v0'])
 test('bkpfail18', normal, backpack_compile_fail, [''])
-test('bkpfail19', normalise_version('base'), backpack_compile_fail, [''])
+test('bkpfail19', normalise_version('base'), backpack_compile_fail, ['-v0'])
 test('bkpfail20', normal, backpack_compile_fail, [''])
 test('bkpfail21', normal, backpack_compile_fail, [''])
 test('bkpfail22', normal, backpack_compile_fail, [''])


=====================================
testsuite/tests/backpack/should_fail/bkpfail16.stderr
=====================================
@@ -1,10 +1,4 @@
-[1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
-[2 of 2] Processing q
-  Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.Bool]
-    Instantiating p[ShouldFail=base-4.19.1.0:Data.Bool]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail16.out/p/p-IWIH695NuFKHfA9JCzN8tU/ShouldFail.o )
 
-: error:
-    Something is amiss; requested module  base-4.19.1.0-inplace:Data.Bool differs from name found in the interface file base:Data.Bool (if these names look the same, try again with -dppr-debug)
+bkpfail16.out/p/p-1OqLaT7dAn947wScQQKCw5/../ShouldFail.hi:1:1: error: [GHC-93011]
+    • ‘Booly’ is exported by the hsig file, but not exported by the implementing module ‘Data.Bool’
+    • While checking that ‘Data.Bool’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.Bool]’.


=====================================
testsuite/tests/backpack/should_fail/bkpfail17.stderr
=====================================
@@ -1,10 +1,11 @@
-[1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
-[2 of 2] Processing q
-  Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Prelude]
-    Instantiating p[ShouldFail=base-4.19.1.0:Prelude]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail17.out/p/p-9af3lmxJNZa50ZueXSR02Y/ShouldFail.o )
 
-: error:
-    Something is amiss; requested module  base-4.19.1.0-inplace:Prelude differs from name found in the interface file base:Prelude (if these names look the same, try again with -dppr-debug)
+: error: [GHC-15843]
+    • Type constructor ‘Either’ has conflicting definitions in the module
+      and its hsig file.
+      Main module: type Either :: * -> * -> *
+                   data Either a b = Left a | Right b
+        Hsig file: type role Either representational phantom phantom
+                   type Either :: * -> * -> * -> *
+                   data Either a b c = Left a
+      The types have different kinds.
+    • While checking that ‘Prelude’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Prelude]’.


=====================================
testsuite/tests/backpack/should_fail/bkpfail19.stderr
=====================================
@@ -1,10 +1,5 @@
-[1 of 2] Processing p
-  [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, nothing )
-[2 of 2] Processing q
-  Instantiating q
-  [1 of 1] Including p[ShouldFail=base-4.19.1.0:Data.STRef]
-    Instantiating p[ShouldFail=base-4.19.1.0:Data.STRef]
-    [1 of 1] Compiling ShouldFail[sig]  ( p/ShouldFail.hsig, bkpfail19.out/p/p-Ak3HDozWrn3BPHIdYYNht5/ShouldFail.o )
 
-: error:
-    Something is amiss; requested module  base-4.19.1.0-inplace:Data.STRef differs from name found in the interface file base:Data.STRef (if these names look the same, try again with -dppr-debug)
+: error: [GHC-12424]
+    • The hsig file (re)exports ‘Data.STRef.Lazy.newSTRef’
+      but the implementing module exports a different identifier ‘GHC.STRef.newSTRef’
+    • While checking that ‘Data.STRef’ implements signature ‘ShouldFail’ in ‘p[ShouldFail=Data.STRef]’.



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 01:57:21 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 21:57:21 -0400
Subject: [Git][ghc/ghc][master] ci: Add support for ONLY_JOBS variable to
 trigger any validation pipeline
Message-ID: <67146381a9e83_21c73610c3cac1244a5@gitlab.mail>



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


Commits:
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -


2 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -548,8 +548,8 @@ data OnOffRules = OnOffRules { rule_set :: Rule -- ^ The enabled rules
                              }
 
 -- The initial set of rules, which assumes a Validate pipeline which is run with FullCI.
-emptyRules :: OnOffRules
-emptyRules = OnOffRules (ValidateOnly (S.singleton FullCI)) OnSuccess
+emptyRules :: String -> OnOffRules
+emptyRules jobName = OnOffRules (ValidateOnly jobName (S.fromList [FullCI])) OnSuccess
 
 -- When to run the job
 data ManualFlag = Manual -- ^ Only run the job when explicitly triggered by a user
@@ -566,10 +566,10 @@ onlyValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
 onlyValidateRule r  = modifyValidateRules (const (S.singleton r))
 
 removeValidateRule :: ValidateRule -> OnOffRules -> OnOffRules
-removeValidateRule r = modifyValidateRules (S.delete r)
+removeValidateRule v = modifyValidateRules (S.delete v)
 
 modifyValidateRules :: (S.Set ValidateRule -> S.Set ValidateRule) -> OnOffRules -> OnOffRules
-modifyValidateRules f (OnOffRules (ValidateOnly rs) m) = OnOffRules (ValidateOnly (f rs)) m
+modifyValidateRules f (OnOffRules (ValidateOnly s rs) m) = OnOffRules (ValidateOnly s (f rs)) m
 modifyValidateRules _ r = error $ "Applying validate rule to nightly/release job:" ++ show (rule_set r)
 
 manualRule :: OnOffRules -> OnOffRules
@@ -582,13 +582,13 @@ enumRules :: OnOffRules -> [OnOffRule]
 enumRules (OnOffRules r _) = rulesList
   where
     rulesList = case r of
-                  ValidateOnly rs -> [OnOffRule On (ValidateOnly rs)
+                  ValidateOnly s rs -> [OnOffRule On (ValidateOnly s rs)
                                     , OnOffRule Off ReleaseOnly
                                     , OnOffRule Off Nightly ]
-                  Nightly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  Nightly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                              , OnOffRule Off ReleaseOnly
                              , OnOffRule On Nightly ]
-                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly S.empty)
+                  ReleaseOnly -> [ OnOffRule Off (ValidateOnly "" S.empty)
                                  , OnOffRule On ReleaseOnly
                                  , OnOffRule Off Nightly ]
 
@@ -626,11 +626,12 @@ or_all rs = intercalate " || " (map parens rs)
 -- run the job.
 data Rule = ReleaseOnly  -- ^ Only run this job in a release pipeline
           | Nightly      -- ^ Only run this job in the nightly pipeline
-          | ValidateOnly (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
+          | ValidateOnly String (S.Set ValidateRule) -- ^ Only run this job in a validate pipeline, when any of these rules are enabled.
           deriving (Show, Ord, Eq)
 
 data ValidateRule =
             FullCI       -- ^ Run this job when the "full-ci" label is present.
+          | FastCI       -- ^ Run this job on every validation pipeline
           | LLVMBackend  -- ^ Run this job when the "LLVM backend" label is present
           | JSBackend    -- ^ Run this job when the "javascript" label is present
           | RiscV        -- ^ Run this job when the "RISC-V" label is present
@@ -640,7 +641,7 @@ data ValidateRule =
           | IpeData      -- ^ Run this job when the "IPE" label is set
           | TestPrimops  -- ^ Run this job when "test-primops" label is set
           | I386Backend  -- ^ Run this job when the "i386" label is set
-          deriving (Show, Enum, Bounded, Ord, Eq)
+          deriving (Show, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
 -- expression language.
@@ -653,25 +654,43 @@ _false = "\"disabled\" != \"disabled\""
 
 -- Convert the state of the rule into a string that gitlab understand.
 ruleString :: OnOff -> Rule -> String
-ruleString On (ValidateOnly vs) =
-  case S.toList vs of
-    [] -> true
-    conds -> or_all (map validateRuleString conds)
+ruleString On (ValidateOnly only_job_name vs) =
+  let conds = S.toList vs
+      empty_only_job = envVarNull "ONLY_JOBS"
+      run_cond = case conds of
+                  [] -> _false
+                  cs -> or_all (map validateRuleString conds)
+      escape :: String -> String
+      escape = concatMap (\c -> if c == '+' then "\\+" else [c])
+
+  in
+    or_all  [
+    -- 1. Case when ONLY_JOBS is set
+      and_all [ "$ONLY_JOBS", "$ONLY_JOBS =~ /.*\\b" ++  escape only_job_name ++ "(\\s|$).*/" ]
+    -- 2. Case when ONLY_JOBS is null
+    , and_all [ empty_only_job, run_cond ]
+    ]
 ruleString Off (ValidateOnly {}) = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
-ruleString Off Nightly = "$NIGHTLY == null"
+ruleString Off Nightly = envVarNull "NIGHTLY"
 
 labelString :: String -> String
 labelString s =  "$CI_MERGE_REQUEST_LABELS =~ /.*" ++ s ++ ".*/"
 
 branchStringExact :: String -> String
-branchStringExact s = "$CI_COMMIT_BRANCH == \"" ++ s ++ "\""
+branchStringExact s = envVarString "CI_COMMIT_BRANCH" s
 
 branchStringLike :: String -> String
 branchStringLike s = "$CI_COMMIT_BRANCH =~ /" ++ s ++ "/"
 
+envVarString :: String -> String -> String
+envVarString var s = "$" ++ var ++ " == \"" ++ s ++ "\""
+
+envVarNull :: String ->  String
+envVarNull var = "$" ++ var ++ " == null"
+
 
 validateRuleString :: ValidateRule -> String
 validateRuleString FullCI = or_all ([ labelString "full-ci"
@@ -679,6 +698,7 @@ validateRuleString FullCI = or_all ([ labelString "full-ci"
                                     , branchStringExact "master"
                                     , branchStringLike "ghc-[0-9]+\\.[0-9]+"
                                     ])
+validateRuleString FastCI = true
 
 validateRuleString LLVMBackend  = labelString "LLVM backend"
 validateRuleString JSBackend    = labelString "javascript"
@@ -736,7 +756,7 @@ job arch opsys buildConfig = NamedJob { name = jobName, jobInfo = Job {..} }
   where
     jobPlatform = (arch, opsys)
 
-    jobRules = emptyRules
+    jobRules = emptyRules jobName
 
     jobName = testEnv arch opsys buildConfig
 
@@ -928,7 +948,7 @@ perfProfilingJobTag arch opsys j = j { jobTags = [ runnerPerfTag arch opsys ] }
 -- | Mark the validate job to run in fast-ci mode
 -- This is default way, to enable all jobs you have to apply the `full-ci` label.
 fastCI :: JobGroup Job -> JobGroup Job
-fastCI = modifyValidateJobs (removeValidateJobRule FullCI)
+fastCI = onlyRule FastCI
 
 -- | Mark a group of jobs as allowed to fail.
 allowFailureGroup :: JobGroup Job -> JobGroup Job
@@ -945,8 +965,10 @@ onlyRule t = modifyValidateJobs (onlyValidateJobRule t)
 
 -- | Don't run the validate job, normally used to alleviate CI load by marking
 -- jobs which are unlikely to fail (ie different linux distros)
+--
+-- These jobs can still be triggered by using the ONLY_JOBS environment variable
 disableValidate :: JobGroup Job -> JobGroup Job
-disableValidate st = st { v = Nothing }
+disableValidate = modifyValidateJobs (removeValidateJobRule FastCI . removeValidateJobRule FullCI)
 
 data NamedJob a = NamedJob { name :: String, jobInfo :: a } deriving (Show, Functor)
 


=====================================
.gitlab/jobs.yaml
=====================================
@@ -37,7 +37,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-darwin-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -66,6 +66,131 @@
       "TEST_ENV": "aarch64-darwin-validate"
     }
   },
+  "aarch64-linux-alpine3_18-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-alpine3_18-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-alpine3_18-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-alpine3_18:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-alpine3_18-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-alpine3_18-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-alpine3_18-validate"
+    }
+  },
+  "aarch64-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-aarch64-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "aarch64-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "aarch64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-aarch64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "aarch64-linux-deb10-validate"
+    }
+  },
   "aarch64-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -103,7 +228,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -165,7 +290,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\baarch64-linux-deb12-validate\\+llvm(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -190,6 +315,68 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-deb10-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-deb10-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-deb10-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-deb10:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-deb10-validate"
+    }
+  },
   "i386-linux-deb12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -227,7 +414,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*i386.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*i386.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4810,7 +4997,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-darwin-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4842,18 +5029,18 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-linux-alpine3_12-validate+fully_static": {
+  "x86_64-linux-alpine3_12-int_native-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": false,
+    "allow_failure": true,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4879,7 +5066,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-int_native-validate\\+fully_static(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4895,17 +5082,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-int_native-validate+fully_static",
       "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
       "BUILD_FLAVOUR": "validate+fully_static",
       "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
+      "TEST_ENV": "x86_64-linux-alpine3_12-int_native-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4916,7 +5103,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4926,14 +5113,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -4942,7 +5129,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -4959,16 +5146,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate"
     }
   },
-  "x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_12-validate+fully_static": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -4979,7 +5166,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_12-validate+fully_static.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -4989,14 +5176,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5005,9 +5192,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_12-validate\\+fully_static(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5022,17 +5208,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_12-validate+fully_static",
+      "BROKEN_TESTS": "ghcilink002 linker_unload_native encoding004 T10458",
+      "BUILD_FLAVOUR": "validate+fully_static",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static"
     }
   },
-  "x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
+  "x86_64-linux-alpine3_20-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5043,7 +5229,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
+        "ghc-x86_64-linux-alpine3_20-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5053,14 +5239,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_20-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5069,9 +5255,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5087,16 +5272,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
-      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
-      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
-      "CROSS_TARGET": "wasm32-wasi",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
+      "TEST_ENV": "x86_64-linux-alpine3_20-validate"
     }
   },
-  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
+  "x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5107,7 +5292,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5117,14 +5302,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5133,7 +5318,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release\\+host_fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5150,17 +5335,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
-      "CROSS_TARGET": "aarch64-linux-gnu",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5171,7 +5355,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5181,14 +5365,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5197,8 +5381,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release\\+host_fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5214,18 +5399,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CONFIGURE_WRAPPER": "emconfigure",
-      "CROSS_EMULATOR": "js-emulator",
-      "CROSS_TARGET": "javascript-unknown-ghcjs",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-int_native-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb12-int_native-validate": {
+  "x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5236,7 +5419,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
+        "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5246,14 +5429,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-alpine3_20-wasm-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_20-wasm:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5262,8 +5445,9 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "on_success"
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release\\+host_fully_static\\+text_simdutf(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*wasm.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
       }
     ],
     "script": [
@@ -5278,16 +5462,17 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf",
+      "BUILD_FLAVOUR": "release+host_fully_static+text_simdutf",
+      "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check",
+      "CROSS_TARGET": "wasm32-wasi",
+      "HADRIAN_ARGS": "--docs=none",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
+      "TEST_ENV": "x86_64-linux-alpine3_20-wasm-unreg-cross_wasm32-wasi-release+host_fully_static+text_simdutf"
     }
   },
-  "x86_64-linux-deb12-no_tntc-validate": {
+  "x86_64-linux-centos7-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5298,7 +5483,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
+        "ghc-x86_64-linux-centos7-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5308,14 +5493,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-centos7-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-centos7:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5324,9 +5509,8 @@
     ],
     "rules": [
       {
-        "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
-        "when": "manual"
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-centos7-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
       }
     ],
     "script": [
@@ -5342,15 +5526,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-centos7-validate",
+      "BROKEN_TESTS": "T22012",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=no-sphinx",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
+      "TEST_ENV": "x86_64-linux-centos7-validate"
     }
   },
-  "x86_64-linux-deb12-numa-slow-validate": {
+  "x86_64-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5361,7 +5547,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5371,14 +5557,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5387,7 +5573,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5404,16 +5590,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
-      "BUILD_FLAVOUR": "slow-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate"
     }
   },
-  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+  "x86_64-linux-deb10-validate+debug_info": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5424,7 +5609,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "ghc-x86_64-linux-deb10-validate+debug_info.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5434,14 +5619,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "key": "x86_64-linux-deb10-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5450,7 +5635,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb10-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5467,17 +5652,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
-      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
-      "CROSS_TARGET": "riscv64-linux-gnu",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb10-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+      "TEST_ENV": "x86_64-linux-deb10-validate+debug_info"
     }
   },
-  "x86_64-linux-deb12-unreg-validate": {
+  "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5488,7 +5671,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5498,14 +5681,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5514,7 +5697,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-cross_aarch64-linux-gnu-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5531,15 +5714,17 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-cross_aarch64-linux-gnu-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-aarch64 -L /usr/aarch64-linux-gnu",
+      "CROSS_TARGET": "aarch64-linux-gnu",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+      "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb12-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5550,7 +5735,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5560,14 +5745,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5576,7 +5761,7 @@
     ],
     "rules": [
       {
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*javascript.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5592,16 +5777,19 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CONFIGURE_WRAPPER": "emconfigure",
+      "CROSS_EMULATOR": "js-emulator",
+      "CROSS_TARGET": "javascript-unknown-ghcjs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
-  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+  "x86_64-linux-deb11-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5612,7 +5800,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "ghc-x86_64-linux-deb11-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5622,14 +5810,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "key": "x86_64-linux-deb11-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5638,7 +5826,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb11-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5655,15 +5843,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
-      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
-      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb11-validate"
     }
   },
-  "x86_64-linux-deb12-validate+llvm": {
+  "x86_64-linux-deb12-int_native-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5674,7 +5862,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "ghc-x86_64-linux-deb12-int_native-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5700,7 +5888,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-int_native-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5716,27 +5904,27 @@
       "x86_64-linux"
     ],
     "variables": {
-      "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
-      "BUILD_FLAVOUR": "validate+llvm",
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+      "TEST_ENV": "x86_64-linux-deb12-int_native-validate"
     }
   },
-  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+  "x86_64-linux-deb12-no_tntc-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
       ".gitlab/ci.sh clean",
       "cat ci_timings"
     ],
-    "allow_failure": true,
+    "allow_failure": false,
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "ghc-x86_64-linux-deb12-no_tntc-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5763,7 +5951,7 @@
     "rules": [
       {
         "allow_failure": true,
-        "if": "((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-no_tntc-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "manual"
       }
     ],
@@ -5780,17 +5968,15 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
-      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "HADRIAN_ARGS": "--docs=none",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-no_tntc-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-tables-next-to-code --enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
-      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+      "TEST_ENV": "x86_64-linux-deb12-no_tntc-validate"
     }
   },
-  "x86_64-linux-deb12-zstd-validate": {
+  "x86_64-linux-deb12-numa-slow-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5801,7 +5987,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "ghc-x86_64-linux-deb12-numa-slow-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5827,7 +6013,7 @@
     ],
     "rules": [
       {
-        "if": "(($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-numa-slow-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5844,15 +6030,16 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
-      "BUILD_FLAVOUR": "validate",
-      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-numa-slow-validate",
+      "BUILD_FLAVOUR": "slow-validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "ENABLE_NUMA": "1",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+      "TEST_ENV": "x86_64-linux-deb12-numa-slow-validate"
     }
   },
-  "x86_64-linux-fedora33-release": {
+  "x86_64-linux-deb12-release-perf": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5863,7 +6050,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "ghc-x86_64-linux-deb12-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5873,14 +6060,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "key": "x86_64-linux-deb12-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5889,7 +6076,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],
@@ -5902,18 +6089,1082 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-linux"
+      "x86_64-linux-perf"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-release",
       "BUILD_FLAVOUR": "release",
       "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
-      "LLC": "/bin/false",
-      "OPT": "/bin/false",
-      "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-fedora33-release"
+      "RUNTEST_ARGS": " --config perf_path=perf",
+      "TEST_ENV": "x86_64-linux-deb12-release"
+    }
+  },
+  "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-riscv-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12-riscv:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*RISC-V.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
+      "CROSS_EMULATOR": "qemu-riscv64 -L /usr/riscv64-linux-gnu",
+      "CROSS_TARGET": "riscv64-linux-gnu",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-riscv-cross_riscv64-linux-gnu-validate"
+    }
+  },
+  "x86_64-linux-deb12-unreg-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-unreg-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-unreg-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-unreg-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-unregisterised --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-unreg-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/)) || ($CI_MERGE_REQUEST_LABELS =~ /.*test-primops.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate"
+    }
+  },
+  "x86_64-linux-deb12-validate+boot_nonmoving_gc": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+boot_nonmoving_gc(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*non-moving GC.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+boot_nonmoving_gc",
+      "BUILD_FLAVOUR": "validate+boot_nonmoving_gc",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "--way=nonmoving --way=nonmoving_thr --way=nonmoving_thr_sanity",
+      "TEST_ENV": "x86_64-linux-deb12-validate+boot_nonmoving_gc"
+    }
+  },
+  "x86_64-linux-deb12-validate+llvm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+llvm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+llvm(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+llvm",
+      "BUILD_FLAVOUR": "validate+llvm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+llvm"
+    }
+  },
+  "x86_64-linux-deb12-validate+thread_sanitizer_cmm": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "allow_failure": true,
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-validate\\+thread_sanitizer_cmm(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "manual"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "BUILD_FLAVOUR": "validate+thread_sanitizer_cmm",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--docs=none",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-validate+thread_sanitizer_cmm",
+      "TSAN_OPTIONS": "suppressions=$CI_PROJECT_DIR/rts/.tsan-suppressions"
+    }
+  },
+  "x86_64-linux-deb12-zstd-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb12-zstd-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb12-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb12:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb12-zstd-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (($CI_MERGE_REQUEST_LABELS =~ /.*IPE.*/)))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb12-zstd-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-ipe-data-compression --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb12-zstd-validate"
+    }
+  },
+  "x86_64-linux-deb9-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-deb9-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-deb9-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-deb9-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb9-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-deb9-validate"
+    }
+  },
+  "x86_64-linux-fedora33-release": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-release-hackage": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-release.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-release(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-release",
+      "BUILD_FLAVOUR": "release",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--haddock-for-hackage",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-release"
+    }
+  },
+  "x86_64-linux-fedora33-validate+debug_info": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora33-validate+debug_info.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora33-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora33-validate\\+debug_info(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora33-validate+debug_info",
+      "BUILD_FLAVOUR": "validate+debug_info",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LLC": "/bin/false",
+      "OPT": "/bin/false",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora33-validate+debug_info"
+    }
+  },
+  "x86_64-linux-fedora38-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-fedora38-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-fedora38-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora38:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-fedora38-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-fedora38-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-fedora38-validate"
+    }
+  },
+  "x86_64-linux-rocky8-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-rocky8-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-rocky8-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-rocky8:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-rocky8-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-rocky8-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-rocky8-validate"
+    }
+  },
+  "x86_64-linux-ubuntu18_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu18_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu18_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu18_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu18_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu18_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu18_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu20_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu20_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu20_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu20_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu20_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu20_04-validate"
+    }
+  },
+  "x86_64-linux-ubuntu22_04-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-linux-ubuntu22_04-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "x86_64-linux-ubuntu22_04-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu22_04:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-linux-ubuntu22_04-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-ubuntu22_04-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-linux-ubuntu22_04-validate"
+    }
+  },
+  "x86_64-windows-int_native-validate": {
+    "after_script": [
+      "bash .gitlab/ci.sh save_cache",
+      "bash .gitlab/ci.sh save_test_output",
+      "bash .gitlab/ci.sh clean"
+    ],
+    "allow_failure": false,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-x86_64-windows-int_native-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "no-caching",
+      "paths": []
+    },
+    "dependencies": [],
+    "image": null,
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-int_native-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && (\"disabled\" != \"disabled\"))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "bash .gitlab/ci.sh setup",
+      "bash .gitlab/ci.sh configure",
+      "bash .gitlab/ci.sh build_hadrian",
+      "bash .gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "new-x86_64-windows"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "native",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-validate",
+      "BUILD_FLAVOUR": "validate",
+      "CABAL_INSTALL_VERSION": "3.10.2.0",
+      "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "GHC_VERSION": "9.6.4",
+      "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
+      "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
+      "LANG": "en_US.UTF-8",
+      "MSYSTEM": "CLANG64",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "x86_64-windows-int_native-validate"
     }
   },
   "x86_64-windows-validate": {
@@ -5949,7 +7200,7 @@
     ],
     "rules": [
       {
-        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bx86_64-windows-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((\"true\" == \"true\")))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
         "when": "on_success"
       }
     ],



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 01:57:54 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 21:57:54 -0400
Subject: [Git][ghc/ghc][master] rel-eng: ghcup metadata generation: generated
 yaml anchors with meaningful names
Message-ID: <671463a2bfe6c_21c73610447901279b4@gitlab.mail>



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


Commits:
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -


1 changed file:

- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py


Changes:

=====================================
.gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
=====================================
@@ -67,6 +67,7 @@ class Artifact(NamedTuple):
     download_name: str
     output_name: str
     subdir: str
+    anchor_name: str
 
 # Platform spec provides a specification which is agnostic to Job
 # PlatformSpecs are converted into Artifacts by looking in the jobs-metadata.json file.
@@ -77,11 +78,13 @@ class PlatformSpec(NamedTuple):
 source_artifact = Artifact('source-tarball'
                           , 'ghc-{version}-src.tar.xz'
                           , 'ghc-{version}-src.tar.xz'
-                          , 'ghc-{version}' )
+                          , 'ghc-{version}'
+                          , 'ghc{version}-src')
 test_artifact = Artifact('source-tarball'
                         , 'ghc-{version}-testsuite.tar.xz'
                         , 'ghc-{version}-testsuite.tar.xz'
-                        , 'ghc-{version}/testsuite' )
+                        , 'ghc-{version}/testsuite'
+                        , 'ghc{version}-testsuite')
 
 def debian(n, arch='x86_64'):
     return linux_platform(arch, "{arch}-linux-deb{n}".format(arch=arch, n=n))
@@ -132,6 +135,8 @@ def download_and_hash(url):
     hash_cache[url] = digest
     return digest
 
+uri_to_anchor_cache=dict()
+
 # Make the metadata for one platform.
 def mk_one_metadata(release_mode, version, job_map, artifact):
     job_id = job_map[artifact.job_name].id
@@ -169,6 +174,9 @@ def mk_one_metadata(release_mode, version, job_map, artifact):
         res["dlOutput"] = output
 
     eprint(res)
+
+    # add the uri to the anchor name cache so we can lookup an anchor for this uri
+    uri_to_anchor_cache[final_url] = artifact.anchor_name
     return res
 
 # Turns a platform into an Artifact respecting pipeline_type
@@ -179,7 +187,8 @@ def mk_from_platform(pipeline_type, platform):
     return Artifact(info['name']
                    , f"{info['jobInfo']['bindistName']}.tar.xz"
                    , "ghc-{version}-{pn}.tar.xz".format(version="{version}", pn=platform.name)
-                   , platform.subdir)
+                   , platform.subdir
+                   , f"ghc{{version}}-{platform.name}")
 
 
 # Generate the new metadata for a specific GHC mode etc
@@ -297,6 +306,19 @@ def setNightlyTags(ghcup_metadata):
             ghcup_metadata['ghcupDownloads']['GHC'][version]["viTags"].append("Nightly")
 
 
+def mk_dumper(version):
+  class CustomAliasDumper(yaml.Dumper):
+      def __init__(self, *args, **kwargs):
+          super().__init__(*args, **kwargs)
+
+      def generate_anchor(self, node):
+          if isinstance(node, yaml.MappingNode):
+            node_dict = { k.value : v.value for (k,v) in node.value }
+            if 'dlUri' in node_dict:
+              return uri_to_anchor_cache[node_dict['dlUri']].format(version=version.replace('.',''))
+          return super().generate_anchor(node)
+
+  return CustomAliasDumper
 
 
 def main() -> None:
@@ -332,7 +354,7 @@ def main() -> None:
 
     new_yaml = mk_new_yaml(args.release_mode, args.version, args.date, pipeline_type, job_map)
     if args.fragment:
-        print(yaml.dump({ args.version : new_yaml }))
+        print(yaml.dump({ args.version : new_yaml }, Dumper=mk_dumper(args.version)))
 
     else:
         with open(args.metadata, 'r') as file:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/280b627869da55a22b4b9a3458e6115b06b5fff4

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 01:58:50 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 19 Oct 2024 21:58:50 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove [AddEpAnn] Commit 4
Message-ID: <671463da46071_21c736fc29d4128140@gitlab.mail>



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


Commits:
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -


22 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/ThToHs.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -31,8 +31,10 @@ module GHC.Hs.Decls (
 
   -- ** Class or type declarations
   TyClDecl(..), LTyClDecl, DataDeclRn(..),
+  AnnDataDefn(..),
   AnnClassDecl(..),
   AnnSynDecl(..),
+  AnnFamilyDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -359,7 +361,7 @@ type instance XSynDecl      GhcPs = AnnSynDecl
 type instance XSynDecl      GhcRn = NameSet -- FVs
 type instance XSynDecl      GhcTc = NameSet -- FVs
 
-type instance XDataDecl     GhcPs = [AddEpAnn]
+type instance XDataDecl     GhcPs = NoExtField
 type instance XDataDecl     GhcRn = DataDeclRn
 type instance XDataDecl     GhcTc = DataDeclRn
 
@@ -379,9 +381,27 @@ type instance XClassDecl    GhcTc = NameSet -- FVs
 
 type instance XXTyClDecl    (GhcPass _) = DataConCantHappen
 
-type instance XCTyFamInstDecl (GhcPass _) = [AddEpAnn]
+type instance XCTyFamInstDecl (GhcPass _) = (EpToken "type", EpToken "instance")
 type instance XXTyFamInstDecl (GhcPass _) = DataConCantHappen
 
+data AnnDataDefn
+  = AnnDataDefn {
+      andd_openp    :: [EpToken "("],
+      andd_closep   :: [EpToken ")"],
+      andd_type     :: EpToken "type",
+      andd_newtype  :: EpToken "newtype",
+      andd_data     :: EpToken "data",
+      andd_instance :: EpToken "instance",
+      andd_dcolon   :: TokDcolon,
+      andd_where    :: EpToken "where",
+      andd_openc    :: EpToken "{",
+      andd_closec   :: EpToken "}",
+      andd_equal    :: EpToken "="
+  } deriving Data
+
+instance NoAnn AnnDataDefn where
+  noAnn = AnnDataDefn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
+
 data AnnClassDecl
   = AnnClassDecl {
       acd_class  :: EpToken "class",
@@ -559,7 +579,7 @@ pprTyClDeclFlavour (DataDecl { tcdDataDefn = HsDataDefn { dd_cons = nd } })
 instance OutputableBndrId p => Outputable (FunDep (GhcPass p)) where
   ppr = pprFunDep
 
-type instance XCFunDep    (GhcPass _) = [AddEpAnn]
+type instance XCFunDep    (GhcPass _) = TokRarrow
 type instance XXFunDep    (GhcPass _) = DataConCantHappen
 
 pprFundeps :: OutputableBndrId p => [FunDep (GhcPass p)] -> SDoc
@@ -593,9 +613,27 @@ type instance XCKindSig         (GhcPass _) = NoExtField
 type instance XTyVarSig         (GhcPass _) = NoExtField
 type instance XXFamilyResultSig (GhcPass _) = DataConCantHappen
 
-type instance XCFamilyDecl    (GhcPass _) = [AddEpAnn]
+type instance XCFamilyDecl    (GhcPass _) = AnnFamilyDecl
 type instance XXFamilyDecl    (GhcPass _) = DataConCantHappen
 
+data AnnFamilyDecl
+  = AnnFamilyDecl {
+      afd_openp  :: [EpToken "("],
+      afd_closep :: [EpToken ")"],
+      afd_type   :: EpToken "type",
+      afd_data   :: EpToken "data",
+      afd_family :: EpToken "family",
+      afd_dcolon :: TokDcolon,
+      afd_equal  :: EpToken "=",
+      afd_vbar   :: EpToken "|",
+      afd_where  :: EpToken "where",
+      afd_openc  :: EpToken "{",
+      afd_dotdot :: EpToken "..",
+      afd_closec :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnFamilyDecl where
+  noAnn = AnnFamilyDecl noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 ------------- Functions over FamilyDecls -----------
 
@@ -620,7 +658,7 @@ resultVariableName _                = Nothing
 
 ------------- Pretty printing FamilyDecls -----------
 
-type instance XCInjectivityAnn  (GhcPass _) = [AddEpAnn]
+type instance XCInjectivityAnn  (GhcPass _) = TokRarrow
 type instance XXInjectivityAnn  (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -664,7 +702,7 @@ instance OutputableBndrId p
 *                                                                      *
 ********************************************************************* -}
 
-type instance XCHsDataDefn    (GhcPass _) = NoExtField
+type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
 type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
@@ -854,7 +892,7 @@ ppr_con_names = pprWithCommas (pprPrefixOcc . unLoc)
 ************************************************************************
 -}
 
-type instance XCFamEqn    (GhcPass _) r = [AddEpAnn]
+type instance XCFamEqn    (GhcPass _) r = ([EpToken "("], [EpToken ")"], EpToken "=")
 type instance XXFamEqn    (GhcPass _) r = DataConCantHappen
 
 ----------------- Class instances -------------
@@ -1145,7 +1183,7 @@ mapDerivStrategy f ds = foldDerivStrategy ds (ViaStrategy . f) ds
 ************************************************************************
 -}
 
-type instance XCDefaultDecl    GhcPs = [AddEpAnn]
+type instance XCDefaultDecl    GhcPs = (EpToken "default", EpToken "(", EpToken ")")
 type instance XCDefaultDecl    GhcRn = NoExtField
 type instance XCDefaultDecl    GhcTc = NoExtField
 
@@ -1233,7 +1271,7 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XCRuleDecls    GhcPs = ([AddEpAnn], SourceText)
+type instance XCRuleDecls    GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XCRuleDecls    GhcRn = SourceText
 type instance XCRuleDecls    GhcTc = SourceText
 
@@ -1318,7 +1356,7 @@ pprFullRuleName st (L _ n) = pprWithSourceText st (doubleQuotes $ ftext n)
 ************************************************************************
 -}
 
-type instance XWarnings      GhcPs = ([AddEpAnn], SourceText)
+type instance XWarnings      GhcPs = ((EpaLocation, EpaLocation), SourceText)
 type instance XWarnings      GhcRn = SourceText
 type instance XWarnings      GhcTc = SourceText
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -61,6 +61,8 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `ext1Q` list
               `extQ` list_addEpAnn
               `extQ` list_epaLocation
+              `extQ` list_epTokenOpenP
+              `extQ` list_epTokenCloseP
               `extQ` string `extQ` fastString `extQ` srcSpan `extQ` realSrcSpan
               `extQ` annotationModule
               `extQ` annotationGrhsAnn
@@ -72,9 +74,13 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
+              `extQ` epTokenInstance
+              `extQ` epTokenForall
               `extQ` annParen
               `extQ` annClassDecl
               `extQ` annSynDecl
+              `extQ` annDataDefn
+              `extQ` annFamilyDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -118,6 +124,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                        $ text "blanked:" <+> text "[EpaLocation]"
               NoBlankEpAnnotations -> list ls
 
+            list_epTokenOpenP :: [EpToken "("] -> SDoc
+            list_epTokenOpenP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
+            list_epTokenCloseP :: [EpToken ")"] -> SDoc
+            list_epTokenCloseP ls = case ba of
+              BlankEpAnnotations -> parens
+                                       $ text "blanked:" <+> text "[EpToken \"(\"]"
+              NoBlankEpAnnotations -> list ls
+
             list []    = brackets empty
             list [x]   = brackets (showAstData' x)
             list (x1 : x2 : xs) =  (text "[" <> showAstData' x1)
@@ -224,6 +242,26 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                         $$ vcat [showAstData' ops, showAstData' cps,
                                  showAstData' t, showAstData' e]
 
+            annDataDefn :: AnnDataDefn -> SDoc
+            annDataDefn (AnnDataDefn a b c d e f g h i j k) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnDataDefn"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnDataDefn"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k]
+
+            annFamilyDecl :: AnnFamilyDecl -> SDoc
+            annFamilyDecl (AnnFamilyDecl a b c d e f g h i j k l) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnFamilyDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e, showAstData' f,
+                                 showAstData' g, showAstData' h, showAstData' i,
+                                 showAstData' j, showAstData' k, showAstData' l]
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -253,6 +291,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenCC :: EpToken "}" -> SDoc
             epTokenCC = epToken'
 
+            epTokenInstance :: EpToken "instance" -> SDoc
+            epTokenInstance = epToken'
+
+            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall = epUniToken'
+
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc
             epToken' (EpTok s) = case ba of
              BlankEpAnnotations -> parens
@@ -265,6 +309,18 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              NoBlankEpAnnotations ->
               parens $ text "NoEpTok"
 
+            epUniToken' :: EpUniToken sym1 sym2 -> SDoc
+            epUniToken' (EpUniTok s f) = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "EpUniTok" <+> epaLocation s <+> ppr f
+            epUniToken' NoEpUniTok = case ba of
+             BlankEpAnnotations -> parens
+                                      $ text "blanked:" <+> text "EpUniToken"
+             NoBlankEpAnnotations ->
+              parens $ text "NoEpUniTok"
+
 
             var  :: Var -> SDoc
             var v      = braces $ text "Var:" <+> ppr v


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.Hs.Type (
         pprHsArrow,
 
         HsType(..), HsCoreTy, LHsType, HsKind, LHsKind,
-        HsForAllTelescope(..), EpAnnForallTy,
+        HsForAllTelescope(..), EpAnnForallVis, EpAnnForallInvis,
         HsTyVarBndr(..), LHsTyVarBndr, AnnTyVarBndr(..),
         HsBndrKind(..),
         HsBndrVar(..),
@@ -163,16 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnnForallTy
+type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnnForallTy
+type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallTy = EpAnn (AddEpAnn, AddEpAnn)
-  -- ^ Location of 'forall' and '->' for HsForAllVis
-  -- Location of 'forall' and '.' for HsForAllInvis
+type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -184,12 +183,12 @@ type instance XHsQTvs GhcTc = HsQTvsRn
 
 type instance XXLHsQTyVars  (GhcPass _) = DataConCantHappen
 
-mkHsForAllVisTele ::EpAnnForallTy ->
+mkHsForAllVisTele ::EpAnnForallVis ->
   [LHsTyVarBndr () (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllVisTele an vis_bndrs =
   HsForAllVis { hsf_xvis = an, hsf_vis_bndrs = vis_bndrs }
 
-mkHsForAllInvisTele :: EpAnnForallTy
+mkHsForAllInvisTele :: EpAnnForallInvis
   -> [LHsTyVarBndr Specificity (GhcPass p)] -> HsForAllTelescope (GhcPass p)
 mkHsForAllInvisTele an invis_bndrs =
   HsForAllInvis { hsf_xinvis = an, hsf_invis_bndrs = invis_bndrs }
@@ -207,7 +206,7 @@ type instance XHsOuterImplicit GhcPs = NoExtField
 type instance XHsOuterImplicit GhcRn = [Name]
 type instance XHsOuterImplicit GhcTc = [TyVar]
 
-type instance XHsOuterExplicit GhcPs _    = EpAnnForallTy
+type instance XHsOuterExplicit GhcPs _    = EpAnnForallInvis
 type instance XHsOuterExplicit GhcRn _    = NoExtField
 type instance XHsOuterExplicit GhcTc flag = [VarBndr TyVar flag]
 
@@ -323,7 +322,7 @@ hsOuterExplicitBndrs (HsOuterImplicit{})                  = []
 mkHsOuterImplicit :: HsOuterTyVarBndrs flag GhcPs
 mkHsOuterImplicit = HsOuterImplicit{hso_ximplicit = noExtField}
 
-mkHsOuterExplicit :: EpAnnForallTy -> [LHsTyVarBndr flag GhcPs]
+mkHsOuterExplicit :: EpAnnForallInvis -> [LHsTyVarBndr flag GhcPs]
                   -> HsOuterTyVarBndrs flag GhcPs
 mkHsOuterExplicit an bndrs = HsOuterExplicit { hso_xexplicit = an
                                              , hso_bndrs     = bndrs }
@@ -333,7 +332,7 @@ mkHsImplicitSigType body =
   HsSig { sig_ext   = noExtField
         , sig_bndrs = mkHsOuterImplicit, sig_body = body }
 
-mkHsExplicitSigType :: EpAnnForallTy
+mkHsExplicitSigType :: EpAnnForallInvis
                     -> [LHsTyVarBndr Specificity GhcPs] -> LHsType GhcPs
                     -> HsSigType GhcPs
 mkHsExplicitSigType an bndrs body =


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1275,9 +1275,9 @@ topdecl :: { LHsDecl GhcPs }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
         | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
-        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
-        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ([mo $1,mc $3], (getWARNING_PRAGs $1)) (fromOL $2))) }
-        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ([mo $1,mc $3], (getRULES_PRAGs $1)) (reverse $2))) }
+        | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
+        | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
+        | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
         | annotation { $1 }
         | decl_no_th                            { $1 }
 
@@ -1300,7 +1300,7 @@ cl_decl :: { LTyClDecl GhcPs }
 --
 default_decl :: { LDefaultDecl GhcPs }
              : 'default' opt_class '(' comma_types0 ')'
-               {% amsA' (sLL $1 $> (DefaultDecl [mj AnnDefault $1,mop $3,mcp $5] $2 $4)) }
+               {% amsA' (sLL $1 $> (DefaultDecl (epTok $1,epTok $3,epTok $5) $2 $4)) }
 
 
 -- Type declarations (toplevel)
@@ -1322,17 +1322,22 @@ ty_decl :: { LTyClDecl GhcPs }
                           where_type_family
                 -- Note the use of type for the head; this allows
                 -- infix type constructors to be declared
-                {% mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
+             {% do { let { (tdcolon, tequal) = fst $ unLoc $4 }
+                   ; let { tvbar = fst $ unLoc $5 }
+                   ; let { (twhere, (toc, tdd, tcc)) = fst $ unLoc $6  }
+                   ; mkFamDecl (comb5 $1 $3 $4 $5 $6) (snd $ unLoc $6) TopLevel $3
                                    (snd $ unLoc $4) (snd $ unLoc $5)
-                           (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)
-                           ++ (fst $ unLoc $5) ++ (fst $ unLoc $6))  }
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar twhere toc tdd tcc) }}
 
           -- ordinary data type or newtype declaration
         | type_data_or_newtype capi_ctype tycl_hdr constrs maybe_derivings
-                {% mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tequal = fst $ unLoc $4 }
+                  ; mkTyData (comb4 $1 $3 $4 $5) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                            Nothing (reverse (snd $ unLoc $4))
                                    (fmap reverse $5)
-                           ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)) }
+                           (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)
+                             }}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
@@ -1340,18 +1345,22 @@ ty_decl :: { LTyClDecl GhcPs }
         | type_data_or_newtype capi_ctype tycl_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
+            {% do { let { (tdata, tnewtype, ttype) = fstOf3 $ unLoc $1}
+                  ; let { tdcolon = fst $ unLoc $4 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $5 }
+                  ; mkTyData (comb5 $1 $3 $4 $5 $6) (sndOf3 $ unLoc $1) (thdOf3 $ unLoc $1) $2 $3
                             (snd $ unLoc $4) (snd $ unLoc $5)
                             (fmap reverse $6)
-                            ((fstOf3 $ unLoc $1)++(fst $ unLoc $4)++(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] ttype tnewtype tdata NoEpTok tdcolon twhere oc cc NoEpTok)}}
                                    -- We need the location on tycl_hdr in case
                                    -- constrs and deriving are both empty
 
           -- data/newtype family
         | 'data' 'family' type opt_datafam_kind_sig
-                {% mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; mkFamDecl (comb4 $1 $2 $3 $4) DataFamily TopLevel $3
                                    (snd $ unLoc $4) Nothing
-                          (mj AnnData $1:mj AnnFamily $2:(fst $ unLoc $4)) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) (epTok $2) tdcolon noAnn noAnn noAnn noAnn noAnn noAnn) }}
 
 -- standalone kind signature
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
@@ -1386,25 +1395,29 @@ inst_decl :: { LInstDecl GhcPs }
            -- type instance declarations
         | 'type' 'instance' ty_fam_inst_eqn
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                        (mj AnnType $1:mj AnnInstance $2:[]) }
+                        (epTok $1) (epTok $2) }
 
           -- data/newtype instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr constrs
                           maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                       Nothing (reverse (snd  $ unLoc $5))
                                               (fmap reverse $6)
-                      ((fst $ unLoc $1):mj AnnInstance $2:(fst $ unLoc $5)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
           -- GADT instance declaration
         | data_or_newtype 'instance' capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-            {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { dcolon = fst $ unLoc $5 }
+                  ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                  ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3 (unLoc $4)
                                    (snd $ unLoc $5) (snd $ unLoc $6)
                                    (fmap reverse $7)
-                     ((fst $ unLoc $1):mj AnnInstance $2
-                       :(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) dcolon twhere oc cc NoEpTok)}}
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
@@ -1439,14 +1452,14 @@ opt_class :: { Maybe (LIdP GhcPs) }
 
 -- Injective type families
 
-opt_injective_info :: { Located ([AddEpAnn], Maybe (LInjectivityAnn GhcPs)) }
-        : {- empty -}               { noLoc ([], Nothing) }
-        | '|' injectivity_cond      { sLL $1 $> ([mj AnnVbar $1]
+opt_injective_info :: { Located (EpToken "|", Maybe (LInjectivityAnn GhcPs)) }
+        : {- empty -}               { noLoc (noAnn, Nothing) }
+        | '|' injectivity_cond      { sLL $1 $> ((epTok $1)
                                                 , Just ($2)) }
 
 injectivity_cond :: { LInjectivityAnn GhcPs }
         : tyvarid '->' inj_varids
-           {% amsA' (sLL $1 $> (InjectivityAnn [mu AnnRarrow $2] $1 (reverse (unLoc $3)))) }
+           {% amsA' (sLL $1 $> (InjectivityAnn (epUniTok $2) $1 (reverse (unLoc $3)))) }
 
 inj_varids :: { Located [LocatedN RdrName] }
         : inj_varids tyvarid  { sLL $1 $> ($2 : unLoc $1) }
@@ -1454,21 +1467,20 @@ inj_varids :: { Located [LocatedN RdrName] }
 
 -- Closed type families
 
-where_type_family :: { Located ([AddEpAnn],FamilyInfo GhcPs) }
-        : {- empty -}                      { noLoc ([],OpenTypeFamily) }
+where_type_family :: { Located ((EpToken "where", (EpToken "{", EpToken "..", EpToken "}")),FamilyInfo GhcPs) }
+        : {- empty -}                      { noLoc (noAnn,OpenTypeFamily) }
         | 'where' ty_fam_inst_eqn_list
-               { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
+               { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
                     ,ClosedTypeFamily (fmap reverse $ snd $ unLoc $2)) }
 
-ty_fam_inst_eqn_list :: { Located ([AddEpAnn],Maybe [LTyFamInstEqn GhcPs]) }
-        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ([moc $1,mcc $3]
+ty_fam_inst_eqn_list :: { Located ((EpToken "{", EpToken "..", EpToken "}"),Maybe [LTyFamInstEqn GhcPs]) }
+        :     '{' ty_fam_inst_eqns '}'     { sLL $1 $> ((epTok $1,noAnn, epTok $3)
                                                 ,Just (unLoc $2)) }
         | vocurly ty_fam_inst_eqns close   { let (L loc _) = $2 in
-                                             L loc ([],Just (unLoc $2)) }
-        |     '{' '..' '}'                 { sLL $1 $> ([moc $1,mj AnnDotdot $2
-                                                 ,mcc $3],Nothing) }
+                                             L loc (noAnn,Just (unLoc $2)) }
+        |     '{' '..' '}'                 { sLL $1 $> ((epTok $1,epTok $2 ,epTok $3),Nothing) }
         | vocurly '..' close               { let (L loc _) = $2 in
-                                             L loc ([mj AnnDotdot $2],Nothing) }
+                                             L loc ((noAnn,epTok $2, noAnn),Nothing) }
 
 ty_fam_inst_eqns :: { Located [LTyFamInstEqn GhcPs] }
         : ty_fam_inst_eqns ';' ty_fam_inst_eqn
@@ -1492,9 +1504,9 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
                     ; tvbs <- fromSpecTyVarBndrs $2
                     ; let loc = comb2 $1 $>
                     ; !cs <- getCommentsFor loc
-                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs) $4 $6 [mj AnnEqual $5] }}
+                    ; mkTyFamInstEqn loc (mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs) $4 $6 (epTok $5) }}
         | type '=' ktype
-              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (mj AnnEqual $2:[]) }
+              {% mkTyFamInstEqn (comb2 $1 $>) mkHsOuterImplicit $1 $3 (epTok $2) }
               -- Note the use of type for the head; this allows
               -- infix type constructors and type patterns
 
@@ -1510,40 +1522,42 @@ ty_fam_inst_eqn :: { LTyFamInstEqn GhcPs }
 at_decl_cls :: { LHsDecl GhcPs }
         :  -- data family declarations, with optional 'family' keyword
           'data' opt_family type opt_datafam_kind_sig
-                {% liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
+             {% do { let { tdcolon = fst $ unLoc $4 }
+                   ; liftM mkTyClD (mkFamDecl (comb3 $1 $3 $4) DataFamily NotTopLevel $3
                                                   (snd $ unLoc $4) Nothing
-                        (mj AnnData $1:$2++(fst $ unLoc $4))) }
+                           (AnnFamilyDecl [] [] noAnn (epTok $1) $2 tdcolon noAnn noAnn noAnn noAnn noAnn noAnn)) }}
 
            -- type family declarations, with optional 'family' keyword
            -- (can't use opt_instance because you get shift/reduce errors
         | 'type' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $3 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $2 $3) OpenTypeFamily NotTopLevel $2
                                    (fst . snd $ unLoc $3)
                                    (snd . snd $ unLoc $3)
-                         (mj AnnType $1:(fst $ unLoc $3)) )}
+                         (AnnFamilyDecl [] [] (epTok $1) noAnn noAnn tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
         | 'type' 'family' type opt_at_kind_inj_sig
-               {% liftM mkTyClD
+            {% do { let { (tdcolon, tequal, tvbar) = fst $ unLoc $4 }
+                  ; liftM mkTyClD
                         (mkFamDecl (comb3 $1 $3 $4) OpenTypeFamily NotTopLevel $3
                                    (fst . snd $ unLoc $4)
                                    (snd . snd $ unLoc $4)
-                         (mj AnnType $1:mj AnnFamily $2:(fst $ unLoc $4)))}
-
+                           (AnnFamilyDecl [] [] (epTok $1) noAnn (epTok $2) tdcolon tequal tvbar noAnn noAnn noAnn noAnn)) }}
            -- default type instances, with optional 'instance' keyword
         | 'type' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $2) (unLoc $2)
-                          [mj AnnType $1]) }
+                          (epTok $1) NoEpTok) }
         | 'type' 'instance' ty_fam_inst_eqn
                 {% liftM mkInstD (mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                              (mj AnnType $1:mj AnnInstance $2:[]) )}
+                              (epTok $1) (epTok $2) )}
 
-opt_family   :: { [AddEpAnn] }
-              : {- empty -}   { [] }
-              | 'family'      { [mj AnnFamily $1] }
+opt_family   :: { EpToken "family" }
+              : {- empty -}   { noAnn }
+              | 'family'      { (epTok $1) }
 
-opt_instance :: { [AddEpAnn] }
-              : {- empty -} { [] }
-              | 'instance'  { [mj AnnInstance $1] }
+opt_instance :: { EpToken "instance" }
+              : {- empty -} { NoEpTok }
+              | 'instance'  { epTok $1 }
 
 -- Associated type instances
 --
@@ -1553,57 +1567,63 @@ at_decl_inst :: { LInstDecl GhcPs }
                 -- Note the use of type for the head; this allows
                 -- infix type constructors and type patterns
                 {% mkTyFamInst (comb2 $1 $3) (unLoc $3)
-                          (mj AnnType $1:$2) }
+                          (epTok $1) $2 }
 
         -- data/newtype instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr constrs maybe_derivings
-               {% mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
+            {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                  ; let { tequal = fst $ unLoc $5 }
+                  ; mkDataFamInst (comb4 $1 $4 $5 $6) (snd $ unLoc $1) $3 (unLoc $4)
                                     Nothing (reverse (snd $ unLoc $5))
-                                            (fmap reverse $6)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)) }
+                                             (fmap reverse $6)
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 NoEpUniTok NoEpTok NoEpTok NoEpTok tequal)}}
 
         -- GADT instance declaration, with optional 'instance' keyword
         | data_or_newtype opt_instance capi_ctype datafam_inst_hdr opt_kind_sig
                  gadt_constrlist
                  maybe_derivings
-                {% mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
+             {% do { let { (tdata, tnewtype) = fst $ unLoc $1 }
+                   ; let { dcolon = fst $ unLoc $5 }
+                   ; let { (twhere, oc, cc) = fst $ unLoc $6 }
+                   ; mkDataFamInst (comb4 $1 $4 $6 $7) (snd $ unLoc $1) $3
                                 (unLoc $4) (snd $ unLoc $5) (snd $ unLoc $6)
                                 (fmap reverse $7)
-                        ((fst $ unLoc $1):$2++(fst $ unLoc $5)++(fst $ unLoc $6)) }
+                            (AnnDataDefn [] [] NoEpTok tnewtype tdata $2 dcolon twhere oc cc NoEpTok)}}
 
-type_data_or_newtype :: { Located ([AddEpAnn], Bool, NewOrData) }
-        : 'data'        { sL1 $1 ([mj AnnData    $1],            False,DataType) }
-        | 'newtype'     { sL1 $1 ([mj AnnNewtype $1],            False,NewType) }
-        | 'type' 'data' { sL1 $1 ([mj AnnType $1, mj AnnData $2],True ,DataType) }
+type_data_or_newtype :: { Located ((EpToken "data", EpToken "newtype", EpToken "type")
+                                   , Bool, NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok,  NoEpTok),  False,DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1, NoEpTok),  False,NewType) }
+        | 'type' 'data' { sL1 $1 ((epTok $2, NoEpTok,  epTok $1), True ,DataType) }
 
-data_or_newtype :: { Located (AddEpAnn, NewOrData) }
-        : 'data'        { sL1 $1 (mj AnnData    $1,DataType) }
-        | 'newtype'     { sL1 $1 (mj AnnNewtype $1,NewType) }
+data_or_newtype :: { Located ((EpToken "data", EpToken "newtype"), NewOrData) }
+        : 'data'        { sL1 $1 ((epTok $1, NoEpTok), DataType) }
+        | 'newtype'     { sL1 $1 ((NoEpTok,  epTok $1),NewType) }
 
 -- Family result/return kind signatures
 
-opt_kind_sig :: { Located ([AddEpAnn], Maybe (LHsKind GhcPs)) }
-        :               { noLoc     ([]               , Nothing) }
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], Just $2) }
+opt_kind_sig :: { Located (TokDcolon, Maybe (LHsKind GhcPs)) }
+        :               { noLoc     (NoEpUniTok , Nothing) }
+        | '::' kind     { sLL $1 $> (epUniTok $1, Just $2) }
 
-opt_datafam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :               { noLoc     ([]               , noLocA (NoSig noExtField)         )}
-        | '::' kind     { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig noExtField $2))}
+opt_datafam_kind_sig :: { Located (TokDcolon, LFamilyResultSig GhcPs) }
+        :               { noLoc     (noAnn,       noLocA (NoSig noExtField)         )}
+        | '::' kind     { sLL $1 $> (epUniTok $1, sLLa $1 $> (KindSig noExtField $2))}
 
-opt_tyfam_kind_sig :: { Located ([AddEpAnn], LFamilyResultSig GhcPs) }
-        :              { noLoc     ([]               , noLocA     (NoSig    noExtField)   )}
-        | '::' kind    { sLL $1 $> ([mu AnnDcolon $1], sLLa $1 $> (KindSig  noExtField $2))}
+opt_tyfam_kind_sig :: { Located ((TokDcolon, EpToken "="), LFamilyResultSig GhcPs) }
+        :              { noLoc     (noAnn               , noLocA     (NoSig    noExtField)   )}
+        | '::' kind    { sLL $1 $> ((epUniTok $1, noAnn), sLLa $1 $> (KindSig  noExtField $2))}
         | '='  tv_bndr {% do { tvb <- fromSpecTyVarBndr $2
-                             ; return $ sLL $1 $> ([mj AnnEqual $1], sLLa $1 $> (TyVarSig noExtField tvb))} }
+                             ; return $ sLL $1 $> ((noAnn, epTok $1), sLLa $1 $> (TyVarSig noExtField tvb))} }
 
-opt_at_kind_inj_sig :: { Located ([AddEpAnn], ( LFamilyResultSig GhcPs
+opt_at_kind_inj_sig :: { Located ((TokDcolon, EpToken "=", EpToken "|"), ( LFamilyResultSig GhcPs
                                             , Maybe (LInjectivityAnn GhcPs)))}
-        :            { noLoc ([], (noLocA (NoSig noExtField), Nothing)) }
-        | '::' kind  { sLL $1 $> ( [mu AnnDcolon $1]
+        :            { noLoc (noAnn, (noLocA (NoSig noExtField), Nothing)) }
+        | '::' kind  { sLL $1 $> ( (epUniTok $1, noAnn, noAnn)
                                  , (sL1a $> (KindSig noExtField $2), Nothing)) }
         | '='  tv_bndr_no_braces '|' injectivity_cond
                 {% do { tvb <- fromSpecTyVarBndr $2
-                      ; return $ sLL $1 $> ([mj AnnEqual $1, mj AnnVbar $3]
+                      ; return $ sLL $1 $> ((noAnn, epTok $1, epTok $3)
                                            , (sLLa $1 $2 (TyVarSig noExtField tvb), Just $4))} }
 
 -- tycl_hdr parses the header of a class or data type decl,
@@ -1623,13 +1643,13 @@ datafam_inst_hdr :: { Located (Maybe (LHsContext GhcPs), HsOuterFamEqnTyVarBndrs
                                                          >>= \tvbs ->
                                                              (acs (comb2 $1 $>) (\loc cs -> (L loc
                                                                                   (Just ( addTrailingDarrowC $4 $5 cs)
-                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) emptyComments) tvbs, $6))))
+                                                                                        , mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) emptyComments) tvbs, $6))))
                                                     }
         | 'forall' tv_bndrs '.' type   {% do { hintExplicitForall $1
                                              ; tvbs <- fromSpecTyVarBndrs $2
                                              ; let loc = comb2 $1 $>
                                              ; !cs <- getCommentsFor loc
-                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (mu AnnForall $1, mj AnnDot $3) cs) tvbs, $4))
+                                             ; return (sL loc (Nothing, mkHsOuterExplicit (EpAnn (glEE $1 $3) (epUniTok $1, epTok $3) cs) tvbs, $4))
                                        } }
         | context '=>' type         {% acs (comb2 $1 $>) (\loc cs -> (L loc (Just (addTrailingDarrowC $1 $2 cs), mkHsOuterImplicit, $3))) }
         | type                      { sL1 $1 (Nothing, mkHsOuterImplicit, $1) }
@@ -2184,11 +2204,11 @@ unpackedness :: { Located UnpackednessPragma }
 forall_telescope :: { Located (HsForAllTelescope GhcPs) }
         : 'forall' tv_bndrs '.'  {% do { hintExplicitForall $1
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnDot $3) cs) $2 )) }}
+                                           mkHsForAllInvisTele (EpAnn (glEE $1 $>) (epUniTok $1,epTok $3) cs) $2 )) }}
         | 'forall' tv_bndrs '->' {% do { hintExplicitForall $1
                                        ; req_tvbs <- fromSpecTyVarBndrs $2
                                        ; acs (comb2 $1 $>) (\loc cs -> (L loc $
-                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (mu AnnForall $1,mu AnnRarrow $3) cs) req_tvbs )) }}
+                                           mkHsForAllVisTele (EpAnn (glEE $1 $>) (epUniTok $1,epUniTok $3) cs) req_tvbs )) }}
 
 -- A ktype is a ctype, possibly with a kind annotation
 ktype :: { LHsType GhcPs }
@@ -2434,7 +2454,7 @@ fds1 :: { Located [LHsFunDep GhcPs] }
 
 fd :: { LHsFunDep GhcPs }
         : varids0 '->' varids0  {% amsA' (L (comb3 $1 $2 $3)
-                                       (FunDep [mu AnnRarrow $2]
+                                       (FunDep (epUniTok $2)
                                                (reverse (unLoc $1))
                                                (reverse (unLoc $3)))) }
 
@@ -2478,20 +2498,20 @@ constructors.
 -----------------------------------------------------------------------------
 -- Datatype declarations
 
-gadt_constrlist :: { Located ([AddEpAnn]
+gadt_constrlist :: { Located ((EpToken "where", EpToken "{", EpToken "}")
                           ,[LConDecl GhcPs]) } -- Returned in order
 
         : 'where' '{'        gadt_constrs '}'    {% checkEmptyGADTs $
                                                       L (comb2 $1 $4)
-                                                        ([mj AnnWhere $1
-                                                         ,moc $2
-                                                         ,mcc $4]
+                                                        ((epTok $1
+                                                         ,epTok $2
+                                                         ,epTok $4)
                                                         , unLoc $3) }
         | 'where' vocurly    gadt_constrs close  {% checkEmptyGADTs $
                                                       L (comb2 $1 $3)
-                                                        ([mj AnnWhere $1]
+                                                        ((epTok $1, NoEpTok, NoEpTok)
                                                         , unLoc $3) }
-        | {- empty -}                            { noLoc ([],[]) }
+        | {- empty -}                            { noLoc (noAnn,[]) }
 
 gadt_constrs :: { Located [LConDecl GhcPs] }
         : gadt_constr ';' gadt_constrs
@@ -2525,8 +2545,8 @@ consequence, GADT constructor names are restricted (names like '(*)' are
 allowed in usual data constructors, but not in GADTs).
 -}
 
-constrs :: { Located ([AddEpAnn],[LConDecl GhcPs]) }
-        : '=' constrs1    { sLL $1 $2 ([mj AnnEqual $1],unLoc $2)}
+constrs :: { Located (EpToken "=",[LConDecl GhcPs]) }
+        : '=' constrs1    { sLL $1 $2 (epTok $1,unLoc $2)}
 
 constrs1 :: { Located [LConDecl GhcPs] }
         : constrs1 '|' constr


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon,
+  TokDcolon, TokRarrow,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -411,6 +411,7 @@ getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
 type TokDcolon = EpUniToken "::" "∷"
+type TokRarrow = EpUniToken "->" "→"
 
 -- | Layout information for declarations.
 data EpLayout =


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -231,41 +231,32 @@ mkTyData :: SrcSpan
          -> Maybe (LHsKind GhcPs)
          -> [LConDecl GhcPs]
          -> Located (HsDeriving GhcPs)
-         -> [AddEpAnn]
+         -> AnnDataDefn
          -> P (LTyClDecl GhcPs)
 mkTyData loc' is_type_data new_or_data cType (L _ (mcxt, tycl_hdr))
          ksig data_cons (L _ maybe_deriv) annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns = annsIn {andd_openp = ops, andd_closep = cps}
        ; data_cons <- checkNewOrData loc' (unLoc tc) is_type_data new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
        ; !cs' <- getCommentsFor loc'
        ; let loc = EpAnn (spanAsAnchor loc') noAnn (cs' Semi.<> cs)
-       ; return (L loc (DataDecl { tcdDExt = anns',
+       ; return (L loc (DataDecl { tcdDExt = noExtField,
                                    tcdLName = tc, tcdTyVars = tyvars,
                                    tcdFixity = fixity,
                                    tcdDataDefn = defn })) }
 
--- TODO:AZ:temporary
-openParen2AddEpAnn :: EpToken "(" -> [AddEpAnn]
-openParen2AddEpAnn (EpTok l) = [AddEpAnn AnnOpenP l]
-openParen2AddEpAnn NoEpTok = []
-
-closeParen2AddEpAnn :: EpToken ")" -> [AddEpAnn]
-closeParen2AddEpAnn (EpTok l) = [AddEpAnn AnnCloseP l]
-closeParen2AddEpAnn NoEpTok = []
-
 mkDataDefn :: Maybe (LocatedP CType)
            -> Maybe (LHsContext GhcPs)
            -> Maybe (LHsKind GhcPs)
            -> DataDefnCons (LConDecl GhcPs)
            -> HsDeriving GhcPs
+           -> AnnDataDefn
            -> P (HsDataDefn GhcPs)
-mkDataDefn cType mcxt ksig data_cons maybe_deriv
+mkDataDefn cType mcxt ksig data_cons maybe_deriv anns
   = do { checkDatatypeContext mcxt
-       ; return (HsDataDefn { dd_ext = noExtField
+       ; return (HsDataDefn { dd_ext = anns
                             , dd_cType = cType
                             , dd_ctxt = mcxt
                             , dd_cons = data_cons
@@ -316,15 +307,13 @@ mkTyFamInstEqn :: SrcSpan
                -> HsOuterFamEqnTyVarBndrs GhcPs
                -> LHsType GhcPs
                -> LHsType GhcPs
-               -> [AddEpAnn]
+               -> EpToken "="
                -> P (LTyFamInstEqn GhcPs)
-mkTyFamInstEqn loc bndrs lhs rhs anns
+mkTyFamInstEqn loc bndrs lhs rhs annEq
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' $ FamEqn
-                        { feqn_ext    = anns'
+                        { feqn_ext    = (ops, cps, annEq)
                         , feqn_tycon  = tc
                         , feqn_bndrs  = bndrs
                         , feqn_pats   = tparams
@@ -339,18 +328,17 @@ mkDataFamInst :: SrcSpan
               -> Maybe (LHsKind GhcPs)
               -> [LConDecl GhcPs]
               -> Located (HsDeriving GhcPs)
-              -> [AddEpAnn]
+              -> AnnDataDefn
               -> P (LInstDecl GhcPs)
 mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
               ksig data_cons (L _ maybe_deriv) anns
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False tycl_hdr
        ; data_cons <- checkNewOrData loc (unLoc tc) False new_or_data data_cons
-       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv
+       ; let anns' = anns {andd_openp = ops, andd_closep = cps}
+       ; defn <- mkDataDefn cType mcxt ksig data_cons maybe_deriv anns'
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = anns Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
        ; return (L loc' (DataFamInstD noExtField (DataFamInstDecl
-                  (FamEqn { feqn_ext    = anns'
+                  (FamEqn { feqn_ext    = ([], [], NoEpTok)
                           , feqn_tycon  = tc
                           , feqn_bndrs  = bndrs
                           , feqn_pats   = tparams
@@ -361,11 +349,12 @@ mkDataFamInst loc new_or_data cType (mcxt, bndrs, tycl_hdr)
 
 mkTyFamInst :: SrcSpan
             -> TyFamInstEqn GhcPs
-            -> [AddEpAnn]
+            -> EpToken "type"
+            -> EpToken "instance"
             -> P (LInstDecl GhcPs)
-mkTyFamInst loc eqn anns = do
+mkTyFamInst loc eqn t i = do
   return (L (noAnnSrcSpan loc) (TyFamInstD noExtField
-              (TyFamInstDecl anns eqn)))
+              (TyFamInstDecl (t,i) eqn)))
 
 mkFamDecl :: SrcSpan
           -> FamilyInfo GhcPs
@@ -373,14 +362,13 @@ mkFamDecl :: SrcSpan
           -> LHsType GhcPs                   -- LHS
           -> LFamilyResultSig GhcPs          -- Optional result signature
           -> Maybe (LInjectivityAnn GhcPs)   -- Injectivity annotation
-          -> [AddEpAnn]
+          -> AnnFamilyDecl
           -> P (LTyClDecl GhcPs)
 mkFamDecl loc info topLevel lhs ksig injAnn annsIn
   = do { (tc, tparams, fixity, ops, cps, cs) <- checkTyClHdr False lhs
        ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams
        ; let loc' = EpAnn (spanAsAnchor loc) noAnn cs
-       ; let anns' = annsIn Semi.<>
-                     concatMap openParen2AddEpAnn ops Semi.<> concatMap closeParen2AddEpAnn cps
+       ; let anns' = annsIn { afd_openp = ops, afd_closep = cps }
        ; return (L loc' (FamDecl noExtField (FamilyDecl
                                            { fdExt       = anns'
                                            , fdTopLevel  = topLevel
@@ -1050,8 +1038,8 @@ checkRecordSyntax lr@(L loc r)
 
 -- | Check if the gadt_constrlist is empty. Only raise parse error for
 -- `data T where` to avoid affecting existing error message, see #8258.
-checkEmptyGADTs :: Located ([AddEpAnn], [LConDecl GhcPs])
-                -> P (Located ([AddEpAnn], [LConDecl GhcPs]))
+checkEmptyGADTs :: Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs])
+                -> P (Located ((EpToken "where", EpToken "{", EpToken "}"), [LConDecl GhcPs]))
 checkEmptyGADTs gadts@(L span (_, []))           -- Empty GADT declaration.
     = do gadtSyntax <- getBit GadtSyntaxBit   -- GADTs implies GADTSyntax
          unless gadtSyntax $ addError $ mkPlainErrorMsgEnvelope span $


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -1883,7 +1883,7 @@ rnDataDefn doc (HsDataDefn { dd_cType = cType, dd_ctxt = context, dd_cons = cond
 
         ; let all_fvs = fvs1 `plusFV` fvs3 `plusFV`
                         con_fvs `plusFV` sig_fvs
-        ; return ( HsDataDefn { dd_ext = noExtField, dd_cType = cType
+        ; return ( HsDataDefn { dd_ext = noAnn, dd_cType = cType
                               , dd_ctxt = context', dd_kindSig = m_sig'
                               , dd_cons = condecls'
                               , dd_derivs = derivs' }


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -291,14 +291,14 @@ cvtDec (NewtypeD ctxt tc tvs ksig constr derivs)
         ; ksig' <- cvtKind `traverse` ksig
         ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = con'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }
@@ -363,7 +363,7 @@ cvtDec (DataInstD ctxt bndrs tys ksig constrs derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; cons' <- cvtDataDefnCons False ksig $ DataTypeCons False constrs
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -385,7 +385,7 @@ cvtDec (NewtypeInstD ctxt bndrs tys ksig constr derivs)
        ; ksig' <- cvtKind `traverse` ksig
        ; con' <- cvtDataDefnCons False ksig $ NewTypeCon constr
        ; derivs' <- cvtDerivs derivs
-       ; let defn = HsDataDefn { dd_ext = noExtField
+       ; let defn = HsDataDefn { dd_ext = noAnn
                                , dd_cType = Nothing
                                , dd_ctxt = mkHsContextMaybe ctxt'
                                , dd_kindSig = ksig'
@@ -504,14 +504,14 @@ cvtGenDataDec type_data ctxt tc tvs ksig constrs derivs
         ; cons' <- cvtDataDefnCons type_data ksig $
                    DataTypeCons type_data constrs
         ; derivs' <- cvtDerivs derivs
-        ; let defn = HsDataDefn { dd_ext = noExtField
+        ; let defn = HsDataDefn { dd_ext = noAnn
                                 , dd_cType = Nothing
                                 , dd_ctxt = mkHsContextMaybe ctxt'
                                 , dd_kindSig = ksig'
                                 , dd_cons = cons'
                                 , dd_derivs = derivs' }
         ; returnJustLA $ TyClD noExtField $
-          DataDecl { tcdDExt = noAnn
+          DataDecl { tcdDExt = noExtField
                    , tcdLName = tc', tcdTyVars = tvs'
                    , tcdFixity = Prefix
                    , tcdDataDefn = defn } }


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -76,9 +76,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnData (EpaSpan { Test20239.hs:5:1-4 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { Test20239.hs:5:6-13 }))
-        ,(AddEpAnn AnnEqual (EpaSpan { Test20239.hs:5:34 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { Test20239.hs:5:15-20 })
@@ -113,7 +114,20 @@
               {OccName: PGMigration})))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:1-4 }))
+          (EpTok (EpaSpan { Test20239.hs:5:6-13 }))
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { Test20239.hs:5:34 })))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -891,7 +891,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:22:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:22:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1032,8 +1045,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:24:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:24:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:24:8-9 })
@@ -1068,7 +1083,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:24:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1239,7 +1267,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:28:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:28:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1380,8 +1421,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:30:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:30:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:30:8-9 })
@@ -1416,7 +1459,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:30:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1587,7 +1643,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:34:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:34:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -1728,8 +1797,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:36:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:36:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:36:8-9 })
@@ -1764,7 +1835,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:36:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -1935,7 +2019,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:40:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:40:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2076,8 +2173,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:42:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:42:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:42:8-9 })
@@ -2112,7 +2211,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:42:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2283,7 +2395,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:46:20-23 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:46:20-23 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2424,8 +2549,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:48:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:48:15-19 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:48:8-9 })
@@ -2460,7 +2587,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:48:15-19 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)
@@ -2631,7 +2771,20 @@
          (EpaComments
           []))
         (FamilyDecl
-         [(AddEpAnn AnnData (EpaSpan { T17544.hs:52:21-24 }))]
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { T17544.hs:52:21-24 }))
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (NotTopLevel)
          (L
@@ -2772,8 +2925,10 @@
            []))
          (DataFamInstDecl
           (FamEqn
-           [(AddEpAnn AnnData (EpaSpan { T17544.hs:54:3-6 }))
-           ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:54:16-20 }))]
+           ((,,)
+            []
+            []
+            (NoEpTok))
            (L
             (EpAnn
              (EpaSpan { T17544.hs:54:8-10 })
@@ -2808,7 +2963,20 @@
                  {OccName: Int})))))]
            (Prefix)
            (HsDataDefn
-            (NoExtField)
+            (AnnDataDefn
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:3-6 }))
+             (NoEpTok)
+             (NoEpUniTok)
+             (EpTok
+              (EpaSpan { T17544.hs:54:16-20 }))
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
             (Nothing)
             (Nothing)
             (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -59,8 +59,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T17544_kw.hs:15:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:16:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:15:6-8 })
@@ -75,7 +74,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:16:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -161,8 +173,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnNewtype (EpaSpan { T17544_kw.hs:18:1-7 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T17544_kw.hs:19:3-7 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T17544_kw.hs:18:9-11 })
@@ -177,7 +188,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:18:1-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T17544_kw.hs:19:3-7 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:3:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:5:3 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:3:6-9 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:3:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:5:3 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -285,8 +297,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:11:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:11:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:11:6-9 })
@@ -301,7 +312,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:11:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -401,8 +425,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:14:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:14:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:14:6-9 })
@@ -417,7 +440,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:14:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -559,8 +595,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:19:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:19:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:19:6-9 })
@@ -575,7 +610,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:19:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -717,8 +765,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:27:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:27:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:27:6-9 })
@@ -733,7 +780,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:27:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -906,8 +966,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:31:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:31:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:31:6-9 })
@@ -922,7 +981,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:31:11 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1107,8 +1179,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T24221.hs:36:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T24221.hs:36:11 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T24221.hs:36:6-9 })
@@ -1123,7 +1194,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T24221.hs:36:11 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -82,8 +82,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:7:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:7:12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:7:6-10 })
@@ -98,7 +97,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:7:12 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -286,10 +298,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:10:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:10:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:10:32-33 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:10:41-45 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:10:32-33 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:10:41-45 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -300,7 +326,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:11:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:11:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:11:3-8 })
@@ -479,7 +509,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:12:19 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:12:19 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:12:3-8 })
@@ -642,8 +676,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:15:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:15:19 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:15:6 })
@@ -734,7 +767,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:15:19 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -1000,10 +1046,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:18:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:18:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:18:42-43 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:18:50-54 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:18:42-43 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:18:50-54 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1014,7 +1074,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { DumpParsedAst.hs:19:17 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:19:17 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:19:3-4 })
@@ -1378,9 +1442,23 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnData (EpaSpan { DumpParsedAst.hs:21:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { DumpParsedAst.hs:21:6-11 }))
-       ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:21:17-18 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:1-4 }))
+        (EpTok
+         (EpaSpan { DumpParsedAst.hs:21:6-11 }))
+        (EpUniTok
+         (EpaSpan { DumpParsedAst.hs:21:17-18 })
+         (NormalSyntax))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (DataFamily)
        (TopLevel)
        (L
@@ -1501,10 +1579,10 @@
       (NoExtField)
       (DataFamInstDecl
        (FamEqn
-        [(AddEpAnn AnnNewtype (EpaSpan { DumpParsedAst.hs:22:1-7 }))
-        ,(AddEpAnn AnnInstance (EpaSpan { DumpParsedAst.hs:22:9-16 }))
-        ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:22:39-40 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { DumpParsedAst.hs:22:62-66 }))]
+        ((,,)
+         []
+         []
+         (NoEpTok))
         (L
          (EpAnn
           (EpaSpan { DumpParsedAst.hs:22:18-20 })
@@ -1613,7 +1691,22 @@
                     {OccName: Type})))))))))))]
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:1-7 }))
+          (NoEpTok)
+          (EpTok (EpaSpan { DumpParsedAst.hs:22:9-16 }))
+          (EpUniTok
+           (EpaSpan { DumpParsedAst.hs:22:39-40 })
+           (NormalSyntax))
+          (EpTok
+           (EpaSpan { DumpParsedAst.hs:22:62-66 }))
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Just
@@ -1779,8 +1872,9 @@
                     (EpAnn
                      (EpaSpan { DumpParsedAst.hs:23:11-20 })
                      ((,)
-                      (AddEpAnn AnnForall (EpaSpan { DumpParsedAst.hs:23:11-16 }))
-                      (AddEpAnn AnnDot (EpaSpan { DumpParsedAst.hs:23:20 })))
+                      (EpUniTok (EpaSpan { DumpParsedAst.hs:23:11-16 }) NormalSyntax)
+                      (EpTok
+                       (EpaSpan { DumpParsedAst.hs:23:20 })))
                      (EpaComments
                       []))
                     [(L


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -154,7 +154,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -245,7 +256,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -256,7 +279,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:13:3-8 })
@@ -429,7 +455,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:14:3-8 })
@@ -671,7 +700,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (DataFamily)
          (TopLevel)
          (L
@@ -784,7 +825,10 @@
         (NoExtField)
         (DataFamInstDecl
          (FamEqn
-          []
+          ((,,)
+           []
+           []
+           (NoEpTok))
           (L
            (EpAnn
             (EpaSpan { DumpRenamedAst.hs:19:18-20 })
@@ -888,7 +932,18 @@
                      {Name: GHC.Types.Type}))))))))))]
           (Prefix)
           (HsDataDefn
-           (NoExtField)
+           (AnnDataDefn
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (Nothing)
            (Nothing)
            (Just
@@ -1041,8 +1096,8 @@
                       (EpAnn
                        (EpaDelta {  } (SameLine 0) [])
                        ((,)
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) []))
-                        (AddEpAnn Annlarrowtail (EpaDelta {  } (SameLine 0) [])))
+                        (NoEpUniTok)
+                        (NoEpTok))
                        (EpaComments
                         []))
                       [(L
@@ -1347,7 +1402,18 @@
                 {Name: k}))))))])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)
@@ -1452,7 +1518,19 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         []
+         (AnnFamilyDecl
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (ClosedTypeFamily
           (Just
            [(L
@@ -1463,7 +1541,10 @@
               (EpaComments
                []))
              (FamEqn
-              []
+              ((,,)
+               []
+               []
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:26:3-4 })
@@ -2006,7 +2087,19 @@
            (EpaComments
             []))
           (FamilyDecl
-           []
+           (AnnFamilyDecl
+            []
+            []
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok)
+            (NoEpTok))
            (OpenTypeFamily)
            (NotTopLevel)
            (L
@@ -2176,9 +2269,15 @@
             (EpaComments
              []))
            (TyFamInstDecl
-            [(AddEpAnn AnnType (EpaSpan { DumpRenamedAst.hs:32:3-6 }))]
+            ((,)
+             (EpTok
+              (EpaSpan { DumpRenamedAst.hs:32:3-6 }))
+             (NoEpTok))
             (FamEqn
-             []
+             ((,,)
+              []
+              []
+              (NoEpTok))
              (L
               (EpAnn
                (EpaSpan { DumpRenamedAst.hs:32:8 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -84,9 +84,22 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       [(AddEpAnn AnnType (EpaSpan { KindSigs.hs:11:1-4 }))
-       ,(AddEpAnn AnnFamily (EpaSpan { KindSigs.hs:11:6-11 }))
-       ,(AddEpAnn AnnWhere (EpaSpan { KindSigs.hs:11:19-23 }))]
+       (AnnFamilyDecl
+        []
+        []
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:1-4 }))
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:6-11 }))
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { KindSigs.hs:11:19-23 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (ClosedTypeFamily
         (Just
          [(L
@@ -97,7 +110,11 @@
             (EpaComments
              []))
            (FamEqn
-            [(AddEpAnn AnnEqual (EpaSpan { KindSigs.hs:12:9 }))]
+            ((,,)
+             []
+             []
+             (EpTok
+              (EpaSpan { KindSigs.hs:12:9 })))
             (L
              (EpAnn
               (EpaSpan { KindSigs.hs:12:3-5 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -37,7 +37,18 @@
          [])
         (Prefix)
         (HsDataDefn
-         (NoExtField)
+         (AnnDataDefn
+          []
+          []
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpUniTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok)
+          (NoEpTok))
          (Nothing)
          (Nothing)
          (Nothing)


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T15323.hs:5:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T15323.hs:5:21-25 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T15323.hs:5:6-17 })
@@ -90,7 +89,20 @@
            (NoExtField))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T15323.hs:5:21-25 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -131,8 +143,9 @@
              (EpAnn
               (EpaSpan { T15323.hs:6:20-29 })
               ((,)
-               (AddEpAnn AnnForall (EpaSpan { T15323.hs:6:20-25 }))
-               (AddEpAnn AnnDot (EpaSpan { T15323.hs:6:29 })))
+               (EpUniTok (EpaSpan { T15323.hs:6:20-25 }) NormalSyntax)
+               (EpTok
+                (EpaSpan { T15323.hs:6:29 })))
               (EpaComments
                []))
              [(L


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:5:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:5:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:5:6-11 })
@@ -111,7 +110,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:5:24 })))
        (Nothing)
        (Nothing)
        (Nothing)
@@ -153,8 +165,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T20452.hs:6:1-4 }))
-      ,(AddEpAnn AnnEqual (EpaSpan { T20452.hs:6:24 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T20452.hs:6:6-11 })
@@ -219,7 +230,20 @@
                {OccName: k})))))))])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T20452.hs:6:24 })))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -47,8 +47,7 @@
     (TyClD
      (NoExtField)
      (DataDecl
-      [(AddEpAnn AnnData (EpaSpan { T18791.hs:4:1-4 }))
-      ,(AddEpAnn AnnWhere (EpaSpan { T18791.hs:4:8-12 }))]
+      (NoExtField)
       (L
        (EpAnn
         (EpaSpan { T18791.hs:4:6 })
@@ -63,7 +62,20 @@
        [])
       (Prefix)
       (HsDataDefn
-       (NoExtField)
+       (AnnDataDefn
+        []
+        []
+        (NoEpTok)
+        (NoEpTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:1-4 }))
+        (NoEpTok)
+        (NoEpUniTok)
+        (EpTok
+         (EpaSpan { T18791.hs:4:8-12 }))
+        (NoEpTok)
+        (NoEpTok)
+        (NoEpTok))
        (Nothing)
        (Nothing)
        (Nothing)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -363,6 +363,14 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
+instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+  trailing _ = []
+  setTrailing a _ = a
+
+instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+  trailing _ = []
+  setTrailing a _ = a
+
 -- ---------------------------------------------------------------------
 
 fromAnn' :: (HasEntry a) => a -> Entry
@@ -918,10 +926,6 @@ markAnnOpenP' :: (Monad m, Monoid w) => AnnPragma -> SourceText -> String -> EP
 markAnnOpenP' an NoSourceText txt   = markEpAnnLMS0 an lapr_open AnnOpen (Just txt)
 markAnnOpenP' an (SourceText txt) _ = markEpAnnLMS0 an lapr_open AnnOpen (Just $ unpackFS txt)
 
-markAnnOpen :: (Monad m, Monoid w) => [AddEpAnn] -> SourceText -> String -> EP w m [AddEpAnn]
-markAnnOpen an NoSourceText txt   = markEpAnnLMS'' an lidl AnnOpen (Just txt)
-markAnnOpen an (SourceText txt) _ = markEpAnnLMS'' an lidl AnnOpen (Just $ unpackFS txt)
-
 markAnnOpen' :: (Monad m, Monoid w)
   => Maybe EpaLocation -> SourceText -> String -> EP w m (Maybe EpaLocation)
 markAnnOpen' ms NoSourceText txt   = printStringAtMLoc' ms txt
@@ -2004,17 +2008,17 @@ exactDataFamInstDecl :: (Monad m, Monoid w)
                      => [AddEpAnn] -> TopLevelFlag -> DataFamInstDecl GhcPs
                      -> EP w m ([AddEpAnn], DataFamInstDecl GhcPs)
 exactDataFamInstDecl an top_lvl
-  (DataFamInstDecl (FamEqn { feqn_ext    = an2
+  (DataFamInstDecl (FamEqn { feqn_ext    = (ops, cps, eq)
                            , feqn_tycon  = tycon
                            , feqn_bndrs  = bndrs
                            , feqn_pats   = pats
                            , feqn_fixity = fixity
                            , feqn_rhs    = defn })) = do
-    (an', an2', tycon', bndrs', pats', defn') <- exactDataDefn an2 pp_hdr defn
+    ((ops', cps', an'), tycon', bndrs', pats', defn') <- exactDataDefn pp_hdr defn
                                           -- See Note [an and an2 in exactDataFamInstDecl]
     return
       (an',
-       DataFamInstDecl ( FamEqn { feqn_ext    = an2'
+       DataFamInstDecl ( FamEqn { feqn_ext    = (ops', cps', eq)
                                 , feqn_tycon  = tycon'
                                 , feqn_bndrs  = bndrs'
                                 , feqn_pats   = pats'
@@ -2024,7 +2028,7 @@ exactDataFamInstDecl an top_lvl
   where
     pp_hdr :: (Monad m, Monoid w)
            => Maybe (LHsContext GhcPs)
-           -> EP w m ( [AddEpAnn]
+           -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
                      , LocatedN RdrName
                      , HsOuterTyVarBndrs () GhcPs
                      , HsFamEqnPats GhcPs
@@ -2033,7 +2037,7 @@ exactDataFamInstDecl an top_lvl
       an0 <- case top_lvl of
                TopLevel -> markEpAnnL an lidl AnnInstance -- TODO: maybe in toplevel
                NotTopLevel -> return an
-      exactHsFamInstLHS an0 tycon bndrs pats fixity mctxt
+      exactHsFamInstLHS ops cps an0 tycon bndrs pats fixity mctxt
 
 {-
 Note [an and an2 in exactDataFamInstDecl]
@@ -2146,11 +2150,11 @@ instance ExactPrint (WarnDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warnings (an,src) warns) = do
-    an0 <- markAnnOpen an src "{-# WARNING" -- Note: might be {-# DEPRECATED
+  exact (Warnings ((o,c),src) warns) = do
+    o' <- markAnnOpen'' o src "{-# WARNING" -- Note: might be {-# DEPRECATED
     warns' <- markAnnotated warns
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (Warnings (an1,src) warns')
+    c' <- printStringAtAA c "#-}"
+    return (Warnings ((o',c'),src) warns')
 
 -- ---------------------------------------------------------------------
 
@@ -2212,14 +2216,14 @@ instance ExactPrint FastString where
 instance ExactPrint (RuleDecls GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (HsRules (an, src) rules) = do
-    an0 <-
+  exact (HsRules ((o,c), src) rules) = do
+    o' <-
       case src of
-        NoSourceText      -> markEpAnnLMS'' an lidl AnnOpen  (Just "{-# RULES")
-        SourceText srcTxt -> markEpAnnLMS'' an lidl AnnOpen  (Just $ unpackFS srcTxt)
+        NoSourceText      -> printStringAtAA o "{-# RULES"
+        SourceText srcTxt -> printStringAtAA o (unpackFS srcTxt)
     rules' <- markAnnotated rules
-    an1 <- markEpAnnLMS'' an0 lidl AnnClose (Just "#-}")
-    return (HsRules (an1,src) rules')
+    c' <- printStringAtAA c "#-}"
+    return (HsRules ((o',c'),src) rules')
 
 -- ---------------------------------------------------------------------
 
@@ -2344,16 +2348,16 @@ instance ExactPrint (RuleBndr GhcPs) where
 instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor fe _ _ _s = fe
-  exact (FamEqn { feqn_ext = an
+  exact (FamEqn { feqn_ext    = (ops, cps, eq)
                 , feqn_tycon  = tycon
                 , feqn_bndrs  = bndrs
                 , feqn_pats   = pats
                 , feqn_fixity = fixity
                 , feqn_rhs    = rhs }) = do
-    (an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS an tycon bndrs pats fixity Nothing
-    an1 <- markEpAnnL an0 lidl AnnEqual
+    (_an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
+    eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (FamEqn { feqn_ext = an1
+    return (FamEqn { feqn_ext    = ([], [], eq')
                    , feqn_tycon  = tycon'
                    , feqn_bndrs  = bndrs'
                    , feqn_pats   = pats'
@@ -2364,48 +2368,52 @@ instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
 
 exactHsFamInstLHS ::
       (Monad m, Monoid w)
-   => [AddEpAnn]
+   => [EpToken "("]
+   -> [EpToken ")"]
+   -> [AddEpAnn]
    -> LocatedN RdrName
    -> HsOuterTyVarBndrs () GhcPs
    -> HsFamEqnPats GhcPs
    -> LexicalFixity
    -> Maybe (LHsContext GhcPs)
-   -> EP w m ( [AddEpAnn]
+   -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
              , LocatedN RdrName
              , HsOuterTyVarBndrs () GhcPs
              , HsFamEqnPats GhcPs, Maybe (LHsContext GhcPs))
-exactHsFamInstLHS an thing bndrs typats fixity mb_ctxt = do
+exactHsFamInstLHS ops cps an thing bndrs typats fixity mb_ctxt = do
+  -- TODO:AZ: do these ans exist? They are in the binders now
   an0 <- markEpAnnL an lidl AnnForall
   bndrs' <- markAnnotated bndrs
   an1 <- markEpAnnL an0 lidl AnnDot
   mb_ctxt' <- mapM markAnnotated mb_ctxt
-  (an2, thing', typats') <- exact_pats an1 typats
-  return (an2, thing', bndrs', typats', mb_ctxt')
+  (ops', cps', thing', typats') <- exact_pats ops cps typats
+  return ((ops', cps', an1), thing', bndrs', typats', mb_ctxt')
   where
     exact_pats :: (Monad m, Monoid w)
-      => [AddEpAnn] -> HsFamEqnPats GhcPs -> EP w m ([AddEpAnn], LocatedN RdrName, HsFamEqnPats GhcPs)
-    exact_pats an' (patl:patr:pats)
+      => [EpToken "("] -> [EpToken ")"] -> HsFamEqnPats GhcPs
+      -> EP w m ([EpToken "("], [EpToken ")"], LocatedN RdrName, HsFamEqnPats GhcPs)
+    exact_pats ops1 cps1 (patl:patr:pats)
       | Infix <- fixity
       = let exact_op_app = do
-              an0 <- markEpAnnAllL' an' lidl AnnOpenP
+              ops' <- mapM markEpToken ops1
               patl' <- markAnnotated patl
               thing' <- markAnnotated thing
               patr' <- markAnnotated patr
-              an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-              return (an1, thing', [patl',patr'])
+              cps' <- mapM markEpToken cps1
+              return (ops', cps', thing', [patl',patr'])
         in case pats of
              [] -> exact_op_app
              _  -> do
-               (an0, thing', p) <- exact_op_app
+               (ops', cps', thing', p) <- exact_op_app
                pats' <- mapM markAnnotated pats
-               return (an0, thing', p++pats')
+               return (ops', cps', thing', p++pats')
 
-    exact_pats an' pats = do
-      an0 <- markEpAnnAllL' an' lidl AnnOpenP
+    exact_pats ops0 cps0 pats = do
+      ops' <- mapM markEpToken ops0
       thing' <- markAnnotated thing
       pats' <- markAnnotated pats
-      an1 <- markEpAnnAllL' an0 lidl AnnCloseP
-      return (an1, thing', pats')
+      cps' <- mapM markEpToken cps0
+      return (ops', cps', thing', pats')
 
 -- ---------------------------------------------------------------------
 
@@ -2471,11 +2479,11 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact d@(TyFamInstDecl { tfid_xtn = an, tfid_eqn = eqn }) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnInstance
+  exact d@(TyFamInstDecl { tfid_xtn = (tt,ti), tfid_eqn = eqn }) = do
+    tt' <- markEpToken tt
+    ti' <- markEpToken ti
     eqn' <- markAnnotated eqn
-    return (d { tfid_xtn = an1, tfid_eqn = eqn' })
+    return (d { tfid_xtn = (tt',ti'), tfid_eqn = eqn' })
 
 -- ---------------------------------------------------------------------
 
@@ -2967,13 +2975,13 @@ instance ExactPrint (DefaultDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DefaultDecl an cl tys) = do
-    an0 <- markEpAnnL an lidl AnnDefault
-    an1 <- markEpAnnL an0 lidl AnnOpenP
+  exact (DefaultDecl (d,op,cp) cl tys) = do
+    d' <- markEpToken d
+    op' <- markEpToken op
     cl' <- markAnnotated cl
     tys' <- markAnnotated tys
-    an2 <- markEpAnnL an1 lidl AnnCloseP
-    return (DefaultDecl an2 cl' tys')
+    cp' <- markEpToken cp
+    return (DefaultDecl (d',op',cp') cl' tys')
 
 -- ---------------------------------------------------------------------
 
@@ -3773,11 +3781,11 @@ instance ExactPrint (TyClDecl GhcPs) where
                     , tcdLName = ltycon', tcdTyVars = tyvars', tcdFixity = fixity
                     , tcdRhs = rhs' })
 
-  exact (DataDecl { tcdDExt = an, tcdLName = ltycon, tcdTyVars = tyvars
+  exact (DataDecl { tcdDExt = x, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
-    (_, an', ltycon', tyvars', _, defn') <-
-      exactDataDefn an (exactVanillaDeclHead ltycon tyvars fixity) defn
-    return (DataDecl { tcdDExt = an', tcdLName = ltycon', tcdTyVars = tyvars'
+    (_, ltycon', tyvars', _, defn') <-
+      exactDataDefn (exactVanillaDeclHead ltycon tyvars fixity) defn
+    return (DataDecl { tcdDExt = x, tcdLName = ltycon', tcdTyVars = tyvars'
                      , tcdFixity = fixity, tcdDataDefn = defn' })
 
   -- -----------------------------------
@@ -3852,7 +3860,7 @@ instance ExactPrint (FunDep GhcPs) where
 
   exact (FunDep an ls rs') = do
     ls' <- markAnnotated ls
-    an0 <- markEpAnnL an lidl AnnRarrow
+    an0 <- markEpUniToken an
     rs'' <- markAnnotated rs'
     return (FunDep an0 ls' rs'')
 
@@ -3862,7 +3870,7 @@ instance ExactPrint (FamilyDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (FamilyDecl { fdExt = an
+  exact (FamilyDecl { fdExt = AnnFamilyDecl ops cps t d f dc eq vb w oc dd cc
                     , fdInfo = info
                     , fdTopLevel = top_level
                     , fdLName = ltycon
@@ -3870,35 +3878,37 @@ instance ExactPrint (FamilyDecl GhcPs) where
                     , fdFixity = fixity
                     , fdResultSig = L lr result
                     , fdInjectivityAnn = mb_inj }) = do
-    an0 <- exactFlavour an info
-    an1 <- exact_top_level an0
-    an2 <- annotationsToComments an1 lidl [AnnOpenP,AnnCloseP]
+    (d',t') <- exactFlavour (d,t) info
+    f' <- exact_top_level f
+
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
     (_, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
-    (an3, result') <- exact_kind an2
-    (an4, mb_inj') <-
+    (dc', eq', result') <- exact_kind (dc, eq)
+    (vb', mb_inj') <-
       case mb_inj of
-        Nothing -> return (an3, mb_inj)
+        Nothing -> return (vb, mb_inj)
         Just inj -> do
-          an4 <- markEpAnnL an3 lidl AnnVbar
+          vb' <- markEpToken vb
           inj' <- markAnnotated inj
-          return (an4, Just inj')
-    (an5, info') <-
+          return (vb', Just inj')
+    (w', oc', dd', cc', info') <-
              case info of
                ClosedTypeFamily mb_eqns -> do
-                 an5 <- markEpAnnL an4 lidl AnnWhere
-                 an6 <- markEpAnnL an5 lidl AnnOpenC
-                 (an7, mb_eqns') <-
+                 w' <- markEpToken w
+                 oc' <- markEpToken oc
+                 (dd', mb_eqns') <-
                    case mb_eqns of
                      Nothing -> do
-                       an7 <- markEpAnnL an6 lidl AnnDotdot
-                       return (an7, mb_eqns)
+                       dd' <- markEpToken dd
+                       return (dd', mb_eqns)
                      Just eqns -> do
                        eqns' <- markAnnotated eqns
-                       return (an6, Just eqns')
-                 an8 <- markEpAnnL an7 lidl AnnCloseC
-                 return (an8, ClosedTypeFamily mb_eqns')
-               _ -> return (an4, info)
-    return (FamilyDecl { fdExt = an5
+                       return (dd, Just eqns')
+                 cc' <- markEpToken cc
+                 return (w',oc',dd',cc', ClosedTypeFamily mb_eqns')
+               _ -> return (w,oc,dd,cc, info)
+    return (FamilyDecl { fdExt = AnnFamilyDecl [] [] t' d' f' dc' eq' vb' w' oc' dd' cc'
                        , fdInfo = info'
                        , fdTopLevel = top_level
                        , fdLName = ltycon'
@@ -3907,86 +3917,91 @@ instance ExactPrint (FamilyDecl GhcPs) where
                        , fdResultSig = L lr result'
                        , fdInjectivityAnn = mb_inj' })
     where
-      exact_top_level an' =
+      exact_top_level tfamily =
         case top_level of
-          TopLevel    -> markEpAnnL an' lidl AnnFamily
+          TopLevel    -> markEpToken tfamily
           NotTopLevel -> do
             -- It seems that in some kind of legacy
             -- mode the 'family' keyword is still
             -- accepted.
-            markEpAnnL an' lidl AnnFamily
+            markEpToken tfamily
 
-      exact_kind an' =
+      exact_kind (tdcolon, tequal) =
         case result of
-          NoSig    _         -> return (an', result)
+          NoSig    _         -> return (tdcolon, tequal, result)
           KindSig  x kind    -> do
-            an0 <- markEpAnnL an' lidl AnnDcolon
+            tdcolon' <- markEpUniToken tdcolon
             kind' <- markAnnotated kind
-            return (an0, KindSig  x kind')
+            return (tdcolon', tequal, KindSig  x kind')
           TyVarSig x tv_bndr -> do
-            an0 <- markEpAnnL an' lidl AnnEqual
+            tequal' <- markEpToken tequal
             tv_bndr' <- markAnnotated tv_bndr
-            return (an0, TyVarSig x tv_bndr')
+            return (tdcolon, tequal', TyVarSig x tv_bndr')
 
 
-exactFlavour :: (Monad m, Monoid w) => [AddEpAnn] -> FamilyInfo GhcPs -> EP w m [AddEpAnn]
-exactFlavour an DataFamily            = markEpAnnL an lidl AnnData
-exactFlavour an OpenTypeFamily        = markEpAnnL an lidl AnnType
-exactFlavour an (ClosedTypeFamily {}) = markEpAnnL an lidl AnnType
+exactFlavour :: (Monad m, Monoid w) => (EpToken "data", EpToken "type") -> FamilyInfo GhcPs -> EP w m (EpToken "data", EpToken "type")
+exactFlavour (td,tt) DataFamily            = (\td' -> (td',tt)) <$> markEpToken td
+exactFlavour (td,tt) OpenTypeFamily        = (td,)              <$> markEpToken tt
+exactFlavour (td,tt) (ClosedTypeFamily {}) = (td,)              <$> markEpToken tt
 
 -- ---------------------------------------------------------------------
 
 exactDataDefn
   :: (Monad m, Monoid w)
-  => [AddEpAnn]
-  -> (Maybe (LHsContext GhcPs) -> EP w m ([AddEpAnn]
+  => (Maybe (LHsContext GhcPs) -> EP w m (r
                                          , LocatedN RdrName
                                          , a
                                          , b
                                          , Maybe (LHsContext GhcPs))) -- Printing the header
   -> HsDataDefn GhcPs
-  -> EP w m ( [AddEpAnn] -- ^ from exactHdr
-            , [AddEpAnn] -- ^ updated one passed in
+  -> EP w m ( r -- ^ from exactHdr
             , LocatedN RdrName, a, b, HsDataDefn GhcPs)
-exactDataDefn an exactHdr
-                 (HsDataDefn { dd_ext = x, dd_ctxt = context
+exactDataDefn exactHdr
+                 (HsDataDefn { dd_ext = AnnDataDefn ops cps t nt d i dc w oc cc eq
+                             , dd_ctxt = context
                              , dd_cType = mb_ct
                              , dd_kindSig = mb_sig
                              , dd_cons = condecls, dd_derivs = derivings }) = do
 
-  an' <- annotationsToComments an lidl [AnnOpenP, AnnCloseP]
 
-  an0 <- case condecls of
-    DataTypeCons is_type_data _ -> do
-      an0' <- if is_type_data
-                then markEpAnnL an' lidl AnnType
-                else return an'
-      markEpAnnL an0' lidl AnnData
-    NewTypeCon   _ -> markEpAnnL an' lidl AnnNewtype
+  epTokensToComments AnnOpenP ops
+  epTokensToComments AnnCloseP cps
 
-  an1 <- markEpAnnL an0 lidl AnnInstance -- optional
+  (t',nt',d') <- case condecls of
+    DataTypeCons is_type_data _ -> do
+      t' <- if is_type_data
+                then markEpToken t
+                else return t
+      d' <- markEpToken d
+      return (t',nt,d')
+    NewTypeCon   _ -> do
+      nt' <- markEpToken nt
+      return (t, nt', d)
+
+  i' <- markEpToken i -- optional
   mb_ct' <- mapM markAnnotated mb_ct
   (anx, ln', tvs', b, mctxt') <- exactHdr context
-  (an2, mb_sig') <- case mb_sig of
-    Nothing -> return (an1, Nothing)
+  (dc', mb_sig') <- case mb_sig of
+    Nothing -> return (dc, Nothing)
     Just kind -> do
-      an2 <- markEpAnnL an1 lidl AnnDcolon
+      dc' <- markEpUniToken dc
       kind' <- markAnnotated kind
-      return (an2, Just kind')
-  an3 <- if (needsWhere condecls)
-    then markEpAnnL an2 lidl AnnWhere
-    else return an2
-  an4 <- markEpAnnL an3 lidl AnnOpenC
-  (an5, condecls') <- exact_condecls an4 (toList condecls)
+      return (dc', Just kind')
+  w' <- if (needsWhere condecls)
+    then markEpToken w
+    else return w
+  oc' <- markEpToken oc
+  (eq', condecls') <- exact_condecls eq (toList condecls)
   let condecls'' = case condecls of
-        DataTypeCons d _ -> DataTypeCons d condecls'
+        DataTypeCons td _ -> DataTypeCons td condecls'
         NewTypeCon _     -> case condecls' of
           [decl] -> NewTypeCon decl
           _ -> panic "exacprint NewTypeCon"
-  an6 <- markEpAnnL an5 lidl AnnCloseC
+  cc' <- markEpToken cc
   derivings' <- mapM markAnnotated derivings
-  return (anx, an6, ln', tvs', b,
-                 (HsDataDefn { dd_ext = x, dd_ctxt = mctxt'
+  return (anx, ln', tvs', b,
+                 (HsDataDefn { dd_ext = AnnDataDefn [] [] t' nt' d' i' dc' w' oc' cc' eq'
+                             , dd_ctxt = mctxt'
                              , dd_cType = mb_ct'
                              , dd_kindSig = mb_sig'
                              , dd_cons = condecls'', dd_derivs = derivings' }))
@@ -4032,12 +4047,11 @@ exactVanillaDeclHead thing tvs@(HsQTvs { hsq_explicit = tyvars }) fixity context
 instance ExactPrint (InjectivityAnn GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (InjectivityAnn an lhs rhs) = do
-    an0 <- markEpAnnL an lidl AnnVbar
+  exact (InjectivityAnn rarrow lhs rhs) = do
     lhs' <- markAnnotated lhs
-    an1 <- markEpAnnL an0 lidl AnnRarrow
+    rarrow' <- markEpUniToken rarrow
     rhs' <- mapM markAnnotated rhs
-    return (InjectivityAnn an1 lhs' rhs')
+    return (InjectivityAnn rarrow' lhs' rhs')
 
 -- ---------------------------------------------------------------------
 
@@ -4238,17 +4252,17 @@ instance ExactPrint (HsForAllTelescope GhcPs) where
   setAnnotationAnchor (HsForAllVis an a) anc ts cs = HsForAllVis (setAnchorEpa an anc ts cs) a
   setAnnotationAnchor (HsForAllInvis an a) anc ts cs = HsForAllInvis (setAnchorEpa an anc ts cs) a
 
-  exact (HsForAllVis an bndrs)   = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllVis (EpAnn l (f,r) cs) bndrs)   = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnRarrow
-    return (HsForAllVis an1 bndrs')
+    r' <- markEpUniToken r
+    return (HsForAllVis (EpAnn l (f',r') cs) bndrs')
 
-  exact (HsForAllInvis an bndrs) = do
-    an0 <- markLensAA an lfst -- AnnForall
+  exact (HsForAllInvis (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- AnnDot
-    return (HsForAllInvis an1 bndrs')
+    d' <- markEpToken d
+    return (HsForAllInvis (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 
@@ -4430,17 +4444,17 @@ markTrailing ts = do
 
 -- based on pp_condecls in Decls.hs
 exact_condecls :: (Monad m, Monoid w)
-  => [AddEpAnn] -> [LConDecl GhcPs] -> EP w m ([AddEpAnn],[LConDecl GhcPs])
-exact_condecls an cs
+  => EpToken "=" -> [LConDecl GhcPs] -> EP w m (EpToken "=",[LConDecl GhcPs])
+exact_condecls eq cs
   | gadt_syntax                  -- In GADT syntax
   = do
       cs' <- mapM markAnnotated cs
-      return (an, cs')
+      return (eq, cs')
   | otherwise                    -- In H98 syntax
   = do
-      an0 <- markEpAnnL an lidl AnnEqual
+      eq0 <- markEpToken eq
       cs' <- mapM markAnnotated cs
-      return (an0, cs')
+      return (eq0, cs')
   where
     gadt_syntax = case cs of
       []                      -> False
@@ -4553,11 +4567,11 @@ instance ExactPrintTVFlag flag => ExactPrint (HsOuterTyVarBndrs flag GhcPs) wher
   setAnnotationAnchor (HsOuterExplicit an a) anc ts cs = HsOuterExplicit (setAnchorEpa an anc ts cs) a
 
   exact b@(HsOuterImplicit _) = pure b
-  exact (HsOuterExplicit an bndrs) = do
-    an0 <- markLensAA an lfst -- "forall"
+  exact (HsOuterExplicit (EpAnn l (f,d) cs) bndrs) = do
+    f' <- markEpUniToken f
     bndrs' <- markAnnotated bndrs
-    an1 <- markLensAA an0 lsnd -- "."
-    return (HsOuterExplicit an1 bndrs')
+    d' <- markEpToken d
+    return (HsOuterExplicit (EpAnn l (f',d') cs) bndrs')
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -209,10 +209,10 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/PprParenFunBind.hs" Nothing
  -- "../../testsuite/tests/printer/Test16279.hs" Nothing
  -- "../../testsuite/tests/printer/HsDocTy.hs" Nothing
- "../../testsuite/tests/printer/Test21355.hs" Nothing
+ -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- -- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -269,7 +269,7 @@ synifyTyCon prr _coax tc
           , tcdFixity = synifyFixity tc
           , tcdDataDefn =
               HsDataDefn
-                { dd_ext = noExtField
+                { dd_ext = noAnn
                 , dd_cons = DataTypeCons False [] -- No constructors; arbitrary lie, they are neither
                 -- algebraic data nor newtype:
                 , dd_ctxt = Nothing
@@ -401,7 +401,7 @@ synifyTyCon _prr coax tc
         alg_deriv = []
         defn =
           HsDataDefn
-            { dd_ext = noExtField
+            { dd_ext = noAnn
             , dd_ctxt = alg_ctx
             , dd_cType = Nothing
             , dd_kindSig = kindSig



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25edf84977fa15b9911ecbdf614789893ad0e108

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 10:04:40 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 20 Oct 2024 06:04:40 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ttg-BooleanFormula-a
Message-ID: <6714d5b8cbd8e_bf4382cf920556bd@gitlab.mail>



Hassan Al-Awwadi pushed new branch wip/ttg-BooleanFormula-a at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ttg-BooleanFormula-a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 12:05:35 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 20 Oct 2024 08:05:35 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 91 commits: testsuite:
 Normalise trailing digits from hole fits output
Message-ID: <6714f20f56fbc_3f1564150d1045498@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
c4856303 by Hassan Al-Awwadi at 2024-10-20T12:08:08+02:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit. We moved the definition of BooleanFormula
over to L.H.S.BooleanFormula, and we parameterized it over the ghcPass instead
of over some arbitrary type.

That said the changes are largely superficial. Most effort was in dealing
with IFaceBooleanFormula, as we used to map the booleanformula to contain a
IfLclName and then transform it to to the IFaceBooleanFormula, but that's
no longer posssible in the current setup. Instead we just folded the
transformation from a Name to an IfLclName in the transformation
from BooleanFormula to IfaceBooleanFormula.

- - - - -
b4f825b6 by Hassan Al-Awwadi at 2024-10-20T12:08:08+02:00
review changes for BooleanFormula

* Removed bfExprMap, instead bfMap is fully defined inside Ghc.Data.BooleanFormula
* Cleaned up some classes for BooleanFormula
* Simplified toIfaceBooleanFormula to no longer be a higher order function
* And removed fromIfaceBooleanFormula completely

- - - - -
94d65274 by Hassan Al-Awwadi at 2024-10-20T12:08:08+02:00
removed unused import

- - - - -
d2d70122 by Hassan Al-Awwadi at 2024-10-20T12:08:09+02:00
Only stores BOoleanFormula source-locations in leaves

- - - - -
2164d09e by Hassan Al-Awwadi at 2024-10-20T12:08:09+02:00
removed unused import

- - - - -
679fd17c by Hassan Al-Awwadi at 2024-10-20T14:05:09+02:00
Changed IFaceBooleanFormula to have a Name

This really simplifies a lot of the code :relieved:

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aabf390924b41d3c8960e31cc0388c39c9274558...679fd17c6df1e5fe2e3eb60b9b1cd9e94649514a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aabf390924b41d3c8960e31cc0388c39c9274558...679fd17c6df1e5fe2e3eb60b9b1cd9e94649514a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 12:10:48 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sun, 20 Oct 2024 08:10:48 -0400
Subject: [Git][ghc/ghc] Pushed new tag ghc-9.8.3-release
Message-ID: <6714f348d4ab4_3f15641493bc462a5@gitlab.mail>



Ben Gamari pushed new tag ghc-9.8.3-release at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/ghc-9.8.3-release
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 12:23:38 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sun, 20 Oct 2024 08:23:38 -0400
Subject: [Git][ghc/ghc][ghc-9.8] 2 commits: Simplify regexes with raw strings
Message-ID: <6714f64a2163a_3f15643591fc476e1@gitlab.mail>



Ben Gamari pushed to branch ghc-9.8 at Glasgow Haskell Compiler / GHC


Commits:
f41b0bda by Brandon Chinn at 2024-10-19T08:13:42-04:00
Simplify regexes with raw strings

(cherry picked from commit c91946f994ad8b734b09cf3023f1fc9671a7475a)

- - - - -
72e04175 by Ben Gamari at 2024-10-19T08:41:21-04:00
testsuite: More aggressive version number normalization

Component names can sometimes have hashes.

- - - - -


1 changed file:

- testsuite/driver/testlib.py


Changes:

=====================================
testsuite/driver/testlib.py
=====================================
@@ -1019,8 +1019,12 @@ def normalise_win32_io_errors(name, opts):
 def normalise_version_( *pkgs ):
     def normalise_version__( str ):
         # (name)(-version)(-hash)(-components)
-        return re.sub('(' + '|'.join(map(re.escape,pkgs)) + ')-[0-9.]+(-[0-9a-zA-Z\+]+)?(-[0-9a-zA-Z]+)?',
-                      '\\1--', str)
+        pkg_names = '(' + '|'.join(map(re.escape,pkgs)) + ')'
+        version = r'[0-9\.]+'
+        pkg_hash = r'(-[0-9a-zA-Z\+]+)'
+        component = r'(-[0-9a-zA-Z]+(\+[0-9a-zA-Z]+)?)'
+        return re.sub(f'{pkg_names}-{version}{pkg_hash}?{component}?',
+                      r'\1--', str)
     return normalise_version__
 
 def normalise_version( *pkgs ):
@@ -1393,7 +1397,7 @@ async def do_test(name: TestName,
     if opts.expect not in ['pass', 'fail', 'missing-lib']:
         framework_fail(name, way, 'bad expected ' + opts.expect)
 
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
 
     if way in opts.fragile_ways:
         if_verbose(1, '*** fragile test %s resulted in %s' % (full_name, 'pass' if result.passed else 'fail'))
@@ -1440,7 +1444,7 @@ def override_options(pre_cmd):
 
 def framework_fail(name: Optional[TestName], way: Optional[WayName], reason: str) -> None:
     opts = getTestOpts()
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
     full_name = '%s(%s)' % (name, way)
     if_verbose(1, '*** framework failure for %s %s ' % (full_name, reason))
     name2 = name if name is not None else TestName('none')
@@ -1451,7 +1455,7 @@ def framework_fail(name: Optional[TestName], way: Optional[WayName], reason: str
 
 def framework_warn(name: TestName, way: WayName, reason: str) -> None:
     opts = getTestOpts()
-    directory = re.sub('^\\.[/\\\\]', '', str(opts.testdir))
+    directory = re.sub(r'^\.[/\\]', '', str(opts.testdir))
     full_name = name + '(' + way + ')'
     if_verbose(1, '*** framework warning for %s %s ' % (full_name, reason))
     t.framework_warnings.append(TestResult(directory, name, reason, way))
@@ -2476,7 +2480,7 @@ def normalise_errmsg(s: str) -> str:
     s = normalise_type_reps(s)
 
     # normalise slashes, minimise Windows/Unix filename differences
-    s = re.sub('\\\\', '/', s)
+    s = re.sub(r'\\', '/', s)
 
     # Normalize the name of the GHC executable. Specifically,
     # this catches the cases that:
@@ -2491,11 +2495,11 @@ def normalise_errmsg(s: str) -> str:
     #    the colon is there because it appears in error messages; this
     #    hacky solution is used in place of more sophisticated filename
     #    mangling
-    s = re.sub('([^\\s])\\.exe', '\\1', s)
+    s = re.sub(r'([^\s])\.exe', r'\1', s)
     # Same thing for .wasm modules generated by the Wasm backend
-    s = re.sub('([^\\s])\\.wasm', '\\1', s)
+    s = re.sub(r'([^\s])\.wasm', r'\1', s)
     # Same thing for .jsexe directories generated by the JS backend
-    s = re.sub('([^\\s])\\.jsexe', '\\1', s)
+    s = re.sub(r'([^\s])\.jsexe', r'\1', s)
 
     # normalise slashes, minimise Windows/Unix filename differences
     s = re.sub('\\\\', '/', s)
@@ -2508,8 +2512,8 @@ def normalise_errmsg(s: str) -> str:
     s = re.sub('ghc-stage[123]', 'ghc', s)
     # Remove platform prefix (e.g. javascript-unknown-ghcjs) for cross-compiled tools
     # (ghc, ghc-pkg, unlit, etc.)
-    s = re.sub('\\w+(-\\w+)*-ghc', 'ghc', s)
-    s = re.sub('\\w+(-\\w+)*-unlit', 'unlit', s)
+    s = re.sub(r'\w+(-\w+)*-ghc', 'ghc', s)
+    s = re.sub(r'\w+(-\w+)*-unlit', 'unlit', s)
 
     # On windows error messages can mention versioned executables
     s = re.sub('ghc-[0-9.]+', 'ghc', s)
@@ -2610,8 +2614,8 @@ def normalise_prof (s: str) -> str:
     return s
 
 def normalise_slashes_( s: str ) -> str:
-    s = re.sub('\\\\', '/', s)
-    s = re.sub('//', '/', s)
+    s = re.sub(r'\\', '/', s)
+    s = re.sub(r'//', '/', s)
     return s
 
 def normalise_exe_( s: str ) -> str:
@@ -2629,9 +2633,9 @@ def normalise_output( s: str ) -> str:
     # and .wasm extension (for the Wasm backend)
     # and .jsexe extension (for the JS backend)
     # This can occur in error messages generated by the program.
-    s = re.sub('([^\\s])\\.exe', '\\1', s)
-    s = re.sub('([^\\s])\\.wasm', '\\1', s)
-    s = re.sub('([^\\s])\\.jsexe', '\\1', s)
+    s = re.sub(r'([^\s])\.exe', r'\1', s)
+    s = re.sub(r'([^\s])\.wasm', r'\1', s)
+    s = re.sub(r'([^\s])\.jsexe', r'\1', s)
     s = normalise_callstacks(s)
     s = normalise_type_reps(s)
     # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is
@@ -2651,7 +2655,7 @@ def normalise_output( s: str ) -> str:
     s = re.sub('.*warning: argument unused during compilation:.*\n', '', s)
 
     # strip the cross prefix if any
-    s = re.sub('\\w+(-\\w+)*-ghc', 'ghc', s)
+    s = re.sub(r'\w+(-\w+)*-ghc', 'ghc', s)
 
     return s
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24e765b4be020c6c3c9641d7c9a2d3da347d45a6...72e041753f8d2c5b1fae0465277b187c61f17634

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24e765b4be020c6c3c9641d7c9a2d3da347d45a6...72e041753f8d2c5b1fae0465277b187c61f17634
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 12:23:45 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Sun, 20 Oct 2024 08:23:45 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/backports-9.8
Message-ID: <6714f6516f713_3f15643591fc4783c@gitlab.mail>



Ben Gamari deleted branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 12:47:15 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sun, 20 Oct 2024 08:47:15 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-centos7
Message-ID: <6714fbd32fdb6_3f15644b7da05993d@gitlab.mail>



Cheng Shao pushed new branch wip/fix-centos7 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-centos7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 13:31:16 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sun, 20 Oct 2024 09:31:16 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-ghci-wrapper
Message-ID: <6715062453ea5_3f15647fa7ec621e4@gitlab.mail>



Cheng Shao pushed new branch wip/fix-ghci-wrapper at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-ghci-wrapper
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 13:38:14 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sun, 20 Oct 2024 09:38:14 -0400
Subject: [Git][ghc/ghc][wip/fix-ghci-wrapper] hadrian: fix bindist executable
 wrapper logic for cross targets
Message-ID: <671507c625539_3f15648cdef86398f@gitlab.mail>



Cheng Shao pushed to branch wip/fix-ghci-wrapper at Glasgow Haskell Compiler / GHC


Commits:
299dd249 by Cheng Shao at 2024-10-20T13:37:12+00:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content.

- - - - -


1 changed file:

- hadrian/src/Rules/BinaryDist.hs


Changes:

=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -437,13 +437,14 @@ pkgToWrappers pkg = do
       | otherwise     -> pure []
 
 wrapper :: FilePath -> Action String
-wrapper "ghc"         = ghcWrapper
-wrapper "ghc-pkg"     = ghcPkgWrapper
-wrapper "ghci" = ghciScriptWrapper
-wrapper "haddock"     = haddockWrapper
-wrapper "hsc2hs"      = hsc2hsWrapper
-wrapper "runghc"      = runGhcWrapper
-wrapper "runhaskell"  = runGhcWrapper
+wrapper wrapper_name
+  | "ghc"        `isSuffixOf` wrapper_name = ghcWrapper
+  | "ghc-pkg"    `isSuffixOf` wrapper_name = ghcPkgWrapper
+  | "ghci"       `isSuffixOf` wrapper_name = ghciScriptWrapper
+  | "haddock"    `isSuffixOf` wrapper_name = haddockWrapper
+  | "hsc2hs"     `isSuffixOf` wrapper_name = hsc2hsWrapper
+  | "runghc"     `isSuffixOf` wrapper_name = runGhcWrapper
+  | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper
 wrapper _             = commonWrapper
 
 -- | Wrapper scripts for different programs. Common is default wrapper.
@@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\
 -- | --interactive flag.
 ghciScriptWrapper :: Action String
 ghciScriptWrapper = do
+  prefix <- crossPrefix
   version <- setting ProjectVersion
   pure $ unlines
-    [ "executable=\"$bindir/ghc-" ++ version ++ "\""
+    [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
     , "exec $executable --interactive \"$@\"" ]
 
 -- | When not on Windows, we want to ship the 3 flavours of the iserv program
@@ -548,4 +550,3 @@ createGhcii outDir = do
       [ "#!/bin/sh"
       , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\""
       ]
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/299dd24945f59e3cd33350ba5092fce0a8493528

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 14:00:24 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 20 Oct 2024 10:00:24 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-5] 74 commits: Changed
 import from Ghc.  module to L.H.S module
Message-ID: <67150cf83c74a_233dae15ff7c98828@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-5 at Glasgow Haskell Compiler / GHC


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
9d688318 by Alan Zimmerman at 2024-10-20T11:15:53+01:00
EPA: Remove [AddEpAnn] from AnnPragma

- - - - -
4fbfb59e by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] From ForeignDecl

- - - - -
a1d9d2e3 by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from RoleAnnotDecl

- - - - -
bb3cabab by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from StandaloneKindSig

- - - - -
f01b9c2c by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] From HsDeriving

- - - - -
a8414a30 by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from ConDeclField

- - - - -
64356f24 by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from ConDeclGADT

- - - - -
c70b9ce7 by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from ConDeclH98

- - - - -
69b615c7 by Alan Zimmerman at 2024-10-20T11:15:58+01:00
EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -


22 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Linker/Deps.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e44633ef60d86e33784e8198373f768d89e1882a...69b615c7e0b7321761330b0390f623b7bbbd99f0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e44633ef60d86e33784e8198373f768d89e1882a...69b615c7e0b7321761330b0390f623b7bbbd99f0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 14:34:42 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 20 Oct 2024 10:34:42 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: ci: Add
 support for ONLY_JOBS variable to trigger any validation pipeline
Message-ID: <671515023cba8_233dae28bb581060ea@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
ea4bfe47 by Luite Stegeman at 2024-10-20T10:34:25-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
4aa42e99 by Matthew James Kraai at 2024-10-20T10:34:30-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4dbc648f by Luite Stegeman at 2024-10-20T10:34:34-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -


18 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/ThToHs.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d01a62a97b38f3f4de971ad9813a7269eac1da0a...4dbc648f0fb5871bcaf8888ddfb9a6c2636d0328

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d01a62a97b38f3f4de971ad9813a7269eac1da0a...4dbc648f0fb5871bcaf8888ddfb9a6c2636d0328
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 15:20:53 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sun, 20 Oct 2024 11:20:53 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-dyld-bump-v8-heap-size-limit
Message-ID: <67151fd57580b_233dae5d7258112580@gitlab.mail>



Cheng Shao pushed new branch wip/wasm-dyld-bump-v8-heap-size-limit at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-dyld-bump-v8-heap-size-limit
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 15:49:24 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 20 Oct 2024 11:49:24 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] back to IfLclName, keep the
 from/toIfacebooleanformula
Message-ID: <67152684dcf21_234a0516d5dc39141@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
320af165 by Hassan Al-Awwadi at 2024-10-20T17:48:58+02:00
back to IfLclName, keep the from/toIfacebooleanformula

use mkUnboundName to switch back and forth.

- - - - -


2 changed files:

- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -50,6 +50,7 @@ module GHC.Iface.Syntax (
 
 import GHC.Prelude
 
+import GHC.Builtin.Names(mkUnboundName)
 import GHC.Data.FastString
 import GHC.Data.BooleanFormula (pprBooleanFormula, isTrue)
 
@@ -63,9 +64,9 @@ import GHC.Types.Demand
 import GHC.Types.Cpr
 import GHC.Core.Class
 import GHC.Types.FieldLabel
-import GHC.Types.Name.Set
 import GHC.Core.Coercion.Axiom ( BranchIndex )
 import GHC.Types.Name
+import GHC.Types.Name.Set
 import GHC.Types.Name.Reader
 import GHC.Types.CostCentre
 import GHC.Types.Literal
@@ -216,7 +217,7 @@ data IfaceClassBody
     }
 
 data IfaceBooleanFormula
-  = IfVar IfaceTopBndr
+  = IfVar IfLclName
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
@@ -224,15 +225,17 @@ data IfaceBooleanFormula
 toIfaceBooleanFormula :: BooleanFormula GhcRn -> IfaceBooleanFormula
 toIfaceBooleanFormula = go
   where
-    go (Var nm   ) = IfVar    $ unLoc  nm
+    go (Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
     go (And bfs  ) = IfAnd    $ map go bfs
     go (Or bfs   ) = IfOr     $ map go bfs
     go (Parens bf) = IfParens $     go bf
 
+-- | note that this makes unbound names, so if you actually want
+-- proper Names, you'll need to properly Rename it (lookupIfaceTop).
 fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
 fromIfaceBooleanFormula = go
   where
-   go (IfVar nm   ) = Var    $ noLocA nm
+   go (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
    go (IfAnd bfs  ) = And    $ map go bfs
    go (IfOr bfs   ) = Or     $ map go bfs
    go (IfParens bf) = Parens $     go bf
@@ -2149,14 +2152,14 @@ instance Binary IfaceDecl where
 
 instance Binary IfaceBooleanFormula where
     put_ bh = \case
-        IfVar a1    -> putByte bh 0 >> putIfaceTopBndr bh a1
+        IfVar a1    -> putByte bh 0 >> put_ bh a1
         IfAnd a1    -> putByte bh 1 >> put_ bh a1
         IfOr a1     -> putByte bh 2 >> put_ bh a1
         IfParens a1 -> putByte bh 3 >> put_ bh a1
 
     get bh = do
         getByte bh >>= \case
-            0 -> IfVar    <$> getIfaceTopBndr bh
+            0 -> IfVar    <$> get bh
             1 -> IfAnd    <$> get bh
             2 -> IfOr     <$> get bh
             _ -> IfParens <$> get bh


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -123,6 +123,10 @@ import GHC.Types.Tickish
 import GHC.Types.TyThing
 import GHC.Types.Error
 
+import GHC.Parser.Annotation (noLocA)
+
+import GHC.Hs.Extension ( GhcRn )
+
 import GHC.Fingerprint
 
 import Control.Monad
@@ -136,7 +140,8 @@ import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
 
-import Language.Haskell.Syntax.BooleanFormula (mkOr)
+import Language.Haskell.Syntax.BooleanFormula (mkOr, BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
 {-
@@ -298,14 +303,9 @@ mergeIfaceDecl d1 d2
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
 
-          -- same as BooleanFormula's mkOr, but specialized to IfaceBooleanFormula,
-          -- which can be taught of as being (BooleanFormula IfacePass) morally.
-          -- In practice, however, its a seperate type so it needs its own function
-          -- It makes an Or and does some super basic simplification.
-
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . mkOr $ map fromIfaceBooleanFormula [ bf1, bf2]
+                ifMinDef = toIfaceBooleanFormula . mkOr . map fromIfaceBooleanFormula $ [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -801,7 +801,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef = fromIfaceBooleanFormula if_mindef
+    ; mindef <- tc_boolean_formula if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)
@@ -850,6 +850,13 @@ tc_iface_decl _parent ignore_prags
                   -- e.g.   type AT a; type AT b = AT [b]   #8002
           return (ATI tc mb_def)
 
+   tc_boolean_formula :: IfaceBooleanFormula -> IfL (BooleanFormula GhcRn)
+   tc_boolean_formula (IfVar nm    ) = BF.Var . noLocA <$>
+    (lookupIfaceTop . mkVarOccFS . ifLclNameFS) nm
+   tc_boolean_formula (IfAnd ibfs  ) = BF.And    <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfOr ibfs   ) = BF.Or     <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfParens ibf) = BF.Parens <$> tc_boolean_formula ibf
+
    mk_sc_doc pred = text "Superclass" <+> ppr pred
    mk_at_doc tc = text "Associated type" <+> ppr tc
    mk_op_doc op_name op_ty = text "Class op" <+> sep [ppr op_name, ppr op_ty]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/320af165fd71594fc678d12956e9d63c81f24000

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 16:52:05 2024
From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns))
Date: Sun, 20 Oct 2024 12:52:05 -0400
Subject: [Git][ghc/ghc][wip/aidylns/ttg-remove-hsunboundvar-via-hshole] HsVar
 Bound/Unbound
Message-ID: <67153535a5257_7b961ea48425282@gitlab.mail>



Adriaan Leijnse pushed to branch wip/aidylns/ttg-remove-hsunboundvar-via-hshole at Glasgow Haskell Compiler / GHC


Commits:
32a151e1 by Adriaan Leijnse at 2024-10-20T18:22:36+02:00
HsVar Bound/Unbound

- - - - -


30 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Instantiate.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32a151e1e0706bb16c9f9a920e796bf2a8f8886b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 18:07:25 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Sun, 20 Oct 2024 14:07:25 -0400
Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP: simd000 - hacked
 further
Message-ID: <671546dd9ae62_7b9616f43d43419f@gitlab.mail>



Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC


Commits:
94ec8cb6 by Sven Tennie at 2024-10-20T20:06:20+02:00
WIP: simd000 - hacked further

- - - - -


13 changed files:

- compiler/CodeGen.Platform.h
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs
- compiler/GHC/Platform/Reg/Class.hs
- hadrian/src/Flavour.hs
- rts/CheckVectorSupport.c
- rts/include/stg/MachRegs/riscv64.h
- testsuite/tests/simd/should_run/all.T


Changes:

=====================================
compiler/CodeGen.Platform.h
=====================================
@@ -411,6 +411,39 @@ import GHC.Platform.Reg
 # define ft10 62
 # define ft11 63
 
+# define v0  64
+# define v1  65
+# define v2  66
+# define v3  67
+# define v4  68
+# define v5  69
+# define v6  70
+# define v7  71
+# define v8  72
+# define v9  73
+# define v10 74
+# define v11 75
+# define v12 76
+# define v13 77
+# define v14 78
+# define v15 79
+# define v16 80
+# define v17 81
+# define v18 82
+# define v19 83
+# define v20 84
+# define v21 85
+# define v22 86
+# define v23 87
+# define v24 88
+# define v25 89
+# define v26 90
+# define v27 91
+# define v28 92
+# define v29 93
+# define v30 94
+# define v31 95
+
 #elif defined(MACHREGS_loongarch64)
 
 # define zero 0
@@ -1218,6 +1251,25 @@ freeReg REG_D5    = False
 freeReg REG_D6    = False
 # endif
 
+# if defined(REG_XMM1)
+freeReg REG_XMM1    = False
+# endif
+# if defined(REG_XMM2)
+freeReg REG_XMM2    = False
+# endif
+# if defined(REG_XMM3)
+freeReg REG_XMM3    = False
+# endif
+# if defined(REG_XMM4)
+freeReg REG_XMM4    = False
+# endif
+# if defined(REG_XMM5)
+freeReg REG_XMM5    = False
+# endif
+# if defined(REG_XMM6)
+freeReg REG_XMM6    = False
+# endif
+
 freeReg _ = True
 
 #else


=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -664,7 +664,7 @@ getRegister' config plat expr =
       Amode addr addr_code <- getAmode plat width mem
       case width of
         w
-          | w <= W64 ->
+          | (w <= W64) || isVecFormat format ->
               -- Load without sign-extension. See Note [Signed arithmetic on RISCV64]
               pure
                 ( Any
@@ -674,6 +674,20 @@ getRegister' config plat expr =
                           `snocOL` LDRU format (OpReg width dst) (OpAddr addr)
                     )
                 )
+        -- TODO: Load vector - instructions VLW, VLB, VLH, ... Encode in ppr of LDRU?
+        -- riscv64-unknown-linux-gnu-ghc: panic! (the 'impossible' happened)
+        -- GHC version 9.13.20241013:
+        --       Width too big! Cannot load: W128
+        -- Fx2V128[Sp + 8]
+        -- Call stack:
+        --     CallStack (from HasCallStack):
+        --       callStackDoc, called at compiler/GHC/Utils/Panic.hs:190:37 in ghc-9.13-inplace:GHC.Utils.Panic
+        --       pprPanic, called at compiler/GHC/CmmToAsm/RV64/CodeGen.hs:678:11 in ghc-9.13-inplace:GHC.CmmToAsm.RV64.CodeGen
+        -- CallStack (from HasCallStack):
+        --   panic, called at compiler/GHC/Utils/Error.hs:507:29 in ghc-9.13-inplace:GHC.Utils.Error
+
+        -- Fx2V128 -> cat= Float, length = 2, widthInBits = 128
+
         _ ->
           pprPanic ("Width too big! Cannot load: " ++ show width) (pdoc plat expr)
     CmmStackSlot _ _ ->
@@ -820,10 +834,10 @@ getRegister' config plat expr =
             code_idx `snocOL`
             annExpr expr (VMV (OpReg w dst) (OpReg w_idx reg_idx))
 
-        MO_VF_Broadcast _length w -> do
+        MO_VF_Broadcast l w -> do
           (reg_idx, format_idx, code_idx) <- getSomeReg e
           let w_idx = formatToWidth format_idx
-          pure $ Any (intFormat w) $ \dst ->
+          pure $ Any (vecFormat (cmmVec l (cmmFloat w))) $ \dst ->
             code_idx `snocOL`
             annExpr expr (VMV (OpReg w dst) (OpReg w_idx reg_idx))
 


=====================================
compiler/GHC/CmmToAsm/RV64/Instr.hs
=====================================
@@ -136,7 +136,10 @@ regUsageOfInstr platform instr = case instr of
         fmt = case cls of
                 RcInteger -> II64
                 RcFloat   -> FF64
-                RcVector  -> sorry "The RISCV64 NCG does not (yet) support vectors; please use -fllvm."
+                -- TODO: We're expecting 128bit vector registers here. This
+                -- needs to be calculated from real format. Probably, we need to
+                -- hand around the format instead of the width for vector regs.
+                RcVector -> VecFormat 2 FmtInt64
         cls = case r of
                 RegVirtual vr -> classOfVirtualReg (platformArch platform) vr
                 RegReal rr -> classOfRealReg rr
@@ -887,13 +890,27 @@ isEncodeableInWidth :: Width -> Integer -> Bool
 isEncodeableInWidth = isNbitEncodeable . widthInBits
 
 isIntOp :: Operand -> Bool
-isIntOp = not . isFloatOp
+isIntOp o = not (isFloatOp o || isVectorOp o)
 
 isFloatOp :: Operand -> Bool
 isFloatOp (OpReg _ reg) | isFloatReg reg = True
 isFloatOp _ = False
 
+isVectorOp :: Operand -> Bool
+isVectorOp (OpReg _ reg) | isVectorReg reg = True
+isVectorOp _ = False
+
 isFloatReg :: Reg -> Bool
-isFloatReg (RegReal (RealRegSingle i)) | i > 31 = True
+isFloatReg (RegReal (RealRegSingle i)) | isFloatRegNo i = True
 isFloatReg (RegVirtual (VirtualRegD _)) = True
 isFloatReg _ = False
+
+isIntReg :: Reg -> Bool
+isIntReg (RegReal (RealRegSingle i)) | isIntRegNo i = True
+isIntReg (RegVirtual (VirtualRegD _)) = True
+isIntReg _ = False
+
+isVectorReg :: Reg -> Bool
+isVectorReg (RegReal (RealRegSingle i)) | isVectorRegNo i = True
+isVectorReg (RegVirtual (VirtualRegD _)) = True
+isVectorReg _ = False


=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -403,11 +403,43 @@ pprReg w r = case r of
     ppr_reg_no 61 = text "ft9"
     ppr_reg_no 62 = text "ft10"
     ppr_reg_no 63 = text "ft11"
+    ppr_reg_no 64 = text "v0"
+    ppr_reg_no 65 = text "v1"
+    ppr_reg_no 66 = text "v2"
+    ppr_reg_no 67 = text "v3"
+    ppr_reg_no 68 = text "v4"
+    ppr_reg_no 69 = text "v5"
+    ppr_reg_no 70 = text "v6"
+    ppr_reg_no 71 = text "v7"
+    ppr_reg_no 72 = text "v8"
+    ppr_reg_no 73 = text "v9"
+    ppr_reg_no 74 = text "v10"
+    ppr_reg_no 75 = text "v11"
+    ppr_reg_no 76 = text "v12"
+    ppr_reg_no 77 = text "v13"
+    ppr_reg_no 78 = text "v14"
+    ppr_reg_no 79 = text "v15"
+    ppr_reg_no 80 = text "v16"
+    ppr_reg_no 81 = text "v17"
+    ppr_reg_no 82 = text "v18"
+    ppr_reg_no 83 = text "v19"
+    ppr_reg_no 84 = text "v20"
+    ppr_reg_no 85 = text "v21"
+    ppr_reg_no 86 = text "v22"
+    ppr_reg_no 87 = text "v23"
+    ppr_reg_no 88 = text "v24"
+    ppr_reg_no 89 = text "v25"
+    ppr_reg_no 90 = text "v26"
+    ppr_reg_no 91 = text "v27"
+    ppr_reg_no 92 = text "v28"
+    ppr_reg_no 93 = text "v29"
+    ppr_reg_no 94 = text "v30"
+    ppr_reg_no 95 = text "v31"
     ppr_reg_no i
       | i < 0 = pprPanic "Unexpected register number (min is 0)" (ppr w <+> int i)
-      | i > 63 = pprPanic "Unexpected register number (max is 63)" (ppr w <+> int i)
+      | i > 95 = pprPanic "Unexpected register number (max is 95)" (ppr w <+> int i)
       -- no support for widths > W64.
-      | otherwise = pprPanic "Unsupported width in register (max is 64)" (ppr w <+> int i)
+      | otherwise = pprPanic "Unsupported width in register (max is 95)" (ppr w <+> int i)
 
 -- | Single precission `Operand` (floating-point)
 isSingleOp :: Operand -> Bool
@@ -621,6 +653,9 @@ pprInstr platform instr = case instr of
   STR II64 o1 o2 -> op2 (text "\tsd") o1 o2
   STR FF32 o1 o2 -> op2 (text "\tfsw") o1 o2
   STR FF64 o1 o2 -> op2 (text "\tfsd") o1 o2
+  STR (VecFormat 2 FmtFloat) o1 o2@(OpAddr _) -> op2 (text "\tvse32.v") o1 o2
+  STR (VecFormat 2 FmtDouble) o1 o2@(OpAddr _) -> op2 (text "\tvse64.v") o1 o2
+  STR f o1 o2 -> pprPanic "Unsupported store" ((text . show) f <+> pprOp platform o1 <+> pprOp platform o2)
   LDR _f o1 (OpImm (ImmIndex lbl off)) ->
     lines_
       [ text "\tla" <+> pprOp platform o1 <> comma <+> pprAsmLabel platform lbl,
@@ -643,6 +678,9 @@ pprInstr platform instr = case instr of
   LDRU FF32 o1 o2@(OpAddr (AddrRegImm _ _)) -> op2 (text "\tflw") o1 o2
   LDRU FF64 o1 o2@(OpAddr (AddrReg _)) -> op2 (text "\tfld") o1 o2
   LDRU FF64 o1 o2@(OpAddr (AddrRegImm _ _)) -> op2 (text "\tfld") o1 o2
+  -- vectors
+  LDRU (VecFormat 2 FmtFloat) o1 o2@(OpAddr _) -> op2 (text "\tvle32.v") o1 o2
+  LDRU (VecFormat 2 FmtDouble) o1 o2@(OpAddr _) -> op2 (text "\tvle64.v") o1 o2
   LDRU f o1 o2 -> pprPanic "Unsupported unsigned load" ((text . show) f <+> pprOp platform o1 <+> pprOp platform o2)
   FENCE r w -> line $ text "\tfence" <+> pprFenceType r <> char ',' <+> pprFenceType w
   FCVT FloatToFloat o1@(OpReg W32 _) o2@(OpReg W64 _) -> op2 (text "\tfcvt.s.d") o1 o2
@@ -677,7 +715,10 @@ pprInstr platform instr = case instr of
           FNMAdd -> text "\tfnmadd" <> dot <> floatPrecission d
           FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d
      in op4 fma d r1 r2 r3
-  VMV o1 o2 -> op2 (text "\tvmv.v.x") o1 o2
+
+  VMV o1@(OpReg w _) o2 | isFloatOp o2 -> op2 (text "\tvfmv" <> dot <> text "f" <> dot <> floatWidthSuffix w) o1 o2
+  VMV o1@(OpReg w _) o2 | isFloatOp o1 -> op2 (text "\tvfmv" <> dot <> opToVInstrSuffix o1 <> dot <> floatWidthSuffix w) o1 o2
+  VMV o1 o2 -> op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> opToVInstrSuffix o2) o1 o2
   VID o1 o2 -> op2 (text "\tvid.v") o1 o2
   VMSEQ o1 o2 o3 -> op3 (text "\tvmseq.v.x") o1 o2 o3
   VMERGE o1 o2 o3 o4 -> op4 (text "\tvmerge.vxm") o1 o2 o3 o4
@@ -718,6 +759,17 @@ pprInstr platform instr = case instr of
     pprMasking MA = text "ma"
     pprMasking MU = text "mu"
 
+    opToVInstrSuffix :: IsLine doc => Operand -> doc
+    opToVInstrSuffix op | isIntOp op = text "x"
+    opToVInstrSuffix op | isFloatOp op = text "f"
+    opToVInstrSuffix op | isVectorOp op = text "v"
+    opToVInstrSuffix op = pprPanic "Unsupported operand for vector instruction" (pprOp platform op)
+
+    floatWidthSuffix :: IsLine doc => Width -> doc
+    floatWidthSuffix W32 = text "s"
+    floatWidthSuffix W64 = text "d"
+    floatWidthSuffix w = pprPanic "Unsupported floating point vector operation width" (ppr w)
+
 floatOpPrecision :: Platform -> Operand -> Operand -> String
 floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isSingleOp l && isSingleOp r = "s" -- single precision
 floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isDoubleOp l && isDoubleOp r = "d" -- double precision


=====================================
compiler/GHC/CmmToAsm/RV64/Regs.hs
=====================================
@@ -78,6 +78,15 @@ v0RegNo = 64
 v31RegNo :: RegNo
 v31RegNo = 95
 
+isVectorRegNo :: RegNo -> Bool
+isVectorRegNo r = v0RegNo <= r && r <= v31RegNo
+
+isFloatRegNo :: RegNo -> Bool
+isFloatRegNo r = d0RegNo <= r && r <= d31RegNo
+
+isIntRegNo :: RegNo -> Bool
+isIntRegNo r = x0RegNo <= r && r <= x31RegNo
+
 -- Note [The made-up RISCV64 TMP (IP) register]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 --
@@ -110,10 +119,12 @@ v0Reg = regSingle v0RegNo
 
 -- | All machine register numbers.
 allMachRegNos :: [RegNo]
-allMachRegNos = intRegs ++ fpRegs
+allMachRegNos = intRegs ++ fpRegs ++ vRegs
   where
     intRegs = [x0RegNo .. x31RegNo]
     fpRegs = [d0RegNo .. d31RegNo]
+    -- TODO: If Vector extension is turned off, this should become the empty list
+    vRegs = [v0RegNo .. v31RegNo]
 
 -- | Registers available to the register allocator.
 --
@@ -210,41 +221,33 @@ realRegSqueeze cls rr =
     RcInteger ->
       case rr of
         RealRegSingle regNo
-          | regNo < d0RegNo
-          -> 1
-          | otherwise
-          -> 0
+          | regNo <= x31RegNo -> 1
+          | otherwise -> 0
     RcFloat ->
       case rr of
         RealRegSingle regNo
-          |  regNo < d0RegNo
-          || regNo > d31RegNo
-          -> 0
-          | otherwise
-          -> 1
+          | regNo <= d31RegNo -> 1
+          | otherwise -> 0
     RcVector ->
       case rr of
         RealRegSingle regNo
-          | regNo > d31RegNo
-          -> 1
-          | otherwise
-          -> 0
+          | regNo <= v31RegNo -> 1
+          | otherwise -> 0
 
 mkVirtualReg :: Unique -> Format -> VirtualReg
 mkVirtualReg u format
-  | not (isFloatFormat format) = VirtualRegI u
-  | otherwise =
-      case format of
-        FF32 -> VirtualRegD u
-        FF64 -> VirtualRegD u
-        _ -> panic "RV64.mkVirtualReg"
+  | isIntFormat format = VirtualRegI u
+  | isFloatFormat format = VirtualRegD u
+  | isVecFormat format = VirtualRegV128 u
+  | otherwise = panic $ "RV64.mkVirtualReg: No virtual register type for " ++ show format
 
 {-# INLINE classOfRealReg #-}
 classOfRealReg :: RealReg -> RegClass
 classOfRealReg (RealRegSingle i)
-  | i < d0RegNo = RcInteger
-  | i > d31RegNo = RcVector
-  | otherwise = RcFloat
+  | i <= x31RegNo = RcInteger
+  | i <= d31RegNo = RcFloat
+  | i <= v31RegNo = RcVector
+  | otherwise = panic $ "RV64.classOfRealReg: Unknown register number: " ++ show i
 
 regDotColor :: RealReg -> SDoc
 regDotColor reg =


=====================================
compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
=====================================
@@ -144,7 +144,7 @@ allocatableRegs arch rc =
     ArchMipsel    -> panic "trivColorable ArchMipsel"
     ArchS390X     -> panic "trivColorable ArchS390X"
     ArchRISCV64   -> case rc of
-      -- TODO for Sven Tennie
+      -- TODO: for Sven Tennie
       Separate.RcInteger -> 14
       Separate.RcFloat   -> 20
       Separate.RcVector  -> 20


=====================================
compiler/GHC/CmmToAsm/Reg/Linear.hs
=====================================
@@ -977,6 +977,7 @@ allocRegsAndSpill_spill reading keep spills alloc r@(VirtualRegWithFormat vr fmt
                         = pprPanic ("RegAllocLinear.allocRegsAndSpill: no spill candidates\n")
                         $ vcat
                                 [ text "allocating vreg:  " <> text (show vr)
+                                , text "regClass:         " <> text (show regclass)
                                 , text "assignment:       " <> ppr assig
                                 , text "format:           " <> ppr fmt
                                 , text "freeRegs:         " <> text (showRegs freeRegs)


=====================================
compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs
=====================================
@@ -31,22 +31,26 @@ data FreeRegs
       !Word32
       -- | floating point registers (`RcDouble`)
       !Word32
+      -- | vector registers (`RcVector`)
+      !Word32
 
 instance Show FreeRegs where
-  show (FreeRegs g f) = "FreeRegs 0b" ++ showBits g ++ " 0b" ++ showBits f
+  show (FreeRegs g f v) = "FreeRegs 0b" ++ showBits g ++ " 0b" ++ showBits f ++ " 0b" ++ showBits v
 
 -- | Show bits as a `String` of @1 at s and @0 at s
 showBits :: Word32 -> String
 showBits w = map (\i -> if testBit w i then '1' else '0') [0 .. 31]
 
 instance Outputable FreeRegs where
-  ppr (FreeRegs g f) =
+  ppr (FreeRegs g f v) =
     text "   "
       <+> foldr (\i x -> pad_int i <+> x) (text "") [0 .. 31]
       $$ text "GPR"
       <+> foldr (\i x -> show_bit g i <+> x) (text "") [0 .. 31]
       $$ text "FPR"
       <+> foldr (\i x -> show_bit f i <+> x) (text "") [0 .. 31]
+      $$ text "VPR"
+      <+> foldr (\i x -> show_bit v i <+> x) (text "") [0 .. 31]
     where
       pad_int i | i < 10 = char ' ' <> int i
       pad_int i = int i
@@ -59,17 +63,16 @@ initFreeRegs :: Platform -> FreeRegs
 initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform)
   where
     noFreeRegs :: FreeRegs
-    noFreeRegs = FreeRegs 0 0
+    noFreeRegs = FreeRegs 0 0 0
 
 -- | Get all free `RealReg`s (i.e. those where the corresponding bit is 1)
 getFreeRegs :: RegClass -> FreeRegs -> [RealReg]
-getFreeRegs cls (FreeRegs g f) =
+getFreeRegs cls (FreeRegs g f v) =
   case cls of
     RcInteger -> go 0 g allocatableIntRegs
     RcFloat -> go 32 f allocatableDoubleRegs
-    RcVector ->
-      sorry "Linear.RV64.getFreeRegs: vector registers are not supported"
-
+    -- TODO: If there's no Vector support, we should return an empty list or panic.
+    RcVector -> go 64 v allocatableVectorRegs
   where
     go _ _ [] = []
     go off x (i : is)
@@ -81,19 +84,24 @@ getFreeRegs cls (FreeRegs g f) =
     -- change often.)
     allocatableIntRegs = [5 .. 7] ++ [10 .. 17] ++ [28 .. 30]
     allocatableDoubleRegs = [0 .. 7] ++ [10 .. 17] ++ [28 .. 31]
+    allocatableVectorRegs = 0 : [7 .. 31]
 
 -- | Set corresponding register bit to 0
 allocateReg :: (HasCallStack) => RealReg -> FreeRegs -> FreeRegs
-allocateReg (RealRegSingle r) (FreeRegs g f)
-  | r > 31 && testBit f (r - 32) = FreeRegs g (clearBit f (r - 32))
-  | r < 32 && testBit g r = FreeRegs (clearBit g r) f
-  | r > 31 = panic $ "Linear.RV64.allocReg: double allocation of float reg v" ++ show (r - 32) ++ "; " ++ showBits f
-  | otherwise = pprPanic "Linear.RV64.allocReg" $ text ("double allocation of gp reg x" ++ show r ++ "; " ++ showBits g)
+allocateReg (RealRegSingle r) (FreeRegs g f v)
+  | r < 32 && testBit g r = FreeRegs (clearBit g r) f v
+  | r >= 32 && testBit f (r - 32) = FreeRegs g (clearBit f (r - 32)) v
+  | r >= 64 && testBit v (r - 64) = FreeRegs g f (clearBit v (r - 64))
+  | otherwise =
+      pprPanic "Linear.RV64.allocateReg"
+        $ text ("invalid allocation of register " ++ show r ++ "; g:" ++ showBits g ++ "; f:" ++ showBits f ++ "; v:" ++ showBits v)
 
 -- | Set corresponding register bit to 1
 releaseReg :: (HasCallStack) => RealReg -> FreeRegs -> FreeRegs
-releaseReg (RealRegSingle r) (FreeRegs g f)
-  | r > 31 && testBit f (r - 32) = pprPanic "Linear.RV64.releaseReg" (text "can't release non-allocated reg v" <> int (r - 32))
-  | r < 32 && testBit g r = pprPanic "Linear.RV64.releaseReg" (text "can't release non-allocated reg x" <> int r)
-  | r > 31 = FreeRegs g (setBit f (r - 32))
-  | otherwise = FreeRegs (setBit g r) f
+releaseReg (RealRegSingle r) (FreeRegs g f v)
+  | r < 32 && not (testBit g r) = FreeRegs (setBit g r) f v
+  | r >= 32 && r <= 63 && not (testBit f (r - 32)) = FreeRegs g (setBit f (r - 32)) v
+  | r >= 64 && not (testBit v (r - 64)) = FreeRegs g f (setBit v (r - 64))
+  | otherwise =
+      pprPanic "Linear.RV64.releaseReg"
+        $ text ("invalid release of register " ++ show r ++ "; g:" ++ showBits g ++ "; f:" ++ showBits f ++ "; v:" ++ showBits v)


=====================================
compiler/GHC/Platform/Reg/Class.hs
=====================================
@@ -49,8 +49,5 @@ registerArch arch =
     ArchPPC       -> Unified
     ArchPPC_64 {} -> Unified
     ArchAArch64   -> Unified
-    -- Support for vector registers not yet implemented for RISC-V
-    -- see panic in `getFreeRegs`.
-    --ArchRISCV64   -> Separate
-    ArchRISCV64   -> NoVectors
+    ArchRISCV64   -> Separate
     _             -> NoVectors


=====================================
hadrian/src/Flavour.hs
=====================================
@@ -70,6 +70,7 @@ flavourTransformers = M.fromList
     , "late_ccs"         =: enableLateCCS
     , "boot_nonmoving_gc" =: enableBootNonmovingGc
     , "dump_stg"         =: enableDumpStg
+    , "vectors"          =: enableVectorSupport
     ]
   where (=:) = (,)
 
@@ -163,6 +164,15 @@ enableDebugInfo = addArgs $ notStage0 ? mconcat
     , builder (Cabal Setup) ? arg "--disable-executable-stripping"
     ]
 
+-- TODO: A bit hand-wavy; this likely needs to be part of autoconf
+enableVectorSupport :: Flavour -> Flavour
+enableVectorSupport = addArgs $ notStage0 ? mconcat
+    [ builder (Ghc CompileHs) ? pure ["-optc=-march=rv64gv", "-opta=-march=rv64gv"]
+    , builder (Ghc CompileCWithGhc) ? pure ["-optc=-march=rv64gv", "-opta=-march=rv64gv"]
+    , builder (Ghc ToolArgs) ? pure ["-optc=-march=rv64gv", "-opta=-march=rv64gv"]
+    , builder (Cc CompileC) ? pure ["-optc=-march=rv64gv", "-opta=-march=rv64gv"]
+    ]
+
 -- | Enable the ticky-ticky profiler in stage2 GHC
 enableTickyGhc :: Flavour -> Flavour
 enableTickyGhc f =


=====================================
rts/CheckVectorSupport.c
=====================================
@@ -1,6 +1,10 @@
 #include 
 #include "CheckVectorSupport.h"
 
+#if defined(__riscv_v) && defined(__riscv_v_intrinsic)
+  #include 
+#endif
+
 // Check support for vector registers (conservative).
 //
 // 0: no support for vector registers
@@ -69,8 +73,7 @@ int checkVectorSupport(void) {
     // supports vectors.
 
     // TODO: Check the machine supports V extension 1.0. Or, implement the older
-    // comman versions.
-    #include 
+    // command versions.
 
     unsigned vlenb = __riscv_vlenb();
 


=====================================
rts/include/stg/MachRegs/riscv64.h
=====================================
@@ -57,5 +57,12 @@
 #define REG_D5          fs10
 #define REG_D6          fs11
 
+#define REG_XMM1        v1
+#define REG_XMM2        v2
+#define REG_XMM3        v3
+#define REG_XMM4        v4
+#define REG_XMM5        v5
+#define REG_XMM6        v6
+
 #define MAX_REAL_FLOAT_REG   6
-#define MAX_REAL_DOUBLE_REG  6
\ No newline at end of file
+#define MAX_REAL_DOUBLE_REG  6


=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -24,7 +24,8 @@ setTestOpts(
   , when(have_cpu_feature('avx512f'), extra_hc_opts('-mavx512f'))
   ])
 
-test('simd000', [], compile_and_run, [''])
+# TODO: Revert debug trace dumps
+test('simd000', [], compile_and_run, ['-opta=-march=rv64gv -dppr-debug -ddump-to-file -ddump-asm'])
 test('simd001', [], compile_and_run, [''])
 test('simd002', [], compile_and_run, [''])
 test('simd003', [], compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/94ec8cb6f225cb1f46067f643ebef75f1861c810

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 18:47:15 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sun, 20 Oct 2024 14:47:15 -0400
Subject: [Git][ghc/ghc][wip/fix-ghci-wrapper] hadrian: fix bindist executable
 wrapper logic for cross targets
Message-ID: <67155033a109d_7b9618c96503662d@gitlab.mail>



Cheng Shao pushed to branch wip/fix-ghci-wrapper at Glasgow Haskell Compiler / GHC


Commits:
464c0738 by Cheng Shao at 2024-10-20T18:46:50+00:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content.

- - - - -


1 changed file:

- hadrian/src/Rules/BinaryDist.hs


Changes:

=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -437,13 +437,14 @@ pkgToWrappers pkg = do
       | otherwise     -> pure []
 
 wrapper :: FilePath -> Action String
-wrapper "ghc"         = ghcWrapper
-wrapper "ghc-pkg"     = ghcPkgWrapper
-wrapper "ghci" = ghciScriptWrapper
-wrapper "haddock"     = haddockWrapper
-wrapper "hsc2hs"      = hsc2hsWrapper
-wrapper "runghc"      = runGhcWrapper
-wrapper "runhaskell"  = runGhcWrapper
+wrapper wrapper_name
+  | "runghc"     `isSuffixOf` wrapper_name = runGhcWrapper
+  | "ghc"        `isSuffixOf` wrapper_name = ghcWrapper
+  | "ghc-pkg"    `isSuffixOf` wrapper_name = ghcPkgWrapper
+  | "ghci"       `isSuffixOf` wrapper_name = ghciScriptWrapper
+  | "haddock"    `isSuffixOf` wrapper_name = haddockWrapper
+  | "hsc2hs"     `isSuffixOf` wrapper_name = hsc2hsWrapper
+  | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper
 wrapper _             = commonWrapper
 
 -- | Wrapper scripts for different programs. Common is default wrapper.
@@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\
 -- | --interactive flag.
 ghciScriptWrapper :: Action String
 ghciScriptWrapper = do
+  prefix <- crossPrefix
   version <- setting ProjectVersion
   pure $ unlines
-    [ "executable=\"$bindir/ghc-" ++ version ++ "\""
+    [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
     , "exec $executable --interactive \"$@\"" ]
 
 -- | When not on Windows, we want to ship the 3 flavours of the iserv program
@@ -548,4 +550,3 @@ createGhcii outDir = do
       [ "#!/bin/sh"
       , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\""
       ]
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/464c0738317a3854bebec467683653307f8f8450

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 20:00:46 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Sun, 20 Oct 2024 16:00:46 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] make caller wrap the pop err ctxt
Message-ID: <6715616ee9202_b532b26c8d46197b@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
a860aa20 by Apoorv Ingle at 2024-10-20T15:00:12-05:00
make caller wrap the pop err ctxt

- - - - -


3 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -586,22 +586,6 @@ mkExpandedPatRn
 mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav
                                                          , xrn_expanded = eExpr })
 
--- | Build an expression using the extension constructor `XExpr`,
---   and the two components of the expansion: original do stmt and
---   expanded expression and associate it with a provided location
-mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
-  -> HsDoFlavour          -- ^ the flavour of the statement
-  -> HsExpr GhcRn         -- ^ expanded expression
-  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
-  = L loc $ mkExpandedStmt oStmt flav eExpr
-
 data XXExprGhcTc
   = WrapExpr        -- Type and evidence application and abstractions
       HsWrapper (HsExpr GhcTc)


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -2258,7 +2258,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
              -- Need 'pureAName' and not 'returnMName' here, so that it requires
              -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed).
              (pure_name, _) <- lookupQualifiedDoName (HsDoStmt ctxt) pureAName
-             let expr = noLocA (HsApp noExtField (noLocA ret) tup)
+             let expr = noLocA (genHsApps pure_name [tup])
              return (expr, emptyFVs)
      return ( ApplicativeArgMany
               { xarg_app_arg_many = noExtField


=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -47,39 +47,39 @@ import Data.List ((\\))
 *                                                                      *
 ************************************************************************
 -}
-
+-- TODO: make caller add the pop error context
 -- | Expand the `do`-statments into expressions right after renaming
 --   so that they can be typechecked.
 --   See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary
 --   and Note [Handling overloaded and rebindable constructs] for high level commentary
 expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn)
-expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts
+expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts doFlav stmts
 
 -- | The main work horse for expanding do block statements into applications of binds and thens
 --   See Note [Expanding HsDo with XXExprGhcRn]
-expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn)
+expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn)
 
-expand_do_stmts _ ListComp _ =
+expand_do_stmts ListComp _ =
   pprPanic "expand_do_stmts: impossible happened. ListComp" empty
         -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
-
-expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) =
+expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) =
   pprPanic "expand_do_stmts: TransStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) =
+expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) =
   pprPanic "expand_do_stmts: ParStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
+expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
+
+expand_do_stmts flav [stmt@(L _ (LastStmt _ (L body_loc body) _ ret_expr))]
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (5) below
 -- last statement of a list comprehension, needs to explicitly return it
 -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
    | NoSyntaxExprRn <- ret_expr
    -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
-   = return $ mkExpandedStmtAt addPop loc stmt flav body
+   = return $ mkExpandedStmtAt stmt flav body
 
    | SyntaxExprRn ret <- ret_expr
    --
@@ -87,18 +87,18 @@ expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_exp
    --               return e  ~~> return e
    -- to make T18324 work
    = do let expansion = genHsApp ret (L body_loc body)
-        return $ mkExpandedStmtAt addPop loc stmt flav expansion
+        return $ mkExpandedStmtAt stmt flav expansion
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
+expand_do_stmts doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
 --                      stmts ~~> stmts'
 --    ------------------------------------------------
 --       let x = e ; stmts ~~> let x = e in stmts'
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
-     let expansion = genHsLet bs expand_stmts
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+  do expand_stmts <- expand_do_stmts doFlavour lstmts
+     let expansion = genPopErrCtxtExpr (wrapGenSpan $ genHsLet bs expand_stmts)
+     return $ mkExpandedStmtAt stmt doFlavour (unLoc expansion)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
+expand_do_stmts doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
   | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn
   , fail_op              <- xbsrn_failOp xbsrn
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (2) below
@@ -107,29 +107,29 @@ expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
 --                                   _   -> fail "Pattern match failure .."
 --    -------------------------------------------------------
 --       pat <- e ; stmts   ~~> (>>=) e f
-  = do expand_stmts <- expand_do_stmts True doFlavour lstmts
-       failable_expr <- mk_failable_expr False doFlavour pat expand_stmts fail_op
+  = do expand_stmts <- genPopErrCtxtExpr <$> expand_do_stmts doFlavour lstmts
+       failable_expr <- mk_failable_expr doFlavour pat expand_stmts fail_op
        let expansion = genHsExpApps bind_op  -- (>>=)
                        [ e
                        , failable_expr ]
-       return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+       return $ mkExpandedStmtAt stmt doFlavour expansion
 
   | otherwise
   = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr  stmt)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
+expand_do_stmts doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
 -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (1) below
 --              stmts ~~> stmts'
 --    ----------------------------------------------
 --      e ; stmts ~~> (>>) e stmts'
-  do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts_expr <- expand_do_stmts doFlavour lstmts
      let expansion = genHsExpApps then_op  -- (>>)
-                                  [ e
-                                  , expand_stmts_expr ]
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+                     [ e
+                     , wrapGenSpan (mkPopErrCtxtExpr expand_stmts_expr) ]
+     return $ mkExpandedStmtAt stmt doFlavour expansion
 
-expand_do_stmts _ doFlavour
+expand_do_stmts doFlavour
        ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts
                         , recS_later_ids = later_ids  -- forward referenced local ids
                         , recS_rec_ids = local_ids     -- ids referenced outside of the rec block
@@ -149,7 +149,7 @@ expand_do_stmts _ doFlavour
 --                                           -> do { rec_stmts
 --                                                 ; return (local_only_ids ++ later_ids) } ))
 --                              (\ [ local_only_ids ++ later_ids ] -> stmts')
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts <- expand_do_stmts doFlavour lstmts
      -- NB: No need to wrap the expansion with an ExpandedStmt
      -- as we want to flatten the rec block statements into its parent do block anyway
      return $ mkHsApps (wrapGenSpan bind_fun)                                           -- (>>=)
@@ -177,7 +177,7 @@ expand_do_stmts _ doFlavour
                              -- NB: LazyPat because we do not want to eagerly evaluate the pattern
                              -- and potentially loop forever
 
-expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
+expand_do_stmts doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
 -- See Note [Applicative BodyStmt]
 --
 --                  stmts ~~> stmts'
@@ -187,7 +187,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
 -- Very similar to HsToCore.Expr.dsDo
 
 -- args are [(<$>, e1), (<*>, e2), .., ]
-  do { xexpr <- expand_do_stmts False doFlavour lstmts
+  do { xexpr <- expand_do_stmts doFlavour lstmts
      -- extracts pats and arg bodies (rhss) from args
 
      ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args
@@ -216,7 +216,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
             { xarg_app_arg_one = mb_fail_op
             , app_arg_pattern = pat
             , arg_expr        = (L rhs_loc rhs) }) =
-      do let xx_expr = mkExpandedStmtAt addPop (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
+      do let xx_expr = mkExpandedStmtAt stmt doFlavour rhs
          traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr])
          return ((pat, mb_fail_op)
                 , xx_expr)
@@ -225,13 +225,13 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
                                , final_expr = ret@(L ret_loc _)
                                , bv_pattern = pat
                                , stmt_context = ctxt }) =
-      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts addPop ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
-         ; traceTc "do_arg" (text "ManyArg" <+> ppr addPop <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
+      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
+         ; traceTc "do_arg" (text "ManyArg" <+> ppr False <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
          ; return ((pat, Nothing)
                   , xx_expr) }
 
     match_args :: (LPat GhcRn, FailOperator GhcRn)  -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn)
-    match_args (pat, fail_op) body = mk_failable_expr addPop doFlavour pat body fail_op
+    match_args (pat, fail_op) body = mk_failable_expr doFlavour pat body fail_op
 
     mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn
     mk_apps l_expr (op, r_expr) =
@@ -239,11 +239,11 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
         SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ]
         NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op)
 
-expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts)
+expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts)
 
 -- checks the pattern `pat` for irrefutability which decides if we need to wrap it with a fail block
-mk_failable_expr :: Bool -> HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
-mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
+mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
+mk_failable_expr doFlav lpat@(L loc pat) expr@(L _exprloc _) fail_op =
   do { is_strict <- xoptM LangExt.Strict
      ; hscEnv <- getTopEnv
      ; rdrEnv <- getGlobalRdrEnv
@@ -252,13 +252,11 @@ mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
      ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat
                                         , text "isIrrefutable:" <+> ppr irrf_pat
                                         ])
-     ; let xexpr | addPop = mkPopErrCtxtExprAt exprloc expr
-                 | otherwise = expr
      ; if irrf_pat -- don't wrap with fail block if
                    -- the pattern is irrefutable
        then case pat of
-              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] xexpr
-              _ -> return $ genHsLamDoExp doFlav [lpat] xexpr
+              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr
+              _ -> return $ genHsLamDoExp doFlav [lpat] expr
 
        else L loc <$> mk_fail_block doFlav lpat expr fail_op
      }
@@ -343,10 +341,10 @@ They capture the essence of statement expansions as implemented in `expand_do_st
 
           (2) DO【 p <- e; ss 】 = if p is irrefutable
                                    then ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\ p -> DO【 ss 】))
+                                          (>>=) s ((\ p -> ‹PopExprCtxt› DO【 ss 】))
                                    else ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\case p -> DO【 ss 】
-                                                                       _ -> fail "pattern p failure"))
+                                          (>>=) s ((\case p -> ‹PopExprCtxt› DO【 ss 】
+                                                          _ -> fail "pattern p failure"))
 
           (3) DO【 let x = e; ss 】
                                  = ‹ExpansionStmt (let x = e)› (let x = e in (‹PopErrCtxt›DO【 ss 】))
@@ -569,11 +567,6 @@ It stores the original statement (with location) and the expanded expression
 mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn
 mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
 
--- | Wrap a located expression with a PopSrcExpr with an appropriate location
-mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
-mkPopErrCtxtExprAt _loc a = wrapGenSpan $ mkPopErrCtxtExpr a
-
-
 genPopErrCtxtExpr :: LHsExpr GhcRn -> LHsExpr GhcRn
 genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 
@@ -581,14 +574,9 @@ genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 --   and the two components of the expansion: original do stmt and
 --   expanded expression and associate it with a provided location
 mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
+  :: ExprLStmt GhcRn      -- ^ source statement
   -> HsDoFlavour          -- ^ the flavour of the statement
   -> HsExpr GhcRn         -- ^ expanded expression
   -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop _loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt _loc (wrapGenSpan $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
+mkExpandedStmtAt oStmt flav eExpr
   = wrapGenSpan $ mkExpandedStmt oStmt flav eExpr



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 20:35:30 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 20 Oct 2024 16:35:30 -0400
Subject: [Git][ghc/ghc][master] Interpreter: Add locking for communication
 with external interpreter
Message-ID: <67156992dc8c0_b532b3a3ef0694aa@gitlab.mail>



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


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -


10 changed files:

- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- + testsuite/tests/th/T25083.hs
- + testsuite/tests/th/T25083.stdout
- + testsuite/tests/th/T25083_A.hs
- + testsuite/tests/th/T25083_B.hs
- testsuite/tests/th/all.T


Changes:

=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -578,10 +578,12 @@ spawnIServ conf = do
                                           []
                                           (iservConfOpts    conf)
   lo_ref <- newIORef Nothing
+  lock <- newMVar ()
   let pipe = Pipe { pipeRead = rh, pipeWrite = wh, pipeLeftovers = lo_ref }
   let process = InterpProcess
                   { interpHandle = ph
                   , interpPipe   = pipe
+                  , interpLock   = lock
                   }
 
   pending_frees <- newMVar []


=====================================
compiler/GHC/Runtime/Interpreter/JS.hs
=====================================
@@ -130,10 +130,12 @@ startTHRunnerProcess interp_js settings = do
   std_in <- readIORef interp_in
 
   lo_ref <- newIORef Nothing
+  lock <- newMVar ()
   let pipe = Pipe { pipeRead = rh, pipeWrite = wh, pipeLeftovers = lo_ref }
   let proc = InterpProcess
               { interpHandle = hdl
               , interpPipe   = pipe
+              , interpLock   = lock
               }
   pure (std_in, proc)
 


=====================================
compiler/GHC/Runtime/Interpreter/Process.hs
=====================================
@@ -1,21 +1,18 @@
+{-# LANGUAGE LambdaCase #-}
 module GHC.Runtime.Interpreter.Process
   (
-  -- * Low-level API
-    callInterpProcess
-  , readInterpProcess
-  , writeInterpProcess
-
   -- * Message API
-  , Message(..)
+    Message(..)
   , DelayedResponse (..)
+  -- * Top-level message API (these acquire/release a lock)
   , sendMessage
   , sendMessageNoResponse
   , sendMessageDelayedResponse
+  , receiveDelayedResponse
+  -- * Nested message API (these require the interpreter to already be locked)
   , sendAnyValue
   , receiveAnyValue
-  , receiveDelayedResponse
   , receiveTHMessage
-
   )
 where
 
@@ -31,45 +28,79 @@ import GHC.Utils.Exception as Ex
 import Data.Binary
 import System.Exit
 import System.Process
+import Control.Concurrent.MVar (MVar, withMVar, takeMVar, putMVar, isEmptyMVar)
 
 data DelayedResponse a = DelayedResponse
 
+-- -----------------------------------------------------------------------------
+-- Top-level Message API
+
 -- | Send a message to the interpreter process that doesn't expect a response
+--   (locks the interpreter while sending)
 sendMessageNoResponse :: ExtInterpInstance d -> Message () -> IO ()
-sendMessageNoResponse i m = writeInterpProcess (instProcess i) (putMessage m)
+sendMessageNoResponse i m =
+  withLock i $ writeInterpProcess (instProcess i) (putMessage m)
 
--- | Send a message to the interpreter that excepts a response
+-- | Send a message to the interpreter that expects a response
+--   (locks the interpreter while until the response is received)
 sendMessage :: Binary a => ExtInterpInstance d -> Message a -> IO a
-sendMessage i m = callInterpProcess (instProcess i) m
+sendMessage i m = withLock i $ callInterpProcess (instProcess i) m
 
 -- | Send a message to the interpreter process whose response is expected later
 --
 -- This is useful to avoid forgetting to receive the value and to ensure that
 -- the type of the response isn't lost. Use receiveDelayedResponse to read it.
+-- (locks the interpreter until the response is received using
+-- `receiveDelayedResponse`)
 sendMessageDelayedResponse :: ExtInterpInstance d -> Message a -> IO (DelayedResponse a)
 sendMessageDelayedResponse i m = do
+  lock i
   writeInterpProcess (instProcess i) (putMessage m)
   pure DelayedResponse
 
--- | Send any value
+-- | Expect a delayed result to be received now
+receiveDelayedResponse :: Binary a => ExtInterpInstance d -> DelayedResponse a -> IO a
+receiveDelayedResponse i DelayedResponse = do
+  ensureLocked i
+  r <- readInterpProcess (instProcess i) get
+  unlock i
+  pure r
+
+-- -----------------------------------------------------------------------------
+-- Nested Message API
+
+-- | Send any value (requires locked interpreter)
 sendAnyValue :: Binary a => ExtInterpInstance d -> a -> IO ()
-sendAnyValue i m = writeInterpProcess (instProcess i) (put m)
+sendAnyValue i m = ensureLocked i >> writeInterpProcess (instProcess i) (put m)
 
--- | Expect a value to be received
+-- | Expect a value to be received (requires locked interpreter)
 receiveAnyValue :: ExtInterpInstance d -> Get a -> IO a
-receiveAnyValue i get = readInterpProcess (instProcess i) get
+receiveAnyValue i get = ensureLocked i >> readInterpProcess (instProcess i) get
 
--- | Expect a delayed result to be received now
-receiveDelayedResponse :: Binary a => ExtInterpInstance d -> DelayedResponse a -> IO a
-receiveDelayedResponse i DelayedResponse = readInterpProcess (instProcess i) get
-
--- | Expect a value to be received
+-- | Wait for a Template Haskell message (requires locked interpreter)
 receiveTHMessage :: ExtInterpInstance d -> IO THMsg
-receiveTHMessage i = receiveAnyValue i getTHMessage
-
+receiveTHMessage i = ensureLocked i >> receiveAnyValue i getTHMessage
 
 -- -----------------------------------------------------------------------------
--- Low-level API
+
+getLock :: ExtInterpInstance d -> MVar ()
+getLock = interpLock . instProcess
+
+withLock :: ExtInterpInstance d -> IO a -> IO a
+withLock i f = withMVar (getLock i) (const f)
+
+lock :: ExtInterpInstance d -> IO ()
+lock i = takeMVar (getLock i)
+
+unlock :: ExtInterpInstance d -> IO ()
+unlock i = putMVar (getLock i) ()
+
+ensureLocked :: ExtInterpInstance d -> IO ()
+ensureLocked i =
+  isEmptyMVar (getLock i) >>= \case
+    False -> panic "ensureLocked: external interpreter not locked"
+    _     -> pure ()
+
 
 -- | Send a 'Message' and receive the response from the interpreter process
 callInterpProcess :: Binary a => InterpProcess -> Message a -> IO a


=====================================
compiler/GHC/Runtime/Interpreter/Types.hs
=====================================
@@ -90,6 +90,7 @@ type WasmInterp = ExtInterpState WasmInterpConfig ()
 data InterpProcess = InterpProcess
   { interpPipe   :: !Pipe           -- ^ Pipe to communicate with the server
   , interpHandle :: !ProcessHandle  -- ^ Process handle of the server
+  , interpLock   :: !(MVar ())      -- ^ Lock to prevent concurrent access to the stream
   }
 
 -- | Status of an external interpreter


=====================================
compiler/GHC/Runtime/Interpreter/Wasm.hs
=====================================
@@ -62,12 +62,14 @@ spawnWasmInterp WasmInterpConfig {..} = do
   hSetBuffering rh NoBuffering
   lo_ref <- newIORef Nothing
   pending_frees <- newMVar []
+  lock <- newMVar ()
   pure
     $ ExtInterpInstance
       { instProcess =
           InterpProcess
             { interpHandle = ph,
-              interpPipe = Pipe {pipeRead = rh, pipeWrite = wh, pipeLeftovers = lo_ref}
+              interpPipe = Pipe {pipeRead = rh, pipeWrite = wh, pipeLeftovers = lo_ref},
+              interpLock = lock
             },
         instPendingFrees = pending_frees,
         instExtra = ()


=====================================
testsuite/tests/th/T25083.hs
=====================================
@@ -0,0 +1,21 @@
+{-
+  T25083_A and T25083_B contain a long-running (100ms) Template Haskell splice.
+
+  Run this with -fexternal-interpreter -j to check that we properly synchronize
+  the communication with the external interpreter.
+
+  This test will fail with a timeout or serialization error if communication
+  is not correctly serialized.
+ -}
+{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
+
+import Language.Haskell.TH
+import Control.Concurrent
+
+import T25083_A
+import T25083_B
+
+main :: IO ()
+main = do
+  print ta
+  print tb


=====================================
testsuite/tests/th/T25083.stdout
=====================================
@@ -0,0 +1,2 @@
+0
+42


=====================================
testsuite/tests/th/T25083_A.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
+module T25083_A where
+
+import Control.Concurrent
+import Language.Haskell.TH
+
+ta :: Integer
+ta =
+  $(do runIO (threadDelay 100000)
+       litE . integerL . toInteger . length =<< reifyInstances ''Show [])


=====================================
testsuite/tests/th/T25083_B.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
+module T25083_B where
+
+import Control.Concurrent
+import Language.Haskell.TH
+
+tb :: Integer
+tb = $(runIO (threadDelay 100000) >> [| 42 |])


=====================================
testsuite/tests/th/all.T
=====================================
@@ -631,3 +631,4 @@ test('T25252',
    req_th,
    req_c],
   compile_and_run, ['-fPIC T25252_c.c'])
+test('T25083', [extra_files(['T25083_A.hs', 'T25083_B.hs'])], multimod_compile_and_run, ['T25083', '-v0 -j'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 20:36:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 20 Oct 2024 16:36:15 -0400
Subject: [Git][ghc/ghc][master] Use monospace font for "Either a b" in fmap
 docs
Message-ID: <671569bf7538e_b532b358edc7289@gitlab.mail>



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


Commits:
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/Base.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -972,7 +972,7 @@ class Functor f where
     -- | 'fmap' is used to apply a function of type @(a -> b)@ to a value of type @f a@,
     -- where f is a functor, to produce a value of type @f b at .
     -- Note that for any type constructor with more than one parameter (e.g., 'Either'),
-    -- only the last type parameter can be modified with `fmap` (e.g., `b` in `Either a b`).
+    -- only the last type parameter can be modified with `fmap` (e.g., `b` in @Either a b@).
     --
     -- Some type constructors with two parameters or more have a @'Data.Bifunctor'@ instance that allows
     -- both the last and the penultimate parameters to be mapped over.



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 20:36:55 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 20 Oct 2024 16:36:55 -0400
Subject: [Git][ghc/ghc][master] Parser: remove non-ASCII characters from
 Parser.y
Message-ID: <671569e7c4375_b532b9a1ff075974@gitlab.mail>



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


Commits:
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -


1 changed file:

- compiler/GHC/Parser.y


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -2160,11 +2160,11 @@ fspec :: { Located ([AddEpAnn]
 -----------------------------------------------------------------------------
 -- Type signatures
 
-opt_sig :: { Maybe (EpUniToken "::" "∷", LHsType GhcPs) }
+opt_sig :: { Maybe (EpUniToken "::" "\8759", LHsType GhcPs) }
         : {- empty -}                   { Nothing }
         | '::' ctype                    { Just (epUniTok $1, $2) }
 
-opt_tyconsig :: { (Maybe (EpUniToken "::" "∷"), Maybe (LocatedN RdrName)) }
+opt_tyconsig :: { (Maybe (EpUniToken "::" "\8759"), Maybe (LocatedN RdrName)) }
              : {- empty -}              { (Nothing, Nothing) }
              | '::' gtycon              { (Just (epUniTok $1), Just $2) }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bc7f9c860f8d7f662947e55068467a3cf8c4d1c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 21:45:13 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 20 Oct 2024 17:45:13 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-5] EPA: Remove [AddEpAnn]
 Commit 5
Message-ID: <671579e9d6abd_b532bded1cc930ad@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-5 at Glasgow Haskell Compiler / GHC


Commits:
c8601c77 by Alan Zimmerman at 2024-10-20T19:26:52+01:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -


22 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -35,6 +35,7 @@ module GHC.Hs.Decls (
   AnnClassDecl(..),
   AnnSynDecl(..),
   AnnFamilyDecl(..),
+  AnnClsInstDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -59,7 +60,7 @@ module GHC.Hs.Decls (
   LClsInstDecl, ClsInstDecl(..),
 
   -- ** Standalone deriving declarations
-  DerivDecl(..), LDerivDecl,
+  DerivDecl(..), LDerivDecl, AnnDerivDecl,
   -- ** Deriving strategies
   DerivStrategy(..), LDerivStrategy,
   derivStrategyName, foldDerivStrategy, mapDerivStrategy,
@@ -80,7 +81,9 @@ module GHC.Hs.Decls (
   CImportSpec(..),
   -- ** Data-constructor declarations
   ConDecl(..), LConDecl,
-  HsConDeclH98Details, HsConDeclGADTDetails(..), hsConDeclTheta,
+  HsConDeclH98Details, HsConDeclGADTDetails(..),
+  AnnConDeclH98(..), AnnConDeclGADT(..),
+  hsConDeclTheta,
   getConNames, getRecConArgs_maybe,
   -- ** Document comments
   DocDecl(..), LDocDecl, docDeclDoc,
@@ -705,7 +708,7 @@ instance OutputableBndrId p
 type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
-type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
+type instance XCHsDerivingClause    (GhcPass _) = EpToken "deriving"
 type instance XXHsDerivingClause    (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -741,7 +744,7 @@ instance OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) where
   ppr (DctSingle _ ty) = ppr ty
   ppr (DctMulti _ tys) = parens (interpp'SP tys)
 
-type instance XStandaloneKindSig GhcPs = [AddEpAnn]
+type instance XStandaloneKindSig GhcPs = (EpToken "type", TokDcolon)
 type instance XStandaloneKindSig GhcRn = NoExtField
 type instance XStandaloneKindSig GhcTc = NoExtField
 
@@ -750,11 +753,11 @@ type instance XXStandaloneKindSig (GhcPass p) = DataConCantHappen
 standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
 standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname
 
-type instance XConDeclGADT GhcPs = (EpUniToken "::" "∷", [AddEpAnn])
+type instance XConDeclGADT GhcPs = AnnConDeclGADT
 type instance XConDeclGADT GhcRn = NoExtField
 type instance XConDeclGADT GhcTc = NoExtField
 
-type instance XConDeclH98  GhcPs = [AddEpAnn]
+type instance XConDeclH98  GhcPs = AnnConDeclH98
 type instance XConDeclH98  GhcRn = NoExtField
 type instance XConDeclH98  GhcTc = NoExtField
 
@@ -768,6 +771,26 @@ type instance XRecConGADT          GhcTc = NoExtField
 
 type instance XXConDeclGADTDetails (GhcPass _) = DataConCantHappen
 
+data AnnConDeclH98
+  = AnnConDeclH98 {
+    acdh_forall  :: TokForall,
+    acdh_dot :: EpToken ".",
+    acdh_darrow :: TokDarrow
+  } deriving Data
+
+instance NoAnn AnnConDeclH98 where
+  noAnn = AnnConDeclH98 noAnn noAnn noAnn
+
+data AnnConDeclGADT
+  = AnnConDeclGADT {
+    acdg_openp  :: [EpToken "("],
+    acdg_closep :: [EpToken ")"],
+    acdg_dcolon :: TokDcolon
+  } deriving Data
+
+instance NoAnn AnnConDeclGADT where
+  noAnn = AnnConDeclGADT noAnn noAnn noAnn
+
 -- Codomain could be 'NonEmpty', but at the moment all users need a list.
 getConNames :: ConDecl GhcRn -> [LocatedN Name]
 getConNames ConDeclH98  {con_name  = name}  = [name]
@@ -901,7 +924,7 @@ type instance XCClsInstDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                              -- The warning of the deprecated instance
                                              -- See Note [Implementation of deprecated instances]
                                              -- in GHC.Tc.Solver.Dict
-                                       , [AddEpAnn]
+                                       , AnnClsInstDecl
                                        , AnnSortKey DeclTag) -- For sorting the additional annotations
                                         -- TODO:AZ:tidy up
 type instance XCClsInstDecl    GhcRn = Maybe (LWarningTxt GhcRn)
@@ -924,6 +947,18 @@ type instance XTyFamInstD   GhcTc = NoExtField
 
 type instance XXInstDecl    (GhcPass _) = DataConCantHappen
 
+data AnnClsInstDecl
+  = AnnClsInstDecl {
+    acid_instance :: EpToken "instance",
+    acid_where    :: EpToken "where",
+    acid_openc    :: EpToken "{",
+    acid_semis    :: [EpToken ";"],
+    acid_closec   :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnClsInstDecl where
+  noAnn = AnnClsInstDecl noAnn noAnn noAnn noAnn noAnn
+
 cidDeprecation :: forall p. IsPass p
                => ClsInstDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1086,15 +1121,17 @@ type instance XCDerivDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
+                                     , AnnDerivDecl )
 type instance XCDerivDecl    GhcRn = ( Maybe (LWarningTxt GhcRn)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
-type instance XCDerivDecl    GhcTc = [AddEpAnn]
+                                     , AnnDerivDecl )
+type instance XCDerivDecl    GhcTc = AnnDerivDecl
 type instance XXDerivDecl    (GhcPass _) = DataConCantHappen
 
+type AnnDerivDecl = (EpToken "deriving", EpToken "instance")
+
 derivDeprecation :: forall p. IsPass p
                => DerivDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1128,15 +1165,15 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XStockStrategy    GhcPs = [AddEpAnn]
+type instance XStockStrategy    GhcPs = EpToken "stock"
 type instance XStockStrategy    GhcRn = NoExtField
 type instance XStockStrategy    GhcTc = NoExtField
 
-type instance XAnyClassStrategy GhcPs = [AddEpAnn]
+type instance XAnyClassStrategy GhcPs = EpToken "anyclass"
 type instance XAnyClassStrategy GhcRn = NoExtField
 type instance XAnyClassStrategy GhcTc = NoExtField
 
-type instance XNewtypeStrategy  GhcPs = [AddEpAnn]
+type instance XNewtypeStrategy  GhcPs = EpToken "newtype"
 type instance XNewtypeStrategy  GhcRn = NoExtField
 type instance XNewtypeStrategy  GhcTc = NoExtField
 
@@ -1144,7 +1181,7 @@ type instance XViaStrategy GhcPs = XViaStrategyPs
 type instance XViaStrategy GhcRn = LHsSigType GhcRn
 type instance XViaStrategy GhcTc = Type
 
-data XViaStrategyPs = XViaStrategyPs [AddEpAnn] (LHsSigType GhcPs)
+data XViaStrategyPs = XViaStrategyPs (EpToken "via") (LHsSigType GhcPs)
 
 instance OutputableBndrId p
         => Outputable (DerivStrategy (GhcPass p)) where
@@ -1202,11 +1239,11 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XForeignImport   GhcPs = [AddEpAnn]
+type instance XForeignImport   GhcPs = (EpToken "foreign", EpToken "import", TokDcolon)
 type instance XForeignImport   GhcRn = NoExtField
 type instance XForeignImport   GhcTc = Coercion
 
-type instance XForeignExport   GhcPs = [AddEpAnn]
+type instance XForeignExport   GhcPs = (EpToken "foreign", EpToken "export", TokDcolon)
 type instance XForeignExport   GhcRn = NoExtField
 type instance XForeignExport   GhcTc = Coercion
 
@@ -1218,6 +1255,7 @@ type instance XXForeignImport  (GhcPass _) = DataConCantHappen
 type instance XCExport (GhcPass _) = LocatedE SourceText -- original source text for the C entity
 type instance XXForeignExport  (GhcPass _) = DataConCantHappen
 
+
 -- pretty printing of foreign declarations
 
 instance OutputableBndrId p
@@ -1362,7 +1400,7 @@ type instance XWarnings      GhcTc = SourceText
 
 type instance XXWarnDecls    (GhcPass _) = DataConCantHappen
 
-type instance XWarning      (GhcPass _) = (NamespaceSpecifier, [AddEpAnn])
+type instance XWarning      (GhcPass _) = (NamespaceSpecifier, (EpToken "[", EpToken "]"))
 type instance XXWarnDecl    (GhcPass _) = DataConCantHappen
 
 
@@ -1418,7 +1456,7 @@ pprAnnProvenance (TypeAnnProvenance (L _ name))
 ************************************************************************
 -}
 
-type instance XCRoleAnnotDecl GhcPs = [AddEpAnn]
+type instance XCRoleAnnotDecl GhcPs = (EpToken "type", EpToken "role")
 type instance XCRoleAnnotDecl GhcRn = NoExtField
 type instance XCRoleAnnotDecl GhcTc = NoExtField
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -81,6 +81,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annSynDecl
               `extQ` annDataDefn
               `extQ` annFamilyDecl
+              `extQ` annClsInstDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -262,6 +263,15 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                  showAstData' g, showAstData' h, showAstData' i,
                                  showAstData' j, showAstData' k, showAstData' l]
 
+            annClsInstDecl :: AnnClsInstDecl -> SDoc
+            annClsInstDecl (AnnClsInstDecl a b c d e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClsInstDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e]
+
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -294,7 +304,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenInstance :: EpToken "instance" -> SDoc
             epTokenInstance = epToken'
 
-            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall :: TokForall -> SDoc
             epTokenForall = epUniToken'
 
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -163,15 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type instance XHsForAllVis   (GhcPass _) = EpAnn (TokForall, EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type instance XHsForAllInvis (GhcPass _) = EpAnn (TokForall, EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
-type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type EpAnnForallVis   = EpAnn (TokForall, TokRarrow)
+type EpAnnForallInvis = EpAnn (TokForall, EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -461,7 +461,7 @@ type instance XListTy          (GhcPass _) = AnnParen
 type instance XTupleTy         (GhcPass _) = AnnParen
 type instance XSumTy           (GhcPass _) = AnnParen
 type instance XOpTy            (GhcPass _) = NoExtField
-type instance XParTy           (GhcPass _) = AnnParen
+type instance XParTy           (GhcPass _) = (EpToken "(", EpToken ")")
 type instance XIParamTy        (GhcPass _) = TokDcolon
 type instance XStarTy          (GhcPass _) = NoExtField
 type instance XKindSig         (GhcPass _) = TokDcolon
@@ -572,7 +572,7 @@ pprHsArrow (HsUnrestrictedArrow _) = pprArrowWithMultiplicity visArgTypeLike (Le
 pprHsArrow (HsLinearArrow _)       = pprArrowWithMultiplicity visArgTypeLike (Left True)
 pprHsArrow (HsExplicitMult _ p)    = pprArrowWithMultiplicity visArgTypeLike (Right (ppr p))
 
-type instance XConDeclField  (GhcPass _) = [AddEpAnn]
+type instance XConDeclField  (GhcPass _) = TokDcolon
 type instance XXConDeclField (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -710,23 +710,22 @@ mkHsAppKindTy at ty k = addCLocA ty k (HsAppKindTy at ty k)
 -- It returns API Annotations for any parens removed
 splitHsFunType ::
      LHsType (GhcPass p)
-  -> ( [AddEpAnn], EpAnnComments -- The locations of any parens and
+  -> ( ([EpToken "("], [EpToken ")"]) , EpAnnComments -- The locations of any parens and
                                   -- comments discarded
      , [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p))
 splitHsFunType ty = go ty
   where
-    go (L l (HsParTy an ty))
+    go (L l (HsParTy (op,cp) ty))
       = let
-          (anns, cs, args, res) = splitHsFunType ty
-          anns' = anns ++ annParen2AddEpAnn an
+          ((ops, cps), cs, args, res) = splitHsFunType ty
           cs' = cs S.<> epAnnComments l
-        in (anns', cs', args, res)
+        in ((ops++[op], cps ++ [cp]), cs', args, res)
 
     go (L ll (HsFunTy _ mult x y))
       | (anns, csy, args, res) <- splitHsFunType y
       = (anns, csy S.<> epAnnComments ll, HsScaled mult x:args, res)
 
-    go other = ([], emptyComments, [], other)
+    go other = (noAnn, emptyComments, [], other)
 
 -- | Retrieve the name of the \"head\" of a nested type application.
 -- This is somewhat like @GHC.Tc.Gen.HsType.splitHsAppTys@, but a little more


=====================================
compiler/GHC/JS/Ppr.hs
=====================================
@@ -33,7 +33,7 @@
 -- * Design
 --
 --     This module follows the architecture and style of the other backends in
---     GHC: it intances Outputable for the relevant types, creates a class that
+--     GHC: it instances Outputable for the relevant types, creates a class that
 --     describes a morphism from the IR domain to JavaScript concrete Syntax and
 --     then generates that syntax on a case by case basis.
 --


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1274,7 +1274,7 @@ topdecl :: { LHsDecl GhcPs }
         | stand_alone_deriving                  { L (getLoc $1) (DerivD noExtField (unLoc $1)) }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
-        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
+        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((unLoc $2) (epTok $1))) }
         | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
         | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
         | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
@@ -1366,7 +1366,7 @@ ty_decl :: { LTyClDecl GhcPs }
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
   : 'type' sks_vars '::' sigktype
       {% mkStandaloneKindSig (comb2 $1 $4) (L (gl $2) $ unLoc $2) $4
-               [mj AnnType $1,mu AnnDcolon $3]}
+               (epTok $1,epUniTok $3)}
 
 -- See also: sig_vars
 sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
@@ -1380,7 +1380,8 @@ sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
 inst_decl :: { LInstDecl GhcPs }
         : 'instance' maybe_warning_pragma overlap_pragma inst_type where_inst
        {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (snd $ unLoc $5)
-             ; let anns = (mj AnnInstance $1 : (fst $ unLoc $5))
+             ; let (twhere, (openc, closec, semis)) = fst $ unLoc $5
+             ; let anns = AnnClsInstDecl (epTok $1) twhere openc semis closec
              ; let cid = ClsInstDecl
                                   { cid_ext = ($2, anns, NoAnnSortKey)
                                   , cid_poly_ty = $4, cid_binds = binds
@@ -1421,27 +1422,27 @@ inst_decl :: { LInstDecl GhcPs }
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPPING'     '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlapping (getOVERLAPPING_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPS'        '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlaps (getOVERLAPS_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# INCOHERENT'      '#-}' {% fmap Just $ amsr (sLL $1 $> (Incoherent (getINCOHERENT_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | {- empty -}                 { Nothing }
 
 deriv_strategy_no_via :: { LDerivStrategy GhcPs }
-  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
 
 deriv_strategy_via :: { LDerivStrategy GhcPs }
-  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs [mj AnnVia $1] $2))) }
+  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs (epTok $1) $2))) }
 
 deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) }
-  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
   | deriv_strategy_via          { Just $1 }
   | {- empty -}                 { Nothing }
 
@@ -1659,11 +1660,11 @@ capi_ctype :: { Maybe (LocatedP CType) }
 capi_ctype : '{-# CTYPE' STRING STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) (Just (Header (getSTRINGs $2) (getSTRING $2)))
                                         (getSTRINGs $3,getSTRING $3)))
-                              (AnnPragma (mo $1) (mc $4) [mj AnnHeader $2,mj AnnVal $3]) }
+                              (AnnPragma (glR $1) (glR $4) noAnn (glR $2) (glR $3) noAnn noAnn) }
 
            | '{-# CTYPE'        STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) Nothing (getSTRINGs $2, getSTRING $2)))
-                              (AnnPragma (mo $1) (mc $3) [mj AnnVal $2]) }
+                              (AnnPragma (glR $1) (glR $3) noAnn noAnn (glR $2) noAnn noAnn) }
 
            |           { Nothing }
 
@@ -1676,7 +1677,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
                 {% do { let { err = text "in the stand-alone deriving instance"
                                     <> colon <+> quotes (ppr $6) }
                       ; amsA' (sLL $1 $>
-                                 (DerivDecl ($4, [mj AnnDeriving $1, mj AnnInstance $3]) (mkHsWildCardBndrs $6) $2 $5)) }}
+                                 (DerivDecl ($4, (epTok $1, epTok $3)) (mkHsWildCardBndrs $6) $2 $5)) }}
 
 -----------------------------------------------------------------------------
 -- Role annotations
@@ -1684,7 +1685,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
 role_annot :: { LRoleAnnotDecl GhcPs }
 role_annot : 'type' 'role' oqtycon maybe_roles
           {% mkRoleAnnotDecl (comb3 $1 $4 $3) $3 (reverse (unLoc $4))
-                   [mj AnnType $1,mj AnnRole $2] }
+                   (epTok $1,epTok $2) }
 
 -- Reversed!
 maybe_roles :: { Located [Located (Maybe FastString)] }
@@ -1816,9 +1817,9 @@ decl_inst  :: { Located (OrdList (LHsDecl GhcPs)) }
 decl_inst  : at_decl_inst               { sL1 $1 (unitOL (sL1a $1 (InstD noExtField (unLoc $1)))) }
            | decl                       { sL1 $1 (unitOL $1) }
 
-decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
+decls_inst :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }   -- Reversed
            : decls_inst ';' decl_inst   {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unLoc $3))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1826,7 +1827,7 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
                                                   return (sLL $1 $> (fst $ unLoc $1
                                                                  , snocOL hs t' `appOL` unLoc $3)) }
            | decls_inst ';'             {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1837,20 +1838,20 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
            | {- empty -}                { noLoc ([],nilOL) }
 
 decllist_inst
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", EpToken "}", [EpToken ";"])
                      , OrdList (LHsDecl GhcPs)) }      -- Reversed
-        : '{'         decls_inst '}'    { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2),snd $ unLoc $2) }
-        |     vocurly decls_inst close  { L (gl $2) (unLoc $2) }
+        : '{'         decls_inst '}'    { sLL $1 $> ((epTok $1,epTok $3,fst $ unLoc $2),snd $ unLoc $2) }
+        |     vocurly decls_inst close  { L (gl $2) ((noAnn,noAnn,fst $ unLoc $2),snd $ unLoc $2) }
 
 -- Instance body
 --
-where_inst :: { Located ([AddEpAnn]
+where_inst :: { Located ((EpToken "where", (EpToken "{", EpToken "}", [EpToken ";"]))
                         , OrdList (LHsDecl GhcPs)) }   -- Reversed
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_inst         { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
-                                             ,(snd $ unLoc $2)) }
-        | {- empty -}                   { noLoc ([],nilOL) }
+        : 'where' decllist_inst         { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
+                                             ,snd $ unLoc $2) }
+        | {- empty -}                   { noLoc (noAnn,nilOL) }
 
 -- Declarations in binding groups other than classes and instances
 --
@@ -2019,10 +2020,10 @@ to varid (used for rule_vars), 'checkRuleTyVarBndrNames' must be updated.
 maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) }
         : '{-# DEPRECATED' strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ DeprecatedTxt (getDEPRECATED_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $2))
-                                (AnnPragma (mo $1) (mc $3) (fst $ unLoc $2)) }
+                                (AnnPragma (glR $1) (glR $3) (fst $ unLoc $2) noAnn noAnn noAnn noAnn) }
         | '{-# WARNING' warning_category strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ WarningTxt $2 (getWARNING_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $3))
-                                (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))}
+                                (AnnPragma (glR $1) (glR $4) (fst $ unLoc $3) noAnn noAnn noAnn noAnn)}
         |  {- empty -}      { Nothing }
 
 warning_category :: { Maybe (LocatedE InWarningCategory) }
@@ -2081,9 +2082,9 @@ deprecation :: { OrdList (LWarnDecl GhcPs) }
              {% fmap unitOL $ amsA' (sL (comb3 $1 $2 $>) $ (Warning (unLoc $1, fst $ unLoc $3) (unLoc $2)
                                           (DeprecatedTxt NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $3))) }
 
-strings :: { Located ([AddEpAnn],[Located StringLiteral]) }
-    : STRING { sL1 $1 ([],[L (gl $1) (getStringLiteral $1)]) }
-    | '[' stringlist ']' { sLL $1 $> $ ([mos $1,mcs $3],fromOL (unLoc $2)) }
+strings :: { Located ((EpToken "[", EpToken "]"),[Located StringLiteral]) }
+    : STRING             { sL1 $1 (noAnn,[L (gl $1) (getStringLiteral $1)]) }
+    | '[' stringlist ']' { sLL $1 $> $ ((epTok $1,epTok $3),fromOL (unLoc $2)) }
 
 stringlist :: { Located (OrdList (Located StringLiteral)) }
     : stringlist ',' STRING {% if isNilOL (unLoc $1)
@@ -2104,35 +2105,35 @@ stringlist :: { Located (OrdList (Located StringLiteral)) }
 annotation :: { LHsDecl GhcPs }
     : '{-# ANN' name_var aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $4) [],
+                                            (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn noAnn,
                                             (getANN_PRAGs $1))
                                             (ValueAnnProvenance $2) $3)) }
 
     | '{-# ANN' 'type' otycon aexp '#-}' {% runPV (unECP $4) >>= \ $4 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $5) [mj AnnType $2],
+                                            (AnnPragma (glR $1) (glR $5) noAnn noAnn noAnn (epTok $2) noAnn,
                                             (getANN_PRAGs $1))
                                             (TypeAnnProvenance $3) $4)) }
 
     | '{-# ANN' 'module' aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                                (AnnPragma (mo $1) (mc $4) [mj AnnModule $2],
+                                                (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn (epTok $2),
                                                 (getANN_PRAGs $1))
                                                  ModuleAnnProvenance $3)) }
 
 -----------------------------------------------------------------------------
 -- Foreign import and export declarations
 
-fdecl :: { Located ([AddEpAnn], [AddEpAnn] -> HsDecl GhcPs) }
+fdecl :: { Located (EpToken "foreign" -> HsDecl GhcPs) }
 fdecl : 'import' callconv safety fspec
-               {% mkImport $2 $3 (snd $ unLoc $4) >>= \i ->
-                 return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $4),i))  }
+               {% mkImport $2 $3 (snd $ unLoc $4) (epTok $1, fst $ unLoc $4) >>= \i ->
+                 return (sLL $1 $> i)  }
       | 'import' callconv        fspec
-               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3);
-                    return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $3),d)) }}
+               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3) (epTok $1, fst $ unLoc $3);
+                    return (sLL $1 $> d) }}
       | 'export' callconv fspec
-               {% mkExport $2 (snd $ unLoc $3) >>= \i ->
-                  return (sLL $1 $> (mj AnnExport $1 : (fst $ unLoc $3),i) ) }
+               {% mkExport $2 (snd $ unLoc $3) (epTok $1, fst $ unLoc $3) >>= \i ->
+                  return (sLL $1 $> i ) }
 
 callconv :: { Located CCallConv }
           : 'stdcall'                   { sLL $1 $> StdCallConv }
@@ -2146,12 +2147,12 @@ safety :: { Located Safety }
         | 'safe'                        { sLL $1 $> PlaySafe }
         | 'interruptible'               { sLL $1 $> PlayInterruptible }
 
-fspec :: { Located ([AddEpAnn]
+fspec :: { Located (TokDcolon
                     ,(Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)) }
-       : STRING var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $3]
+       : STRING var '::' sigtype        { sLL $1 $> (epUniTok $3
                                              ,(L (getLoc $1)
                                                     (getStringLiteral $1), $2, $4)) }
-       |        var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $2]
+       |        var '::' sigtype        { sLL $1 $> (epUniTok $2
                                              ,(noLoc (StringLiteral NoSourceText nilFS Nothing), $1, $3)) }
          -- if the entity string is missing, it defaults to the empty string;
          -- the meaning of an empty entity string depends on the calling
@@ -2343,7 +2344,7 @@ atype :: { LHsType GhcPs }
         | '(#' bar_types2 '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsA' (sLL $1 $> $ HsSumTy (AnnParen AnnParensHash (glR $1) (glR $3)) $2) } }
         | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (glR $1) $2 (glR $3)) }
-        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
+        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy (epTok $1, epTok $3) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                             ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
@@ -2559,22 +2560,22 @@ constr :: { LConDecl GhcPs }
         : forall context '=>' constr_stuff
                 {% amsA' (let (con,details) = unLoc $4 in
                   (L (comb4 $1 $2 $3 $4) (mkConDeclH98
-                                                       (mu AnnDarrow $3:(fst $ unLoc $1))
+                                                       (epUniTok $3,(fst $ unLoc $1))
                                                        con
                                                        (snd $ unLoc $1)
                                                        (Just $2)
                                                        details))) }
         | forall constr_stuff
                 {% amsA' (let (con,details) = unLoc $2 in
-                  (L (comb2 $1 $2) (mkConDeclH98 (fst $ unLoc $1)
+                  (L (comb2 $1 $2) (mkConDeclH98 (noAnn, fst $ unLoc $1)
                                                       con
                                                       (snd $ unLoc $1)
                                                       Nothing   -- No context
                                                       details))) }
 
-forall :: { Located ([AddEpAnn], Maybe [LHsTyVarBndr Specificity GhcPs]) }
-        : 'forall' tv_bndrs '.'       { sLL $1 $> ([mu AnnForall $1,mj AnnDot $3], Just $2) }
-        | {- empty -}                 { noLoc ([], Nothing) }
+forall :: { Located ((TokForall, EpToken "."), Maybe [LHsTyVarBndr Specificity GhcPs]) }
+        : 'forall' tv_bndrs '.'       { sLL $1 $> ((epUniTok $1,epTok $3), Just $2) }
+        | {- empty -}                 { noLoc (noAnn, Nothing) }
 
 constr_stuff :: { Located (LocatedN RdrName, HsConDeclH98Details GhcPs) }
         : infixtype       {% do { b <- runPV $1
@@ -2599,7 +2600,7 @@ fielddecl :: { LConDeclField GhcPs }
                                               -- A list because of   f,g :: Int
         : sig_vars '::' ctype
             {% amsA' (L (comb2 $1 $3)
-                      (ConDeclField [mu AnnDcolon $2]
+                      (ConDeclField (epUniTok $2)
                                     (reverse (map (\ln@(L l n)
                                                -> L (fromTrailingN l) $ FieldOcc noExtField (L (noTrailingN l) n)) (unLoc $1))) $3 Nothing))}
 
@@ -2618,15 +2619,15 @@ derivings :: { Located (HsDeriving GhcPs) }
 deriving :: { LHsDerivingClause GhcPs }
         : 'deriving' deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] Nothing $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) Nothing $2) }
 
         | 'deriving' deriv_strategy_no_via deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $2) $3) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $2) $3) }
 
         | 'deriving' deriv_clause_types deriv_strategy_via
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $3) $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $3) $2) }
 
 deriv_clause_types :: { LDerivClauseTys GhcPs }
         : qtycon              { let { tc = sL1a $1 $ mkHsImplicitSigType $
@@ -2971,12 +2972,12 @@ prag_e :: { Located (HsPragE GhcPs) }
       : '{-# SCC' STRING '#-}'      {% do { scc <- getSCC $2
                                           ; return (sLL $1 $>
                                              (HsPragSCC
-                                                (AnnPragma (mo $1) (mc $3) [mj AnnValStr $2],
+                                                (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                 (getSCC_PRAGs $1))
                                                 (StringLiteral (getSTRINGs $2) scc Nothing)))} }
       | '{-# SCC' VARID  '#-}'      { sLL $1 $>
                                              (HsPragSCC
-                                               (AnnPragma (mo $1) (mc $3) [mj AnnVal $2],
+                                               (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                (getSCC_PRAGs $1))
                                                (StringLiteral NoSourceText (getVARID $2) Nothing)) }
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon, TokRarrow,
+  TokDcolon, TokDarrow, TokRarrow, TokForall,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -410,8 +410,11 @@ getEpTokenLoc :: EpToken tok -> EpaLocation
 getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
+-- TODO:AZ: check we have all of the unicode tokens
 type TokDcolon = EpUniToken "::" "∷"
+type TokDarrow = EpUniToken "=>"  "⇒"
 type TokRarrow = EpUniToken "->" "→"
+type TokForall = EpUniToken "forall" "∀"
 
 -- | Layout information for declarations.
 data EpLayout =
@@ -813,9 +816,13 @@ data NameAdornment
 -- annotations in pragmas.
 data AnnPragma
   = AnnPragma {
-      apr_open      :: AddEpAnn,
-      apr_close     :: AddEpAnn,
-      apr_rest      :: [AddEpAnn]
+      apr_open      :: EpaLocation,
+      apr_close     :: EpaLocation,
+      apr_squares   :: (EpToken "[", EpToken "]"),
+      apr_loc1      :: EpaLocation,
+      apr_loc2      :: EpaLocation,
+      apr_type      :: EpToken "type",
+      apr_module    :: EpToken "module"
       } deriving (Data,Eq)
 
 -- ---------------------------------------------------------------------
@@ -1402,7 +1409,7 @@ instance NoAnn NameAnn where
   noAnn = NameAnnTrailing []
 
 instance NoAnn AnnPragma where
-  noAnn = AnnPragma noAnn noAnn []
+  noAnn = AnnPragma noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 instance NoAnn AnnParen where
   noAnn = AnnParen AnnParens noAnn noAnn
@@ -1496,4 +1503,6 @@ instance Outputable AnnList where
     = text "AnnList" <+> ppr a <+> ppr o <+> ppr c <+> ppr r <+> ppr t
 
 instance Outputable AnnPragma where
-  ppr (AnnPragma o c r) = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr r
+  ppr (AnnPragma o c s l ca t m)
+    = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr s <+> ppr l
+                       <+> ppr ca <+> ppr ca <+> ppr t <+> ppr m


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -283,7 +283,7 @@ mkStandaloneKindSig
   :: SrcSpan
   -> Located [LocatedN RdrName]   -- LHS
   -> LHsSigType GhcPs             -- RHS
-  -> [AddEpAnn]
+  -> (EpToken "type", TokDcolon)
   -> P (LStandaloneKindSig GhcPs)
 mkStandaloneKindSig loc lhs rhs anns =
   do { vs <- mapM check_lhs_name (unLoc lhs)
@@ -408,7 +408,7 @@ mkSpliceDecl lexpr@(L loc expr)
 mkRoleAnnotDecl :: SrcSpan
                 -> LocatedN RdrName                -- type being annotated
                 -> [Located (Maybe FastString)]    -- roles
-                -> [AddEpAnn]
+                -> (EpToken "type", EpToken "role")
                 -> P (LRoleAnnotDecl GhcPs)
 mkRoleAnnotDecl loc tycon roles anns
   = do { roles' <- mapM parse_role roles
@@ -773,12 +773,12 @@ recordPatSynErr loc pat =
     addFatalError $ mkPlainErrorMsgEnvelope loc $
       (PsErrRecordSyntaxInPatSynDecl pat)
 
-mkConDeclH98 :: [AddEpAnn] -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
+mkConDeclH98 :: (TokDarrow, (TokForall, EpToken ".")) -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
                 -> Maybe (LHsContext GhcPs) -> HsConDeclH98Details GhcPs
                 -> ConDecl GhcPs
 
-mkConDeclH98 ann name mb_forall mb_cxt args
-  = ConDeclH98 { con_ext    = ann
+mkConDeclH98 (tdarrow, (tforall,tdot)) name mb_forall mb_cxt args
+  = ConDeclH98 { con_ext    = AnnConDeclH98 tforall tdot tdarrow
                , con_name   = name
                , con_forall = isJust mb_forall
                , con_ex_tvs = mb_forall `orElse` []
@@ -795,12 +795,12 @@ mkConDeclH98 ann name mb_forall mb_cxt args
 --   Note [GADT abstract syntax] in "GHC.Hs.Decls" for more details.
 mkGadtDecl :: SrcSpan
            -> NonEmpty (LocatedN RdrName)
-           -> EpUniToken "::" "∷"
+           -> TokDcolon
            -> LHsSigType GhcPs
            -> P (LConDecl GhcPs)
 mkGadtDecl loc names dcol ty = do
 
-  (args, res_ty, annsa, csa) <-
+  (args, res_ty, (ops, cps), csa) <-
     case body_ty of
      L ll (HsFunTy _ hsArr (L (EpAnn anc _ cs) (HsRecTy an rf)) res_ty) -> do
        arr <- case hsArr of
@@ -810,10 +810,10 @@ mkGadtDecl loc names dcol ty = do
                  return noAnn
 
        return ( RecConGADT arr (L (EpAnn anc an cs) rf), res_ty
-              , [], epAnnComments ll)
+              , ([], []), epAnnComments ll)
      _ -> do
-       let (anns, cs, arg_types, res_type) = splitHsFunType body_ty
-       return (PrefixConGADT noExtField arg_types, res_type, anns, cs)
+       let ((ops, cps), cs, arg_types, res_type) = splitHsFunType body_ty
+       return (PrefixConGADT noExtField arg_types, res_type, (ops,cps), cs)
 
   let bndrs_loc = case outer_bndrs of
         HsOuterImplicit{} -> getLoc ty
@@ -822,7 +822,7 @@ mkGadtDecl loc names dcol ty = do
   let l = EpAnn (spanAsAnchor loc) noAnn csa
 
   pure $ L l ConDeclGADT
-                     { con_g_ext  = (dcol, annsa)
+                     { con_g_ext  = AnnConDeclGADT ops cps dcol
                      , con_names  = names
                      , con_bndrs  = L bndrs_loc outer_bndrs
                      , con_mb_cxt = mcxt
@@ -1079,9 +1079,7 @@ checkTyClHdr is_cls ty
       | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
-    go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
-      where
-        (o,c) = mkParensEpToks (realSrcSpan (locA l))
+    go cs l (HsParTy (o,c) ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
@@ -1098,12 +1096,12 @@ checkTyClHdr is_cls ty
 
     -- Combine the annotations from the HsParTy and HsStarTy into a
     -- new one for the LocatedN RdrName
-    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> AnnParen -> SrcSpanAnnN
-    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (AnnParen _ o c) =
+    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> (EpToken "(", EpToken ")") -> SrcSpanAnnN
+    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (o,c) =
       let
         lr = combineSrcSpans (locA l1) (locA l)
       in
-        EpAnn (EpaSpan lr) (NameAnn NameParens o ap c ta) (csp0 Semi.<> csp)
+        EpAnn (EpaSpan lr) (NameAnn NameParens (getEpTokenLoc o) ap (getEpTokenLoc c) ta) (csp0 Semi.<> csp)
 
 -- | Yield a parse error if we have a function applied directly to a do block
 -- etc. and BlockArguments is not enabled.
@@ -1171,9 +1169,9 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
             EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
             _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
-  check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
-                                  -- to be sure HsParTy doesn't get into the way
-    = check (ap_open ann':opi, ap_close ann':cpi, csi) ty
+  check (opi,cpi,csi) (L _lp1 (HsParTy (o,c) ty))
+                                             -- to be sure HsParTy doesn't get into the way
+    = check (getEpTokenLoc o:opi, getEpTokenLoc c:cpi, csi) ty
 
   -- No need for anns, returning original
   check (_opi,_cpi,_csi) _t = unprocessed
@@ -3023,8 +3021,9 @@ checkNewOrData span name is_type_data = curry $ \ case
 mkImport :: Located CCallConv
          -> Located Safety
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
+         -> (EpToken "import", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) (timport, td) =
     case unLoc cconv of
       CCallConv          -> returnSpec =<< mkCImport
       CApiConv           -> do
@@ -3060,8 +3059,8 @@ mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
         funcTarget = CFunction (StaticTarget esrc entity' Nothing True)
         importSpec = CImport (L (l2l loc) esrc) (reLoc cconv) (reLoc safety) Nothing funcTarget
 
-    returnSpec spec = return $ \ann -> ForD noExtField $ ForeignImport
-          { fd_i_ext  = ann
+    returnSpec spec = return $ \tforeign -> ForD noExtField $ ForeignImport
+          { fd_i_ext  = (tforeign, timport, td)
           , fd_name   = v
           , fd_sig_ty = ty
           , fd_fi     = spec
@@ -3133,10 +3132,11 @@ parseCImport cconv safety nm str sourceText =
 --
 mkExport :: Located CCallConv
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty)
- = return $ \ann -> ForD noExtField $
-   ForeignExport { fd_e_ext = ann, fd_name = v, fd_sig_ty = ty
+         -> ( EpToken "export", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty) (texport, td)
+ = return $ \tforeign -> ForD noExtField $
+   ForeignExport { fd_e_ext = (tforeign, texport, td), fd_name = v, fd_sig_ty = ty
                  , fd_fe = CExport (L (l2l le) esrc) (L (l2l lc) (CExportStatic esrc entity' cconv)) }
   where
     entity' | nullFS entity = mkExtName (unLoc v)


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -142,7 +142,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:5:36-49 })
@@ -190,7 +193,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:7:36-48 })
@@ -218,10 +224,11 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaSpan { Test20239.hs:7:50 })
-                   (EpaSpan { Test20239.hs:7:86 }))
+                  ((,)
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:50 }))
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:86 })))
                   (L
                    (EpAnn
                     (EpaSpan { Test20239.hs:7:51-85 })
@@ -290,10 +297,11 @@
                         (EpaComments
                          []))
                        (HsParTy
-                        (AnnParen
-                         AnnParens
-                         (EpaSpan { Test20239.hs:7:68 })
-                         (EpaSpan { Test20239.hs:7:85 }))
+                        ((,)
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:68 }))
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:85 })))
                         (L
                          (EpAnn
                           (EpaSpan { Test20239.hs:7:69-84 })


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -972,8 +972,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:23:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:23:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:23:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:23:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1110,11 +1115,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:25:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1348,8 +1354,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:29:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:29:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:29:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:29:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1486,11 +1497,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:31:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1724,8 +1736,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:35:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:35:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:35:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:35:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1862,11 +1879,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:37:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2100,8 +2118,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:41:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:41:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:41:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:41:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2238,11 +2261,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:43:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2476,8 +2500,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:47:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:47:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:47:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:47:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2614,11 +2643,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:49:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2852,8 +2882,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:53:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:53:18-22 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:53:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:53:18-22 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2990,11 +3025,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:55:11-12 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -101,11 +101,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T17544_kw.hs:16:15-16 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -214,11 +215,12 @@
           (EpaComments
            []))
          (ConDeclGADT
-          ((,)
+          (AnnConDeclGADT
+           []
+           []
            (EpUniTok
             (EpaSpan { T17544_kw.hs:19:15-16 })
-            (NormalSyntax))
-           [])
+            (NormalSyntax)))
           (:|
            (L
             (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -90,7 +90,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:5:5-8 })
@@ -151,7 +154,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:7:5-8 })
@@ -211,7 +217,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:9:9-10 })
@@ -339,7 +348,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:12:7-8 })
@@ -467,7 +479,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:16:3-4 })
@@ -637,7 +652,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:23:3-4 })
@@ -807,7 +825,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:28:3-8 })
@@ -844,7 +865,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:28:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:28:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:28:12-13 })
@@ -903,7 +926,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:29:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:29:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:29:12-13 })
@@ -1008,7 +1033,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:32:3-8 })
@@ -1045,7 +1073,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:33:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:33:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:33:7-8 })
@@ -1104,7 +1134,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:34:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:34:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:34:7-8 })
@@ -1221,7 +1253,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:38:3-8 })
@@ -1258,7 +1293,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:40:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:40:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:40:5-6 })
@@ -1317,7 +1354,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:42:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:42:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:42:5-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -125,7 +125,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:14-17 })
@@ -150,7 +153,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:21-24 })
@@ -201,8 +207,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:9:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:9:13-14 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:9:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:9:13-14 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:9:6-11 })
@@ -352,10 +362,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:10 })
-                 (EpaSpan { DumpParsedAst.hs:11:17 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:17 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:11-16 })
@@ -450,10 +461,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:26 })
-                 (EpaSpan { DumpParsedAst.hs:11:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:26 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:27-35 })
@@ -794,7 +806,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:15:21-23 })
@@ -822,10 +837,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:15:25 })
-                 (EpaSpan { DumpParsedAst.hs:15:29 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:25 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:29 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:15:26-28 })
@@ -885,8 +901,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:17:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:17:9-10 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:17:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:17:9-10 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:17:6-7 })
@@ -960,10 +980,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:17:17 })
-               (EpaSpan { DumpParsedAst.hs:17:27 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:17 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:27 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:17:18-26 })
@@ -1604,10 +1625,11 @@
             (EpaComments
              []))
            (HsParTy
-            (AnnParen
-             AnnParens
-             (EpaSpan { DumpParsedAst.hs:22:22 })
-             (EpaSpan { DumpParsedAst.hs:22:37 }))
+            ((,)
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:22 }))
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:37 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:22:23-36 })
@@ -1731,10 +1753,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:22:42 })
-               (EpaSpan { DumpParsedAst.hs:22:52 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:42 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:52 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:22:43-51 })
@@ -1814,11 +1837,12 @@
             (EpaComments
              []))
            (ConDeclGADT
-            ((,)
+            (AnnConDeclGADT
+             []
+             []
              (EpUniTok
               (EpaSpan { DumpParsedAst.hs:23:7-8 })
-              (NormalSyntax))
-             [])
+              (NormalSyntax)))
             (:|
              (L
               (EpAnn
@@ -1855,10 +1879,11 @@
                  (EpaComments
                   []))
                 (HsParTy
-                 (AnnParen
-                  AnnParens
-                  (EpaSpan { DumpParsedAst.hs:23:10 })
-                  (EpaSpan { DumpParsedAst.hs:23:34 }))
+                 ((,)
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:10 }))
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:34 })))
                  (L
                   (EpAnn
                    (EpaSpan { DumpParsedAst.hs:23:11-33 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -304,10 +304,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:11-16 })
@@ -398,10 +397,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:27-35 })
@@ -850,10 +848,9 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaDelta {  } (SameLine 0) [])
-               (EpaDelta {  } (SameLine 0) []))
+              ((,)
+               (NoEpTok)
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:19:23-36 })
@@ -966,10 +963,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:19:43-51 })
@@ -1079,10 +1075,9 @@
                    (EpaComments
                     []))
                   (HsParTy
-                   (AnnParen
-                    AnnParens
-                    (EpaDelta {  } (SameLine 0) [])
-                    (EpaDelta {  } (SameLine 0) []))
+                   ((,)
+                    (NoEpTok)
+                    (NoEpTok))
                    (L
                     (EpAnn
                      (EpaSpan { DumpRenamedAst.hs:20:11-33 })
@@ -1452,10 +1447,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:22:26-28 })
@@ -1955,10 +1949,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:24:18-26 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -831,10 +831,11 @@
              (EpaComments
               []))
             (HsParTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { KindSigs.hs:22:8 })
-              (EpaSpan { KindSigs.hs:22:20 }))
+             ((,)
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:8 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:20 })))
              (L
               (EpAnn
                (EpaSpan { KindSigs.hs:22:9-19 })
@@ -924,10 +925,11 @@
                (EpaComments
                 []))
               (HsParTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { KindSigs.hs:22:33 })
-                (EpaSpan { KindSigs.hs:22:44 }))
+               ((,)
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:33 }))
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:44 })))
                (L
                 (EpAnn
                  (EpaSpan { KindSigs.hs:22:34-43 })
@@ -1643,10 +1645,11 @@
            (EpaComments
             []))
           (HsParTy
-           (AnnParen
-            AnnParens
-            (EpaSpan { KindSigs.hs:34:9 })
-            (EpaSpan { KindSigs.hs:34:22 }))
+           ((,)
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:9 }))
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:22 })))
            (L
             (EpAnn
              (EpaSpan { KindSigs.hs:34:10-21 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -167,7 +167,7 @@
                   (EpaComments
                    []))
                  (ConDeclField
-                  []
+                  (NoEpUniTok)
                   [(L
                     (EpAnn
                      (EpaSpan { T14189.hs:6:33 })


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -116,11 +116,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T15323.hs:6:17-18 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -196,10 +197,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { T15323.hs:6:31 })
-                 (EpaSpan { T15323.hs:6:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:31 }))
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { T15323.hs:6:32-35 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -137,7 +137,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:5:26-31 })
@@ -257,7 +260,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:6:26-31 })


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -89,11 +89,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T18791.hs:5:7-8 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -57,7 +57,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:4:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:4:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -449,8 +454,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:14:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.hs:14:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:14:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.hs:14:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -717,7 +727,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:3:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:3:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1036,8 +1051,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:5:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.ppr.hs:5:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:5:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.ppr.hs:5:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -63,7 +63,6 @@ import Data.Data ( Data )
 import Data.Dynamic
 import Data.Foldable
 import Data.Functor.Const
-import qualified Data.Set as Set
 import Data.Typeable
 import Data.List ( partition, sort, sortBy)
 import qualified Data.List.NonEmpty as NE
@@ -363,11 +362,11 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+instance HasTrailing (TokForall, EpUniToken "->" "→") where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+instance HasTrailing (TokForall, EpToken ".") where
   trailing _ = []
   setTrailing a _ = a
 
@@ -646,23 +645,6 @@ flushComments !trailing_anns = do
 
 -- ---------------------------------------------------------------------
 
--- |In order to interleave annotations into the stream, we turn them into
--- comments. They are removed from the annotation to avoid duplication.
-annotationsToComments :: (Monad m, Monoid w)
-  => a -> Lens a [AddEpAnn] -> [AnnKeywordId] -> EP w m a
-annotationsToComments a l kws = do
-  let (newComments, newAnns) = go ([],[]) (view l a)
-  addComments True newComments
-  return (set l (reverse newAnns) a)
-  where
-    keywords = Set.fromList kws
-
-    go :: ([Comment], [AddEpAnn]) -> [AddEpAnn] -> ([Comment], [AddEpAnn])
-    go acc [] = acc
-    go (cs',ans) ((AddEpAnn k ss) : ls)
-      | Set.member k keywords = go ((mkKWComment k (epaToNoCommentsLocation ss)):cs', ans) ls
-      | otherwise             = go (cs', (AddEpAnn k ss):ans)    ls
-
 epTokensToComments :: (Monad m, Monoid w)
   => AnnKeywordId -> [EpToken tok] -> EP w m ()
 epTokensToComments kw toks
@@ -825,10 +807,6 @@ markLensAA' a l = do
 
 -- -------------------------------------
 
-markEpAnnLMS :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS epann l kw ms = markEpAnnLMS'' epann (lepa . l) kw ms
-
 markEpAnnLMS'' :: (Monad m, Monoid w)
   => a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m a
 markEpAnnLMS'' an l kw Nothing = markEpAnnL an l kw
@@ -843,26 +821,6 @@ markEpAnnLMS'' a l kw (Just str) = do
           return (AddEpAnn kw' r')
       | otherwise = return (AddEpAnn kw' r)
 
--- -------------------------------------
-
-markEpAnnLMS' :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
-
-markEpAnnLMS0 :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m a
-markEpAnnLMS0 an l _kw Nothing = markLensKwA an l
-markEpAnnLMS0 a l kw (Just str) = do
-  anns <- go (view l a)
-  return (set l anns a)
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
 -- ---------------------------------------------------------------------
 
 -- markEpTokenM :: forall m w tok . (Monad m, Monoid w, KnownSymbol tok)
@@ -912,19 +870,8 @@ markArrow (HsExplicitMult (pct, arr) t) = do
 
 -- ---------------------------------------------------------------------
 
-markAnnCloseP :: (Monad m, Monoid w) => EpAnn AnnPragma -> EP w m (EpAnn AnnPragma)
-markAnnCloseP an = markEpAnnLMS' an lapr_close AnnClose (Just "#-}")
-
-markAnnCloseP' :: (Monad m, Monoid w) => AnnPragma -> EP w m AnnPragma
-markAnnCloseP' an = markEpAnnLMS0 an lapr_close AnnClose (Just "#-}")
-
-markAnnOpenP :: (Monad m, Monoid w) => EpAnn AnnPragma -> SourceText -> String -> EP w m (EpAnn AnnPragma)
-markAnnOpenP an NoSourceText txt   = markEpAnnLMS' an lapr_open AnnOpen (Just txt)
-markAnnOpenP an (SourceText txt) _ = markEpAnnLMS' an lapr_open AnnOpen (Just $ unpackFS txt)
-
-markAnnOpenP' :: (Monad m, Monoid w) => AnnPragma -> SourceText -> String -> EP w m AnnPragma
-markAnnOpenP' an NoSourceText txt   = markEpAnnLMS0 an lapr_open AnnOpen (Just txt)
-markAnnOpenP' an (SourceText txt) _ = markEpAnnLMS0 an lapr_open AnnOpen (Just $ unpackFS txt)
+markAnnCloseP'' :: (Monad m, Monoid w) => EpaLocation -> EP w m EpaLocation
+markAnnCloseP'' l = printStringAtAA l "#-}"
 
 markAnnOpen' :: (Monad m, Monoid w)
   => Maybe EpaLocation -> SourceText -> String -> EP w m (Maybe EpaLocation)
@@ -1089,18 +1036,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lapr_rest :: Lens AnnPragma [AddEpAnn]
-lapr_rest k parent = fmap (\newAnns -> parent { apr_rest = newAnns })
-                          (k (apr_rest parent))
-
-lapr_open :: Lens AnnPragma AddEpAnn
-lapr_open k parent = fmap (\new -> parent { apr_open = new })
-                          (k (apr_open parent))
-
-lapr_close :: Lens AnnPragma AddEpAnn
-lapr_close k parent = fmap (\new -> parent { apr_close = new })
-                          (k (apr_close parent))
-
 lidl :: Lens [AddEpAnn] [AddEpAnn]
 lidl k parent = fmap (\new -> new)
                      (k parent)
@@ -1340,12 +1275,6 @@ lepl_case k parent = fmap (\new -> parent { epl_case = new })
 -- End of lenses
 -- ---------------------------------------------------------------------
 
-markLensKwA :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> EP w m a
-markLensKwA a l = do
-  loc <- markKw (view l a)
-  return (set l loc a)
-
 markLensKw' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a EpaLocation -> AnnKeywordId -> EP w m (EpAnn a)
 markLensKw' (EpAnn anc a cs) l kw = do
@@ -1785,22 +1714,22 @@ instance ExactPrint (LocatedP (WarningTxt GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (WarningTxt mb_cat src ws)) = do
-    an0 <- markAnnOpenP an src "{-# WARNING"
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (WarningTxt mb_cat src ws)) = do
+    o' <- markAnnOpen'' o src "{-# WARNING"
     mb_cat' <- markAnnotated mb_cat
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (WarningTxt mb_cat' src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (WarningTxt mb_cat' src ws'))
 
-  exact (L an (DeprecatedTxt src ws)) = do
-    an0 <- markAnnOpenP an src "{-# DEPRECATED"
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (DeprecatedTxt src ws)) = do
+    o' <- markAnnOpen'' o src "{-# DEPRECATED"
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (DeprecatedTxt src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (DeprecatedTxt src ws'))
 
 instance ExactPrint InWarningCategory where
   getAnnotationEntry _ = NoEntryVal
@@ -2057,14 +1986,14 @@ instance ExactPrint (DerivDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DerivDecl (mw, an) typ ms mov) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+  exact (DerivDecl (mw, (td,ti)) typ ms mov) = do
+    td' <- markEpToken td
     ms' <- mapM markAnnotated ms
-    an1 <- markEpAnnL an0 lidl AnnInstance
+    ti' <- markEpToken ti
     mw' <- mapM markAnnotated mw
     mov' <- mapM markAnnotated mov
     typ' <- markAnnotated typ
-    return (DerivDecl (mw', an1) typ' ms' mov')
+    return (DerivDecl (mw', (td',ti')) typ' ms' mov')
 
 -- ---------------------------------------------------------------------
 
@@ -2072,25 +2001,25 @@ instance ExactPrint (ForeignDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ForeignImport an n ty fimport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnImport
+  exact (ForeignImport (tf,ti,td) n ty fimport) = do
+    tf' <- markEpToken tf
+    ti' <- markEpToken ti
 
     fimport' <- markAnnotated fimport
 
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignImport an2 n' ty' fimport')
+    return (ForeignImport (tf',ti',td') n' ty' fimport')
 
-  exact (ForeignExport an n ty fexport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnExport
+  exact (ForeignExport (tf,te,td) n ty fexport) = do
+    tf' <- markEpToken tf
+    te' <- markEpToken te
     fexport' <- markAnnotated fexport
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignExport an2 n' ty' fexport')
+    return (ForeignExport (tf',te',td') n' ty' fexport')
 
 -- ---------------------------------------------------------------------
 
@@ -2162,24 +2091,22 @@ instance ExactPrint (WarnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warning (ns_spec, an) lns  (WarningTxt mb_cat src ls )) = do
+  exact (Warning (ns_spec, (o,c)) lns  (WarningTxt mb_cat src ls )) = do
     mb_cat' <- markAnnotated mb_cat
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns'  (WarningTxt mb_cat' src ls'))
-    -- return (Warning an1 lns'  (WarningTxt mb_cat' src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns'  (WarningTxt mb_cat' src ls'))
 
-  exact (Warning (ns_spec, an) lns (DeprecatedTxt src ls)) = do
+  exact (Warning (ns_spec, (o,c)) lns (DeprecatedTxt src ls)) = do
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns' (DeprecatedTxt src ls'))
-    -- return (Warning an1 lns' (DeprecatedTxt src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns' (DeprecatedTxt src ls'))
 
 exactNsSpec :: (Monad m, Monoid w) => NamespaceSpecifier -> EP w m NamespaceSpecifier
 exactNsSpec NoNamespaceSpecifier = pure NoNamespaceSpecifier
@@ -2306,9 +2233,9 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (RoleAnnotDecl an ltycon roles) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnRole
+  exact (RoleAnnotDecl (tt,tr) ltycon roles) = do
+    tt' <- markEpToken tt
+    tr' <- markEpToken tr
     ltycon' <- markAnnotated ltycon
     let markRole (L l (Just r)) = do
           (L l' r') <- markAnnotated (L l r)
@@ -2317,7 +2244,7 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
           e' <- printStringAtAA  (entry l) "_"
           return (L (l { entry = e'}) Nothing)
     roles' <- mapM markRole roles
-    return (RoleAnnotDecl an1 ltycon' roles')
+    return (RoleAnnotDecl (tt',tr') ltycon' roles')
 
 -- ---------------------------------------------------------------------
 
@@ -2437,28 +2364,28 @@ instance ExactPrint (ClsInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ClsInstDecl { cid_ext = (mbWarn, an, sortKey)
+  exact (ClsInstDecl { cid_ext = (mbWarn, AnnClsInstDecl i w oc semis cc, sortKey)
                      , cid_poly_ty = inst_ty, cid_binds = binds
                      , cid_sigs = sigs, cid_tyfam_insts = ats
                      , cid_overlap_mode = mbOverlap
                      , cid_datafam_insts = adts })
       = do
-          (mbWarn', an0, mbOverlap', inst_ty') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lid AnnSemi
+          (mbWarn', i', w', mbOverlap', inst_ty') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsAtTag, prepareListAnnotationA ats),
                                 (ClsAtdTag, prepareListAnnotationF adts),
                                 (ClsMethodTag, prepareListAnnotationA binds),
                                 (ClsSigTag, prepareListAnnotationA sigs)
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC -- '}'
+          cc' <- markEpToken cc
           let
             ats'   = undynamic ds
             adts'  = undynamic ds
             binds' = undynamic ds
             sigs'  = undynamic ds
-          return (ClsInstDecl { cid_ext = (mbWarn', an3, sortKey')
+          return (ClsInstDecl { cid_ext = (mbWarn', AnnClsInstDecl i' w' oc' semis' cc', sortKey')
                               , cid_poly_ty = inst_ty', cid_binds = binds'
                               , cid_sigs = sigs', cid_tyfam_insts = ats'
                               , cid_overlap_mode = mbOverlap'
@@ -2466,12 +2393,12 @@ instance ExactPrint (ClsInstDecl GhcPs) where
 
       where
         top_matter = do
-          an0 <- markEpAnnL an lidl AnnInstance
+          i' <- markEpToken i
           mw <- mapM markAnnotated mbWarn
           mo <- mapM markAnnotated mbOverlap
           it <- markAnnotated inst_ty
-          an1 <- markEpAnnL an0 lidl AnnWhere -- Optional
-          return (mw, an1, mo,it)
+          w' <- markEpToken w -- Optional
+          return (mw, i', w', mo,it)
 
 -- ---------------------------------------------------------------------
 
@@ -2492,35 +2419,35 @@ instance ExactPrint (LocatedP OverlapMode) where
   setAnnotationAnchor = setAnchorAn
 
   -- NOTE: NoOverlap is only used in the typechecker
-  exact (L an (NoOverlap src)) = do
-    an0 <- markAnnOpenP an src "{-# NO_OVERLAP"
-    an1 <- markAnnCloseP an0
-    return (L an1 (NoOverlap src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NoOverlap src)) = do
+    o' <- markAnnOpen'' o src "{-# NO_OVERLAP"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (NoOverlap src))
 
-  exact (L an (Overlappable src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPABLE"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlappable src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlappable src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPABLE"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlappable src))
 
-  exact (L an (Overlapping src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPING"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlapping src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlapping src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPING"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlapping src))
 
-  exact (L an (Overlaps src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPS"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlaps src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlaps src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPS"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlaps src))
 
-  exact (L an (Incoherent src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Incoherent src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
-  exact (L an (NonCanonical src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NonCanonical src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
 -- ---------------------------------------------------------------------
 
@@ -2962,12 +2889,12 @@ instance ExactPrint (StandaloneKindSig GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StandaloneKindSig an vars sig) = do
-    an0 <- markEpAnnL an lidl AnnType
+  exact (StandaloneKindSig (tt,td) vars sig) = do
+    tt' <- markEpToken tt
     vars' <- markAnnotated vars
-    an1 <- markEpAnnL an0 lidl AnnDcolon
+    td' <- markEpUniToken td
     sig' <- markAnnotated sig
-    return (StandaloneKindSig an1 vars' sig')
+    return (StandaloneKindSig (tt',td') vars' sig')
 
 -- ---------------------------------------------------------------------
 
@@ -2989,24 +2916,24 @@ instance ExactPrint (AnnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsAnnotation (an, src) prov e) = do
-    an0 <- markAnnOpenP' an src "{-# ANN"
-    (an1, prov') <-
+  exact (HsAnnotation (AnnPragma o c s l1 l2 t m, src) prov e) = do
+    o' <- markAnnOpen'' o src "{-# ANN"
+    (t', m', prov') <-
       case prov of
         (ValueAnnProvenance n) -> do
           n' <- markAnnotated n
-          return (an0, ValueAnnProvenance n')
+          return (t, m, ValueAnnProvenance n')
         (TypeAnnProvenance n) -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnType
+          t' <- markEpToken t
           n' <- markAnnotated n
-          return (an1, TypeAnnProvenance n')
+          return (t', m, TypeAnnProvenance n')
         ModuleAnnProvenance -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnModule
-          return (an1, prov)
+          m' <- markEpToken m
+          return (t, m', prov)
 
     e' <- markAnnotated e
-    an2 <- markAnnCloseP' an1
-    return (HsAnnotation (an2,src) prov' e')
+    c' <- printStringAtAA c "#-}"
+    return (HsAnnotation (AnnPragma o' c' s l1 l2 t' m',src) prov' e')
 
 -- ---------------------------------------------------------------------
 
@@ -3418,13 +3345,11 @@ instance ExactPrint (HsPragE GhcPs) where
   getAnnotationEntry HsPragSCC{}  = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsPragSCC (an,st) sl) = do
-    an0 <- markAnnOpenP' an st "{-# SCC"
-    let txt = sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl)
-    an1 <- markEpAnnLMS'' an0 lapr_rest AnnVal    (Just txt) -- optional
-    an2 <- markEpAnnLMS'' an1 lapr_rest AnnValStr (Just txt) -- optional
-    an3 <- markAnnCloseP' an2
-    return (HsPragSCC (an3,st) sl)
+  exact (HsPragSCC (AnnPragma o c s l1 l2 t m,st) sl) = do
+    o' <- markAnnOpen'' o st  "{-# SCC"
+    l1' <- printStringAtAA l1 (sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl))
+    c' <- printStringAtAA c "#-}"
+    return (HsPragSCC (AnnPragma o' c' s l1' l2 t m,st) sl)
 
 
 -- ---------------------------------------------------------------------
@@ -4178,11 +4103,11 @@ instance ExactPrint (HsType GhcPs) where
     lo' <- markAnnotated lo
     t2' <- markAnnotated t2
     return (HsOpTy x promoted t1' lo' t2')
-  exact (HsParTy an ty) = do
-    an0 <- markOpeningParen an
+  exact (HsParTy (o,c) ty) = do
+    o' <- markEpToken o
     ty' <- markAnnotated ty
-    an1 <- markClosingParen an0
-    return (HsParTy an1 ty')
+    c' <- markEpToken c
+    return (HsParTy (o',c') ty')
   exact (HsIParamTy an n t) = do
     n' <- markAnnotated n
     an0 <- markEpUniToken an
@@ -4273,7 +4198,7 @@ instance ExactPrint (HsDerivingClause GhcPs) where
   exact (HsDerivingClause { deriv_clause_ext      = an
                           , deriv_clause_strategy = dcs
                           , deriv_clause_tys      = dct }) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+    an0 <- markEpToken an
     dcs0 <- case dcs of
             Just (L _ ViaStrategy{}) -> return dcs
             _ -> mapM markAnnotated dcs
@@ -4292,16 +4217,16 @@ instance ExactPrint (DerivStrategy GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
   exact (StockStrategy an)    = do
-    an0 <- markEpAnnL an lid AnnStock
+    an0 <- markEpToken an
     return (StockStrategy an0)
   exact (AnyclassStrategy an) = do
-    an0 <- markEpAnnL an lid AnnAnyclass
+    an0 <- markEpToken an
     return (AnyclassStrategy an0)
   exact (NewtypeStrategy an)  = do
-    an0 <- markEpAnnL an lid AnnNewtype
+    an0 <- markEpToken an
     return (NewtypeStrategy an0)
   exact (ViaStrategy (XViaStrategyPs an ty)) = do
-    an0 <- markEpAnnL an lid AnnVia
+    an0 <- markEpToken an
     ty' <- markAnnotated ty
     return (ViaStrategy (XViaStrategyPs an0 ty'))
 
@@ -4468,27 +4393,27 @@ instance ExactPrint (ConDecl GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
 -- based on pprConDecl
-  exact (ConDeclH98 { con_ext = an
+  exact (ConDeclH98 { con_ext = AnnConDeclH98 tforall tdot tdarrow
                     , con_name = con
                     , con_forall = has_forall
                     , con_ex_tvs = ex_tvs
                     , con_mb_cxt = mcxt
                     , con_args = args
                     , con_doc = doc }) = do
-    an0 <- if has_forall
-      then markEpAnnL an lidl AnnForall
-      else return an
+    tforall' <- if has_forall
+      then markEpUniToken tforall
+      else return tforall
     ex_tvs' <- mapM markAnnotated ex_tvs
-    an1 <- if has_forall
-      then markEpAnnL an0 lidl AnnDot
-      else return an0
+    tdot' <- if has_forall
+      then markEpToken tdot
+      else return tdot
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
+    tdarrow' <- if (isJust mcxt)
+      then markEpUniToken tdarrow
+      else return tdarrow
 
     (con', args') <- exact_details args
-    return (ConDeclH98 { con_ext = an2
+    return (ConDeclH98 { con_ext = AnnConDeclH98 tforall' tdot' tdarrow'
                        , con_name = con'
                        , con_forall = has_forall
                        , con_ex_tvs = ex_tvs'
@@ -4516,14 +4441,15 @@ instance ExactPrint (ConDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ConDeclGADT { con_g_ext = (dcol, an)
+  exact (ConDeclGADT { con_g_ext = AnnConDeclGADT ops cps dcol
                      , con_names = cons
                      , con_bndrs = bndrs
                      , con_mb_cxt = mcxt, con_g_args = args
                      , con_res_ty = res_ty, con_doc = doc }) = do
     cons' <- mapM markAnnotated cons
     dcol' <- markEpUniToken dcol
-    an1 <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
 
     -- Work around https://gitlab.haskell.org/ghc/ghc/-/issues/20558
     bndrs' <- case bndrs of
@@ -4531,9 +4457,6 @@ instance ExactPrint (ConDecl GhcPs) where
       _ -> markAnnotated bndrs
 
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
     args' <-
       case args of
           (PrefixConGADT x args0) -> do
@@ -4544,7 +4467,7 @@ instance ExactPrint (ConDecl GhcPs) where
             rarr' <- markEpUniToken rarr
             return (RecConGADT rarr' fields')
     res_ty' <- markAnnotated res_ty
-    return (ConDeclGADT { con_g_ext = (dcol', an2)
+    return (ConDeclGADT { con_g_ext = AnnConDeclGADT [] [] dcol'
                         , con_names = cons'
                         , con_bndrs = bndrs'
                         , con_mb_cxt = mcxt', con_g_args = args'
@@ -4579,11 +4502,11 @@ instance ExactPrint (ConDeclField GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ConDeclField an names ftype mdoc) = do
+  exact (ConDeclField td names ftype mdoc) = do
     names' <- markAnnotated names
-    an0 <- markEpAnnL an lidl AnnDcolon
+    td' <- markEpUniToken td
     ftype' <- markAnnotated ftype
-    return (ConDeclField an0 names' ftype' mdoc)
+    return (ConDeclField td' names' ftype' mdoc)
 
 -- ---------------------------------------------------------------------
 
@@ -4610,15 +4533,15 @@ instance ExactPrint (LocatedP CType) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (CType stp mh (stct,ct))) = do
-    an0 <- markAnnOpenP an stp "{-# CTYPE"
-    an1 <- case mh of
-             Nothing -> return an0
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (CType stp mh (stct,ct))) = do
+    o' <- markAnnOpen'' o stp "{-# CTYPE"
+    l1' <- case mh of
+             Nothing -> return l1
              Just (Header srcH _h) ->
-               markEpAnnLMS an0 lapr_rest AnnHeader (Just (toSourceTextWithSuffix srcH "" ""))
-    an2 <- markEpAnnLMS an1 lapr_rest AnnVal (Just (toSourceTextWithSuffix stct (unpackFS ct) ""))
-    an3 <- markAnnCloseP an2
-    return (L an3 (CType stp mh (stct,ct)))
+               printStringAtAA l1 (toSourceTextWithSuffix srcH "" "")
+    l2' <- printStringAtAA l2 (toSourceTextWithSuffix stct (unpackFS ct) "")
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' s l1' l2' t m) cs) (CType stp mh (stct,ct)))
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -105,7 +105,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Ppr012.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr013.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr014.hs" Nothing
- -- "../../testsuite/tests/printer/Ppr015.hs" Nothing
+ "../../testsuite/tests/printer/Ppr015.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr016.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr017.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr018.hs" Nothing
@@ -212,7 +212,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ -- "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
 {-# LANGUAGE DerivingStrategies #-}
@@ -820,7 +821,7 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
 
 type XRecCond a =
-  ( XParTy a ~ AnnParen
+  ( XParTy a ~ (EpToken "(", EpToken ")")
   , NoGhcTc a ~ a
   , MapXRec a
   , UnXRec a
@@ -852,7 +853,7 @@ type instance XListTy DocNameI = EpAnn AnnParen
 type instance XTupleTy DocNameI = EpAnn AnnParen
 type instance XSumTy DocNameI = EpAnn AnnParen
 type instance XOpTy DocNameI = EpAnn [AddEpAnn]
-type instance XParTy DocNameI = AnnParen
+type instance XParTy DocNameI = (EpToken "(", EpToken ")")
 type instance XIParamTy DocNameI = EpAnn [AddEpAnn]
 type instance XKindSig DocNameI = EpAnn [AddEpAnn]
 type instance XSpliceTy DocNameI = DataConCantHappen



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 20 23:49:43 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Sun, 20 Oct 2024 19:49:43 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] make caller wrap the pop err ctxt
Message-ID: <671597177944a_2046a93cee487862@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
14a561c2 by Apoorv Ingle at 2024-10-20T18:48:55-05:00
make caller wrap the pop err ctxt

- - - - -


3 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -586,22 +586,6 @@ mkExpandedPatRn
 mkExpandedPatRn oPat flav eExpr = XExpr (ExpandedThingRn { xrn_orig = OrigPat oPat flav
                                                          , xrn_expanded = eExpr })
 
--- | Build an expression using the extension constructor `XExpr`,
---   and the two components of the expansion: original do stmt and
---   expanded expression and associate it with a provided location
-mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
-  -> HsDoFlavour          -- ^ the flavour of the statement
-  -> HsExpr GhcRn         -- ^ expanded expression
-  -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt loc (L loc $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
-  = L loc $ mkExpandedStmt oStmt flav eExpr
-
 data XXExprGhcTc
   = WrapExpr        -- Type and evidence application and abstractions
       HsWrapper (HsExpr GhcTc)


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -2258,7 +2258,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
              -- Need 'pureAName' and not 'returnMName' here, so that it requires
              -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed).
              (pure_name, _) <- lookupQualifiedDoName (HsDoStmt ctxt) pureAName
-             let expr = noLocA (HsApp noExtField (noLocA ret) tup)
+             let expr = noLocA (genHsApps pure_name [tup])
              return (expr, emptyFVs)
      return ( ApplicativeArgMany
               { xarg_app_arg_many = noExtField


=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -47,39 +47,39 @@ import Data.List ((\\))
 *                                                                      *
 ************************************************************************
 -}
-
+-- TODO: make caller add the pop error context
 -- | Expand the `do`-statments into expressions right after renaming
 --   so that they can be typechecked.
 --   See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary
 --   and Note [Handling overloaded and rebindable constructs] for high level commentary
 expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn)
-expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts
+expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts doFlav stmts
 
 -- | The main work horse for expanding do block statements into applications of binds and thens
 --   See Note [Expanding HsDo with XXExprGhcRn]
-expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn)
+expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn)
 
-expand_do_stmts _ ListComp _ =
+expand_do_stmts ListComp _ =
   pprPanic "expand_do_stmts: impossible happened. ListComp" empty
         -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
-
-expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) =
+expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) =
   pprPanic "expand_do_stmts: TransStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) =
+expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) =
   pprPanic "expand_do_stmts: ParStmt" $ ppr stmt
   -- handeled by `GHC.Tc.Gen.Match.tcLcStmt`
 
-expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))]
+expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty
+
+expand_do_stmts flav [stmt@(L _ (LastStmt _ (L body_loc body) _ ret_expr))]
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (5) below
 -- last statement of a list comprehension, needs to explicitly return it
 -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt`
    | NoSyntaxExprRn <- ret_expr
    -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt
-   = return $ mkExpandedStmtAt addPop loc stmt flav body
+   = return $ mkExpandedStmtAt stmt flav body
 
    | SyntaxExprRn ret <- ret_expr
    --
@@ -87,18 +87,18 @@ expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_exp
    --               return e  ~~> return e
    -- to make T18324 work
    = do let expansion = genHsApp ret (L body_loc body)
-        return $ mkExpandedStmtAt addPop loc stmt flav expansion
+        return $ mkExpandedStmtAt stmt flav expansion
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) =
+expand_do_stmts doFlavour (stmt@(L _loc (LetStmt _ bs)) : lstmts) =
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (3) below
 --                      stmts ~~> stmts'
 --    ------------------------------------------------
 --       let x = e ; stmts ~~> let x = e in stmts'
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
-     let expansion = genHsLet bs expand_stmts
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+  do expand_stmts <- expand_do_stmts doFlavour lstmts
+     let expansion = genPopErrCtxtExpr (wrapGenSpan $ genHsLet bs expand_stmts)
+     return $ mkExpandedStmtAt stmt doFlavour (unLoc expansion)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
+expand_do_stmts doFlavour (stmt@(L _loc (BindStmt xbsrn pat e)): lstmts)
   | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn
   , fail_op              <- xbsrn_failOp xbsrn
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (2) below
@@ -107,29 +107,29 @@ expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts)
 --                                   _   -> fail "Pattern match failure .."
 --    -------------------------------------------------------
 --       pat <- e ; stmts   ~~> (>>=) e f
-  = do expand_stmts <- expand_do_stmts True doFlavour lstmts
-       failable_expr <- mk_failable_expr False doFlavour pat expand_stmts fail_op
+  = do expand_stmts <- genPopErrCtxtExpr <$> expand_do_stmts doFlavour lstmts
+       failable_expr <- mk_failable_expr doFlavour pat expand_stmts fail_op
        let expansion = genHsExpApps bind_op  -- (>>=)
                        [ e
                        , failable_expr ]
-       return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+       return $ mkExpandedStmtAt stmt doFlavour expansion
 
   | otherwise
   = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr  stmt)
 
-expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
+expand_do_stmts doFlavour (stmt@(L _loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) =
 -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr
 -- See  Note [Expanding HsDo with XXExprGhcRn] Equation (1) below
 --              stmts ~~> stmts'
 --    ----------------------------------------------
 --      e ; stmts ~~> (>>) e stmts'
-  do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts_expr <- expand_do_stmts doFlavour lstmts
      let expansion = genHsExpApps then_op  -- (>>)
-                                  [ e
-                                  , expand_stmts_expr ]
-     return $ mkExpandedStmtAt addPop loc stmt doFlavour expansion
+                     [ e
+                     , genPopErrCtxtExpr expand_stmts_expr ]
+     return $ mkExpandedStmtAt stmt doFlavour expansion
 
-expand_do_stmts _ doFlavour
+expand_do_stmts doFlavour
        ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts
                         , recS_later_ids = later_ids  -- forward referenced local ids
                         , recS_rec_ids = local_ids     -- ids referenced outside of the rec block
@@ -149,7 +149,7 @@ expand_do_stmts _ doFlavour
 --                                           -> do { rec_stmts
 --                                                 ; return (local_only_ids ++ later_ids) } ))
 --                              (\ [ local_only_ids ++ later_ids ] -> stmts')
-  do expand_stmts <- expand_do_stmts True doFlavour lstmts
+  do expand_stmts <- expand_do_stmts doFlavour lstmts
      -- NB: No need to wrap the expansion with an ExpandedStmt
      -- as we want to flatten the rec block statements into its parent do block anyway
      return $ mkHsApps (wrapGenSpan bind_fun)                                           -- (>>=)
@@ -177,7 +177,7 @@ expand_do_stmts _ doFlavour
                              -- NB: LazyPat because we do not want to eagerly evaluate the pattern
                              -- and potentially loop forever
 
-expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
+expand_do_stmts doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) =
 -- See Note [Applicative BodyStmt]
 --
 --                  stmts ~~> stmts'
@@ -187,7 +187,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
 -- Very similar to HsToCore.Expr.dsDo
 
 -- args are [(<$>, e1), (<*>, e2), .., ]
-  do { xexpr <- expand_do_stmts False doFlavour lstmts
+  do { xexpr <- expand_do_stmts doFlavour lstmts
      -- extracts pats and arg bodies (rhss) from args
 
      ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args
@@ -216,7 +216,7 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
             { xarg_app_arg_one = mb_fail_op
             , app_arg_pattern = pat
             , arg_expr        = (L rhs_loc rhs) }) =
-      do let xx_expr = mkExpandedStmtAt addPop (noAnnSrcSpan generatedSrcSpan) stmt doFlavour rhs
+      do let xx_expr = mkExpandedStmtAt stmt doFlavour rhs
          traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr])
          return ((pat, mb_fail_op)
                 , xx_expr)
@@ -225,13 +225,13 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
                                , final_expr = ret@(L ret_loc _)
                                , bv_pattern = pat
                                , stmt_context = ctxt }) =
-      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts addPop ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
-         ; traceTc "do_arg" (text "ManyArg" <+> ppr addPop <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
+      do { xx_expr <- (wrapGenSpan . unLoc) <$> (expand_do_stmts ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret])
+         ; traceTc "do_arg" (text "ManyArg" <+> ppr False <+> vcat [ppr (stmts ++ [L ret_loc $ mkLastStmt ret]), text "--", ppr xx_expr])
          ; return ((pat, Nothing)
                   , xx_expr) }
 
     match_args :: (LPat GhcRn, FailOperator GhcRn)  -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn)
-    match_args (pat, fail_op) body = mk_failable_expr addPop doFlavour pat body fail_op
+    match_args (pat, fail_op) body = mk_failable_expr doFlavour pat body fail_op
 
     mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn
     mk_apps l_expr (op, r_expr) =
@@ -239,11 +239,11 @@ expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join)
         SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ]
         NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op)
 
-expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts)
+expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts)
 
 -- checks the pattern `pat` for irrefutability which decides if we need to wrap it with a fail block
-mk_failable_expr :: Bool -> HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
-mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
+mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn)
+mk_failable_expr doFlav lpat@(L loc pat) expr@(L _exprloc _) fail_op =
   do { is_strict <- xoptM LangExt.Strict
      ; hscEnv <- getTopEnv
      ; rdrEnv <- getGlobalRdrEnv
@@ -252,13 +252,11 @@ mk_failable_expr addPop doFlav lpat@(L loc pat) expr@(L exprloc _) fail_op =
      ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat
                                         , text "isIrrefutable:" <+> ppr irrf_pat
                                         ])
-     ; let xexpr | addPop = mkPopErrCtxtExprAt exprloc expr
-                 | otherwise = expr
      ; if irrf_pat -- don't wrap with fail block if
                    -- the pattern is irrefutable
        then case pat of
-              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] xexpr
-              _ -> return $ genHsLamDoExp doFlav [lpat] xexpr
+              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr
+              _ -> return $ genHsLamDoExp doFlav [lpat] expr
 
        else L loc <$> mk_fail_block doFlav lpat expr fail_op
      }
@@ -343,10 +341,10 @@ They capture the essence of statement expansions as implemented in `expand_do_st
 
           (2) DO【 p <- e; ss 】 = if p is irrefutable
                                    then ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\ p -> DO【 ss 】))
+                                          (>>=) s ((\ p -> ‹PopExprCtxt› DO【 ss 】))
                                    else ‹ExpansionStmt (p <- e)›
-                                          (>>=) s (‹PopExprCtxt›(\case p -> DO【 ss 】
-                                                                       _ -> fail "pattern p failure"))
+                                          (>>=) s ((\case p -> ‹PopExprCtxt› DO【 ss 】
+                                                          _ -> fail "pattern p failure"))
 
           (3) DO【 let x = e; ss 】
                                  = ‹ExpansionStmt (let x = e)› (let x = e in (‹PopErrCtxt›DO【 ss 】))
@@ -569,11 +567,6 @@ It stores the original statement (with location) and the expanded expression
 mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn
 mkPopErrCtxtExpr a = XExpr (PopErrCtxt a)
 
--- | Wrap a located expression with a PopSrcExpr with an appropriate location
-mkPopErrCtxtExprAt :: SrcSpanAnnA ->  LHsExpr GhcRn -> LHsExpr GhcRn
-mkPopErrCtxtExprAt _loc a = wrapGenSpan $ mkPopErrCtxtExpr a
-
-
 genPopErrCtxtExpr :: LHsExpr GhcRn -> LHsExpr GhcRn
 genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 
@@ -581,14 +574,9 @@ genPopErrCtxtExpr a = wrapGenSpan $ mkPopErrCtxtExpr a
 --   and the two components of the expansion: original do stmt and
 --   expanded expression and associate it with a provided location
 mkExpandedStmtAt
-  :: Bool                 -- ^ Wrap this expansion with a pop?
-  -> SrcSpanAnnA          -- ^ Location for the expansion expression
-  -> ExprLStmt GhcRn      -- ^ source statement
+  :: ExprLStmt GhcRn      -- ^ source statement
   -> HsDoFlavour          -- ^ the flavour of the statement
   -> HsExpr GhcRn         -- ^ expanded expression
   -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt addPop _loc oStmt flav eExpr
-  | addPop
-  = mkPopErrCtxtExprAt _loc (wrapGenSpan $ mkExpandedStmt oStmt flav eExpr)
-  | otherwise
+mkExpandedStmtAt oStmt flav eExpr
   = wrapGenSpan $ mkExpandedStmt oStmt flav eExpr



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14a561c29ee3885426c5073a3666ae240ae43f75

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 00:10:36 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 20 Oct 2024 20:10:36 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ttg/types/basic
Message-ID: <67159bfc46f2b_2046a94f3238811a@gitlab.mail>



Hassan Al-Awwadi pushed new branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ttg/types/basic
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 02:09:40 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 20 Oct 2024 22:09:40 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Interpreter:
 Add locking for communication with external interpreter
Message-ID: <6715b7e43fe6d_2046a9b280541238a@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
c3290fa2 by Alan Zimmerman at 2024-10-20T22:09:35-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
e54f0343 by Cheng Shao at 2024-10-20T22:09:35-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -


30 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- + testsuite/tests/th/T25083.hs
- + testsuite/tests/th/T25083.stdout
- + testsuite/tests/th/T25083_A.hs
- + testsuite/tests/th/T25083_B.hs
- testsuite/tests/th/all.T


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dbc648f0fb5871bcaf8888ddfb9a6c2636d0328...e54f034315b461c03d8fb2cbf41ca29208df04c0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4dbc648f0fb5871bcaf8888ddfb9a6c2636d0328...e54f034315b461c03d8fb2cbf41ca29208df04c0
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 07:55:21 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 21 Oct 2024 03:55:21 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] whitespace
Message-ID: <671608e99a41d_1c8d4d61b7003617f@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
632e137e by Hassan Al-Awwadi at 2024-10-21T09:54:46+02:00
whitespace

- - - - -


2 changed files:

- compiler/GHC/Hs/InlinePragma.hs
- compiler/Language/Haskell/Syntax/InlinePragma.hs


Changes:

=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -24,7 +24,7 @@ module GHC.Hs.InlinePragma(
         pprInline, pprInlineDebug,
         convertInlinePragma, convertInlineSpec, convertActivation
 
-) where 
+) where
 
 import GHC.Prelude
 import GHC.Types.SourceText(SourceText (..), pprWithSourceText)
@@ -59,7 +59,7 @@ type instance XOpaque    (GhcPass _) = SourceText
 type instance XNoUserInlinePrag (GhcPass _) = NoExtField
 type instance XXInlineSpec      (GhcPass _) = DataConCantHappen
 
-deriving instance Eq (InlineSpec (GhcPass p))  
+deriving instance Eq (InlineSpec (GhcPass p))
 
 instance Show (InlineSpec (GhcPass p)) where
   show (Inline s)    = "Inline "    ++ show s
@@ -77,7 +77,7 @@ type instance XFinalActive  (GhcPass _) = NoExtField
 type instance XNeverActive  (GhcPass _) = NoExtField
 type instance XXActivation  (GhcPass _) = DataConCantHappen
 
-deriving instance Eq (Activation (GhcPass p))  
+deriving instance Eq (Activation (GhcPass p))
     -- Eq used in comparing rules in GHC.Hs.Decls
 
 
@@ -274,7 +274,7 @@ inlineSpecSource spec = case spec of
 -- exprIsConApp_maybe can "see" its unfolding
 -- (However, its actual Unfolding is a DFunUnfolding, which is
 --  never inlined other than via exprIsConApp_maybe.)
-dfunInlinePragma = let 
+dfunInlinePragma = let
   always_active         = set_pragma_activation defaultInlinePragma (AlwaysActive noExtField)
   always_active_conlike = set_pragma_rule always_active ConLike
   in always_active_conlike
@@ -284,7 +284,7 @@ isDefaultInlinePragma (InlinePragma { inl_act = activation
                                     , inl_rule = match_info
                                     , inl_inline = inline })
   = noUserInlineSpec inline && isAlwaysActive activation && isFunLike match_info
-isDefaultInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible 
+isDefaultInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible
 
 isInlinePragma :: InlinePragma (GhcPass p) -> Bool
 isInlinePragma prag@(InlinePragma{}) = case inl_inline prag of
@@ -538,7 +538,7 @@ inlinePragmaName (Inlinable         _)  = text "INLINABLE"
 inlinePragmaName (NoInline          _)  = text "NOINLINE"
 inlinePragmaName (Opaque            _)  = text "OPAQUE"
 inlinePragmaName (NoUserInlinePrag  _)   = empty
-inlinePragmaName (XInlineSpec impossible) = dataConCantHappen impossible 
+inlinePragmaName (XInlineSpec impossible) = dataConCantHappen impossible
 
 -- | Pretty-print without displaying the user-specified 'InlineSpec'.
 pprInline :: InlinePragma (GhcPass p) -> SDoc


=====================================
compiler/Language/Haskell/Syntax/InlinePragma.hs
=====================================
@@ -1,7 +1,7 @@
-module Language.Haskell.Syntax.InlinePragma where 
+module Language.Haskell.Syntax.InlinePragma where
 
 import GHC.Prelude
-import Data.Data 
+
 import Language.Haskell.Syntax.Basic(Arity)
 import Language.Haskell.Syntax.Extension
 
@@ -21,7 +21,7 @@ data InlinePragma p           -- Note [InlinePragma] in GHC.Hs.InlinePragma
                                       -- See Note [inl_inline and inl_act] in GHC.Hs.InlinePragma
 
       , inl_rule   :: RuleMatchInfo   -- Should the function be treated like a constructor?
-    } 
+    }
   | XCInlinePragma (XXCInlinePragma p)
 
 
@@ -33,7 +33,7 @@ data InlineSpec p   -- What the user's INLINE pragma looked like
   | Opaque    (XOpaque    p)       -- User wrote OPAQUE
                                -- Each of the above keywords is accompanied with
                                -- a string of type SourceText written by the user
-  | NoUserInlinePrag (XNoUserInlinePrag p) 
+  | NoUserInlinePrag (XNoUserInlinePrag p)
                      -- User did not write any of INLINE/INLINABLE/NOINLINE
                      -- e.g. in `defaultInlinePragma` or when created by CSE
   | XInlineSpec (XXInlineSpec p)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/632e137e6240953e0824dad3260781cce1273cc5

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 07:59:16 2024
From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven))
Date: Mon, 21 Oct 2024 03:59:16 -0400
Subject: [Git][ghc/ghc][wip/supersven/riscv-vectors] WIP
Message-ID: <671609d4d68a1_1c8d4d621740377b1@gitlab.mail>



Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC


Commits:
fc56e7ae by Sven Tennie at 2024-10-21T09:58:42+02:00
WIP

- - - - -


1 changed file:

- compiler/GHC/CmmToAsm/RV64/Ppr.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/Ppr.hs
=====================================
@@ -551,6 +551,8 @@ pprInstr platform instr = case instr of
     | isFloatOp o1 && not (isFloatOp o2) && isDoubleOp o1 -> op2 (text "\tfmv.d.x") o1 o2
     | not (isFloatOp o1) && isFloatOp o2 && isSingleOp o2 -> op2 (text "\tfmv.x.w") o1 o2
     | not (isFloatOp o1) && isFloatOp o2 && isDoubleOp o2 -> op2 (text "\tfmv.x.d") o1 o2
+    -- TODO: Why does this NOP (reg1 == reg2) happen?
+    | isVectorOp o1 && isVectorOp o2 -> op2 (text "\tvmv.v.v") o1 o2
     | (OpImm (ImmInteger i)) <- o2,
       fitsIn12bitImm i ->
         lines_ [text "\taddi" <+> pprOp platform o1 <> comma <+> pprOp platform x0 <> comma <+> pprOp platform o2]
@@ -716,8 +718,8 @@ pprInstr platform instr = case instr of
           FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d
      in op4 fma d r1 r2 r3
 
-  VMV o1@(OpReg w _) o2 | isFloatOp o2 -> op2 (text "\tvfmv" <> dot <> text "f" <> dot <> floatWidthSuffix w) o1 o2
-  VMV o1@(OpReg w _) o2 | isFloatOp o1 -> op2 (text "\tvfmv" <> dot <> opToVInstrSuffix o1 <> dot <> floatWidthSuffix w) o1 o2
+  VMV o1@(OpReg w _) o2 | isFloatOp o1 -> op2 (text "\tvfmv" <> dot <> text "f" <> dot <> floatWidthSuffix w) o1 o2
+  VMV o1@(OpReg _w _) o2 | isFloatOp o2 -> op2 (text "\tvfmv" <> dot <> opToVInstrSuffix o1 <> dot <> text "f") o1 o2
   VMV o1 o2 -> op2 (text "\tvmv" <> dot <> opToVInstrSuffix o1 <> dot <> opToVInstrSuffix o2) o1 o2
   VID o1 o2 -> op2 (text "\tvid.v") o1 o2
   VMSEQ o1 o2 o3 -> op3 (text "\tvmseq.v.x") o1 o2 o3



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 08:31:51 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 21 Oct 2024 04:31:51 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-9.12
Message-ID: <671611772272_326e28bec441662b@gitlab.mail>



Cheng Shao pushed new branch wip/ghc-9.12 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-9.12
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 08:32:52 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 21 Oct 2024 04:32:52 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/ghc-9.12
Message-ID: <671611b44825e_326e2819edd0168c@gitlab.mail>



Cheng Shao deleted branch wip/ghc-9.12 at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 10:37:44 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Mon, 21 Oct 2024 06:37:44 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25406
Message-ID: <67162ef89741d_23de5f1bba5c10893b@gitlab.mail>



Sebastian Graf pushed new branch wip/T25406 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25406
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 10:41:01 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 06:41:01 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove [AddEpAnn] Commit 5
Message-ID: <67162fbce767c_23de5f310c401144da@gitlab.mail>



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


Commits:
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -


22 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -35,6 +35,7 @@ module GHC.Hs.Decls (
   AnnClassDecl(..),
   AnnSynDecl(..),
   AnnFamilyDecl(..),
+  AnnClsInstDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -59,7 +60,7 @@ module GHC.Hs.Decls (
   LClsInstDecl, ClsInstDecl(..),
 
   -- ** Standalone deriving declarations
-  DerivDecl(..), LDerivDecl,
+  DerivDecl(..), LDerivDecl, AnnDerivDecl,
   -- ** Deriving strategies
   DerivStrategy(..), LDerivStrategy,
   derivStrategyName, foldDerivStrategy, mapDerivStrategy,
@@ -80,7 +81,9 @@ module GHC.Hs.Decls (
   CImportSpec(..),
   -- ** Data-constructor declarations
   ConDecl(..), LConDecl,
-  HsConDeclH98Details, HsConDeclGADTDetails(..), hsConDeclTheta,
+  HsConDeclH98Details, HsConDeclGADTDetails(..),
+  AnnConDeclH98(..), AnnConDeclGADT(..),
+  hsConDeclTheta,
   getConNames, getRecConArgs_maybe,
   -- ** Document comments
   DocDecl(..), LDocDecl, docDeclDoc,
@@ -705,7 +708,7 @@ instance OutputableBndrId p
 type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
-type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
+type instance XCHsDerivingClause    (GhcPass _) = EpToken "deriving"
 type instance XXHsDerivingClause    (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -741,7 +744,7 @@ instance OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) where
   ppr (DctSingle _ ty) = ppr ty
   ppr (DctMulti _ tys) = parens (interpp'SP tys)
 
-type instance XStandaloneKindSig GhcPs = [AddEpAnn]
+type instance XStandaloneKindSig GhcPs = (EpToken "type", TokDcolon)
 type instance XStandaloneKindSig GhcRn = NoExtField
 type instance XStandaloneKindSig GhcTc = NoExtField
 
@@ -750,11 +753,11 @@ type instance XXStandaloneKindSig (GhcPass p) = DataConCantHappen
 standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
 standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname
 
-type instance XConDeclGADT GhcPs = (EpUniToken "::" "∷", [AddEpAnn])
+type instance XConDeclGADT GhcPs = AnnConDeclGADT
 type instance XConDeclGADT GhcRn = NoExtField
 type instance XConDeclGADT GhcTc = NoExtField
 
-type instance XConDeclH98  GhcPs = [AddEpAnn]
+type instance XConDeclH98  GhcPs = AnnConDeclH98
 type instance XConDeclH98  GhcRn = NoExtField
 type instance XConDeclH98  GhcTc = NoExtField
 
@@ -768,6 +771,26 @@ type instance XRecConGADT          GhcTc = NoExtField
 
 type instance XXConDeclGADTDetails (GhcPass _) = DataConCantHappen
 
+data AnnConDeclH98
+  = AnnConDeclH98 {
+    acdh_forall  :: TokForall,
+    acdh_dot :: EpToken ".",
+    acdh_darrow :: TokDarrow
+  } deriving Data
+
+instance NoAnn AnnConDeclH98 where
+  noAnn = AnnConDeclH98 noAnn noAnn noAnn
+
+data AnnConDeclGADT
+  = AnnConDeclGADT {
+    acdg_openp  :: [EpToken "("],
+    acdg_closep :: [EpToken ")"],
+    acdg_dcolon :: TokDcolon
+  } deriving Data
+
+instance NoAnn AnnConDeclGADT where
+  noAnn = AnnConDeclGADT noAnn noAnn noAnn
+
 -- Codomain could be 'NonEmpty', but at the moment all users need a list.
 getConNames :: ConDecl GhcRn -> [LocatedN Name]
 getConNames ConDeclH98  {con_name  = name}  = [name]
@@ -901,7 +924,7 @@ type instance XCClsInstDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                              -- The warning of the deprecated instance
                                              -- See Note [Implementation of deprecated instances]
                                              -- in GHC.Tc.Solver.Dict
-                                       , [AddEpAnn]
+                                       , AnnClsInstDecl
                                        , AnnSortKey DeclTag) -- For sorting the additional annotations
                                         -- TODO:AZ:tidy up
 type instance XCClsInstDecl    GhcRn = Maybe (LWarningTxt GhcRn)
@@ -924,6 +947,18 @@ type instance XTyFamInstD   GhcTc = NoExtField
 
 type instance XXInstDecl    (GhcPass _) = DataConCantHappen
 
+data AnnClsInstDecl
+  = AnnClsInstDecl {
+    acid_instance :: EpToken "instance",
+    acid_where    :: EpToken "where",
+    acid_openc    :: EpToken "{",
+    acid_semis    :: [EpToken ";"],
+    acid_closec   :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnClsInstDecl where
+  noAnn = AnnClsInstDecl noAnn noAnn noAnn noAnn noAnn
+
 cidDeprecation :: forall p. IsPass p
                => ClsInstDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1086,15 +1121,17 @@ type instance XCDerivDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
+                                     , AnnDerivDecl )
 type instance XCDerivDecl    GhcRn = ( Maybe (LWarningTxt GhcRn)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
-type instance XCDerivDecl    GhcTc = [AddEpAnn]
+                                     , AnnDerivDecl )
+type instance XCDerivDecl    GhcTc = AnnDerivDecl
 type instance XXDerivDecl    (GhcPass _) = DataConCantHappen
 
+type AnnDerivDecl = (EpToken "deriving", EpToken "instance")
+
 derivDeprecation :: forall p. IsPass p
                => DerivDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1128,15 +1165,15 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XStockStrategy    GhcPs = [AddEpAnn]
+type instance XStockStrategy    GhcPs = EpToken "stock"
 type instance XStockStrategy    GhcRn = NoExtField
 type instance XStockStrategy    GhcTc = NoExtField
 
-type instance XAnyClassStrategy GhcPs = [AddEpAnn]
+type instance XAnyClassStrategy GhcPs = EpToken "anyclass"
 type instance XAnyClassStrategy GhcRn = NoExtField
 type instance XAnyClassStrategy GhcTc = NoExtField
 
-type instance XNewtypeStrategy  GhcPs = [AddEpAnn]
+type instance XNewtypeStrategy  GhcPs = EpToken "newtype"
 type instance XNewtypeStrategy  GhcRn = NoExtField
 type instance XNewtypeStrategy  GhcTc = NoExtField
 
@@ -1144,7 +1181,7 @@ type instance XViaStrategy GhcPs = XViaStrategyPs
 type instance XViaStrategy GhcRn = LHsSigType GhcRn
 type instance XViaStrategy GhcTc = Type
 
-data XViaStrategyPs = XViaStrategyPs [AddEpAnn] (LHsSigType GhcPs)
+data XViaStrategyPs = XViaStrategyPs (EpToken "via") (LHsSigType GhcPs)
 
 instance OutputableBndrId p
         => Outputable (DerivStrategy (GhcPass p)) where
@@ -1202,11 +1239,11 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XForeignImport   GhcPs = [AddEpAnn]
+type instance XForeignImport   GhcPs = (EpToken "foreign", EpToken "import", TokDcolon)
 type instance XForeignImport   GhcRn = NoExtField
 type instance XForeignImport   GhcTc = Coercion
 
-type instance XForeignExport   GhcPs = [AddEpAnn]
+type instance XForeignExport   GhcPs = (EpToken "foreign", EpToken "export", TokDcolon)
 type instance XForeignExport   GhcRn = NoExtField
 type instance XForeignExport   GhcTc = Coercion
 
@@ -1218,6 +1255,7 @@ type instance XXForeignImport  (GhcPass _) = DataConCantHappen
 type instance XCExport (GhcPass _) = LocatedE SourceText -- original source text for the C entity
 type instance XXForeignExport  (GhcPass _) = DataConCantHappen
 
+
 -- pretty printing of foreign declarations
 
 instance OutputableBndrId p
@@ -1362,7 +1400,7 @@ type instance XWarnings      GhcTc = SourceText
 
 type instance XXWarnDecls    (GhcPass _) = DataConCantHappen
 
-type instance XWarning      (GhcPass _) = (NamespaceSpecifier, [AddEpAnn])
+type instance XWarning      (GhcPass _) = (NamespaceSpecifier, (EpToken "[", EpToken "]"))
 type instance XXWarnDecl    (GhcPass _) = DataConCantHappen
 
 
@@ -1418,7 +1456,7 @@ pprAnnProvenance (TypeAnnProvenance (L _ name))
 ************************************************************************
 -}
 
-type instance XCRoleAnnotDecl GhcPs = [AddEpAnn]
+type instance XCRoleAnnotDecl GhcPs = (EpToken "type", EpToken "role")
 type instance XCRoleAnnotDecl GhcRn = NoExtField
 type instance XCRoleAnnotDecl GhcTc = NoExtField
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -81,6 +81,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annSynDecl
               `extQ` annDataDefn
               `extQ` annFamilyDecl
+              `extQ` annClsInstDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -262,6 +263,15 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                  showAstData' g, showAstData' h, showAstData' i,
                                  showAstData' j, showAstData' k, showAstData' l]
 
+            annClsInstDecl :: AnnClsInstDecl -> SDoc
+            annClsInstDecl (AnnClsInstDecl a b c d e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClsInstDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e]
+
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -294,7 +304,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenInstance :: EpToken "instance" -> SDoc
             epTokenInstance = epToken'
 
-            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall :: TokForall -> SDoc
             epTokenForall = epUniToken'
 
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -163,15 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type instance XHsForAllVis   (GhcPass _) = EpAnn (TokForall, EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type instance XHsForAllInvis (GhcPass _) = EpAnn (TokForall, EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
-type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type EpAnnForallVis   = EpAnn (TokForall, TokRarrow)
+type EpAnnForallInvis = EpAnn (TokForall, EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -461,7 +461,7 @@ type instance XListTy          (GhcPass _) = AnnParen
 type instance XTupleTy         (GhcPass _) = AnnParen
 type instance XSumTy           (GhcPass _) = AnnParen
 type instance XOpTy            (GhcPass _) = NoExtField
-type instance XParTy           (GhcPass _) = AnnParen
+type instance XParTy           (GhcPass _) = (EpToken "(", EpToken ")")
 type instance XIParamTy        (GhcPass _) = TokDcolon
 type instance XStarTy          (GhcPass _) = NoExtField
 type instance XKindSig         (GhcPass _) = TokDcolon
@@ -572,7 +572,7 @@ pprHsArrow (HsUnrestrictedArrow _) = pprArrowWithMultiplicity visArgTypeLike (Le
 pprHsArrow (HsLinearArrow _)       = pprArrowWithMultiplicity visArgTypeLike (Left True)
 pprHsArrow (HsExplicitMult _ p)    = pprArrowWithMultiplicity visArgTypeLike (Right (ppr p))
 
-type instance XConDeclField  (GhcPass _) = [AddEpAnn]
+type instance XConDeclField  (GhcPass _) = TokDcolon
 type instance XXConDeclField (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -710,23 +710,22 @@ mkHsAppKindTy at ty k = addCLocA ty k (HsAppKindTy at ty k)
 -- It returns API Annotations for any parens removed
 splitHsFunType ::
      LHsType (GhcPass p)
-  -> ( [AddEpAnn], EpAnnComments -- The locations of any parens and
+  -> ( ([EpToken "("], [EpToken ")"]) , EpAnnComments -- The locations of any parens and
                                   -- comments discarded
      , [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p))
 splitHsFunType ty = go ty
   where
-    go (L l (HsParTy an ty))
+    go (L l (HsParTy (op,cp) ty))
       = let
-          (anns, cs, args, res) = splitHsFunType ty
-          anns' = anns ++ annParen2AddEpAnn an
+          ((ops, cps), cs, args, res) = splitHsFunType ty
           cs' = cs S.<> epAnnComments l
-        in (anns', cs', args, res)
+        in ((ops++[op], cps ++ [cp]), cs', args, res)
 
     go (L ll (HsFunTy _ mult x y))
       | (anns, csy, args, res) <- splitHsFunType y
       = (anns, csy S.<> epAnnComments ll, HsScaled mult x:args, res)
 
-    go other = ([], emptyComments, [], other)
+    go other = (noAnn, emptyComments, [], other)
 
 -- | Retrieve the name of the \"head\" of a nested type application.
 -- This is somewhat like @GHC.Tc.Gen.HsType.splitHsAppTys@, but a little more


=====================================
compiler/GHC/JS/Ppr.hs
=====================================
@@ -33,7 +33,7 @@
 -- * Design
 --
 --     This module follows the architecture and style of the other backends in
---     GHC: it intances Outputable for the relevant types, creates a class that
+--     GHC: it instances Outputable for the relevant types, creates a class that
 --     describes a morphism from the IR domain to JavaScript concrete Syntax and
 --     then generates that syntax on a case by case basis.
 --


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1274,7 +1274,7 @@ topdecl :: { LHsDecl GhcPs }
         | stand_alone_deriving                  { L (getLoc $1) (DerivD noExtField (unLoc $1)) }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
-        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
+        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((unLoc $2) (epTok $1))) }
         | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
         | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
         | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
@@ -1366,7 +1366,7 @@ ty_decl :: { LTyClDecl GhcPs }
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
   : 'type' sks_vars '::' sigktype
       {% mkStandaloneKindSig (comb2 $1 $4) (L (gl $2) $ unLoc $2) $4
-               [mj AnnType $1,mu AnnDcolon $3]}
+               (epTok $1,epUniTok $3)}
 
 -- See also: sig_vars
 sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
@@ -1380,7 +1380,8 @@ sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
 inst_decl :: { LInstDecl GhcPs }
         : 'instance' maybe_warning_pragma overlap_pragma inst_type where_inst
        {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (snd $ unLoc $5)
-             ; let anns = (mj AnnInstance $1 : (fst $ unLoc $5))
+             ; let (twhere, (openc, closec, semis)) = fst $ unLoc $5
+             ; let anns = AnnClsInstDecl (epTok $1) twhere openc semis closec
              ; let cid = ClsInstDecl
                                   { cid_ext = ($2, anns, NoAnnSortKey)
                                   , cid_poly_ty = $4, cid_binds = binds
@@ -1421,27 +1422,27 @@ inst_decl :: { LInstDecl GhcPs }
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPPING'     '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlapping (getOVERLAPPING_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPS'        '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlaps (getOVERLAPS_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# INCOHERENT'      '#-}' {% fmap Just $ amsr (sLL $1 $> (Incoherent (getINCOHERENT_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | {- empty -}                 { Nothing }
 
 deriv_strategy_no_via :: { LDerivStrategy GhcPs }
-  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
 
 deriv_strategy_via :: { LDerivStrategy GhcPs }
-  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs [mj AnnVia $1] $2))) }
+  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs (epTok $1) $2))) }
 
 deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) }
-  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
   | deriv_strategy_via          { Just $1 }
   | {- empty -}                 { Nothing }
 
@@ -1659,11 +1660,11 @@ capi_ctype :: { Maybe (LocatedP CType) }
 capi_ctype : '{-# CTYPE' STRING STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) (Just (Header (getSTRINGs $2) (getSTRING $2)))
                                         (getSTRINGs $3,getSTRING $3)))
-                              (AnnPragma (mo $1) (mc $4) [mj AnnHeader $2,mj AnnVal $3]) }
+                              (AnnPragma (glR $1) (glR $4) noAnn (glR $2) (glR $3) noAnn noAnn) }
 
            | '{-# CTYPE'        STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) Nothing (getSTRINGs $2, getSTRING $2)))
-                              (AnnPragma (mo $1) (mc $3) [mj AnnVal $2]) }
+                              (AnnPragma (glR $1) (glR $3) noAnn noAnn (glR $2) noAnn noAnn) }
 
            |           { Nothing }
 
@@ -1676,7 +1677,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
                 {% do { let { err = text "in the stand-alone deriving instance"
                                     <> colon <+> quotes (ppr $6) }
                       ; amsA' (sLL $1 $>
-                                 (DerivDecl ($4, [mj AnnDeriving $1, mj AnnInstance $3]) (mkHsWildCardBndrs $6) $2 $5)) }}
+                                 (DerivDecl ($4, (epTok $1, epTok $3)) (mkHsWildCardBndrs $6) $2 $5)) }}
 
 -----------------------------------------------------------------------------
 -- Role annotations
@@ -1684,7 +1685,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
 role_annot :: { LRoleAnnotDecl GhcPs }
 role_annot : 'type' 'role' oqtycon maybe_roles
           {% mkRoleAnnotDecl (comb3 $1 $4 $3) $3 (reverse (unLoc $4))
-                   [mj AnnType $1,mj AnnRole $2] }
+                   (epTok $1,epTok $2) }
 
 -- Reversed!
 maybe_roles :: { Located [Located (Maybe FastString)] }
@@ -1816,9 +1817,9 @@ decl_inst  :: { Located (OrdList (LHsDecl GhcPs)) }
 decl_inst  : at_decl_inst               { sL1 $1 (unitOL (sL1a $1 (InstD noExtField (unLoc $1)))) }
            | decl                       { sL1 $1 (unitOL $1) }
 
-decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
+decls_inst :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }   -- Reversed
            : decls_inst ';' decl_inst   {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unLoc $3))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1826,7 +1827,7 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
                                                   return (sLL $1 $> (fst $ unLoc $1
                                                                  , snocOL hs t' `appOL` unLoc $3)) }
            | decls_inst ';'             {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1837,20 +1838,20 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
            | {- empty -}                { noLoc ([],nilOL) }
 
 decllist_inst
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", EpToken "}", [EpToken ";"])
                      , OrdList (LHsDecl GhcPs)) }      -- Reversed
-        : '{'         decls_inst '}'    { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2),snd $ unLoc $2) }
-        |     vocurly decls_inst close  { L (gl $2) (unLoc $2) }
+        : '{'         decls_inst '}'    { sLL $1 $> ((epTok $1,epTok $3,fst $ unLoc $2),snd $ unLoc $2) }
+        |     vocurly decls_inst close  { L (gl $2) ((noAnn,noAnn,fst $ unLoc $2),snd $ unLoc $2) }
 
 -- Instance body
 --
-where_inst :: { Located ([AddEpAnn]
+where_inst :: { Located ((EpToken "where", (EpToken "{", EpToken "}", [EpToken ";"]))
                         , OrdList (LHsDecl GhcPs)) }   -- Reversed
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_inst         { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
-                                             ,(snd $ unLoc $2)) }
-        | {- empty -}                   { noLoc ([],nilOL) }
+        : 'where' decllist_inst         { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
+                                             ,snd $ unLoc $2) }
+        | {- empty -}                   { noLoc (noAnn,nilOL) }
 
 -- Declarations in binding groups other than classes and instances
 --
@@ -2019,10 +2020,10 @@ to varid (used for rule_vars), 'checkRuleTyVarBndrNames' must be updated.
 maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) }
         : '{-# DEPRECATED' strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ DeprecatedTxt (getDEPRECATED_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $2))
-                                (AnnPragma (mo $1) (mc $3) (fst $ unLoc $2)) }
+                                (AnnPragma (glR $1) (glR $3) (fst $ unLoc $2) noAnn noAnn noAnn noAnn) }
         | '{-# WARNING' warning_category strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ WarningTxt $2 (getWARNING_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $3))
-                                (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))}
+                                (AnnPragma (glR $1) (glR $4) (fst $ unLoc $3) noAnn noAnn noAnn noAnn)}
         |  {- empty -}      { Nothing }
 
 warning_category :: { Maybe (LocatedE InWarningCategory) }
@@ -2081,9 +2082,9 @@ deprecation :: { OrdList (LWarnDecl GhcPs) }
              {% fmap unitOL $ amsA' (sL (comb3 $1 $2 $>) $ (Warning (unLoc $1, fst $ unLoc $3) (unLoc $2)
                                           (DeprecatedTxt NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $3))) }
 
-strings :: { Located ([AddEpAnn],[Located StringLiteral]) }
-    : STRING { sL1 $1 ([],[L (gl $1) (getStringLiteral $1)]) }
-    | '[' stringlist ']' { sLL $1 $> $ ([mos $1,mcs $3],fromOL (unLoc $2)) }
+strings :: { Located ((EpToken "[", EpToken "]"),[Located StringLiteral]) }
+    : STRING             { sL1 $1 (noAnn,[L (gl $1) (getStringLiteral $1)]) }
+    | '[' stringlist ']' { sLL $1 $> $ ((epTok $1,epTok $3),fromOL (unLoc $2)) }
 
 stringlist :: { Located (OrdList (Located StringLiteral)) }
     : stringlist ',' STRING {% if isNilOL (unLoc $1)
@@ -2104,35 +2105,35 @@ stringlist :: { Located (OrdList (Located StringLiteral)) }
 annotation :: { LHsDecl GhcPs }
     : '{-# ANN' name_var aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $4) [],
+                                            (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn noAnn,
                                             (getANN_PRAGs $1))
                                             (ValueAnnProvenance $2) $3)) }
 
     | '{-# ANN' 'type' otycon aexp '#-}' {% runPV (unECP $4) >>= \ $4 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $5) [mj AnnType $2],
+                                            (AnnPragma (glR $1) (glR $5) noAnn noAnn noAnn (epTok $2) noAnn,
                                             (getANN_PRAGs $1))
                                             (TypeAnnProvenance $3) $4)) }
 
     | '{-# ANN' 'module' aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                                (AnnPragma (mo $1) (mc $4) [mj AnnModule $2],
+                                                (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn (epTok $2),
                                                 (getANN_PRAGs $1))
                                                  ModuleAnnProvenance $3)) }
 
 -----------------------------------------------------------------------------
 -- Foreign import and export declarations
 
-fdecl :: { Located ([AddEpAnn], [AddEpAnn] -> HsDecl GhcPs) }
+fdecl :: { Located (EpToken "foreign" -> HsDecl GhcPs) }
 fdecl : 'import' callconv safety fspec
-               {% mkImport $2 $3 (snd $ unLoc $4) >>= \i ->
-                 return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $4),i))  }
+               {% mkImport $2 $3 (snd $ unLoc $4) (epTok $1, fst $ unLoc $4) >>= \i ->
+                 return (sLL $1 $> i)  }
       | 'import' callconv        fspec
-               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3);
-                    return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $3),d)) }}
+               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3) (epTok $1, fst $ unLoc $3);
+                    return (sLL $1 $> d) }}
       | 'export' callconv fspec
-               {% mkExport $2 (snd $ unLoc $3) >>= \i ->
-                  return (sLL $1 $> (mj AnnExport $1 : (fst $ unLoc $3),i) ) }
+               {% mkExport $2 (snd $ unLoc $3) (epTok $1, fst $ unLoc $3) >>= \i ->
+                  return (sLL $1 $> i ) }
 
 callconv :: { Located CCallConv }
           : 'stdcall'                   { sLL $1 $> StdCallConv }
@@ -2146,12 +2147,12 @@ safety :: { Located Safety }
         | 'safe'                        { sLL $1 $> PlaySafe }
         | 'interruptible'               { sLL $1 $> PlayInterruptible }
 
-fspec :: { Located ([AddEpAnn]
+fspec :: { Located (TokDcolon
                     ,(Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)) }
-       : STRING var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $3]
+       : STRING var '::' sigtype        { sLL $1 $> (epUniTok $3
                                              ,(L (getLoc $1)
                                                     (getStringLiteral $1), $2, $4)) }
-       |        var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $2]
+       |        var '::' sigtype        { sLL $1 $> (epUniTok $2
                                              ,(noLoc (StringLiteral NoSourceText nilFS Nothing), $1, $3)) }
          -- if the entity string is missing, it defaults to the empty string;
          -- the meaning of an empty entity string depends on the calling
@@ -2343,7 +2344,7 @@ atype :: { LHsType GhcPs }
         | '(#' bar_types2 '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsA' (sLL $1 $> $ HsSumTy (AnnParen AnnParensHash (glR $1) (glR $3)) $2) } }
         | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (glR $1) $2 (glR $3)) }
-        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
+        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy (epTok $1, epTok $3) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                             ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
@@ -2559,22 +2560,22 @@ constr :: { LConDecl GhcPs }
         : forall context '=>' constr_stuff
                 {% amsA' (let (con,details) = unLoc $4 in
                   (L (comb4 $1 $2 $3 $4) (mkConDeclH98
-                                                       (mu AnnDarrow $3:(fst $ unLoc $1))
+                                                       (epUniTok $3,(fst $ unLoc $1))
                                                        con
                                                        (snd $ unLoc $1)
                                                        (Just $2)
                                                        details))) }
         | forall constr_stuff
                 {% amsA' (let (con,details) = unLoc $2 in
-                  (L (comb2 $1 $2) (mkConDeclH98 (fst $ unLoc $1)
+                  (L (comb2 $1 $2) (mkConDeclH98 (noAnn, fst $ unLoc $1)
                                                       con
                                                       (snd $ unLoc $1)
                                                       Nothing   -- No context
                                                       details))) }
 
-forall :: { Located ([AddEpAnn], Maybe [LHsTyVarBndr Specificity GhcPs]) }
-        : 'forall' tv_bndrs '.'       { sLL $1 $> ([mu AnnForall $1,mj AnnDot $3], Just $2) }
-        | {- empty -}                 { noLoc ([], Nothing) }
+forall :: { Located ((TokForall, EpToken "."), Maybe [LHsTyVarBndr Specificity GhcPs]) }
+        : 'forall' tv_bndrs '.'       { sLL $1 $> ((epUniTok $1,epTok $3), Just $2) }
+        | {- empty -}                 { noLoc (noAnn, Nothing) }
 
 constr_stuff :: { Located (LocatedN RdrName, HsConDeclH98Details GhcPs) }
         : infixtype       {% do { b <- runPV $1
@@ -2599,7 +2600,7 @@ fielddecl :: { LConDeclField GhcPs }
                                               -- A list because of   f,g :: Int
         : sig_vars '::' ctype
             {% amsA' (L (comb2 $1 $3)
-                      (ConDeclField [mu AnnDcolon $2]
+                      (ConDeclField (epUniTok $2)
                                     (reverse (map (\ln@(L l n)
                                                -> L (fromTrailingN l) $ FieldOcc noExtField (L (noTrailingN l) n)) (unLoc $1))) $3 Nothing))}
 
@@ -2618,15 +2619,15 @@ derivings :: { Located (HsDeriving GhcPs) }
 deriving :: { LHsDerivingClause GhcPs }
         : 'deriving' deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] Nothing $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) Nothing $2) }
 
         | 'deriving' deriv_strategy_no_via deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $2) $3) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $2) $3) }
 
         | 'deriving' deriv_clause_types deriv_strategy_via
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $3) $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $3) $2) }
 
 deriv_clause_types :: { LDerivClauseTys GhcPs }
         : qtycon              { let { tc = sL1a $1 $ mkHsImplicitSigType $
@@ -2971,12 +2972,12 @@ prag_e :: { Located (HsPragE GhcPs) }
       : '{-# SCC' STRING '#-}'      {% do { scc <- getSCC $2
                                           ; return (sLL $1 $>
                                              (HsPragSCC
-                                                (AnnPragma (mo $1) (mc $3) [mj AnnValStr $2],
+                                                (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                 (getSCC_PRAGs $1))
                                                 (StringLiteral (getSTRINGs $2) scc Nothing)))} }
       | '{-# SCC' VARID  '#-}'      { sLL $1 $>
                                              (HsPragSCC
-                                               (AnnPragma (mo $1) (mc $3) [mj AnnVal $2],
+                                               (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                (getSCC_PRAGs $1))
                                                (StringLiteral NoSourceText (getVARID $2) Nothing)) }
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon, TokRarrow,
+  TokDcolon, TokDarrow, TokRarrow, TokForall,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -410,8 +410,11 @@ getEpTokenLoc :: EpToken tok -> EpaLocation
 getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
+-- TODO:AZ: check we have all of the unicode tokens
 type TokDcolon = EpUniToken "::" "∷"
+type TokDarrow = EpUniToken "=>"  "⇒"
 type TokRarrow = EpUniToken "->" "→"
+type TokForall = EpUniToken "forall" "∀"
 
 -- | Layout information for declarations.
 data EpLayout =
@@ -813,9 +816,13 @@ data NameAdornment
 -- annotations in pragmas.
 data AnnPragma
   = AnnPragma {
-      apr_open      :: AddEpAnn,
-      apr_close     :: AddEpAnn,
-      apr_rest      :: [AddEpAnn]
+      apr_open      :: EpaLocation,
+      apr_close     :: EpaLocation,
+      apr_squares   :: (EpToken "[", EpToken "]"),
+      apr_loc1      :: EpaLocation,
+      apr_loc2      :: EpaLocation,
+      apr_type      :: EpToken "type",
+      apr_module    :: EpToken "module"
       } deriving (Data,Eq)
 
 -- ---------------------------------------------------------------------
@@ -1402,7 +1409,7 @@ instance NoAnn NameAnn where
   noAnn = NameAnnTrailing []
 
 instance NoAnn AnnPragma where
-  noAnn = AnnPragma noAnn noAnn []
+  noAnn = AnnPragma noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 instance NoAnn AnnParen where
   noAnn = AnnParen AnnParens noAnn noAnn
@@ -1496,4 +1503,6 @@ instance Outputable AnnList where
     = text "AnnList" <+> ppr a <+> ppr o <+> ppr c <+> ppr r <+> ppr t
 
 instance Outputable AnnPragma where
-  ppr (AnnPragma o c r) = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr r
+  ppr (AnnPragma o c s l ca t m)
+    = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr s <+> ppr l
+                       <+> ppr ca <+> ppr ca <+> ppr t <+> ppr m


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -283,7 +283,7 @@ mkStandaloneKindSig
   :: SrcSpan
   -> Located [LocatedN RdrName]   -- LHS
   -> LHsSigType GhcPs             -- RHS
-  -> [AddEpAnn]
+  -> (EpToken "type", TokDcolon)
   -> P (LStandaloneKindSig GhcPs)
 mkStandaloneKindSig loc lhs rhs anns =
   do { vs <- mapM check_lhs_name (unLoc lhs)
@@ -408,7 +408,7 @@ mkSpliceDecl lexpr@(L loc expr)
 mkRoleAnnotDecl :: SrcSpan
                 -> LocatedN RdrName                -- type being annotated
                 -> [Located (Maybe FastString)]    -- roles
-                -> [AddEpAnn]
+                -> (EpToken "type", EpToken "role")
                 -> P (LRoleAnnotDecl GhcPs)
 mkRoleAnnotDecl loc tycon roles anns
   = do { roles' <- mapM parse_role roles
@@ -773,12 +773,12 @@ recordPatSynErr loc pat =
     addFatalError $ mkPlainErrorMsgEnvelope loc $
       (PsErrRecordSyntaxInPatSynDecl pat)
 
-mkConDeclH98 :: [AddEpAnn] -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
+mkConDeclH98 :: (TokDarrow, (TokForall, EpToken ".")) -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
                 -> Maybe (LHsContext GhcPs) -> HsConDeclH98Details GhcPs
                 -> ConDecl GhcPs
 
-mkConDeclH98 ann name mb_forall mb_cxt args
-  = ConDeclH98 { con_ext    = ann
+mkConDeclH98 (tdarrow, (tforall,tdot)) name mb_forall mb_cxt args
+  = ConDeclH98 { con_ext    = AnnConDeclH98 tforall tdot tdarrow
                , con_name   = name
                , con_forall = isJust mb_forall
                , con_ex_tvs = mb_forall `orElse` []
@@ -795,12 +795,12 @@ mkConDeclH98 ann name mb_forall mb_cxt args
 --   Note [GADT abstract syntax] in "GHC.Hs.Decls" for more details.
 mkGadtDecl :: SrcSpan
            -> NonEmpty (LocatedN RdrName)
-           -> EpUniToken "::" "∷"
+           -> TokDcolon
            -> LHsSigType GhcPs
            -> P (LConDecl GhcPs)
 mkGadtDecl loc names dcol ty = do
 
-  (args, res_ty, annsa, csa) <-
+  (args, res_ty, (ops, cps), csa) <-
     case body_ty of
      L ll (HsFunTy _ hsArr (L (EpAnn anc _ cs) (HsRecTy an rf)) res_ty) -> do
        arr <- case hsArr of
@@ -810,10 +810,10 @@ mkGadtDecl loc names dcol ty = do
                  return noAnn
 
        return ( RecConGADT arr (L (EpAnn anc an cs) rf), res_ty
-              , [], epAnnComments ll)
+              , ([], []), epAnnComments ll)
      _ -> do
-       let (anns, cs, arg_types, res_type) = splitHsFunType body_ty
-       return (PrefixConGADT noExtField arg_types, res_type, anns, cs)
+       let ((ops, cps), cs, arg_types, res_type) = splitHsFunType body_ty
+       return (PrefixConGADT noExtField arg_types, res_type, (ops,cps), cs)
 
   let bndrs_loc = case outer_bndrs of
         HsOuterImplicit{} -> getLoc ty
@@ -822,7 +822,7 @@ mkGadtDecl loc names dcol ty = do
   let l = EpAnn (spanAsAnchor loc) noAnn csa
 
   pure $ L l ConDeclGADT
-                     { con_g_ext  = (dcol, annsa)
+                     { con_g_ext  = AnnConDeclGADT ops cps dcol
                      , con_names  = names
                      , con_bndrs  = L bndrs_loc outer_bndrs
                      , con_mb_cxt = mcxt
@@ -1079,9 +1079,7 @@ checkTyClHdr is_cls ty
       | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
-    go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
-      where
-        (o,c) = mkParensEpToks (realSrcSpan (locA l))
+    go cs l (HsParTy (o,c) ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
@@ -1098,12 +1096,12 @@ checkTyClHdr is_cls ty
 
     -- Combine the annotations from the HsParTy and HsStarTy into a
     -- new one for the LocatedN RdrName
-    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> AnnParen -> SrcSpanAnnN
-    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (AnnParen _ o c) =
+    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> (EpToken "(", EpToken ")") -> SrcSpanAnnN
+    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (o,c) =
       let
         lr = combineSrcSpans (locA l1) (locA l)
       in
-        EpAnn (EpaSpan lr) (NameAnn NameParens o ap c ta) (csp0 Semi.<> csp)
+        EpAnn (EpaSpan lr) (NameAnn NameParens (getEpTokenLoc o) ap (getEpTokenLoc c) ta) (csp0 Semi.<> csp)
 
 -- | Yield a parse error if we have a function applied directly to a do block
 -- etc. and BlockArguments is not enabled.
@@ -1171,9 +1169,9 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
             EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
             _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
-  check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
-                                  -- to be sure HsParTy doesn't get into the way
-    = check (ap_open ann':opi, ap_close ann':cpi, csi) ty
+  check (opi,cpi,csi) (L _lp1 (HsParTy (o,c) ty))
+                                             -- to be sure HsParTy doesn't get into the way
+    = check (getEpTokenLoc o:opi, getEpTokenLoc c:cpi, csi) ty
 
   -- No need for anns, returning original
   check (_opi,_cpi,_csi) _t = unprocessed
@@ -3023,8 +3021,9 @@ checkNewOrData span name is_type_data = curry $ \ case
 mkImport :: Located CCallConv
          -> Located Safety
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
+         -> (EpToken "import", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) (timport, td) =
     case unLoc cconv of
       CCallConv          -> returnSpec =<< mkCImport
       CApiConv           -> do
@@ -3060,8 +3059,8 @@ mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
         funcTarget = CFunction (StaticTarget esrc entity' Nothing True)
         importSpec = CImport (L (l2l loc) esrc) (reLoc cconv) (reLoc safety) Nothing funcTarget
 
-    returnSpec spec = return $ \ann -> ForD noExtField $ ForeignImport
-          { fd_i_ext  = ann
+    returnSpec spec = return $ \tforeign -> ForD noExtField $ ForeignImport
+          { fd_i_ext  = (tforeign, timport, td)
           , fd_name   = v
           , fd_sig_ty = ty
           , fd_fi     = spec
@@ -3133,10 +3132,11 @@ parseCImport cconv safety nm str sourceText =
 --
 mkExport :: Located CCallConv
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty)
- = return $ \ann -> ForD noExtField $
-   ForeignExport { fd_e_ext = ann, fd_name = v, fd_sig_ty = ty
+         -> ( EpToken "export", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty) (texport, td)
+ = return $ \tforeign -> ForD noExtField $
+   ForeignExport { fd_e_ext = (tforeign, texport, td), fd_name = v, fd_sig_ty = ty
                  , fd_fe = CExport (L (l2l le) esrc) (L (l2l lc) (CExportStatic esrc entity' cconv)) }
   where
     entity' | nullFS entity = mkExtName (unLoc v)


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -142,7 +142,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:5:36-49 })
@@ -190,7 +193,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:7:36-48 })
@@ -218,10 +224,11 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaSpan { Test20239.hs:7:50 })
-                   (EpaSpan { Test20239.hs:7:86 }))
+                  ((,)
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:50 }))
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:86 })))
                   (L
                    (EpAnn
                     (EpaSpan { Test20239.hs:7:51-85 })
@@ -290,10 +297,11 @@
                         (EpaComments
                          []))
                        (HsParTy
-                        (AnnParen
-                         AnnParens
-                         (EpaSpan { Test20239.hs:7:68 })
-                         (EpaSpan { Test20239.hs:7:85 }))
+                        ((,)
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:68 }))
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:85 })))
                         (L
                          (EpAnn
                           (EpaSpan { Test20239.hs:7:69-84 })


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -972,8 +972,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:23:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:23:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:23:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:23:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1110,11 +1115,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:25:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1348,8 +1354,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:29:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:29:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:29:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:29:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1486,11 +1497,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:31:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1724,8 +1736,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:35:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:35:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:35:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:35:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1862,11 +1879,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:37:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2100,8 +2118,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:41:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:41:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:41:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:41:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2238,11 +2261,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:43:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2476,8 +2500,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:47:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:47:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:47:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:47:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2614,11 +2643,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:49:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2852,8 +2882,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:53:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:53:18-22 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:53:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:53:18-22 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2990,11 +3025,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:55:11-12 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -101,11 +101,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T17544_kw.hs:16:15-16 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -214,11 +215,12 @@
           (EpaComments
            []))
          (ConDeclGADT
-          ((,)
+          (AnnConDeclGADT
+           []
+           []
            (EpUniTok
             (EpaSpan { T17544_kw.hs:19:15-16 })
-            (NormalSyntax))
-           [])
+            (NormalSyntax)))
           (:|
            (L
             (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -90,7 +90,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:5:5-8 })
@@ -151,7 +154,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:7:5-8 })
@@ -211,7 +217,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:9:9-10 })
@@ -339,7 +348,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:12:7-8 })
@@ -467,7 +479,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:16:3-4 })
@@ -637,7 +652,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:23:3-4 })
@@ -807,7 +825,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:28:3-8 })
@@ -844,7 +865,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:28:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:28:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:28:12-13 })
@@ -903,7 +926,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:29:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:29:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:29:12-13 })
@@ -1008,7 +1033,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:32:3-8 })
@@ -1045,7 +1073,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:33:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:33:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:33:7-8 })
@@ -1104,7 +1134,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:34:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:34:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:34:7-8 })
@@ -1221,7 +1253,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:38:3-8 })
@@ -1258,7 +1293,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:40:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:40:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:40:5-6 })
@@ -1317,7 +1354,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:42:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:42:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:42:5-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -125,7 +125,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:14-17 })
@@ -150,7 +153,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:21-24 })
@@ -201,8 +207,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:9:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:9:13-14 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:9:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:9:13-14 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:9:6-11 })
@@ -352,10 +362,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:10 })
-                 (EpaSpan { DumpParsedAst.hs:11:17 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:17 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:11-16 })
@@ -450,10 +461,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:26 })
-                 (EpaSpan { DumpParsedAst.hs:11:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:26 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:27-35 })
@@ -794,7 +806,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:15:21-23 })
@@ -822,10 +837,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:15:25 })
-                 (EpaSpan { DumpParsedAst.hs:15:29 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:25 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:29 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:15:26-28 })
@@ -885,8 +901,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:17:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:17:9-10 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:17:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:17:9-10 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:17:6-7 })
@@ -960,10 +980,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:17:17 })
-               (EpaSpan { DumpParsedAst.hs:17:27 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:17 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:27 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:17:18-26 })
@@ -1604,10 +1625,11 @@
             (EpaComments
              []))
            (HsParTy
-            (AnnParen
-             AnnParens
-             (EpaSpan { DumpParsedAst.hs:22:22 })
-             (EpaSpan { DumpParsedAst.hs:22:37 }))
+            ((,)
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:22 }))
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:37 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:22:23-36 })
@@ -1731,10 +1753,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:22:42 })
-               (EpaSpan { DumpParsedAst.hs:22:52 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:42 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:52 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:22:43-51 })
@@ -1814,11 +1837,12 @@
             (EpaComments
              []))
            (ConDeclGADT
-            ((,)
+            (AnnConDeclGADT
+             []
+             []
              (EpUniTok
               (EpaSpan { DumpParsedAst.hs:23:7-8 })
-              (NormalSyntax))
-             [])
+              (NormalSyntax)))
             (:|
              (L
               (EpAnn
@@ -1855,10 +1879,11 @@
                  (EpaComments
                   []))
                 (HsParTy
-                 (AnnParen
-                  AnnParens
-                  (EpaSpan { DumpParsedAst.hs:23:10 })
-                  (EpaSpan { DumpParsedAst.hs:23:34 }))
+                 ((,)
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:10 }))
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:34 })))
                  (L
                   (EpAnn
                    (EpaSpan { DumpParsedAst.hs:23:11-33 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -304,10 +304,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:11-16 })
@@ -398,10 +397,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:27-35 })
@@ -850,10 +848,9 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaDelta {  } (SameLine 0) [])
-               (EpaDelta {  } (SameLine 0) []))
+              ((,)
+               (NoEpTok)
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:19:23-36 })
@@ -966,10 +963,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:19:43-51 })
@@ -1079,10 +1075,9 @@
                    (EpaComments
                     []))
                   (HsParTy
-                   (AnnParen
-                    AnnParens
-                    (EpaDelta {  } (SameLine 0) [])
-                    (EpaDelta {  } (SameLine 0) []))
+                   ((,)
+                    (NoEpTok)
+                    (NoEpTok))
                    (L
                     (EpAnn
                      (EpaSpan { DumpRenamedAst.hs:20:11-33 })
@@ -1452,10 +1447,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:22:26-28 })
@@ -1955,10 +1949,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:24:18-26 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -831,10 +831,11 @@
              (EpaComments
               []))
             (HsParTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { KindSigs.hs:22:8 })
-              (EpaSpan { KindSigs.hs:22:20 }))
+             ((,)
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:8 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:20 })))
              (L
               (EpAnn
                (EpaSpan { KindSigs.hs:22:9-19 })
@@ -924,10 +925,11 @@
                (EpaComments
                 []))
               (HsParTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { KindSigs.hs:22:33 })
-                (EpaSpan { KindSigs.hs:22:44 }))
+               ((,)
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:33 }))
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:44 })))
                (L
                 (EpAnn
                  (EpaSpan { KindSigs.hs:22:34-43 })
@@ -1643,10 +1645,11 @@
            (EpaComments
             []))
           (HsParTy
-           (AnnParen
-            AnnParens
-            (EpaSpan { KindSigs.hs:34:9 })
-            (EpaSpan { KindSigs.hs:34:22 }))
+           ((,)
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:9 }))
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:22 })))
            (L
             (EpAnn
              (EpaSpan { KindSigs.hs:34:10-21 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -167,7 +167,7 @@
                   (EpaComments
                    []))
                  (ConDeclField
-                  []
+                  (NoEpUniTok)
                   [(L
                     (EpAnn
                      (EpaSpan { T14189.hs:6:33 })


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -116,11 +116,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T15323.hs:6:17-18 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -196,10 +197,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { T15323.hs:6:31 })
-                 (EpaSpan { T15323.hs:6:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:31 }))
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { T15323.hs:6:32-35 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -137,7 +137,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:5:26-31 })
@@ -257,7 +260,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:6:26-31 })


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -89,11 +89,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T18791.hs:5:7-8 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -57,7 +57,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:4:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:4:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -449,8 +454,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:14:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.hs:14:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:14:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.hs:14:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -717,7 +727,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:3:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:3:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1036,8 +1051,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:5:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.ppr.hs:5:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:5:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.ppr.hs:5:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -63,7 +63,6 @@ import Data.Data ( Data )
 import Data.Dynamic
 import Data.Foldable
 import Data.Functor.Const
-import qualified Data.Set as Set
 import Data.Typeable
 import Data.List ( partition, sort, sortBy)
 import qualified Data.List.NonEmpty as NE
@@ -363,11 +362,11 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+instance HasTrailing (TokForall, EpUniToken "->" "→") where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+instance HasTrailing (TokForall, EpToken ".") where
   trailing _ = []
   setTrailing a _ = a
 
@@ -646,23 +645,6 @@ flushComments !trailing_anns = do
 
 -- ---------------------------------------------------------------------
 
--- |In order to interleave annotations into the stream, we turn them into
--- comments. They are removed from the annotation to avoid duplication.
-annotationsToComments :: (Monad m, Monoid w)
-  => a -> Lens a [AddEpAnn] -> [AnnKeywordId] -> EP w m a
-annotationsToComments a l kws = do
-  let (newComments, newAnns) = go ([],[]) (view l a)
-  addComments True newComments
-  return (set l (reverse newAnns) a)
-  where
-    keywords = Set.fromList kws
-
-    go :: ([Comment], [AddEpAnn]) -> [AddEpAnn] -> ([Comment], [AddEpAnn])
-    go acc [] = acc
-    go (cs',ans) ((AddEpAnn k ss) : ls)
-      | Set.member k keywords = go ((mkKWComment k (epaToNoCommentsLocation ss)):cs', ans) ls
-      | otherwise             = go (cs', (AddEpAnn k ss):ans)    ls
-
 epTokensToComments :: (Monad m, Monoid w)
   => AnnKeywordId -> [EpToken tok] -> EP w m ()
 epTokensToComments kw toks
@@ -825,10 +807,6 @@ markLensAA' a l = do
 
 -- -------------------------------------
 
-markEpAnnLMS :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS epann l kw ms = markEpAnnLMS'' epann (lepa . l) kw ms
-
 markEpAnnLMS'' :: (Monad m, Monoid w)
   => a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m a
 markEpAnnLMS'' an l kw Nothing = markEpAnnL an l kw
@@ -843,26 +821,6 @@ markEpAnnLMS'' a l kw (Just str) = do
           return (AddEpAnn kw' r')
       | otherwise = return (AddEpAnn kw' r)
 
--- -------------------------------------
-
-markEpAnnLMS' :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
-
-markEpAnnLMS0 :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m a
-markEpAnnLMS0 an l _kw Nothing = markLensKwA an l
-markEpAnnLMS0 a l kw (Just str) = do
-  anns <- go (view l a)
-  return (set l anns a)
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
 -- ---------------------------------------------------------------------
 
 -- markEpTokenM :: forall m w tok . (Monad m, Monoid w, KnownSymbol tok)
@@ -912,19 +870,8 @@ markArrow (HsExplicitMult (pct, arr) t) = do
 
 -- ---------------------------------------------------------------------
 
-markAnnCloseP :: (Monad m, Monoid w) => EpAnn AnnPragma -> EP w m (EpAnn AnnPragma)
-markAnnCloseP an = markEpAnnLMS' an lapr_close AnnClose (Just "#-}")
-
-markAnnCloseP' :: (Monad m, Monoid w) => AnnPragma -> EP w m AnnPragma
-markAnnCloseP' an = markEpAnnLMS0 an lapr_close AnnClose (Just "#-}")
-
-markAnnOpenP :: (Monad m, Monoid w) => EpAnn AnnPragma -> SourceText -> String -> EP w m (EpAnn AnnPragma)
-markAnnOpenP an NoSourceText txt   = markEpAnnLMS' an lapr_open AnnOpen (Just txt)
-markAnnOpenP an (SourceText txt) _ = markEpAnnLMS' an lapr_open AnnOpen (Just $ unpackFS txt)
-
-markAnnOpenP' :: (Monad m, Monoid w) => AnnPragma -> SourceText -> String -> EP w m AnnPragma
-markAnnOpenP' an NoSourceText txt   = markEpAnnLMS0 an lapr_open AnnOpen (Just txt)
-markAnnOpenP' an (SourceText txt) _ = markEpAnnLMS0 an lapr_open AnnOpen (Just $ unpackFS txt)
+markAnnCloseP'' :: (Monad m, Monoid w) => EpaLocation -> EP w m EpaLocation
+markAnnCloseP'' l = printStringAtAA l "#-}"
 
 markAnnOpen' :: (Monad m, Monoid w)
   => Maybe EpaLocation -> SourceText -> String -> EP w m (Maybe EpaLocation)
@@ -1089,18 +1036,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lapr_rest :: Lens AnnPragma [AddEpAnn]
-lapr_rest k parent = fmap (\newAnns -> parent { apr_rest = newAnns })
-                          (k (apr_rest parent))
-
-lapr_open :: Lens AnnPragma AddEpAnn
-lapr_open k parent = fmap (\new -> parent { apr_open = new })
-                          (k (apr_open parent))
-
-lapr_close :: Lens AnnPragma AddEpAnn
-lapr_close k parent = fmap (\new -> parent { apr_close = new })
-                          (k (apr_close parent))
-
 lidl :: Lens [AddEpAnn] [AddEpAnn]
 lidl k parent = fmap (\new -> new)
                      (k parent)
@@ -1340,12 +1275,6 @@ lepl_case k parent = fmap (\new -> parent { epl_case = new })
 -- End of lenses
 -- ---------------------------------------------------------------------
 
-markLensKwA :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> EP w m a
-markLensKwA a l = do
-  loc <- markKw (view l a)
-  return (set l loc a)
-
 markLensKw' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a EpaLocation -> AnnKeywordId -> EP w m (EpAnn a)
 markLensKw' (EpAnn anc a cs) l kw = do
@@ -1785,22 +1714,22 @@ instance ExactPrint (LocatedP (WarningTxt GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (WarningTxt mb_cat src ws)) = do
-    an0 <- markAnnOpenP an src "{-# WARNING"
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (WarningTxt mb_cat src ws)) = do
+    o' <- markAnnOpen'' o src "{-# WARNING"
     mb_cat' <- markAnnotated mb_cat
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (WarningTxt mb_cat' src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (WarningTxt mb_cat' src ws'))
 
-  exact (L an (DeprecatedTxt src ws)) = do
-    an0 <- markAnnOpenP an src "{-# DEPRECATED"
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (DeprecatedTxt src ws)) = do
+    o' <- markAnnOpen'' o src "{-# DEPRECATED"
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (DeprecatedTxt src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (DeprecatedTxt src ws'))
 
 instance ExactPrint InWarningCategory where
   getAnnotationEntry _ = NoEntryVal
@@ -2057,14 +1986,14 @@ instance ExactPrint (DerivDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DerivDecl (mw, an) typ ms mov) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+  exact (DerivDecl (mw, (td,ti)) typ ms mov) = do
+    td' <- markEpToken td
     ms' <- mapM markAnnotated ms
-    an1 <- markEpAnnL an0 lidl AnnInstance
+    ti' <- markEpToken ti
     mw' <- mapM markAnnotated mw
     mov' <- mapM markAnnotated mov
     typ' <- markAnnotated typ
-    return (DerivDecl (mw', an1) typ' ms' mov')
+    return (DerivDecl (mw', (td',ti')) typ' ms' mov')
 
 -- ---------------------------------------------------------------------
 
@@ -2072,25 +2001,25 @@ instance ExactPrint (ForeignDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ForeignImport an n ty fimport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnImport
+  exact (ForeignImport (tf,ti,td) n ty fimport) = do
+    tf' <- markEpToken tf
+    ti' <- markEpToken ti
 
     fimport' <- markAnnotated fimport
 
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignImport an2 n' ty' fimport')
+    return (ForeignImport (tf',ti',td') n' ty' fimport')
 
-  exact (ForeignExport an n ty fexport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnExport
+  exact (ForeignExport (tf,te,td) n ty fexport) = do
+    tf' <- markEpToken tf
+    te' <- markEpToken te
     fexport' <- markAnnotated fexport
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignExport an2 n' ty' fexport')
+    return (ForeignExport (tf',te',td') n' ty' fexport')
 
 -- ---------------------------------------------------------------------
 
@@ -2162,24 +2091,22 @@ instance ExactPrint (WarnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warning (ns_spec, an) lns  (WarningTxt mb_cat src ls )) = do
+  exact (Warning (ns_spec, (o,c)) lns  (WarningTxt mb_cat src ls )) = do
     mb_cat' <- markAnnotated mb_cat
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns'  (WarningTxt mb_cat' src ls'))
-    -- return (Warning an1 lns'  (WarningTxt mb_cat' src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns'  (WarningTxt mb_cat' src ls'))
 
-  exact (Warning (ns_spec, an) lns (DeprecatedTxt src ls)) = do
+  exact (Warning (ns_spec, (o,c)) lns (DeprecatedTxt src ls)) = do
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns' (DeprecatedTxt src ls'))
-    -- return (Warning an1 lns' (DeprecatedTxt src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns' (DeprecatedTxt src ls'))
 
 exactNsSpec :: (Monad m, Monoid w) => NamespaceSpecifier -> EP w m NamespaceSpecifier
 exactNsSpec NoNamespaceSpecifier = pure NoNamespaceSpecifier
@@ -2306,9 +2233,9 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (RoleAnnotDecl an ltycon roles) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnRole
+  exact (RoleAnnotDecl (tt,tr) ltycon roles) = do
+    tt' <- markEpToken tt
+    tr' <- markEpToken tr
     ltycon' <- markAnnotated ltycon
     let markRole (L l (Just r)) = do
           (L l' r') <- markAnnotated (L l r)
@@ -2317,7 +2244,7 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
           e' <- printStringAtAA  (entry l) "_"
           return (L (l { entry = e'}) Nothing)
     roles' <- mapM markRole roles
-    return (RoleAnnotDecl an1 ltycon' roles')
+    return (RoleAnnotDecl (tt',tr') ltycon' roles')
 
 -- ---------------------------------------------------------------------
 
@@ -2437,28 +2364,28 @@ instance ExactPrint (ClsInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ClsInstDecl { cid_ext = (mbWarn, an, sortKey)
+  exact (ClsInstDecl { cid_ext = (mbWarn, AnnClsInstDecl i w oc semis cc, sortKey)
                      , cid_poly_ty = inst_ty, cid_binds = binds
                      , cid_sigs = sigs, cid_tyfam_insts = ats
                      , cid_overlap_mode = mbOverlap
                      , cid_datafam_insts = adts })
       = do
-          (mbWarn', an0, mbOverlap', inst_ty') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lid AnnSemi
+          (mbWarn', i', w', mbOverlap', inst_ty') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsAtTag, prepareListAnnotationA ats),
                                 (ClsAtdTag, prepareListAnnotationF adts),
                                 (ClsMethodTag, prepareListAnnotationA binds),
                                 (ClsSigTag, prepareListAnnotationA sigs)
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC -- '}'
+          cc' <- markEpToken cc
           let
             ats'   = undynamic ds
             adts'  = undynamic ds
             binds' = undynamic ds
             sigs'  = undynamic ds
-          return (ClsInstDecl { cid_ext = (mbWarn', an3, sortKey')
+          return (ClsInstDecl { cid_ext = (mbWarn', AnnClsInstDecl i' w' oc' semis' cc', sortKey')
                               , cid_poly_ty = inst_ty', cid_binds = binds'
                               , cid_sigs = sigs', cid_tyfam_insts = ats'
                               , cid_overlap_mode = mbOverlap'
@@ -2466,12 +2393,12 @@ instance ExactPrint (ClsInstDecl GhcPs) where
 
       where
         top_matter = do
-          an0 <- markEpAnnL an lidl AnnInstance
+          i' <- markEpToken i
           mw <- mapM markAnnotated mbWarn
           mo <- mapM markAnnotated mbOverlap
           it <- markAnnotated inst_ty
-          an1 <- markEpAnnL an0 lidl AnnWhere -- Optional
-          return (mw, an1, mo,it)
+          w' <- markEpToken w -- Optional
+          return (mw, i', w', mo,it)
 
 -- ---------------------------------------------------------------------
 
@@ -2492,35 +2419,35 @@ instance ExactPrint (LocatedP OverlapMode) where
   setAnnotationAnchor = setAnchorAn
 
   -- NOTE: NoOverlap is only used in the typechecker
-  exact (L an (NoOverlap src)) = do
-    an0 <- markAnnOpenP an src "{-# NO_OVERLAP"
-    an1 <- markAnnCloseP an0
-    return (L an1 (NoOverlap src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NoOverlap src)) = do
+    o' <- markAnnOpen'' o src "{-# NO_OVERLAP"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (NoOverlap src))
 
-  exact (L an (Overlappable src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPABLE"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlappable src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlappable src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPABLE"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlappable src))
 
-  exact (L an (Overlapping src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPING"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlapping src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlapping src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPING"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlapping src))
 
-  exact (L an (Overlaps src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPS"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlaps src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlaps src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPS"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlaps src))
 
-  exact (L an (Incoherent src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Incoherent src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
-  exact (L an (NonCanonical src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NonCanonical src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
 -- ---------------------------------------------------------------------
 
@@ -2962,12 +2889,12 @@ instance ExactPrint (StandaloneKindSig GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StandaloneKindSig an vars sig) = do
-    an0 <- markEpAnnL an lidl AnnType
+  exact (StandaloneKindSig (tt,td) vars sig) = do
+    tt' <- markEpToken tt
     vars' <- markAnnotated vars
-    an1 <- markEpAnnL an0 lidl AnnDcolon
+    td' <- markEpUniToken td
     sig' <- markAnnotated sig
-    return (StandaloneKindSig an1 vars' sig')
+    return (StandaloneKindSig (tt',td') vars' sig')
 
 -- ---------------------------------------------------------------------
 
@@ -2989,24 +2916,24 @@ instance ExactPrint (AnnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsAnnotation (an, src) prov e) = do
-    an0 <- markAnnOpenP' an src "{-# ANN"
-    (an1, prov') <-
+  exact (HsAnnotation (AnnPragma o c s l1 l2 t m, src) prov e) = do
+    o' <- markAnnOpen'' o src "{-# ANN"
+    (t', m', prov') <-
       case prov of
         (ValueAnnProvenance n) -> do
           n' <- markAnnotated n
-          return (an0, ValueAnnProvenance n')
+          return (t, m, ValueAnnProvenance n')
         (TypeAnnProvenance n) -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnType
+          t' <- markEpToken t
           n' <- markAnnotated n
-          return (an1, TypeAnnProvenance n')
+          return (t', m, TypeAnnProvenance n')
         ModuleAnnProvenance -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnModule
-          return (an1, prov)
+          m' <- markEpToken m
+          return (t, m', prov)
 
     e' <- markAnnotated e
-    an2 <- markAnnCloseP' an1
-    return (HsAnnotation (an2,src) prov' e')
+    c' <- printStringAtAA c "#-}"
+    return (HsAnnotation (AnnPragma o' c' s l1 l2 t' m',src) prov' e')
 
 -- ---------------------------------------------------------------------
 
@@ -3418,13 +3345,11 @@ instance ExactPrint (HsPragE GhcPs) where
   getAnnotationEntry HsPragSCC{}  = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsPragSCC (an,st) sl) = do
-    an0 <- markAnnOpenP' an st "{-# SCC"
-    let txt = sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl)
-    an1 <- markEpAnnLMS'' an0 lapr_rest AnnVal    (Just txt) -- optional
-    an2 <- markEpAnnLMS'' an1 lapr_rest AnnValStr (Just txt) -- optional
-    an3 <- markAnnCloseP' an2
-    return (HsPragSCC (an3,st) sl)
+  exact (HsPragSCC (AnnPragma o c s l1 l2 t m,st) sl) = do
+    o' <- markAnnOpen'' o st  "{-# SCC"
+    l1' <- printStringAtAA l1 (sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl))
+    c' <- printStringAtAA c "#-}"
+    return (HsPragSCC (AnnPragma o' c' s l1' l2 t m,st) sl)
 
 
 -- ---------------------------------------------------------------------
@@ -4178,11 +4103,11 @@ instance ExactPrint (HsType GhcPs) where
     lo' <- markAnnotated lo
     t2' <- markAnnotated t2
     return (HsOpTy x promoted t1' lo' t2')
-  exact (HsParTy an ty) = do
-    an0 <- markOpeningParen an
+  exact (HsParTy (o,c) ty) = do
+    o' <- markEpToken o
     ty' <- markAnnotated ty
-    an1 <- markClosingParen an0
-    return (HsParTy an1 ty')
+    c' <- markEpToken c
+    return (HsParTy (o',c') ty')
   exact (HsIParamTy an n t) = do
     n' <- markAnnotated n
     an0 <- markEpUniToken an
@@ -4273,7 +4198,7 @@ instance ExactPrint (HsDerivingClause GhcPs) where
   exact (HsDerivingClause { deriv_clause_ext      = an
                           , deriv_clause_strategy = dcs
                           , deriv_clause_tys      = dct }) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+    an0 <- markEpToken an
     dcs0 <- case dcs of
             Just (L _ ViaStrategy{}) -> return dcs
             _ -> mapM markAnnotated dcs
@@ -4292,16 +4217,16 @@ instance ExactPrint (DerivStrategy GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
   exact (StockStrategy an)    = do
-    an0 <- markEpAnnL an lid AnnStock
+    an0 <- markEpToken an
     return (StockStrategy an0)
   exact (AnyclassStrategy an) = do
-    an0 <- markEpAnnL an lid AnnAnyclass
+    an0 <- markEpToken an
     return (AnyclassStrategy an0)
   exact (NewtypeStrategy an)  = do
-    an0 <- markEpAnnL an lid AnnNewtype
+    an0 <- markEpToken an
     return (NewtypeStrategy an0)
   exact (ViaStrategy (XViaStrategyPs an ty)) = do
-    an0 <- markEpAnnL an lid AnnVia
+    an0 <- markEpToken an
     ty' <- markAnnotated ty
     return (ViaStrategy (XViaStrategyPs an0 ty'))
 
@@ -4468,27 +4393,27 @@ instance ExactPrint (ConDecl GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
 -- based on pprConDecl
-  exact (ConDeclH98 { con_ext = an
+  exact (ConDeclH98 { con_ext = AnnConDeclH98 tforall tdot tdarrow
                     , con_name = con
                     , con_forall = has_forall
                     , con_ex_tvs = ex_tvs
                     , con_mb_cxt = mcxt
                     , con_args = args
                     , con_doc = doc }) = do
-    an0 <- if has_forall
-      then markEpAnnL an lidl AnnForall
-      else return an
+    tforall' <- if has_forall
+      then markEpUniToken tforall
+      else return tforall
     ex_tvs' <- mapM markAnnotated ex_tvs
-    an1 <- if has_forall
-      then markEpAnnL an0 lidl AnnDot
-      else return an0
+    tdot' <- if has_forall
+      then markEpToken tdot
+      else return tdot
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
+    tdarrow' <- if (isJust mcxt)
+      then markEpUniToken tdarrow
+      else return tdarrow
 
     (con', args') <- exact_details args
-    return (ConDeclH98 { con_ext = an2
+    return (ConDeclH98 { con_ext = AnnConDeclH98 tforall' tdot' tdarrow'
                        , con_name = con'
                        , con_forall = has_forall
                        , con_ex_tvs = ex_tvs'
@@ -4516,14 +4441,15 @@ instance ExactPrint (ConDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ConDeclGADT { con_g_ext = (dcol, an)
+  exact (ConDeclGADT { con_g_ext = AnnConDeclGADT ops cps dcol
                      , con_names = cons
                      , con_bndrs = bndrs
                      , con_mb_cxt = mcxt, con_g_args = args
                      , con_res_ty = res_ty, con_doc = doc }) = do
     cons' <- mapM markAnnotated cons
     dcol' <- markEpUniToken dcol
-    an1 <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
 
     -- Work around https://gitlab.haskell.org/ghc/ghc/-/issues/20558
     bndrs' <- case bndrs of
@@ -4531,9 +4457,6 @@ instance ExactPrint (ConDecl GhcPs) where
       _ -> markAnnotated bndrs
 
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
     args' <-
       case args of
           (PrefixConGADT x args0) -> do
@@ -4544,7 +4467,7 @@ instance ExactPrint (ConDecl GhcPs) where
             rarr' <- markEpUniToken rarr
             return (RecConGADT rarr' fields')
     res_ty' <- markAnnotated res_ty
-    return (ConDeclGADT { con_g_ext = (dcol', an2)
+    return (ConDeclGADT { con_g_ext = AnnConDeclGADT [] [] dcol'
                         , con_names = cons'
                         , con_bndrs = bndrs'
                         , con_mb_cxt = mcxt', con_g_args = args'
@@ -4579,11 +4502,11 @@ instance ExactPrint (ConDeclField GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ConDeclField an names ftype mdoc) = do
+  exact (ConDeclField td names ftype mdoc) = do
     names' <- markAnnotated names
-    an0 <- markEpAnnL an lidl AnnDcolon
+    td' <- markEpUniToken td
     ftype' <- markAnnotated ftype
-    return (ConDeclField an0 names' ftype' mdoc)
+    return (ConDeclField td' names' ftype' mdoc)
 
 -- ---------------------------------------------------------------------
 
@@ -4610,15 +4533,15 @@ instance ExactPrint (LocatedP CType) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (CType stp mh (stct,ct))) = do
-    an0 <- markAnnOpenP an stp "{-# CTYPE"
-    an1 <- case mh of
-             Nothing -> return an0
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (CType stp mh (stct,ct))) = do
+    o' <- markAnnOpen'' o stp "{-# CTYPE"
+    l1' <- case mh of
+             Nothing -> return l1
              Just (Header srcH _h) ->
-               markEpAnnLMS an0 lapr_rest AnnHeader (Just (toSourceTextWithSuffix srcH "" ""))
-    an2 <- markEpAnnLMS an1 lapr_rest AnnVal (Just (toSourceTextWithSuffix stct (unpackFS ct) ""))
-    an3 <- markAnnCloseP an2
-    return (L an3 (CType stp mh (stct,ct)))
+               printStringAtAA l1 (toSourceTextWithSuffix srcH "" "")
+    l2' <- printStringAtAA l2 (toSourceTextWithSuffix stct (unpackFS ct) "")
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' s l1' l2' t m) cs) (CType stp mh (stct,ct)))
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -105,7 +105,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Ppr012.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr013.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr014.hs" Nothing
- -- "../../testsuite/tests/printer/Ppr015.hs" Nothing
+ "../../testsuite/tests/printer/Ppr015.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr016.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr017.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr018.hs" Nothing
@@ -212,7 +212,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ -- "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
 {-# LANGUAGE DerivingStrategies #-}
@@ -820,7 +821,7 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
 
 type XRecCond a =
-  ( XParTy a ~ AnnParen
+  ( XParTy a ~ (EpToken "(", EpToken ")")
   , NoGhcTc a ~ a
   , MapXRec a
   , UnXRec a
@@ -852,7 +853,7 @@ type instance XListTy DocNameI = EpAnn AnnParen
 type instance XTupleTy DocNameI = EpAnn AnnParen
 type instance XSumTy DocNameI = EpAnn AnnParen
 type instance XOpTy DocNameI = EpAnn [AddEpAnn]
-type instance XParTy DocNameI = AnnParen
+type instance XParTy DocNameI = (EpToken "(", EpToken ")")
 type instance XIParamTy DocNameI = EpAnn [AddEpAnn]
 type instance XKindSig DocNameI = EpAnn [AddEpAnn]
 type instance XSpliceTy DocNameI = DataConCantHappen



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f61ed4e6f3b4d5933fa699ec2fc9dbab8052f7e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 10:41:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 06:41:25 -0400
Subject: [Git][ghc/ghc][master] wasm: bump dyld v8 heap size limit
Message-ID: <67162fd569c9c_23de5f57f5f8116827@gitlab.mail>



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


Commits:
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -


1 changed file:

- utils/jsffi/dyld.mjs


Changes:

=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -1,4 +1,4 @@
-#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --no-turbo-fast-api-calls --wasm-lazy-validation
+#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --max-old-space-size=8192 --no-turbo-fast-api-calls --wasm-lazy-validation
 
 // Note [The Wasm Dynamic Linker]
 // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 11:13:52 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Mon, 21 Oct 2024 07:13:52 -0400
Subject: [Git][ghc/ghc][wip/T25266] 16 commits: Bump transformers submodule
Message-ID: <67163770e181_23de5f8a12041270de@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25266 at Glasgow Haskell Compiler / GHC


Commits:
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
1035bfa9 by Simon Peyton Jones at 2024-10-21T12:13:44+01:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
6e4acbf1 by Simon Peyton Jones at 2024-10-21T12:13:44+01:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


10 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- cabal.project-reinstall
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cf7cb14086b4322c3b4b0511c341e0ab69301b9...6e4acbf1d4bd6ad455b276c70c873fa545540d63

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cf7cb14086b4322c3b4b0511c341e0ab69301b9...6e4acbf1d4bd6ad455b276c70c873fa545540d63
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 12:22:06 2024
From: gitlab at gitlab.haskell.org (jeffrey young (@doyougnu))
Date: Mon, 21 Oct 2024 08:22:06 -0400
Subject: [Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef]
 16 commits: Bump transformers submodule
Message-ID: <6716476ecc7f4_6686425d3ac2462a@gitlab.mail>



jeffrey young pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
8745040b by doyougnu at 2024-10-21T08:21:11-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
9bfd1b54 by doyougnu at 2024-10-21T08:21:21-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -


9 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- cabal.project-reinstall
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ee0bee9ac3becdf2f2b27b2786fdfa3ae024d8a...9bfd1b547f1a5bf294593eb300b8d45955f74285

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ee0bee9ac3becdf2f2b27b2786fdfa3ae024d8a...9bfd1b547f1a5bf294593eb300b8d45955f74285
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 12:58:15 2024
From: gitlab at gitlab.haskell.org (jeffrey young (@doyougnu))
Date: Mon, 21 Oct 2024 08:58:15 -0400
Subject: [Git][ghc/ghc][wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef]
 ghc-internal: hide linkerOptimistic in MiscFlags
Message-ID: <67164fe7e4c61_1702be1dfaec5434e@gitlab.mail>



jeffrey young pushed to branch wip/haskell-nix-patches/musl64/ghc-9.6-missing-symbols-deadbeef at Glasgow Haskell Compiler / GHC


Commits:
63b008da by doyougnu at 2024-10-21T08:57:30-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -


7 changed files:

- − docs/users_guide/9.12.1-notes.rst
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
docs/users_guide/9.12.1-notes.rst deleted
=====================================
@@ -1,236 +0,0 @@
-.. _release-9-11-1:
-
-Version 9.12.1
-==============
-
-The significant changes to the various parts of the compiler are listed in the
-following sections. See the `migration guide
-`_ on the GHC Wiki
-for specific guidance on migrating programs to this release.
-
-Language
-~~~~~~~~
-
-- New language extension: :extension:`OrPatterns` implements `GHC Proposal #522
-  `_).
-- GHC Proposal `#569 `_
-  "Multiline string literals" has been implemented.
-  The following code is now accepted by GHC::
-
-    {-# LANGUAGE MultilineStrings #-}
-
-    x :: String
-    x =
-      """
-      This is a
-      multiline
-
-          string
-
-      literal
-      """
-
-  This feature is guarded behind :extension:`MultilineStrings`.
-
-- The ordering of variables used for visible type application has been changed in two cases.
-  It is supposed to be left-to-right, but due to an oversight, it was wrong:
-
-  - in an infix application ``f :: a `op` b``, it is now ``forall a op b.`` rather than
-    ``forall op a b.``
-  - in a linear type ``f :: a %m -> b``, it is now ``forall a m b.`` rather than
-    ``forall a b m.``.
-
-  This change is backwards-incompatible, although in practice we don't expect it
-  to cause significant disruption.
-
-- The built-in ``HasField`` class, used by :extension:`OverloadedRecordDot`, now
-  supports representation polymorphism (implementing part of `GHC Proposal #583
-  `_).
-  This means that code using :extension:`UnliftedDatatypes` or
-  :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`.
-
-- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension
-  (`#22155 `_).
-
-- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)``
-  is used as the one and only function argument.
-
-- The venerable ``default`` declarations have been generalized. They can now name a class
-  other than ``Num`` and the class defaults can be exported. The functionality is guarded
-  by the new ``NamedDefaults`` language extension. See the `GHC proposal
-  `__
-  for details.
-
-- GHC now takes COMPLETE pragmas into consideration when deciding whether
-  pattern matches in do notation are fallible.
-
-- As part of `GHC Proposal #281 `_
-  GHC now accepts type syntax in expressions, namely function type arrow ``a -> b``,
-  constraint arrow ``a => b``, and ``forall`` telescopes: ::
-
-    g = f (forall a. Show a => a -> String)
-      where f :: forall a -> ...
-
-Compiler
-~~~~~~~~
-
-- Constructor ``PluginProv`` of type ``UnivCoProvenance``, relevant
-  for typing plugins, gets an extra ``DCoVarSet`` argument.
-  The argument is intended to contain the in-scope coercion variables
-  that the the proof represented by the coercion makes use of.
-  See ``Note [The importance of tracking free coercion variables]``
-  in ``GHC.Core.TyCo.Rep``, :ref:`constraint-solving-with-plugins`
-  and the migration guide.
-
-- The flag :ghc-flag:`-fprof-late` will no longer prevent top level constructors from being statically allocated.
-
-  It used to be the case that we would add a cost centre for bindings like ``foo = Just bar``.
-  This turned the binding into a CAF that would allocate the constructor on first evaluation.
-
-  However without the cost centre ``foo`` can be allocated at compile time. This reduces code-bloat and
-  reduces overhead for short-running applications.
-
-  The tradeoff is that calling ``whoCreated`` on top level value definitions like ``foo`` will be less informative.
-
-- A new flag :ghc-flag:`-fexpose-overloaded-unfoldings` has been added providing a lightweight alternative to :ghc-flag:`-fexpose-all-unfoldings`.
-
-- :ghc-flag:`-Wderiving-typeable` has been added to :ghc-flag:`-Wall`.
-
-- i386 Windows support is now completely removed amid massive cleanup
-  of legacy code to pave way for Arm64 Windows support (`#24883
-  `_). Rest
-  assured, this does not impact existing support for x86_64 Windows or
-  i386 Linux. For end users, the ``stdcall`` C calling convention is
-  now fully deprecated and GHC will unconditionally produce a warning
-  and treat it as ``ccall``. All C import/export declarations on
-  Windows should now use ``ccall``.
-
-- 32-bit macOS/iOS support has also been completely removed (`#24921
-  `_). This does
-  not affect existing support of apple systems on x86_64/aarch64.
-
-- The flag :ghc-flag:`-fignore-asserts` will now also enable the
-  :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967
-  `_).
-  This enables people to write their own custom assertion functions.
-  See :ref:`assertions`.
-
-- The flag :ghc-flag:`-fkeep-auto-rules` that forces GHC to keep auto generated
-  specialization rules was added. It was actually added ghc-9.10.1 already but
-  mistakenly not mentioned in the 9.10.1 changelog.
-
-- Fixed a bug that caused GHC to panic when using the aarch64 ncg and -fregs-graph
-  on certain programs. (#24941)
-
-- A new warning :ghc-flag:`-Wview-pattern-signatures` is introduced to notify users about
-  future changes in parsing of view patterns in combination with pattern signatures
-
-GHCi
-~~~~
-
-- Fix a bug where GHCi would not start alongside a local file called ``Prelude.hs``
-  or ``Prelude.lhs`` (:ghc-ticket:`10920`).
-
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- Reduce fragmentation incurred by the nonmoving GC's segment allocator. In one application this reduced resident set size by 26%. See :ghc-ticket:`24150`.
-
-- Memory return logic now uses live bytes rather than live blocks to measure the size of the heap.
-  This primarily affects the non-moving GC, which should now be more willing to return memory to the OS.
-  Users who have fine-tuned the :rts-flag:`-F ⟨factor⟩`, :rts-flag:`-Fd ⟨factor⟩`, or :rts-flag:`-O ⟨size⟩` flags,
-  and use the non-moving GC, should see if adjustments are needed in light of this change.
-
-- The new runtime flag :rts-flag:`--read-tix-file=\` allows to modify whether a preexisting .tix file is read in at the beginning of a program run.
-  The default is currently ``--read-tix-file=yes`` but will change to ``--read-tix-file=no`` in a future version of GHC.
-  For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing ``--read-tix-file=yes``.
-  Details can be found in `GHC proposal 612 `__.
-
-- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
-  runtime linker to continue in the presence of unknown symbols. By default this
-  flag is not passed, preserving previous behavior.
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- Add exception type metadata to SomeException's displayException and
-  "Exception:" header to the default handler
-  (i.e. ``GHC.Conc.Sync.uncaughtExceptionHandler``):
-
-  https://github.com/haskell/core-libraries-committee/issues/231
-  https://github.com/haskell/core-libraries-committee/issues/261
-
-- The `deprecation process of GHC.Pack ` has come its term. The module has now been removed from ``base``.
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-- Usage of deprecated primops is now correctly reported (#19629).
-- New primops `isMutableByteArrayWeaklyPinned#` and `isByteArrayWeaklyPinned#`
-  to allow users to avoid copying large arrays safely when dealing with ffi.
-  See the users guide for more details on the different kinds of
-  pinned arrays in 9.12.
-
-  This need for this distinction originally surfaced in https://gitlab.haskell.org/ghc/ghc/-/issues/22255
-
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-``ghc-heap`` library
-~~~~~~~~~~~~~~~~~~~~
-
-``ghc-experimental`` library
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-``template-haskell`` library
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-Included libraries
-~~~~~~~~~~~~~~~~~~
-
-The package database provided with this distribution also contains a number of
-packages other than GHC itself. See the changelogs provided with these packages
-for further change information.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:                         Dependency of ``ghc`` library
-    libraries/base/base.cabal:                           Core library
-    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
-    compiler/ghc.cabal:                                  The compiler itself
-    libraries/ghci/ghci.cabal:                           The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal:             Core library
-    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:                   Core library
-    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
-    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
-    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal:             Core library
-    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
-    libraries/process/process.cabal:                     Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal:   Core library
-    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
-    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
-    libraries/time/time.cabal:                           Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
-    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
-    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -29,6 +29,10 @@ GHCi
 Runtime system
 ~~~~~~~~~~~~~~
 
+- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
+  runtime linker to continue in the presence of unknown symbols. By default this
+  flag is not passed, preserving previous behavior.
+
 Cmm
 ~~~
 


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,7 +162,8 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
-    , linkerOptimistic      :: Bool
+    -- TODO: #25354 uncomment to expose this flag to base.
+    -- , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag
@@ -537,8 +538,6 @@ getMiscFlags = do
                   (#{peek MISC_FLAGS, internalCounters} ptr :: IO CBool))
             <*> (toBool <$>
                   (#{peek MISC_FLAGS, linkerAlwaysPic} ptr :: IO CBool))
-            <*> (toBool <$>
-                  (#{peek MISC_FLAGS, linkerOptimistic} ptr :: IO CBool))
             <*> #{peek MISC_FLAGS, linkerMemBase} ptr
             <*> (toEnum . fromIntegral
                  <$> (#{peek MISC_FLAGS, ioManager} ptr :: IO Word32))


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9111,7 +9111,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -12153,7 +12153,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -9335,7 +9335,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -9111,7 +9111,7 @@ module GHC.RTS.Flags where
   type IoSubSystem :: *
   data IoSubSystem = IoPOSIX | IoNative
   type MiscFlags :: *
-  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerOptimistic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/63b008da8d18b5ffd1691f62d91a7e1df92f997f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 13:02:08 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 21 Oct 2024 09:02:08 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] Moved OverlapMode from
 GHC.Types.Basic to L.H.S.OverlapPragma
Message-ID: <671650d01e947_1702be1312d0545b4@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
09915909 by Hassan Al-Awwadi at 2024-10-21T15:00:44+02:00
Moved OverlapMode from GHC.Types.Basic to L.H.S.OverlapPragma

Parameterized it over the pass too. The rest is churn.

- - - - -


30 changed files:

- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Hs/Instances.hs
- + compiler/GHC/Hs/OverlapPragma.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/InlinePragma.hs
- + compiler/Language/Haskell/Syntax/OverlapPragma.hs
- compiler/ghc.cabal.in
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Builtin/PrimOps/Ids.hs
=====================================
@@ -23,7 +23,6 @@ import GHC.Builtin.Uniques
 import GHC.Builtin.Names
 import GHC.Builtin.Types.Prim
 
-import GHC.Types.Basic
 import GHC.Types.Cpr
 import GHC.Types.Demand
 import GHC.Types.Id
@@ -37,7 +36,7 @@ import GHC.Types.Var.Set
 import GHC.Tc.Types.Origin
 import GHC.Tc.Utils.TcType ( ConcreteTvOrigin(..), ConcreteTyVars, TcType )
 
-import GHC.Hs.InlinePragma(InlinePragma(..), neverInlinePragma )
+import GHC.Hs.InlinePragma(neverInlinePragma)
 import GHC.Data.SmallArray
 
 import Data.Maybe ( mapMaybe, listToMaybe, catMaybes, maybeToList )


=====================================
compiler/GHC/Core/InstEnv.hs
=====================================
@@ -12,7 +12,7 @@ The bits common to GHC.Tc.TyCl.Instance and GHC.Tc.Deriv.
 module GHC.Core.InstEnv (
         DFunId, InstMatch, ClsInstLookupResult,
         CanonicalEvidence(..), PotentialUnifiers(..), getCoherentUnifiers, nullUnifiers,
-        OverlapFlag(..), OverlapMode(..), setOverlapModeMaybe,
+        OverlapFlag(..), OverlapMode(..),
         ClsInst(..), DFunInstType, pprInstance, pprInstanceHdr, pprDFunId, pprInstances,
         instanceWarning, instanceHead, instanceSig, mkLocalClsInst, mkImportedClsInst,
         instanceDFunId, updateClsInstDFuns, updateClsInstDFun,
@@ -43,6 +43,7 @@ import GHC.Core.Class
 import GHC.Core.Unify
 import GHC.Core.FVs( orphNamesOfTypes, orphNamesOfType )
 import GHC.Hs.Extension
+import GHC.Hs.OverlapPragma
 
 import GHC.Unit.Module.Env
 import GHC.Unit.Module.Warnings
@@ -52,10 +53,8 @@ import GHC.Types.Unique.DSet
 import GHC.Types.Var.Set
 import GHC.Types.Name
 import GHC.Types.Name.Set
-import GHC.Types.Basic
 import GHC.Types.Id
 import GHC.Generics (Generic)
-import Data.Data        ( Data )
 import Data.List.NonEmpty ( NonEmpty (..), nonEmpty )
 import qualified Data.List.NonEmpty as NE
 import Data.Maybe       ( isJust )
@@ -114,7 +113,7 @@ data ClsInst
                 -- See Note [Implementation of deprecated instances]
                 -- in GHC.Tc.Solver.Dict
     }
-  deriving Data
+  -- deriving Data
 
 -- | A fuzzy comparison function for class instances, intended for sorting
 -- instances before displaying them to the user.


=====================================
compiler/GHC/Hs.hs
=====================================
@@ -33,6 +33,7 @@ module GHC.Hs (
         module GHC.Hs.Doc,
         module GHC.Hs.Extension,
         module GHC.Hs.InlinePragma,
+        module GHC.Hs.OverlapPragma,
         module GHC.Parser.Annotation,
         Fixity,
 
@@ -56,6 +57,7 @@ import GHC.Hs.Type
 import GHC.Hs.Utils
 import GHC.Hs.Doc
 import GHC.Hs.InlinePragma
+import GHC.Hs.OverlapPragma
 import GHC.Hs.Instances () -- For Data instances
 
 -- others:


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -12,6 +12,7 @@
 
 {-# OPTIONS_GHC -Wno-orphans #-} -- Outputable
 {-# LANGUAGE InstanceSigs #-}
+{-# LANGUAGE LambdaCase #-}
 
 {-
 (c) The University of Glasgow 2006
@@ -137,6 +138,7 @@ import GHC.Data.Maybe
 import Data.Data (Data)
 import Data.List (concatMap)
 import Data.Foldable (toList)
+import GHC.Hs.OverlapPragma
 
 {-
 ************************************************************************
@@ -1025,16 +1027,15 @@ ppDerivStrategy mb =
     Nothing       -> empty
     Just (L _ ds) -> ppr ds
 
-ppOverlapPragma :: Maybe (LocatedP OverlapMode) -> SDoc
-ppOverlapPragma mb =
-  case mb of
+ppOverlapPragma :: Maybe (LOverlapMode (GhcPass p)) -> SDoc
+ppOverlapPragma = \case
     Nothing           -> empty
-    Just (L _ (NoOverlap s))    -> maybe_stext s "{-# NO_OVERLAP #-}"
-    Just (L _ (Overlappable s)) -> maybe_stext s "{-# OVERLAPPABLE #-}"
-    Just (L _ (Overlapping s))  -> maybe_stext s "{-# OVERLAPPING #-}"
-    Just (L _ (Overlaps s))     -> maybe_stext s "{-# OVERLAPS #-}"
-    Just (L _ (Incoherent s))   -> maybe_stext s "{-# INCOHERENT #-}"
-    Just (L _ (NonCanonical s)) -> maybe_stext s "{-# INCOHERENT #-}" -- No surface syntax for NONCANONICAL yet
+    Just (L _ (NoOverlap s))                   -> maybe_stext s "{-# NO_OVERLAP #-}"
+    Just (L _ (Overlappable s))                -> maybe_stext s "{-# OVERLAPPABLE #-}"
+    Just (L _ (Overlapping s))                 -> maybe_stext s "{-# OVERLAPPING #-}"
+    Just (L _ (Overlaps s))                    -> maybe_stext s "{-# OVERLAPS #-}"
+    Just (L _ (Incoherent s))                  -> maybe_stext s "{-# INCOHERENT #-}"
+    Just (L _ (XOverlapMode (NonCanonical s))) -> maybe_stext s "{-# INCOHERENT #-}" -- No surface syntax for NONCANONICAL yet
   where
     maybe_stext NoSourceText     alt = text alt
     maybe_stext (SourceText src) _   = ftext src <+> text "#-}"
@@ -1466,7 +1467,7 @@ type instance Anno (ClsInstDecl (GhcPass p)) = SrcSpanAnnA
 type instance Anno (InstDecl (GhcPass p)) = SrcSpanAnnA
 type instance Anno (DocDecl (GhcPass p)) = SrcSpanAnnA
 type instance Anno (DerivDecl (GhcPass p)) = SrcSpanAnnA
-type instance Anno OverlapMode = SrcSpanAnnP
+type instance Anno (OverlapMode (GhcPass p)) = SrcSpanAnnP
 type instance Anno (DerivStrategy (GhcPass p)) = EpAnnCO
 type instance Anno (DefaultDecl (GhcPass p)) = SrcSpanAnnA
 type instance Anno (ForeignDecl (GhcPass p)) = SrcSpanAnnA


=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -3,13 +3,14 @@
 {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
 {-# HLINT ignore "Use camelCase" #-}
 module GHC.Hs.InlinePragma(
-        CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
+        module Language.Haskell.Syntax.InlinePragma,
+        CompilerPhase(..), beginPhase, nextPhase, laterPhase,
 
         Activation(..), isActive, competesWith,
         isNeverActive, isAlwaysActive, activeInFinalPhase,
         activateAfterInitial, activateDuringFinal, activeAfter,
 
-        RuleMatchInfo(..), isConLike, isFunLike,
+        RuleMatchInfo(..),
         InlineSpec(..), noUserInlineSpec,
         InlinePragma(..), defaultInlinePragma, alwaysInlinePragma,
         neverInlinePragma, dfunInlinePragma,
@@ -22,8 +23,9 @@ module GHC.Hs.InlinePragma(
         inlinePragmaActivation, inlinePragmaRuleMatchInfo,
         setInlinePragmaActivation, setInlinePragmaRuleMatchInfo,
         pprInline, pprInlineDebug,
-        convertInlinePragma, convertInlineSpec, convertActivation
+        convertInlinePragma, convertInlineSpec, convertActivation,
 
+        set_pragma_inline, set_pragma_activation, set_pragma_rule
 ) where
 
 import GHC.Prelude
@@ -46,18 +48,18 @@ import GHC.Data.FastString (fsLit)
 -}
 
 --InlinePragma
-type instance XInlinePragma   (GhcPass _) = SourceText
-type instance XXCInlinePragma (GhcPass _) = DataConCantHappen
+type instance XInlinePragma   (GhcPass p) = SourceText
+type instance XXCInlinePragma (GhcPass p) = DataConCantHappen
 
 deriving instance Eq (InlinePragma (GhcPass p))
 
 --InlineSpec
-type instance XInline    (GhcPass _) = SourceText
-type instance XInlinable (GhcPass _) = SourceText
-type instance XNoInline  (GhcPass _) = SourceText
-type instance XOpaque    (GhcPass _) = SourceText
-type instance XNoUserInlinePrag (GhcPass _) = NoExtField
-type instance XXInlineSpec      (GhcPass _) = DataConCantHappen
+type instance XInline    (GhcPass p) = SourceText
+type instance XInlinable (GhcPass p) = SourceText
+type instance XNoInline  (GhcPass p) = SourceText
+type instance XOpaque    (GhcPass p) = SourceText
+type instance XNoUserInlinePrag (GhcPass p) = NoExtField
+type instance XXInlineSpec      (GhcPass p) = DataConCantHappen
 
 deriving instance Eq (InlineSpec (GhcPass p))
 
@@ -250,9 +252,11 @@ alwaysInlineConLikePragma :: InlinePragma (GhcPass p)
 alwaysInlineConLikePragma = set_pragma_rule alwaysInlinePragma ConLike
 
 inlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec (GhcPass p)
-inlinePragmaSpec = inl_inline
+inlinePragmaSpec inl@(InlinePragma{}) = inl_inline inl
+inlinePragmaSpec (XCInlinePragma imp) = dataConCantHappen imp
 
 inlinePragmaSource :: InlinePragma (GhcPass p) -> SourceText
+inlinePragmaSource (XCInlinePragma imp) = dataConCantHappen imp
 inlinePragmaSource prag = case inl_inline prag of
                             Inline    x        -> x
                             Inlinable y        -> y
@@ -293,29 +297,38 @@ isInlinePragma prag@(InlinePragma{}) = case inl_inline prag of
 isInlinePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isInlinablePragma :: InlinePragma (GhcPass p) -> Bool
-isInlinablePragma prag = case inl_inline prag of
-                           Inlinable _  -> True
-                           _            -> False
+isInlinablePragma prag@(InlinePragma{}) =
+  case inl_inline prag of
+    Inlinable _  -> True
+    _            -> False
+isInlinablePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isNoInlinePragma :: InlinePragma (GhcPass p) -> Bool
-isNoInlinePragma prag = case inl_inline prag of
-                          NoInline _   -> True
-                          _            -> False
+isNoInlinePragma prag@(InlinePragma{}) =
+  case inl_inline prag of
+    NoInline _   -> True
+    _            -> False
+isNoInlinePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isAnyInlinePragma :: InlinePragma (GhcPass p) -> Bool
 -- INLINE or INLINABLE
-isAnyInlinePragma prag = case inl_inline prag of
-                        Inline    _   -> True
-                        Inlinable _   -> True
-                        _             -> False
+isAnyInlinePragma prag@(InlinePragma{}) =
+  case inl_inline prag of
+    Inline    _   -> True
+    Inlinable _   -> True
+    _             -> False
+isAnyInlinePragma (XCInlinePragma imp)  = dataConCantHappen imp
 
 isOpaquePragma :: InlinePragma (GhcPass p) -> Bool
-isOpaquePragma prag = case inl_inline prag of
-                        Opaque _ -> True
-                        _        -> False
+isOpaquePragma prag@(InlinePragma{}) =
+  case inl_inline prag of
+    Opaque _ -> True
+    _        -> False
+isOpaquePragma (XCInlinePragma imp)  = dataConCantHappen imp
 
 inlinePragmaSat :: InlinePragma (GhcPass p) -> Maybe Arity
-inlinePragmaSat = inl_sat
+inlinePragmaSat prag@(InlinePragma{}) = inl_sat prag
+inlinePragmaSat (XCInlinePragma imp)  = dataConCantHappen imp
 
 inlinePragmaActivation :: InlinePragma (GhcPass p) -> Activation (GhcPass p)
 inlinePragmaActivation (InlinePragma { inl_act = activation }) = activation


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -32,8 +32,11 @@ import GHC.Hs.Lit
 import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
+import GHC.Hs.OverlapPragma
+import GHC.Hs.InlinePragma
+
 import GHC.Parser.Annotation
-import Language.Haskell.Syntax.InlinePragma
+--import GHC.Core.InstEnv (ClsInst)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -595,6 +598,7 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+-- Data derivations from GHC.Hs.InlinePragma ---------------------------
 
 deriving instance Data (Activation GhcPs)
 deriving instance Data (Activation GhcRn)
@@ -606,4 +610,14 @@ deriving instance Data (InlineSpec GhcTc)
 
 deriving instance Data (InlinePragma GhcPs)
 deriving instance Data (InlinePragma GhcRn)
-deriving instance Data (InlinePragma GhcTc)
\ No newline at end of file
+deriving instance Data (InlinePragma GhcTc)
+
+deriving instance Data RuleMatchInfo
+
+-- ---------------------------------------------------------------------
+-- Data derivations from GHC.Hs.OverlapPragma --------------------------
+deriving instance Data (OverlapMode GhcPs)
+deriving instance Data (OverlapMode GhcRn)
+deriving instance Data (OverlapMode GhcTc)
+deriving instance Data NonCanonical
+deriving instance Data OverlapFlag
\ No newline at end of file


=====================================
compiler/GHC/Hs/OverlapPragma.hs
=====================================
@@ -0,0 +1,144 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+module GHC.Hs.OverlapPragma(
+  module Language.Haskell.Syntax.OverlapPragma
+  , NonCanonical(..)
+  , OverlapFlag(..)
+  , hasIncoherentFlag
+  , hasOverlappableFlag
+  , hasOverlappingFlag
+  , hasNonCanonicalFlag
+  , pprSafeOverlap
+  , convertOverlapMode
+) where
+
+import Language.Haskell.Syntax.OverlapPragma
+import Language.Haskell.Syntax.Extension 
+
+import GHC.Prelude
+import GHC.Types.SourceText 
+import GHC.Hs.Extension (GhcPass, GhcTc)
+
+import GHC.Utils.Binary
+import GHC.Utils.Outputable
+
+import GHC.Utils.Panic (panic)
+
+------------------------
+-- type family instances
+
+type instance XNoOverlap    (GhcPass _) = SourceText
+type instance XOverlappable (GhcPass _) = SourceText
+type instance XOverlapping  (GhcPass _) = SourceText
+type instance XOverlaps     (GhcPass _) = SourceText
+type instance XIncoherent   (GhcPass _) = SourceText
+type instance XXOverlapMode (GhcPass _) = NonCanonical
+newtype NonCanonical = NonCanonical SourceText
+  deriving (Eq)
+    -- ^ Behave like Incoherent, but the instance choice is observable
+    -- by the program behaviour. See Note [Coherence and specialisation: overview].
+    --
+    -- We don't have surface syntax for the distinction between
+    -- Incoherent and NonCanonical instances; instead, the flag
+    -- `-f{no-}specialise-incoherents` (on by default) controls
+    -- whether `INCOHERENT` instances are regarded as Incoherent or
+    -- NonCanonical.
+
+
+-----------------------
+-- converting 
+convertOverlapMode :: OverlapMode (GhcPass p) -> OverlapMode (GhcPass p')
+convertOverlapMode = \case
+  NoOverlap s    -> NoOverlap s
+  Overlappable s -> Overlappable s
+  Overlapping s  -> Overlapping s
+  Overlaps s     -> Overlaps s
+  Incoherent s   -> Incoherent s
+  XOverlapMode s -> XOverlapMode s
+
+------------------------
+-- overlap flag
+data OverlapFlag = OverlapFlag
+  { overlapMode   :: OverlapMode GhcTc
+  , isSafeOverlap :: Bool
+  } deriving (Eq)
+
+------------------------
+-- deriving instances
+deriving instance Eq (OverlapMode (GhcPass p))
+
+------------------------
+-- hand rolled instances
+instance Outputable (OverlapMode (GhcPass p)) where
+  ppr (NoOverlap    _)                = empty
+  ppr (Overlappable _)                = text "[overlappable]"
+  ppr (Overlapping  _)                = text "[overlapping]"
+  ppr (Overlaps     _)                = text "[overlap ok]"
+  ppr (Incoherent   _)                = text "[incoherent]"
+  ppr (XOverlapMode (NonCanonical _)) = text "[noncanonical]"
+
+
+instance Outputable OverlapFlag where
+   ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag)
+
+-- might want to make an explicit IfaceOverlapMode, I guess
+instance Binary (OverlapMode (GhcPass p)) where
+    put_ bh (NoOverlap    s)                = putByte bh 0 >> put_ bh s
+    put_ bh (Overlaps     s)                = putByte bh 1 >> put_ bh s
+    put_ bh (Incoherent   s)                = putByte bh 2 >> put_ bh s
+    put_ bh (Overlapping  s)                = putByte bh 3 >> put_ bh s
+    put_ bh (Overlappable s)                = putByte bh 4 >> put_ bh s
+    put_ bh (XOverlapMode (NonCanonical s)) = putByte bh 5 >> put_ bh s
+    get bh = do
+        h <- getByte bh
+        case h of
+            0 -> (get bh) >>= \s -> return $ NoOverlap s
+            1 -> (get bh) >>= \s -> return $ Overlaps s
+            2 -> (get bh) >>= \s -> return $ Incoherent s
+            3 -> (get bh) >>= \s -> return $ Overlapping s
+            4 -> (get bh) >>= \s -> return $ Overlappable s
+            5 -> (get bh) >>= \s -> return $ XOverlapMode (NonCanonical s)
+            _ -> panic ("get OverlapMode" ++ show h)
+
+
+instance Binary OverlapFlag where
+    put_ bh flag = do put_ bh (overlapMode flag)
+                      put_ bh (isSafeOverlap flag)
+    get bh = do
+        h <- get bh
+        b <- get bh
+        return OverlapFlag { overlapMode = h, isSafeOverlap = b }
+
+------------------------
+-- helper functions 
+hasIncoherentFlag :: OverlapMode (GhcPass p) -> Bool
+hasIncoherentFlag = \case
+  Incoherent   _                -> True
+  XOverlapMode (NonCanonical _) -> True
+  _                             -> False
+
+hasOverlappableFlag :: OverlapMode (GhcPass p) -> Bool
+hasOverlappableFlag = \case
+  Overlappable _                -> True
+  Overlaps     _                -> True
+  Incoherent   _                -> True
+  XOverlapMode (NonCanonical _) -> True
+  _                             -> False
+
+hasOverlappingFlag :: OverlapMode (GhcPass p) -> Bool
+hasOverlappingFlag = \case 
+  Overlapping  _                -> True
+  Overlaps     _                -> True
+  Incoherent   _                -> True
+  XOverlapMode (NonCanonical _) -> True
+  _                             -> False
+
+hasNonCanonicalFlag :: OverlapMode (GhcPass p) -> Bool
+hasNonCanonicalFlag = \case
+  XOverlapMode (NonCanonical _) -> True
+  _                             -> False
+
+pprSafeOverlap :: Bool -> SDoc
+pprSafeOverlap True  = text "[safe]"
+pprSafeOverlap False = empty


=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -442,12 +442,15 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs
   = (gbl_id `setIdUnfolding` mkCompulsoryUnfolding' simpl_opts rhs, rhs)
 
   | otherwise
-  = case inlinePragmaSpec inline_prag of
+  = case inline_prag of
+      XCInlinePragma imp              -> dataConCantHappen imp
+      InlinePragma{inl_inline = spec} -> case spec of
           NoUserInlinePrag{} -> (gbl_id, rhs)
           NoInline  {}       -> (gbl_id, rhs)
           Opaque    {}       -> (gbl_id, rhs)
           Inlinable {}       -> (gbl_id `setIdUnfolding` inlinable_unf, rhs)
           Inline    {}       -> inline_pair
+          XInlineSpec i      -> dataConCantHappen i
   where
     simpl_opts    = initSimpleOpts dflags
     inline_prag   = idInlinePragma gbl_id


=====================================
compiler/GHC/HsToCore/Foreign/C.hs
=====================================
@@ -39,7 +39,6 @@ import GHC.Types.Name
 import GHC.Types.RepType
 import GHC.Types.ForeignCall
 import GHC.Types.Basic
-import GHC.Hs.InlinePragma ( Activation(..) )
 import GHC.Unit.Module
 
 import GHC.Driver.DynFlags
@@ -60,7 +59,6 @@ import GHC.Utils.Encoding
 
 import Data.Maybe
 import Data.List (nub)
-import Language.Haskell.Syntax (noExtField)
 
 dsCFExport:: Id                 -- Either the exported Id,
                                 -- or the foreign-export-dynamic constructor


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -2707,18 +2707,18 @@ repNewtypeStrategy = rep2 newtypeStrategyName []
 repViaStrategy :: Core (M TH.Type) -> MetaM (Core (M TH.DerivStrategy))
 repViaStrategy (MkC t) = rep2 viaStrategyName [t]
 
-repOverlap :: Maybe OverlapMode -> MetaM (Core (Maybe TH.Overlap))
+repOverlap :: Maybe (OverlapMode (GhcPass p)) -> MetaM (Core (Maybe TH.Overlap))
 repOverlap mb =
   case mb of
     Nothing -> nothing
     Just o ->
       case o of
-        NoOverlap _    -> nothing
-        Overlappable _ -> just =<< dataCon overlappableDataConName
-        Overlapping _  -> just =<< dataCon overlappingDataConName
-        Overlaps _     -> just =<< dataCon overlapsDataConName
-        Incoherent _   -> just =<< dataCon incoherentDataConName
-        NonCanonical _ -> just =<< dataCon incoherentDataConName
+        NoOverlap _                   -> nothing
+        Overlappable _                -> just =<< dataCon overlappableDataConName
+        Overlapping _                 -> just =<< dataCon overlappingDataConName
+        Overlaps _                    -> just =<< dataCon overlapsDataConName
+        Incoherent _                  -> just =<< dataCon incoherentDataConName
+        XOverlapMode (NonCanonical _) -> just =<< dataCon incoherentDataConName
   where
   nothing = coreNothing overlapTyConName
   just    = coreJust overlapTyConName


=====================================
compiler/GHC/HsToCore/Ticks.hs
=====================================
@@ -45,9 +45,6 @@ import GHC.Types.CostCentre
 import GHC.Types.CostCentre.State
 import GHC.Types.Tickish
 import GHC.Types.ProfAuto
-
-import GHC.Hs.InlinePragma(isInlinePragma)
-
 import Control.Monad
 import Data.List (isSuffixOf, intersperse)
 


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -1742,7 +1742,7 @@ instance ToHie (RScoped (LocatedAn NoEpAnns (DerivStrategy GhcRn))) where
       NewtypeStrategy _ -> []
       ViaStrategy s -> [ toHie (TS (ResolvedScopes [sc]) s) ]
 
-instance ToHie (LocatedP OverlapMode) where
+instance ToHie (LocatedP (OverlapMode (GhcPass p))) where
   toHie (L span _) = locOnly (locA span)
 
 instance ToHie a => ToHie (HsScaled GhcRn a) where


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -86,7 +86,11 @@ import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
 import GHC.Builtin.Types ( constraintKindTyConName )
 import GHC.Stg.InferTags.TagSig
 import GHC.Parser.Annotation (noLocA)
+
 import GHC.Hs.Extension ( GhcRn, GhcPass )
+import GHC.Hs.OverlapPragma
+import GHC.Hs.InlinePragma
+
 import GHC.Hs.Doc ( WithHsDocIdentifiers(..) )
 
 import GHC.Utils.Lexeme (isLexSym)
@@ -98,7 +102,6 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
                        seqList, zipWithEqual )
 
-import Language.Haskell.Syntax.InlinePragma
 import Language.Haskell.Syntax.Extension(noExtField)
 
 import Control.Monad
@@ -1685,6 +1688,7 @@ instance Binary IfaceActivation where
               _ -> do src <- get bh
                       ab <- get bh
                       return (IfActiveAfter src ab)
+
 instance Binary RuleMatchInfo where
     put_ bh FunLike = putByte bh 0
     put_ bh ConLike = putByte bh 1


=====================================
compiler/GHC/Parser.y
=====================================
@@ -95,7 +95,6 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, sumTyCon,
                            listTyCon_RDR, consDataCon_RDR,
                            unrestrictedFunTyCon )
 
-import Language.Haskell.Syntax.InlinePragma(InlinePragma(..))
 import Language.Haskell.Syntax.Basic (FieldLabelString(..))
 
 import qualified Data.Semigroup as Semi
@@ -1420,7 +1419,7 @@ inst_decl :: { LInstDecl GhcPs }
                                    (fmap reverse $7)
                             (AnnDataDefn [] [] NoEpTok tnewtype tdata (epTok $2) dcolon twhere oc cc NoEpTok)}}
 
-overlap_pragma :: { Maybe (LocatedP OverlapMode) }
+overlap_pragma :: { Maybe (LOverlapMode GhcPs) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
                                        (AnnPragma (mo $1) (mc $2) []) }
   | '{-# OVERLAPPING'     '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlapping (getOVERLAPPING_PRAGs $1)))


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -632,7 +632,8 @@ rnClsInstDecl (ClsInstDecl { cid_ext = (inst_warn_ps, _, _)
        ; return (ClsInstDecl { cid_ext = inst_warn_rn
                              , cid_poly_ty = inst_ty', cid_binds = mbinds'
                              , cid_sigs = uprags', cid_tyfam_insts = ats'
-                             , cid_overlap_mode = oflag
+                             , cid_overlap_mode = fmap (fmap convertOverlapMode) oflag
+                                  --double fmap to pierce through the Maybe and the Located wrapper
                              , cid_datafam_insts = adts' },
                  all_fvs) }
              -- We return the renamed associated data type declarations so
@@ -1139,7 +1140,9 @@ rnSrcDerivDecl (DerivDecl (inst_warn_ps, ann) ty mds overlap)
            NFC_StandaloneDerivedInstanceHead
            (getLHsInstDeclHead $ dropWildCards ty')
        ; inst_warn_rn <- mapM rnLWarningTxt inst_warn_ps
-       ; return (DerivDecl (inst_warn_rn, ann) ty' mds' overlap, fvs) }
+       ; return (DerivDecl (inst_warn_rn, ann) ty' mds' (fmap (fmap convertOverlapMode) overlap), fvs) }
+                                         --double fmap to pierce through the Maybe and the Located wrapper
+
   where
     ctxt    = DerivDeclCtx
     nowc_ty = dropWildCards ty


=====================================
compiler/GHC/Tc/Deriv.hs
=====================================
@@ -762,7 +762,7 @@ deriveStandalone (L loc (DerivDecl (warn, _) deriv_ty mb_lderiv_strat overlap_mo
          then do warnUselessTypeable
                  return Nothing
          else do early_deriv_spec <-
-                   mkEqnHelp (fmap unLoc overlap_mode)
+                   mkEqnHelp (fmap (convertOverlapMode . unLoc) overlap_mode)
                              tvs' cls inst_tys'
                              deriv_ctxt' mb_deriv_strat'
                              (fmap unLoc warn)
@@ -1217,7 +1217,7 @@ instance (at least from the user's perspective), the amount of engineering
 required to obtain the latter instance just isn't worth it.
 -}
 
-mkEqnHelp :: Maybe OverlapMode
+mkEqnHelp :: Maybe (OverlapMode GhcTc)
           -> [TyVar]
           -> Class -> [Type]
           -> DerivContext


=====================================
compiler/GHC/Tc/Deriv/Utils.hs
=====================================
@@ -120,7 +120,7 @@ mkDerivOrigin standalone_wildcard
 -- determining what its @EarlyDerivSpec@ should be.
 -- See @Note [DerivEnv and DerivSpecMechanism]@.
 data DerivEnv = DerivEnv
-  { denv_overlap_mode :: Maybe OverlapMode
+  { denv_overlap_mode :: Maybe (OverlapMode GhcTc)
     -- ^ Is this an overlapping instance?
   , denv_tvs          :: [TyVar]
     -- ^ Universally quantified type variables in the instance. If the
@@ -175,7 +175,7 @@ data DerivSpec theta = DS { ds_loc                 :: SrcSpan
                           , ds_tys                 :: [Type]
                           , ds_skol_info           :: SkolemInfo
                           , ds_user_ctxt           :: UserTypeCtxt
-                          , ds_overlap             :: Maybe OverlapMode
+                          , ds_overlap             :: Maybe (OverlapMode GhcTc)
                           , ds_standalone_wildcard :: Maybe SrcSpan
                               -- See Note [Inferring the instance context]
                               -- in GHC.Tc.Deriv.Infer


=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -2535,12 +2535,12 @@ reifyClassInstance is_poly_tvs i
      cls_tc   = classTyCon cls
      dfun     = instanceDFunId i
      over     = case overlapMode (is_flag i) of
-                  NoOverlap _     -> Nothing
-                  Overlappable _  -> Just TH.Overlappable
-                  Overlapping _   -> Just TH.Overlapping
-                  Overlaps _      -> Just TH.Overlaps
-                  Incoherent _    -> Just TH.Incoherent
-                  NonCanonical _  -> Just TH.Incoherent
+                  NoOverlap _                    -> Nothing
+                  Overlappable _                 -> Just TH.Overlappable
+                  Overlapping _                  -> Just TH.Overlapping
+                  Overlaps _                     -> Just TH.Overlaps
+                  Incoherent _                   -> Just TH.Incoherent
+                  XOverlapMode (NonCanonical _)  -> Just TH.Incoherent
 
 ------------------------------
 reifyFamilyInstances :: TyCon -> [FamInst] -> TcM [TH.Dec]


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -543,7 +543,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_ext = lwarn
                 -- Dfun location is that of instance *header*
 
         ; let warn = fmap unLoc lwarn
-        ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name
+        ; ispec <- newClsInst (fmap (convertOverlapMode . unLoc) overlap_mode) dfun_name
                               tyvars theta clas inst_tys warn
 
         ; let inst_binds = InstBindings


=====================================
compiler/GHC/Tc/Utils/Instantiate.hs
=====================================
@@ -940,7 +940,7 @@ hasFixedRuntimeRepRes std_nm user_expr ty = mapM_ do_check mb_arity
 ************************************************************************
 -}
 
-getOverlapFlag :: Maybe OverlapMode   -- User pragma if any
+getOverlapFlag :: Maybe (OverlapMode GhcTc)  -- User pragma if any
                -> TcM OverlapFlag
 -- Construct the OverlapFlag from the global module flags,
 -- but if the overlap_mode argument is (Just m),
@@ -974,7 +974,7 @@ getOverlapFlag overlap_mode_prag
               -- See GHC.Core.InstEnv Note [Coherence and specialisation: overview]
               final_overlap_mode
                 | Incoherent s <- overlap_mode
-                , noncanonical_incoherence       = NonCanonical s
+                , noncanonical_incoherence       = XOverlapMode (NonCanonical s)
                 | otherwise                      = overlap_mode
 
         ; return (OverlapFlag { isSafeOverlap = safeLanguageOn dflags
@@ -985,7 +985,7 @@ tcGetInsts :: TcM [ClsInst]
 -- Gets the local class instances.
 tcGetInsts = fmap tcg_insts getGblEnv
 
-newClsInst :: Maybe OverlapMode   -- User pragma
+newClsInst :: Maybe (OverlapMode GhcTc)  -- User pragma
            -> Name -> [TyVar] -> ThetaType
            -> Class -> [Type] -> Maybe (WarningTxt GhcRn) -> TcM ClsInst
 newClsInst overlap_mode dfun_name tvs theta clas tys warn


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -45,9 +45,6 @@ module GHC.Types.Basic (
 
         TopLevelFlag(..), isTopLevel, isNotTopLevel,
 
-        OverlapFlag(..), OverlapMode(..), setOverlapModeMaybe,
-        hasOverlappingFlag, hasOverlappableFlag, hasIncoherentFlag, hasNonCanonicalFlag,
-
         Boxity(..), isBoxed,
 
         CbvMark(..), isMarkedCbv,
@@ -619,174 +616,6 @@ of whether we should do pattern-match checks; see the calls of the requiresPMC
 function (e.g. isMatchContextPmChecked and needToRunPmCheck in GHC.HsToCore.Pmc.Utils).
 -}
 
-{-
-************************************************************************
-*                                                                      *
-                Instance overlap flag
-*                                                                      *
-************************************************************************
--}
-
--- | The semantics allowed for overlapping instances for a particular
--- instance. See Note [Safe Haskell isSafeOverlap] in GHC.Core.InstEnv for a
--- explanation of the `isSafeOverlap` field.
---
--- - 'GHC.Parser.Annotation.AnnKeywordId' :
---      'GHC.Parser.Annotation.AnnOpen' @'\{-\# OVERLAPPABLE'@ or
---                              @'\{-\# OVERLAPPING'@ or
---                              @'\{-\# OVERLAPS'@ or
---                              @'\{-\# INCOHERENT'@,
---      'GHC.Parser.Annotation.AnnClose' @`\#-\}`@,
-
--- For details on above see Note [exact print annotations] in "GHC.Parser.Annotation"
-data OverlapFlag = OverlapFlag
-  { overlapMode   :: OverlapMode
-  , isSafeOverlap :: Bool
-  } deriving (Eq, Data)
-
-setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
-setOverlapModeMaybe f Nothing  = f
-setOverlapModeMaybe f (Just m) = f { overlapMode = m }
-
-hasIncoherentFlag :: OverlapMode -> Bool
-hasIncoherentFlag mode =
-  case mode of
-    Incoherent   _ -> True
-    NonCanonical _ -> True
-    _              -> False
-
-hasOverlappableFlag :: OverlapMode -> Bool
-hasOverlappableFlag mode =
-  case mode of
-    Overlappable _ -> True
-    Overlaps     _ -> True
-    Incoherent   _ -> True
-    NonCanonical _ -> True
-    _              -> False
-
-hasOverlappingFlag :: OverlapMode -> Bool
-hasOverlappingFlag mode =
-  case mode of
-    Overlapping  _ -> True
-    Overlaps     _ -> True
-    Incoherent   _ -> True
-    NonCanonical _ -> True
-    _              -> False
-
-hasNonCanonicalFlag :: OverlapMode -> Bool
-hasNonCanonicalFlag = \case
-  NonCanonical{} -> True
-  _              -> False
-
-data OverlapMode  -- See Note [Rules for instance lookup] in GHC.Core.InstEnv
-  = NoOverlap SourceText
-                  -- See Note [Pragma source text]
-    -- ^ This instance must not overlap another `NoOverlap` instance.
-    -- However, it may be overlapped by `Overlapping` instances,
-    -- and it may overlap `Overlappable` instances.
-
-
-  | Overlappable SourceText
-                  -- See Note [Pragma source text]
-    -- ^ Silently ignore this instance if you find a
-    -- more specific one that matches the constraint
-    -- you are trying to resolve
-    --
-    -- Example: constraint (Foo [Int])
-    --   instance                      Foo [Int]
-    --   instance {-# OVERLAPPABLE #-} Foo [a]
-    --
-    -- Since the second instance has the Overlappable flag,
-    -- the first instance will be chosen (otherwise
-    -- its ambiguous which to choose)
-
-
-  | Overlapping SourceText
-                  -- See Note [Pragma source text]
-    -- ^ Silently ignore any more general instances that may be
-    --   used to solve the constraint.
-    --
-    -- Example: constraint (Foo [Int])
-    --   instance {-# OVERLAPPING #-} Foo [Int]
-    --   instance                     Foo [a]
-    --
-    -- Since the first instance has the Overlapping flag,
-    -- the second---more general---instance will be ignored (otherwise
-    -- it is ambiguous which to choose)
-
-
-  | Overlaps SourceText
-                  -- See Note [Pragma source text]
-    -- ^ Equivalent to having both `Overlapping` and `Overlappable` flags.
-
-  | Incoherent SourceText
-                  -- See Note [Pragma source text]
-    -- ^ Behave like Overlappable and Overlapping, and in addition pick
-    -- an arbitrary one if there are multiple matching candidates, and
-    -- don't worry about later instantiation
-    --
-    -- Example: constraint (Foo [b])
-    -- instance {-# INCOHERENT -} Foo [Int]
-    -- instance                   Foo [a]
-    -- Without the Incoherent flag, we'd complain that
-    -- instantiating 'b' would change which instance
-    -- was chosen. See also Note [Incoherent instances] in "GHC.Core.InstEnv"
-
-  | NonCanonical SourceText
-    -- ^ Behave like Incoherent, but the instance choice is observable
-    -- by the program behaviour. See Note [Coherence and specialisation: overview].
-    --
-    -- We don't have surface syntax for the distinction between
-    -- Incoherent and NonCanonical instances; instead, the flag
-    -- `-f{no-}specialise-incoherents` (on by default) controls
-    -- whether `INCOHERENT` instances are regarded as Incoherent or
-    -- NonCanonical.
-
-  deriving (Eq, Data)
-
-
-instance Outputable OverlapFlag where
-   ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag)
-
-instance Outputable OverlapMode where
-   ppr (NoOverlap    _) = empty
-   ppr (Overlappable _) = text "[overlappable]"
-   ppr (Overlapping  _) = text "[overlapping]"
-   ppr (Overlaps     _) = text "[overlap ok]"
-   ppr (Incoherent   _) = text "[incoherent]"
-   ppr (NonCanonical _) = text "[noncanonical]"
-
-instance Binary OverlapMode where
-    put_ bh (NoOverlap    s) = putByte bh 0 >> put_ bh s
-    put_ bh (Overlaps     s) = putByte bh 1 >> put_ bh s
-    put_ bh (Incoherent   s) = putByte bh 2 >> put_ bh s
-    put_ bh (Overlapping  s) = putByte bh 3 >> put_ bh s
-    put_ bh (Overlappable s) = putByte bh 4 >> put_ bh s
-    put_ bh (NonCanonical s) = putByte bh 5 >> put_ bh s
-    get bh = do
-        h <- getByte bh
-        case h of
-            0 -> (get bh) >>= \s -> return $ NoOverlap s
-            1 -> (get bh) >>= \s -> return $ Overlaps s
-            2 -> (get bh) >>= \s -> return $ Incoherent s
-            3 -> (get bh) >>= \s -> return $ Overlapping s
-            4 -> (get bh) >>= \s -> return $ Overlappable s
-            5 -> (get bh) >>= \s -> return $ NonCanonical s
-            _ -> panic ("get OverlapMode" ++ show h)
-
-
-instance Binary OverlapFlag where
-    put_ bh flag = do put_ bh (overlapMode flag)
-                      put_ bh (isSafeOverlap flag)
-    get bh = do
-        h <- get bh
-        b <- get bh
-        return OverlapFlag { overlapMode = h, isSafeOverlap = b }
-
-pprSafeOverlap :: Bool -> SDoc
-pprSafeOverlap True  = text "[safe]"
-pprSafeOverlap False = empty
-
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -612,7 +612,7 @@ mkDataConWorkId wkr_name data_con
                    `setLFInfo`             wkr_lf_info
           -- No strictness: see Note [Data-con worker strictness] in GHC.Core.DataCon
 
-    wkr_inline_prag = defaultInlinePragma { inl_rule = ConLike }
+    wkr_inline_prag = set_pragma_rule defaultInlinePragma ConLike
     wkr_arity = dataConRepArity data_con
 
     -- See Note [LFInfo of DataCon workers and wrappers]


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -98,8 +98,8 @@ import Language.Haskell.Syntax.Type
 import Language.Haskell.Syntax.Basic (Role, LexicalFixity, TyConFlavour(..), TypeOrData(..))
 import Language.Haskell.Syntax.Specificity (Specificity)
 import Language.Haskell.Syntax.InlinePragma(Activation)
-
-import GHC.Types.Basic (OverlapMode, RuleName)
+import Language.Haskell.Syntax.OverlapPragma(LOverlapMode)
+import GHC.Types.Basic (RuleName)
 import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
 
 import GHC.Unit.Module.Warnings (WarningTxt)
@@ -1383,7 +1383,7 @@ data ClsInstDecl pass
       , cid_sigs          :: [LSig pass]         -- User-supplied pragmatic info
       , cid_tyfam_insts   :: [LTyFamInstDecl pass]   -- Type family instances
       , cid_datafam_insts :: [LDataFamInstDecl pass] -- Data family instances
-      , cid_overlap_mode  :: Maybe (XRec pass OverlapMode)
+      , cid_overlap_mode  :: Maybe (LOverlapMode pass)
          -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
          --                                    'GHC.Parser.Annotation.AnnClose',
 
@@ -1436,7 +1436,7 @@ data DerivDecl pass = DerivDecl
           -- See Note [Inferring the instance context] in GHC.Tc.Deriv.Infer.
 
         , deriv_strategy     :: Maybe (LDerivStrategy pass)
-        , deriv_overlap_mode :: Maybe (XRec pass OverlapMode)
+        , deriv_overlap_mode :: Maybe (LOverlapMode pass)
          -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDeriving',
          --        'GHC.Parser.Annotation.AnnInstance', 'GHC.Parser.Annotation.AnnStock',
          --        'GHC.Parser.Annotation.AnnAnyClass', 'GHC.Parser.Annotation.AnnNewtype',


=====================================
compiler/Language/Haskell/Syntax/Extension.hs
=====================================
@@ -735,7 +735,7 @@ type family XOpaque    p
 type family XNoUserInlinePrag p
 type family XXInlineSpec   p
 
--- Activaiton
+-- Activation
 type family XAlwaysActive p
 type family XActiveBefore p
 type family XActiveAfter  p
@@ -743,6 +743,17 @@ type family XFinalActive  p
 type family XNeverActive  p
 type family XXActivation  p
 
+
+-- -------------------------------------
+-- Overlap pragma
+
+type family XNoOverlap p
+type family XOverlappable p
+type family XOverlapping p
+type family XOverlaps p
+type family XIncoherent p
+type family XXOverlapMode p
+
 -- =====================================================================
 -- Misc
 


=====================================
compiler/Language/Haskell/Syntax/InlinePragma.hs
=====================================
@@ -55,7 +55,7 @@ type PhaseNum = Int  -- Compilation phase
 -- | Rule Match Information
 data RuleMatchInfo = ConLike -- See Note [CONLIKE pragma] in GHC.Hs.InlinePragma
                    | FunLike
-                   deriving( Eq, Data, Show )
+                   deriving( Eq, Show )
   -- Show needed for GHC.Parser.Lexer
 
 isConLike :: RuleMatchInfo -> Bool


=====================================
compiler/Language/Haskell/Syntax/OverlapPragma.hs
=====================================
@@ -0,0 +1,72 @@
+module Language.Haskell.Syntax.OverlapPragma where
+
+import Language.Haskell.Syntax.Extension
+
+-- | The semantics allowed for overlapping instances for a particular
+-- instance. See Note [Safe Haskell isSafeOverlap] in GHC.Core.InstEnv for a
+-- explanation of the `isSafeOverlap` field.
+--
+-- - 'GHC.Parser.Annotation.AnnKeywordId' :
+--      'GHC.Parser.Annotation.AnnOpen' @'\{-\# OVERLAPPABLE'@ or
+--                              @'\{-\# OVERLAPPING'@ or
+--                              @'\{-\# OVERLAPS'@ or
+--                              @'\{-\# INCOHERENT'@,
+--      'GHC.Parser.Annotation.AnnClose' @`\#-\}`@,
+
+type LOverlapMode p = XRec p (OverlapMode p)
+data OverlapMode p -- See Note [Rules for instance lookup] in GHC.Core.InstEnv
+  = NoOverlap (XNoOverlap p)
+                  -- See Note [Pragma source text]
+    -- ^ This instance must not overlap another `NoOverlap` instance.
+    -- However, it may be overlapped by `Overlapping` instances,
+    -- and it may overlap `Overlappable` instances.
+
+
+  | Overlappable (XOverlappable p)
+                  -- See Note [Pragma source text]
+    -- ^ Silently ignore this instance if you find a
+    -- more specific one that matches the constraint
+    -- you are trying to resolve
+    --
+    -- Example: constraint (Foo [Int])
+    --   instance                      Foo [Int]
+    --   instance {-# OVERLAPPABLE #-} Foo [a]
+    --
+    -- Since the second instance has the Overlappable flag,
+    -- the first instance will be chosen (otherwise
+    -- its ambiguous which to choose)
+
+
+  | Overlapping (XOverlapping p)
+                  -- See Note [Pragma source text]
+    -- ^ Silently ignore any more general instances that may be
+    --   used to solve the constraint.
+    --
+    -- Example: constraint (Foo [Int])
+    --   instance {-# OVERLAPPING #-} Foo [Int]
+    --   instance                     Foo [a]
+    --
+    -- Since the first instance has the Overlapping flag,
+    -- the second---more general---instance will be ignored (otherwise
+    -- it is ambiguous which to choose)
+
+
+  | Overlaps (XOverlaps p)
+                  -- See Note [Pragma source text]
+    -- ^ Equivalent to having both `Overlapping` and `Overlappable` flags.
+
+  | Incoherent (XIncoherent p)
+                  -- See Note [Pragma source text]
+    -- ^ Behave like Overlappable and Overlapping, and in addition pick
+    -- an arbitrary one if there are multiple matching candidates, and
+    -- don't worry about later instantiation
+    --
+    -- Example: constraint (Foo [b])
+    -- instance {-# INCOHERENT -} Foo [Int]
+    -- instance                   Foo [a]
+    -- Without the Incoherent flag, we'd complain that
+    -- instantiating 'b' would change which instance
+    -- was chosen. See also Note [Incoherent instances] in "GHC.Core.InstEnv"
+
+  | XOverlapMode (XXOverlapMode p)
+


=====================================
compiler/ghc.cabal.in
=====================================
@@ -548,6 +548,7 @@ Library
         GHC.Hs.Specificity
         GHC.Hs.Stats
         GHC.Hs.InlinePragma
+        GHC.Hs.OverlapPragma
         GHC.HsToCore
         GHC.HsToCore.Arrows
         GHC.HsToCore.Binds
@@ -1001,6 +1002,7 @@ Library
         Language.Haskell.Syntax.Specificity
         Language.Haskell.Syntax.Type
         Language.Haskell.Syntax.InlinePragma
+        Language.Haskell.Syntax.OverlapPragma
 
     autogen-modules: GHC.Platform.Constants
                      GHC.Settings.Config


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -47,6 +47,8 @@ import GHC.Types.PkgQual
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc
 import GHC.Types.Var
+import GHC.Hs.OverlapPragma
+import GHC.Hs.InlinePragma
 import GHC.Unit.Module.Warnings
 import GHC.Utils.Misc
 import GHC.Utils.Outputable hiding ( (<>) )
@@ -2487,7 +2489,7 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (LocatedP OverlapMode) where
+instance ExactPrint (LOverlapMode (GhcPass p)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -801,6 +801,15 @@ renameInstD (DataFamInstD{dfid_inst = d}) = do
   d' <- renameDataFamInstD d
   return (DataFamInstD{dfid_ext = noExtField, dfid_inst = d'})
 
+convert_overlap_mode :: OverlapMode (GhcPass p) -> OverlapMode DocNameI
+convert_overlap_mode = \case
+  NoOverlap    _                -> NoOverlap noExtField
+  Overlappable _                -> Overlappable noExtField
+  Overlapping  _                -> Overlapping noExtField
+  Overlaps     _                -> Overlaps noExtField
+  Incoherent   _                -> Incoherent noExtField
+  XOverlapMode (NonCanonical _) -> XOverlapMode NonCanon
+
 renameDerivD :: DerivDecl GhcRn -> RnM (DerivDecl DocNameI)
 renameDerivD
   ( DerivDecl
@@ -816,9 +825,9 @@ renameDerivD
           { deriv_ext = noExtField
           , deriv_type = ty'
           , deriv_strategy = strat'
-          , deriv_overlap_mode = omode
+          , deriv_overlap_mode = fmap (fmap convert_overlap_mode) omode
           }
-      )
+      ) 
 
 renameDerivStrategy :: DerivStrategy GhcRn -> RnM (DerivStrategy DocNameI)
 renameDerivStrategy (StockStrategy a) = pure (StockStrategy a)
@@ -841,7 +850,7 @@ renameClsInstD
     return
       ( ClsInstDecl
           { cid_ext = noExtField
-          , cid_overlap_mode = omode
+          , cid_overlap_mode = fmap (fmap convert_overlap_mode)  omode
           , cid_poly_ty = ltype'
           , cid_binds = []
           , cid_sigs = []


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -972,6 +972,15 @@ type instance XCFunDep DocNameI = NoExtField
 
 type instance XCTyFamInstDecl DocNameI = NoExtField
 
+type instance Anno (OverlapMode DocNameI) = SrcSpanAnnP
+type instance XNoOverlap    DocNameI = NoExtField
+type instance XOverlappable DocNameI = NoExtField
+type instance XOverlapping  DocNameI = NoExtField
+type instance XOverlaps     DocNameI = NoExtField
+type instance XIncoherent   DocNameI = NoExtField
+type instance XXOverlapMode DocNameI = NonCanon
+data NonCanon = NonCanon -- no longer need the source text :relieved:
+
 -----------------------------------------------------------------------------
 
 -- * NFData instances for GHC types



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/099159094092132eca2e32569d66c9f42871d899

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 13:26:52 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 21 Oct 2024 09:26:52 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] move RuleName to L.H.S.Basic
Message-ID: <6716569cebd3e_1702be517d1858567@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
b83a69b1 by Hassan Al-Awwadi at 2024-10-21T15:26:36+02:00
move RuleName to L.H.S.Basic

- - - - -


3 changed files:

- compiler/GHC/Types/Basic.hs
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Decls.hs


Changes:

=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -102,16 +102,15 @@ module GHC.Types.Basic (
 import GHC.Prelude
 
 import GHC.ForeignSrcLang
-import GHC.Data.FastString
 import GHC.Utils.Outputable
 import GHC.Utils.Panic ( panic )
 import GHC.Utils.Binary
-import GHC.Types.SourceText
 import qualified GHC.LanguageExtensions as LangExt
 
 import Language.Haskell.Syntax.Basic  (Boxity(..), isBoxed, ConTag, TyConFlavour(..)
                                       , TypeOrData(..), tyConFlavourAssoc_maybe
-                                      , Arity, VisArity, RepArity, JoinArity, FullArgCount,
+                                      , Arity, VisArity, RepArity, JoinArity, FullArgCount
+                                      , RuleName
                                       )
 import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted)
 import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour)
@@ -404,7 +403,6 @@ instance Binary FunctionOrData where
 ************************************************************************
 -}
 
-type RuleName = FastString
 
 pprRuleName :: RuleName -> SDoc
 pprRuleName rn = doubleQuotes (ftext rn)


=====================================
compiler/Language/Haskell/Syntax/Basic.hs
=====================================
@@ -12,6 +12,16 @@ import GHC.Data.FastString (FastString)
 import GHC.Prelude (Functor, Maybe(..))
 import Control.DeepSeq
 
+{-
+************************************************************************
+*                                                                      *
+                Rules
+*                                                                      *
+************************************************************************
+-}
+
+type RuleName = FastString
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -95,11 +95,10 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
 import Language.Haskell.Syntax.Binds
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
-import Language.Haskell.Syntax.Basic (Role, LexicalFixity, TyConFlavour(..), TypeOrData(..))
+import Language.Haskell.Syntax.Basic (Role, LexicalFixity, TyConFlavour(..), TypeOrData(..), RuleName)
 import Language.Haskell.Syntax.Specificity (Specificity)
 import Language.Haskell.Syntax.InlinePragma(Activation)
 import Language.Haskell.Syntax.OverlapPragma(LOverlapMode)
-import GHC.Types.Basic (RuleName)
 import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec)
 
 import GHC.Unit.Module.Warnings (WarningTxt)



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 13:30:49 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 21 Oct 2024 09:30:49 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] cleanup
Message-ID: <67165789a1e9b_1702be55983058739@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
f2131576 by Hassan Al-Awwadi at 2024-10-21T15:30:31+02:00
cleanup

- - - - -


3 changed files:

- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Hs/OverlapPragma.hs
- compiler/GHC/Iface/Syntax.hs


Changes:

=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -38,6 +38,7 @@ import Language.Haskell.Syntax.Basic(Arity)
 import Language.Haskell.Syntax.InlinePragma
 import Language.Haskell.Syntax.Extension
 import GHC.Data.FastString (fsLit)
+import GHC.Utils.Binary (Binary, put_, get, putByte, getByte)
 
 {-
 ************************************************************************
@@ -583,3 +584,11 @@ pprInline' emptyInline (InlinePragma
       pp_info | isFunLike info = empty
               | otherwise      = ppr info
 pprInline' _ (XCInlinePragma impossible) = dataConCantHappen impossible
+
+instance Binary RuleMatchInfo where
+    put_ bh FunLike = putByte bh 0
+    put_ bh ConLike = putByte bh 1
+    get bh = do
+            h <- getByte bh
+            if h == 1 then return ConLike
+                      else return FunLike
\ No newline at end of file


=====================================
compiler/GHC/Hs/OverlapPragma.hs
=====================================
@@ -13,13 +13,15 @@ module GHC.Hs.OverlapPragma(
   , convertOverlapMode
 ) where
 
+import GHC.Prelude
+
 import Language.Haskell.Syntax.OverlapPragma
-import Language.Haskell.Syntax.Extension 
+import Language.Haskell.Syntax.Extension
 
-import GHC.Prelude
-import GHC.Types.SourceText 
 import GHC.Hs.Extension (GhcPass, GhcTc)
 
+import GHC.Types.SourceText
+
 import GHC.Utils.Binary
 import GHC.Utils.Outputable
 
@@ -47,7 +49,7 @@ newtype NonCanonical = NonCanonical SourceText
 
 
 -----------------------
--- converting 
+-- converting
 convertOverlapMode :: OverlapMode (GhcPass p) -> OverlapMode (GhcPass p')
 convertOverlapMode = \case
   NoOverlap s    -> NoOverlap s
@@ -110,8 +112,9 @@ instance Binary OverlapFlag where
         b <- get bh
         return OverlapFlag { overlapMode = h, isSafeOverlap = b }
 
+
 ------------------------
--- helper functions 
+-- helper functions
 hasIncoherentFlag :: OverlapMode (GhcPass p) -> Bool
 hasIncoherentFlag = \case
   Incoherent   _                -> True
@@ -127,7 +130,7 @@ hasOverlappableFlag = \case
   _                             -> False
 
 hasOverlappingFlag :: OverlapMode (GhcPass p) -> Bool
-hasOverlappingFlag = \case 
+hasOverlappingFlag = \case
   Overlapping  _                -> True
   Overlaps     _                -> True
   Incoherent   _                -> True


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -1689,14 +1689,6 @@ instance Binary IfaceActivation where
                       ab <- get bh
                       return (IfActiveAfter src ab)
 
-instance Binary RuleMatchInfo where
-    put_ bh FunLike = putByte bh 0
-    put_ bh ConLike = putByte bh 1
-    get bh = do
-            h <- getByte bh
-            if h == 1 then return ConLike
-                      else return FunLike
-
 instance Binary IfaceInlineSpec where
     put_ bh  IfNoUserInlinePrag  = putByte bh 0
     put_ bh (IfInline s)         = do putByte bh 1



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 15:14:19 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 11:14:19 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: EPA: Remove
 [AddEpAnn] Commit 5
Message-ID: <67166fcbb035b_291e2b69f1b81206d3@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
bad6a849 by Andrzej Rybczak at 2024-10-21T11:13:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
46c8e121 by Cheng Shao at 2024-10-21T11:13:41-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content.

- - - - -


25 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- hadrian/src/Rules/BinaryDist.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/jsffi/dyld.mjs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -35,6 +35,7 @@ module GHC.Hs.Decls (
   AnnClassDecl(..),
   AnnSynDecl(..),
   AnnFamilyDecl(..),
+  AnnClsInstDecl(..),
   TyClGroup(..),
   tyClGroupTyClDecls, tyClGroupInstDecls, tyClGroupRoleDecls,
   tyClGroupKindSigs,
@@ -59,7 +60,7 @@ module GHC.Hs.Decls (
   LClsInstDecl, ClsInstDecl(..),
 
   -- ** Standalone deriving declarations
-  DerivDecl(..), LDerivDecl,
+  DerivDecl(..), LDerivDecl, AnnDerivDecl,
   -- ** Deriving strategies
   DerivStrategy(..), LDerivStrategy,
   derivStrategyName, foldDerivStrategy, mapDerivStrategy,
@@ -80,7 +81,9 @@ module GHC.Hs.Decls (
   CImportSpec(..),
   -- ** Data-constructor declarations
   ConDecl(..), LConDecl,
-  HsConDeclH98Details, HsConDeclGADTDetails(..), hsConDeclTheta,
+  HsConDeclH98Details, HsConDeclGADTDetails(..),
+  AnnConDeclH98(..), AnnConDeclGADT(..),
+  hsConDeclTheta,
   getConNames, getRecConArgs_maybe,
   -- ** Document comments
   DocDecl(..), LDocDecl, docDeclDoc,
@@ -705,7 +708,7 @@ instance OutputableBndrId p
 type instance XCHsDataDefn    (GhcPass _) = AnnDataDefn
 type instance XXHsDataDefn    (GhcPass _) = DataConCantHappen
 
-type instance XCHsDerivingClause    (GhcPass _) = [AddEpAnn]
+type instance XCHsDerivingClause    (GhcPass _) = EpToken "deriving"
 type instance XXHsDerivingClause    (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -741,7 +744,7 @@ instance OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) where
   ppr (DctSingle _ ty) = ppr ty
   ppr (DctMulti _ tys) = parens (interpp'SP tys)
 
-type instance XStandaloneKindSig GhcPs = [AddEpAnn]
+type instance XStandaloneKindSig GhcPs = (EpToken "type", TokDcolon)
 type instance XStandaloneKindSig GhcRn = NoExtField
 type instance XStandaloneKindSig GhcTc = NoExtField
 
@@ -750,11 +753,11 @@ type instance XXStandaloneKindSig (GhcPass p) = DataConCantHappen
 standaloneKindSigName :: StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
 standaloneKindSigName (StandaloneKindSig _ lname _) = unLoc lname
 
-type instance XConDeclGADT GhcPs = (EpUniToken "::" "∷", [AddEpAnn])
+type instance XConDeclGADT GhcPs = AnnConDeclGADT
 type instance XConDeclGADT GhcRn = NoExtField
 type instance XConDeclGADT GhcTc = NoExtField
 
-type instance XConDeclH98  GhcPs = [AddEpAnn]
+type instance XConDeclH98  GhcPs = AnnConDeclH98
 type instance XConDeclH98  GhcRn = NoExtField
 type instance XConDeclH98  GhcTc = NoExtField
 
@@ -768,6 +771,26 @@ type instance XRecConGADT          GhcTc = NoExtField
 
 type instance XXConDeclGADTDetails (GhcPass _) = DataConCantHappen
 
+data AnnConDeclH98
+  = AnnConDeclH98 {
+    acdh_forall  :: TokForall,
+    acdh_dot :: EpToken ".",
+    acdh_darrow :: TokDarrow
+  } deriving Data
+
+instance NoAnn AnnConDeclH98 where
+  noAnn = AnnConDeclH98 noAnn noAnn noAnn
+
+data AnnConDeclGADT
+  = AnnConDeclGADT {
+    acdg_openp  :: [EpToken "("],
+    acdg_closep :: [EpToken ")"],
+    acdg_dcolon :: TokDcolon
+  } deriving Data
+
+instance NoAnn AnnConDeclGADT where
+  noAnn = AnnConDeclGADT noAnn noAnn noAnn
+
 -- Codomain could be 'NonEmpty', but at the moment all users need a list.
 getConNames :: ConDecl GhcRn -> [LocatedN Name]
 getConNames ConDeclH98  {con_name  = name}  = [name]
@@ -901,7 +924,7 @@ type instance XCClsInstDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                              -- The warning of the deprecated instance
                                              -- See Note [Implementation of deprecated instances]
                                              -- in GHC.Tc.Solver.Dict
-                                       , [AddEpAnn]
+                                       , AnnClsInstDecl
                                        , AnnSortKey DeclTag) -- For sorting the additional annotations
                                         -- TODO:AZ:tidy up
 type instance XCClsInstDecl    GhcRn = Maybe (LWarningTxt GhcRn)
@@ -924,6 +947,18 @@ type instance XTyFamInstD   GhcTc = NoExtField
 
 type instance XXInstDecl    (GhcPass _) = DataConCantHappen
 
+data AnnClsInstDecl
+  = AnnClsInstDecl {
+    acid_instance :: EpToken "instance",
+    acid_where    :: EpToken "where",
+    acid_openc    :: EpToken "{",
+    acid_semis    :: [EpToken ";"],
+    acid_closec   :: EpToken "}"
+  } deriving Data
+
+instance NoAnn AnnClsInstDecl where
+  noAnn = AnnClsInstDecl noAnn noAnn noAnn noAnn noAnn
+
 cidDeprecation :: forall p. IsPass p
                => ClsInstDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1086,15 +1121,17 @@ type instance XCDerivDecl    GhcPs = ( Maybe (LWarningTxt GhcPs)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
+                                     , AnnDerivDecl )
 type instance XCDerivDecl    GhcRn = ( Maybe (LWarningTxt GhcRn)
                                            -- The warning of the deprecated derivation
                                            -- See Note [Implementation of deprecated instances]
                                            -- in GHC.Tc.Solver.Dict
-                                     , [AddEpAnn] )
-type instance XCDerivDecl    GhcTc = [AddEpAnn]
+                                     , AnnDerivDecl )
+type instance XCDerivDecl    GhcTc = AnnDerivDecl
 type instance XXDerivDecl    (GhcPass _) = DataConCantHappen
 
+type AnnDerivDecl = (EpToken "deriving", EpToken "instance")
+
 derivDeprecation :: forall p. IsPass p
                => DerivDecl (GhcPass p)
                -> Maybe (WarningTxt (GhcPass p))
@@ -1128,15 +1165,15 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XStockStrategy    GhcPs = [AddEpAnn]
+type instance XStockStrategy    GhcPs = EpToken "stock"
 type instance XStockStrategy    GhcRn = NoExtField
 type instance XStockStrategy    GhcTc = NoExtField
 
-type instance XAnyClassStrategy GhcPs = [AddEpAnn]
+type instance XAnyClassStrategy GhcPs = EpToken "anyclass"
 type instance XAnyClassStrategy GhcRn = NoExtField
 type instance XAnyClassStrategy GhcTc = NoExtField
 
-type instance XNewtypeStrategy  GhcPs = [AddEpAnn]
+type instance XNewtypeStrategy  GhcPs = EpToken "newtype"
 type instance XNewtypeStrategy  GhcRn = NoExtField
 type instance XNewtypeStrategy  GhcTc = NoExtField
 
@@ -1144,7 +1181,7 @@ type instance XViaStrategy GhcPs = XViaStrategyPs
 type instance XViaStrategy GhcRn = LHsSigType GhcRn
 type instance XViaStrategy GhcTc = Type
 
-data XViaStrategyPs = XViaStrategyPs [AddEpAnn] (LHsSigType GhcPs)
+data XViaStrategyPs = XViaStrategyPs (EpToken "via") (LHsSigType GhcPs)
 
 instance OutputableBndrId p
         => Outputable (DerivStrategy (GhcPass p)) where
@@ -1202,11 +1239,11 @@ instance OutputableBndrId p
 ************************************************************************
 -}
 
-type instance XForeignImport   GhcPs = [AddEpAnn]
+type instance XForeignImport   GhcPs = (EpToken "foreign", EpToken "import", TokDcolon)
 type instance XForeignImport   GhcRn = NoExtField
 type instance XForeignImport   GhcTc = Coercion
 
-type instance XForeignExport   GhcPs = [AddEpAnn]
+type instance XForeignExport   GhcPs = (EpToken "foreign", EpToken "export", TokDcolon)
 type instance XForeignExport   GhcRn = NoExtField
 type instance XForeignExport   GhcTc = Coercion
 
@@ -1218,6 +1255,7 @@ type instance XXForeignImport  (GhcPass _) = DataConCantHappen
 type instance XCExport (GhcPass _) = LocatedE SourceText -- original source text for the C entity
 type instance XXForeignExport  (GhcPass _) = DataConCantHappen
 
+
 -- pretty printing of foreign declarations
 
 instance OutputableBndrId p
@@ -1362,7 +1400,7 @@ type instance XWarnings      GhcTc = SourceText
 
 type instance XXWarnDecls    (GhcPass _) = DataConCantHappen
 
-type instance XWarning      (GhcPass _) = (NamespaceSpecifier, [AddEpAnn])
+type instance XWarning      (GhcPass _) = (NamespaceSpecifier, (EpToken "[", EpToken "]"))
 type instance XXWarnDecl    (GhcPass _) = DataConCantHappen
 
 
@@ -1418,7 +1456,7 @@ pprAnnProvenance (TypeAnnProvenance (L _ name))
 ************************************************************************
 -}
 
-type instance XCRoleAnnotDecl GhcPs = [AddEpAnn]
+type instance XCRoleAnnotDecl GhcPs = (EpToken "type", EpToken "role")
 type instance XCRoleAnnotDecl GhcRn = NoExtField
 type instance XCRoleAnnotDecl GhcTc = NoExtField
 


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -81,6 +81,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annSynDecl
               `extQ` annDataDefn
               `extQ` annFamilyDecl
+              `extQ` annClsInstDecl
               `extQ` lit `extQ` litr `extQ` litt
               `extQ` sourceText
               `extQ` deltaPos
@@ -262,6 +263,15 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                  showAstData' g, showAstData' h, showAstData' i,
                                  showAstData' j, showAstData' k, showAstData' l]
 
+            annClsInstDecl :: AnnClsInstDecl -> SDoc
+            annClsInstDecl (AnnClsInstDecl a b c d e) = case ba of
+             BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnFamilyDecl"
+             NoBlankEpAnnotations ->
+              parens $ text "AnnClsInstDecl"
+                        $$ vcat [showAstData' a, showAstData' b, showAstData' c,
+                                 showAstData' d, showAstData' e]
+
+
             addEpAnn :: AddEpAnn -> SDoc
             addEpAnn (AddEpAnn a s) = case ba of
              BlankEpAnnotations -> parens
@@ -294,7 +304,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             epTokenInstance :: EpToken "instance" -> SDoc
             epTokenInstance = epToken'
 
-            epTokenForall :: EpUniToken "forall" "∀" -> SDoc
+            epTokenForall :: TokForall -> SDoc
             epTokenForall = epUniToken'
 
             epToken' :: KnownSymbol sym => EpToken sym -> SDoc


=====================================
compiler/GHC/Hs/Type.hs
=====================================
@@ -163,15 +163,15 @@ getBangStrictness _ = (mkHsSrcBang NoSourceText NoSrcUnpack NoSrcStrict)
 fromMaybeContext :: Maybe (LHsContext (GhcPass p)) -> HsContext (GhcPass p)
 fromMaybeContext mctxt = unLoc $ fromMaybe (noLocA []) mctxt
 
-type instance XHsForAllVis   (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
+type instance XHsForAllVis   (GhcPass _) = EpAnn (TokForall, EpUniToken "->" "→")
                                            -- Location of 'forall' and '->'
-type instance XHsForAllInvis (GhcPass _) = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type instance XHsForAllInvis (GhcPass _) = EpAnn (TokForall, EpToken ".")
                                            -- Location of 'forall' and '.'
 
 type instance XXHsForAllTelescope (GhcPass _) = DataConCantHappen
 
-type EpAnnForallVis   = EpAnn (EpUniToken "forall" "∀", EpUniToken "->" "→")
-type EpAnnForallInvis = EpAnn (EpUniToken "forall" "∀", EpToken ".")
+type EpAnnForallVis   = EpAnn (TokForall, TokRarrow)
+type EpAnnForallInvis = EpAnn (TokForall, EpToken ".")
 
 type HsQTvsRn = [Name]  -- Implicit variables
   -- For example, in   data T (a :: k1 -> k2) = ...
@@ -461,7 +461,7 @@ type instance XListTy          (GhcPass _) = AnnParen
 type instance XTupleTy         (GhcPass _) = AnnParen
 type instance XSumTy           (GhcPass _) = AnnParen
 type instance XOpTy            (GhcPass _) = NoExtField
-type instance XParTy           (GhcPass _) = AnnParen
+type instance XParTy           (GhcPass _) = (EpToken "(", EpToken ")")
 type instance XIParamTy        (GhcPass _) = TokDcolon
 type instance XStarTy          (GhcPass _) = NoExtField
 type instance XKindSig         (GhcPass _) = TokDcolon
@@ -572,7 +572,7 @@ pprHsArrow (HsUnrestrictedArrow _) = pprArrowWithMultiplicity visArgTypeLike (Le
 pprHsArrow (HsLinearArrow _)       = pprArrowWithMultiplicity visArgTypeLike (Left True)
 pprHsArrow (HsExplicitMult _ p)    = pprArrowWithMultiplicity visArgTypeLike (Right (ppr p))
 
-type instance XConDeclField  (GhcPass _) = [AddEpAnn]
+type instance XConDeclField  (GhcPass _) = TokDcolon
 type instance XXConDeclField (GhcPass _) = DataConCantHappen
 
 instance OutputableBndrId p
@@ -710,23 +710,22 @@ mkHsAppKindTy at ty k = addCLocA ty k (HsAppKindTy at ty k)
 -- It returns API Annotations for any parens removed
 splitHsFunType ::
      LHsType (GhcPass p)
-  -> ( [AddEpAnn], EpAnnComments -- The locations of any parens and
+  -> ( ([EpToken "("], [EpToken ")"]) , EpAnnComments -- The locations of any parens and
                                   -- comments discarded
      , [HsScaled (GhcPass p) (LHsType (GhcPass p))], LHsType (GhcPass p))
 splitHsFunType ty = go ty
   where
-    go (L l (HsParTy an ty))
+    go (L l (HsParTy (op,cp) ty))
       = let
-          (anns, cs, args, res) = splitHsFunType ty
-          anns' = anns ++ annParen2AddEpAnn an
+          ((ops, cps), cs, args, res) = splitHsFunType ty
           cs' = cs S.<> epAnnComments l
-        in (anns', cs', args, res)
+        in ((ops++[op], cps ++ [cp]), cs', args, res)
 
     go (L ll (HsFunTy _ mult x y))
       | (anns, csy, args, res) <- splitHsFunType y
       = (anns, csy S.<> epAnnComments ll, HsScaled mult x:args, res)
 
-    go other = ([], emptyComments, [], other)
+    go other = (noAnn, emptyComments, [], other)
 
 -- | Retrieve the name of the \"head\" of a nested type application.
 -- This is somewhat like @GHC.Tc.Gen.HsType.splitHsAppTys@, but a little more


=====================================
compiler/GHC/JS/Ppr.hs
=====================================
@@ -33,7 +33,7 @@
 -- * Design
 --
 --     This module follows the architecture and style of the other backends in
---     GHC: it intances Outputable for the relevant types, creates a class that
+--     GHC: it instances Outputable for the relevant types, creates a class that
 --     describes a morphism from the IR domain to JavaScript concrete Syntax and
 --     then generates that syntax on a case by case basis.
 --


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1274,7 +1274,7 @@ topdecl :: { LHsDecl GhcPs }
         | stand_alone_deriving                  { L (getLoc $1) (DerivD noExtField (unLoc $1)) }
         | role_annot                            { L (getLoc $1) (RoleAnnotD noExtField (unLoc $1)) }
         | default_decl                          { L (getLoc $1) (DefD noExtField (unLoc $1)) }
-        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((snd $ unLoc $2) (mj AnnForeign $1:(fst $ unLoc $2)))) }
+        | 'foreign' fdecl                       {% amsA' (sLL $1 $> ((unLoc $2) (epTok $1))) }
         | '{-# DEPRECATED' deprecations '#-}'   {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getDEPRECATED_PRAGs $1)) (fromOL $2))) }
         | '{-# WARNING' warnings '#-}'          {% amsA' (sLL $1 $> $ WarningD noExtField (Warnings ((glR $1,glR $3), (getWARNING_PRAGs $1)) (fromOL $2))) }
         | '{-# RULES' rules '#-}'               {% amsA' (sLL $1 $> $ RuleD noExtField (HsRules ((glR $1,glR $3), (getRULES_PRAGs $1)) (reverse $2))) }
@@ -1366,7 +1366,7 @@ ty_decl :: { LTyClDecl GhcPs }
 standalone_kind_sig :: { LStandaloneKindSig GhcPs }
   : 'type' sks_vars '::' sigktype
       {% mkStandaloneKindSig (comb2 $1 $4) (L (gl $2) $ unLoc $2) $4
-               [mj AnnType $1,mu AnnDcolon $3]}
+               (epTok $1,epUniTok $3)}
 
 -- See also: sig_vars
 sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
@@ -1380,7 +1380,8 @@ sks_vars :: { Located [LocatedN RdrName] }  -- Returned in reverse order
 inst_decl :: { LInstDecl GhcPs }
         : 'instance' maybe_warning_pragma overlap_pragma inst_type where_inst
        {% do { (binds, sigs, _, ats, adts, _) <- cvBindsAndSigs (snd $ unLoc $5)
-             ; let anns = (mj AnnInstance $1 : (fst $ unLoc $5))
+             ; let (twhere, (openc, closec, semis)) = fst $ unLoc $5
+             ; let anns = AnnClsInstDecl (epTok $1) twhere openc semis closec
              ; let cid = ClsInstDecl
                                   { cid_ext = ($2, anns, NoAnnSortKey)
                                   , cid_poly_ty = $4, cid_binds = binds
@@ -1421,27 +1422,27 @@ inst_decl :: { LInstDecl GhcPs }
 
 overlap_pragma :: { Maybe (LocatedP OverlapMode) }
   : '{-# OVERLAPPABLE'    '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlappable (getOVERLAPPABLE_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPPING'     '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlapping (getOVERLAPPING_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# OVERLAPS'        '#-}' {% fmap Just $ amsr (sLL $1 $> (Overlaps (getOVERLAPS_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | '{-# INCOHERENT'      '#-}' {% fmap Just $ amsr (sLL $1 $> (Incoherent (getINCOHERENT_PRAGs $1)))
-                                       (AnnPragma (mo $1) (mc $2) []) }
+                                       (AnnPragma (glR $1) (glR $2) noAnn noAnn noAnn noAnn noAnn) }
   | {- empty -}                 { Nothing }
 
 deriv_strategy_no_via :: { LDerivStrategy GhcPs }
-  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
 
 deriv_strategy_via :: { LDerivStrategy GhcPs }
-  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs [mj AnnVia $1] $2))) }
+  : 'via' sigktype          {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs (epTok $1) $2))) }
 
 deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) }
-  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) }
-  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) }
-  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) }
+  : 'stock'                     {% fmap Just $ amsA' (sL1 $1 (StockStrategy (epTok $1))) }
+  | 'anyclass'                  {% fmap Just $ amsA' (sL1 $1 (AnyclassStrategy (epTok $1))) }
+  | 'newtype'                   {% fmap Just $ amsA' (sL1 $1 (NewtypeStrategy (epTok $1))) }
   | deriv_strategy_via          { Just $1 }
   | {- empty -}                 { Nothing }
 
@@ -1659,11 +1660,11 @@ capi_ctype :: { Maybe (LocatedP CType) }
 capi_ctype : '{-# CTYPE' STRING STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) (Just (Header (getSTRINGs $2) (getSTRING $2)))
                                         (getSTRINGs $3,getSTRING $3)))
-                              (AnnPragma (mo $1) (mc $4) [mj AnnHeader $2,mj AnnVal $3]) }
+                              (AnnPragma (glR $1) (glR $4) noAnn (glR $2) (glR $3) noAnn noAnn) }
 
            | '{-# CTYPE'        STRING '#-}'
                        {% fmap Just $ amsr (sLL $1 $> (CType (getCTYPEs $1) Nothing (getSTRINGs $2, getSTRING $2)))
-                              (AnnPragma (mo $1) (mc $3) [mj AnnVal $2]) }
+                              (AnnPragma (glR $1) (glR $3) noAnn noAnn (glR $2) noAnn noAnn) }
 
            |           { Nothing }
 
@@ -1676,7 +1677,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
                 {% do { let { err = text "in the stand-alone deriving instance"
                                     <> colon <+> quotes (ppr $6) }
                       ; amsA' (sLL $1 $>
-                                 (DerivDecl ($4, [mj AnnDeriving $1, mj AnnInstance $3]) (mkHsWildCardBndrs $6) $2 $5)) }}
+                                 (DerivDecl ($4, (epTok $1, epTok $3)) (mkHsWildCardBndrs $6) $2 $5)) }}
 
 -----------------------------------------------------------------------------
 -- Role annotations
@@ -1684,7 +1685,7 @@ stand_alone_deriving :: { LDerivDecl GhcPs }
 role_annot :: { LRoleAnnotDecl GhcPs }
 role_annot : 'type' 'role' oqtycon maybe_roles
           {% mkRoleAnnotDecl (comb3 $1 $4 $3) $3 (reverse (unLoc $4))
-                   [mj AnnType $1,mj AnnRole $2] }
+                   (epTok $1,epTok $2) }
 
 -- Reversed!
 maybe_roles :: { Located [Located (Maybe FastString)] }
@@ -1816,9 +1817,9 @@ decl_inst  :: { Located (OrdList (LHsDecl GhcPs)) }
 decl_inst  : at_decl_inst               { sL1 $1 (unitOL (sL1a $1 (InstD noExtField (unLoc $1)))) }
            | decl                       { sL1 $1 (unitOL $1) }
 
-decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
+decls_inst :: { Located ([EpToken ";"],OrdList (LHsDecl GhcPs)) }   -- Reversed
            : decls_inst ';' decl_inst   {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLL $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                     , unLoc $3))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1826,7 +1827,7 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
                                                   return (sLL $1 $> (fst $ unLoc $1
                                                                  , snocOL hs t' `appOL` unLoc $3)) }
            | decls_inst ';'             {% if isNilOL (snd $ unLoc $1)
-                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ (mz AnnSemi $2)
+                                             then return (sLZ $1 $> ((fst $ unLoc $1) ++ [mzEpTok $2]
                                                                                    ,snd $ unLoc $1))
                                              else case (snd $ unLoc $1) of
                                                SnocOL hs t -> do
@@ -1837,20 +1838,20 @@ decls_inst :: { Located ([AddEpAnn],OrdList (LHsDecl GhcPs)) }   -- Reversed
            | {- empty -}                { noLoc ([],nilOL) }
 
 decllist_inst
-        :: { Located ([AddEpAnn]
+        :: { Located ((EpToken "{", EpToken "}", [EpToken ";"])
                      , OrdList (LHsDecl GhcPs)) }      -- Reversed
-        : '{'         decls_inst '}'    { sLL $1 $> (moc $1:mcc $3:(fst $ unLoc $2),snd $ unLoc $2) }
-        |     vocurly decls_inst close  { L (gl $2) (unLoc $2) }
+        : '{'         decls_inst '}'    { sLL $1 $> ((epTok $1,epTok $3,fst $ unLoc $2),snd $ unLoc $2) }
+        |     vocurly decls_inst close  { L (gl $2) ((noAnn,noAnn,fst $ unLoc $2),snd $ unLoc $2) }
 
 -- Instance body
 --
-where_inst :: { Located ([AddEpAnn]
+where_inst :: { Located ((EpToken "where", (EpToken "{", EpToken "}", [EpToken ";"]))
                         , OrdList (LHsDecl GhcPs)) }   -- Reversed
                                 -- No implicit parameters
                                 -- May have type declarations
-        : 'where' decllist_inst         { sLL $1 $> (mj AnnWhere $1:(fst $ unLoc $2)
-                                             ,(snd $ unLoc $2)) }
-        | {- empty -}                   { noLoc ([],nilOL) }
+        : 'where' decllist_inst         { sLL $1 $> ((epTok $1,(fst $ unLoc $2))
+                                             ,snd $ unLoc $2) }
+        | {- empty -}                   { noLoc (noAnn,nilOL) }
 
 -- Declarations in binding groups other than classes and instances
 --
@@ -2019,10 +2020,10 @@ to varid (used for rule_vars), 'checkRuleTyVarBndrNames' must be updated.
 maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) }
         : '{-# DEPRECATED' strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ DeprecatedTxt (getDEPRECATED_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $2))
-                                (AnnPragma (mo $1) (mc $3) (fst $ unLoc $2)) }
+                                (AnnPragma (glR $1) (glR $3) (fst $ unLoc $2) noAnn noAnn noAnn noAnn) }
         | '{-# WARNING' warning_category strings '#-}'
                             {% fmap Just $ amsr (sLL $1 $> $ WarningTxt $2 (getWARNING_PRAGs $1) (map stringLiteralToHsDocWst $ snd $ unLoc $3))
-                                (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))}
+                                (AnnPragma (glR $1) (glR $4) (fst $ unLoc $3) noAnn noAnn noAnn noAnn)}
         |  {- empty -}      { Nothing }
 
 warning_category :: { Maybe (LocatedE InWarningCategory) }
@@ -2081,9 +2082,9 @@ deprecation :: { OrdList (LWarnDecl GhcPs) }
              {% fmap unitOL $ amsA' (sL (comb3 $1 $2 $>) $ (Warning (unLoc $1, fst $ unLoc $3) (unLoc $2)
                                           (DeprecatedTxt NoSourceText $ map stringLiteralToHsDocWst $ snd $ unLoc $3))) }
 
-strings :: { Located ([AddEpAnn],[Located StringLiteral]) }
-    : STRING { sL1 $1 ([],[L (gl $1) (getStringLiteral $1)]) }
-    | '[' stringlist ']' { sLL $1 $> $ ([mos $1,mcs $3],fromOL (unLoc $2)) }
+strings :: { Located ((EpToken "[", EpToken "]"),[Located StringLiteral]) }
+    : STRING             { sL1 $1 (noAnn,[L (gl $1) (getStringLiteral $1)]) }
+    | '[' stringlist ']' { sLL $1 $> $ ((epTok $1,epTok $3),fromOL (unLoc $2)) }
 
 stringlist :: { Located (OrdList (Located StringLiteral)) }
     : stringlist ',' STRING {% if isNilOL (unLoc $1)
@@ -2104,35 +2105,35 @@ stringlist :: { Located (OrdList (Located StringLiteral)) }
 annotation :: { LHsDecl GhcPs }
     : '{-# ANN' name_var aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $4) [],
+                                            (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn noAnn,
                                             (getANN_PRAGs $1))
                                             (ValueAnnProvenance $2) $3)) }
 
     | '{-# ANN' 'type' otycon aexp '#-}' {% runPV (unECP $4) >>= \ $4 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                            (AnnPragma (mo $1) (mc $5) [mj AnnType $2],
+                                            (AnnPragma (glR $1) (glR $5) noAnn noAnn noAnn (epTok $2) noAnn,
                                             (getANN_PRAGs $1))
                                             (TypeAnnProvenance $3) $4)) }
 
     | '{-# ANN' 'module' aexp '#-}'      {% runPV (unECP $3) >>= \ $3 ->
                                             amsA' (sLL $1 $> (AnnD noExtField $ HsAnnotation
-                                                (AnnPragma (mo $1) (mc $4) [mj AnnModule $2],
+                                                (AnnPragma (glR $1) (glR $4) noAnn noAnn noAnn noAnn (epTok $2),
                                                 (getANN_PRAGs $1))
                                                  ModuleAnnProvenance $3)) }
 
 -----------------------------------------------------------------------------
 -- Foreign import and export declarations
 
-fdecl :: { Located ([AddEpAnn], [AddEpAnn] -> HsDecl GhcPs) }
+fdecl :: { Located (EpToken "foreign" -> HsDecl GhcPs) }
 fdecl : 'import' callconv safety fspec
-               {% mkImport $2 $3 (snd $ unLoc $4) >>= \i ->
-                 return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $4),i))  }
+               {% mkImport $2 $3 (snd $ unLoc $4) (epTok $1, fst $ unLoc $4) >>= \i ->
+                 return (sLL $1 $> i)  }
       | 'import' callconv        fspec
-               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3);
-                    return (sLL $1 $> (mj AnnImport $1 : (fst $ unLoc $3),d)) }}
+               {% do { d <- mkImport $2 (noLoc PlaySafe) (snd $ unLoc $3) (epTok $1, fst $ unLoc $3);
+                    return (sLL $1 $> d) }}
       | 'export' callconv fspec
-               {% mkExport $2 (snd $ unLoc $3) >>= \i ->
-                  return (sLL $1 $> (mj AnnExport $1 : (fst $ unLoc $3),i) ) }
+               {% mkExport $2 (snd $ unLoc $3) (epTok $1, fst $ unLoc $3) >>= \i ->
+                  return (sLL $1 $> i ) }
 
 callconv :: { Located CCallConv }
           : 'stdcall'                   { sLL $1 $> StdCallConv }
@@ -2146,12 +2147,12 @@ safety :: { Located Safety }
         | 'safe'                        { sLL $1 $> PlaySafe }
         | 'interruptible'               { sLL $1 $> PlayInterruptible }
 
-fspec :: { Located ([AddEpAnn]
+fspec :: { Located (TokDcolon
                     ,(Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)) }
-       : STRING var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $3]
+       : STRING var '::' sigtype        { sLL $1 $> (epUniTok $3
                                              ,(L (getLoc $1)
                                                     (getStringLiteral $1), $2, $4)) }
-       |        var '::' sigtype        { sLL $1 $> ([mu AnnDcolon $2]
+       |        var '::' sigtype        { sLL $1 $> (epUniTok $2
                                              ,(noLoc (StringLiteral NoSourceText nilFS Nothing), $1, $3)) }
          -- if the entity string is missing, it defaults to the empty string;
          -- the meaning of an empty entity string depends on the calling
@@ -2343,7 +2344,7 @@ atype :: { LHsType GhcPs }
         | '(#' bar_types2 '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsA' (sLL $1 $> $ HsSumTy (AnnParen AnnParensHash (glR $1) (glR $3)) $2) } }
         | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (glR $1) $2 (glR $3)) }
-        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy  (AnnParen AnnParens       (glR $1) (glR $3)) $2) }
+        | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy (epTok $1, epTok $3) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                             ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $3) []) }}
@@ -2559,22 +2560,22 @@ constr :: { LConDecl GhcPs }
         : forall context '=>' constr_stuff
                 {% amsA' (let (con,details) = unLoc $4 in
                   (L (comb4 $1 $2 $3 $4) (mkConDeclH98
-                                                       (mu AnnDarrow $3:(fst $ unLoc $1))
+                                                       (epUniTok $3,(fst $ unLoc $1))
                                                        con
                                                        (snd $ unLoc $1)
                                                        (Just $2)
                                                        details))) }
         | forall constr_stuff
                 {% amsA' (let (con,details) = unLoc $2 in
-                  (L (comb2 $1 $2) (mkConDeclH98 (fst $ unLoc $1)
+                  (L (comb2 $1 $2) (mkConDeclH98 (noAnn, fst $ unLoc $1)
                                                       con
                                                       (snd $ unLoc $1)
                                                       Nothing   -- No context
                                                       details))) }
 
-forall :: { Located ([AddEpAnn], Maybe [LHsTyVarBndr Specificity GhcPs]) }
-        : 'forall' tv_bndrs '.'       { sLL $1 $> ([mu AnnForall $1,mj AnnDot $3], Just $2) }
-        | {- empty -}                 { noLoc ([], Nothing) }
+forall :: { Located ((TokForall, EpToken "."), Maybe [LHsTyVarBndr Specificity GhcPs]) }
+        : 'forall' tv_bndrs '.'       { sLL $1 $> ((epUniTok $1,epTok $3), Just $2) }
+        | {- empty -}                 { noLoc (noAnn, Nothing) }
 
 constr_stuff :: { Located (LocatedN RdrName, HsConDeclH98Details GhcPs) }
         : infixtype       {% do { b <- runPV $1
@@ -2599,7 +2600,7 @@ fielddecl :: { LConDeclField GhcPs }
                                               -- A list because of   f,g :: Int
         : sig_vars '::' ctype
             {% amsA' (L (comb2 $1 $3)
-                      (ConDeclField [mu AnnDcolon $2]
+                      (ConDeclField (epUniTok $2)
                                     (reverse (map (\ln@(L l n)
                                                -> L (fromTrailingN l) $ FieldOcc noExtField (L (noTrailingN l) n)) (unLoc $1))) $3 Nothing))}
 
@@ -2618,15 +2619,15 @@ derivings :: { Located (HsDeriving GhcPs) }
 deriving :: { LHsDerivingClause GhcPs }
         : 'deriving' deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] Nothing $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) Nothing $2) }
 
         | 'deriving' deriv_strategy_no_via deriv_clause_types
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $2) $3) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $2) $3) }
 
         | 'deriving' deriv_clause_types deriv_strategy_via
               {% let { full_loc = comb2 $1 $> }
-                 in amsA' (L full_loc $ HsDerivingClause [mj AnnDeriving $1] (Just $3) $2) }
+                 in amsA' (L full_loc $ HsDerivingClause (epTok $1) (Just $3) $2) }
 
 deriv_clause_types :: { LDerivClauseTys GhcPs }
         : qtycon              { let { tc = sL1a $1 $ mkHsImplicitSigType $
@@ -2971,12 +2972,12 @@ prag_e :: { Located (HsPragE GhcPs) }
       : '{-# SCC' STRING '#-}'      {% do { scc <- getSCC $2
                                           ; return (sLL $1 $>
                                              (HsPragSCC
-                                                (AnnPragma (mo $1) (mc $3) [mj AnnValStr $2],
+                                                (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                 (getSCC_PRAGs $1))
                                                 (StringLiteral (getSTRINGs $2) scc Nothing)))} }
       | '{-# SCC' VARID  '#-}'      { sLL $1 $>
                                              (HsPragSCC
-                                               (AnnPragma (mo $1) (mc $3) [mj AnnVal $2],
+                                               (AnnPragma (glR $1) (glR $3) noAnn (glR $2) noAnn noAnn noAnn,
                                                (getSCC_PRAGs $1))
                                                (StringLiteral NoSourceText (getVARID $2) Nothing)) }
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Parser.Annotation (
   AnnKeywordId(..),
   EpToken(..), EpUniToken(..),
   getEpTokenSrcSpan, getEpTokenLocs, getEpTokenLoc,
-  TokDcolon, TokRarrow,
+  TokDcolon, TokDarrow, TokRarrow, TokForall,
   EpLayout(..),
   EpaComment(..), EpaCommentTok(..),
   IsUnicodeSyntax(..),
@@ -410,8 +410,11 @@ getEpTokenLoc :: EpToken tok -> EpaLocation
 getEpTokenLoc NoEpTok   = noAnn
 getEpTokenLoc (EpTok l) = l
 
+-- TODO:AZ: check we have all of the unicode tokens
 type TokDcolon = EpUniToken "::" "∷"
+type TokDarrow = EpUniToken "=>"  "⇒"
 type TokRarrow = EpUniToken "->" "→"
+type TokForall = EpUniToken "forall" "∀"
 
 -- | Layout information for declarations.
 data EpLayout =
@@ -813,9 +816,13 @@ data NameAdornment
 -- annotations in pragmas.
 data AnnPragma
   = AnnPragma {
-      apr_open      :: AddEpAnn,
-      apr_close     :: AddEpAnn,
-      apr_rest      :: [AddEpAnn]
+      apr_open      :: EpaLocation,
+      apr_close     :: EpaLocation,
+      apr_squares   :: (EpToken "[", EpToken "]"),
+      apr_loc1      :: EpaLocation,
+      apr_loc2      :: EpaLocation,
+      apr_type      :: EpToken "type",
+      apr_module    :: EpToken "module"
       } deriving (Data,Eq)
 
 -- ---------------------------------------------------------------------
@@ -1402,7 +1409,7 @@ instance NoAnn NameAnn where
   noAnn = NameAnnTrailing []
 
 instance NoAnn AnnPragma where
-  noAnn = AnnPragma noAnn noAnn []
+  noAnn = AnnPragma noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 instance NoAnn AnnParen where
   noAnn = AnnParen AnnParens noAnn noAnn
@@ -1496,4 +1503,6 @@ instance Outputable AnnList where
     = text "AnnList" <+> ppr a <+> ppr o <+> ppr c <+> ppr r <+> ppr t
 
 instance Outputable AnnPragma where
-  ppr (AnnPragma o c r) = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr r
+  ppr (AnnPragma o c s l ca t m)
+    = text "AnnPragma" <+> ppr o <+> ppr c <+> ppr s <+> ppr l
+                       <+> ppr ca <+> ppr ca <+> ppr t <+> ppr m


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -283,7 +283,7 @@ mkStandaloneKindSig
   :: SrcSpan
   -> Located [LocatedN RdrName]   -- LHS
   -> LHsSigType GhcPs             -- RHS
-  -> [AddEpAnn]
+  -> (EpToken "type", TokDcolon)
   -> P (LStandaloneKindSig GhcPs)
 mkStandaloneKindSig loc lhs rhs anns =
   do { vs <- mapM check_lhs_name (unLoc lhs)
@@ -408,7 +408,7 @@ mkSpliceDecl lexpr@(L loc expr)
 mkRoleAnnotDecl :: SrcSpan
                 -> LocatedN RdrName                -- type being annotated
                 -> [Located (Maybe FastString)]    -- roles
-                -> [AddEpAnn]
+                -> (EpToken "type", EpToken "role")
                 -> P (LRoleAnnotDecl GhcPs)
 mkRoleAnnotDecl loc tycon roles anns
   = do { roles' <- mapM parse_role roles
@@ -773,12 +773,12 @@ recordPatSynErr loc pat =
     addFatalError $ mkPlainErrorMsgEnvelope loc $
       (PsErrRecordSyntaxInPatSynDecl pat)
 
-mkConDeclH98 :: [AddEpAnn] -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
+mkConDeclH98 :: (TokDarrow, (TokForall, EpToken ".")) -> LocatedN RdrName -> Maybe [LHsTyVarBndr Specificity GhcPs]
                 -> Maybe (LHsContext GhcPs) -> HsConDeclH98Details GhcPs
                 -> ConDecl GhcPs
 
-mkConDeclH98 ann name mb_forall mb_cxt args
-  = ConDeclH98 { con_ext    = ann
+mkConDeclH98 (tdarrow, (tforall,tdot)) name mb_forall mb_cxt args
+  = ConDeclH98 { con_ext    = AnnConDeclH98 tforall tdot tdarrow
                , con_name   = name
                , con_forall = isJust mb_forall
                , con_ex_tvs = mb_forall `orElse` []
@@ -795,12 +795,12 @@ mkConDeclH98 ann name mb_forall mb_cxt args
 --   Note [GADT abstract syntax] in "GHC.Hs.Decls" for more details.
 mkGadtDecl :: SrcSpan
            -> NonEmpty (LocatedN RdrName)
-           -> EpUniToken "::" "∷"
+           -> TokDcolon
            -> LHsSigType GhcPs
            -> P (LConDecl GhcPs)
 mkGadtDecl loc names dcol ty = do
 
-  (args, res_ty, annsa, csa) <-
+  (args, res_ty, (ops, cps), csa) <-
     case body_ty of
      L ll (HsFunTy _ hsArr (L (EpAnn anc _ cs) (HsRecTy an rf)) res_ty) -> do
        arr <- case hsArr of
@@ -810,10 +810,10 @@ mkGadtDecl loc names dcol ty = do
                  return noAnn
 
        return ( RecConGADT arr (L (EpAnn anc an cs) rf), res_ty
-              , [], epAnnComments ll)
+              , ([], []), epAnnComments ll)
      _ -> do
-       let (anns, cs, arg_types, res_type) = splitHsFunType body_ty
-       return (PrefixConGADT noExtField arg_types, res_type, anns, cs)
+       let ((ops, cps), cs, arg_types, res_type) = splitHsFunType body_ty
+       return (PrefixConGADT noExtField arg_types, res_type, (ops,cps), cs)
 
   let bndrs_loc = case outer_bndrs of
         HsOuterImplicit{} -> getLoc ty
@@ -822,7 +822,7 @@ mkGadtDecl loc names dcol ty = do
   let l = EpAnn (spanAsAnchor loc) noAnn csa
 
   pure $ L l ConDeclGADT
-                     { con_g_ext  = (dcol, annsa)
+                     { con_g_ext  = AnnConDeclGADT ops cps dcol
                      , con_names  = names
                      , con_bndrs  = L bndrs_loc outer_bndrs
                      , con_mb_cxt = mcxt
@@ -1079,9 +1079,7 @@ checkTyClHdr is_cls ty
       | isRdrTc tc               = return (ltc, lhs:rhs:acc, Infix, (reverse ops), cps, cs Semi.<> comments l)
       where lhs = HsValArg noExtField t1
             rhs = HsValArg noExtField t2
-    go cs l (HsParTy _ ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
-      where
-        (o,c) = mkParensEpToks (realSrcSpan (locA l))
+    go cs l (HsParTy (o,c) ty)    acc ops cps fix = goL (cs Semi.<> comments l) ty acc (o:ops) (c:cps) fix
     go cs l (HsAppTy _ t1 t2) acc ops cps fix = goL (cs Semi.<> comments l) t1 (HsValArg noExtField t2:acc) ops cps fix
     go cs l (HsAppKindTy at ty ki) acc ops cps fix = goL (cs Semi.<> comments l) ty (HsTypeArg at ki:acc) ops cps fix
     go cs l (HsTupleTy _ HsBoxedOrConstraintTuple ts) [] ops cps fix
@@ -1098,12 +1096,12 @@ checkTyClHdr is_cls ty
 
     -- Combine the annotations from the HsParTy and HsStarTy into a
     -- new one for the LocatedN RdrName
-    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> AnnParen -> SrcSpanAnnN
-    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (AnnParen _ o c) =
+    newAnns :: SrcSpanAnnA -> SrcSpanAnnA -> (EpToken "(", EpToken ")") -> SrcSpanAnnN
+    newAnns l@(EpAnn _ (AnnListItem _) csp0) l1@(EpAnn ap (AnnListItem ta) csp) (o,c) =
       let
         lr = combineSrcSpans (locA l1) (locA l)
       in
-        EpAnn (EpaSpan lr) (NameAnn NameParens o ap c ta) (csp0 Semi.<> csp)
+        EpAnn (EpaSpan lr) (NameAnn NameParens (getEpTokenLoc o) ap (getEpTokenLoc c) ta) (csp0 Semi.<> csp)
 
 -- | Yield a parse error if we have a function applied directly to a do block
 -- etc. and BlockArguments is not enabled.
@@ -1171,9 +1169,9 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
             EpTok ql -> ([AddEpAnn AnnSimpleQuote ql], [cl])
             _        -> ([ol], [cl])
         mkCTuple (oparens ++ (addLoc <$> op), (addLoc <$> cp) ++ cparens, cs) ts
-  check (opi,cpi,csi) (L _lp1 (HsParTy ann' ty))
-                                  -- to be sure HsParTy doesn't get into the way
-    = check (ap_open ann':opi, ap_close ann':cpi, csi) ty
+  check (opi,cpi,csi) (L _lp1 (HsParTy (o,c) ty))
+                                             -- to be sure HsParTy doesn't get into the way
+    = check (getEpTokenLoc o:opi, getEpTokenLoc c:cpi, csi) ty
 
   -- No need for anns, returning original
   check (_opi,_cpi,_csi) _t = unprocessed
@@ -3023,8 +3021,9 @@ checkNewOrData span name is_type_data = curry $ \ case
 mkImport :: Located CCallConv
          -> Located Safety
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
+         -> (EpToken "import", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) (timport, td) =
     case unLoc cconv of
       CCallConv          -> returnSpec =<< mkCImport
       CApiConv           -> do
@@ -3060,8 +3059,8 @@ mkImport cconv safety (L loc (StringLiteral esrc entity _), v, ty) =
         funcTarget = CFunction (StaticTarget esrc entity' Nothing True)
         importSpec = CImport (L (l2l loc) esrc) (reLoc cconv) (reLoc safety) Nothing funcTarget
 
-    returnSpec spec = return $ \ann -> ForD noExtField $ ForeignImport
-          { fd_i_ext  = ann
+    returnSpec spec = return $ \tforeign -> ForD noExtField $ ForeignImport
+          { fd_i_ext  = (tforeign, timport, td)
           , fd_name   = v
           , fd_sig_ty = ty
           , fd_fi     = spec
@@ -3133,10 +3132,11 @@ parseCImport cconv safety nm str sourceText =
 --
 mkExport :: Located CCallConv
          -> (Located StringLiteral, LocatedN RdrName, LHsSigType GhcPs)
-         -> P ([AddEpAnn] -> HsDecl GhcPs)
-mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty)
- = return $ \ann -> ForD noExtField $
-   ForeignExport { fd_e_ext = ann, fd_name = v, fd_sig_ty = ty
+         -> ( EpToken "export", TokDcolon)
+         -> P (EpToken "foreign" -> HsDecl GhcPs)
+mkExport (L lc cconv) (L le (StringLiteral esrc entity _), v, ty) (texport, td)
+ = return $ \tforeign -> ForD noExtField $
+   ForeignExport { fd_e_ext = (tforeign, texport, td), fd_name = v, fd_sig_ty = ty
                  , fd_fe = CExport (L (l2l le) esrc) (L (l2l lc) (CExportStatic esrc entity' cconv)) }
   where
     entity' | nullFS entity = mkExtName (unLoc v)


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -437,13 +437,14 @@ pkgToWrappers pkg = do
       | otherwise     -> pure []
 
 wrapper :: FilePath -> Action String
-wrapper "ghc"         = ghcWrapper
-wrapper "ghc-pkg"     = ghcPkgWrapper
-wrapper "ghci" = ghciScriptWrapper
-wrapper "haddock"     = haddockWrapper
-wrapper "hsc2hs"      = hsc2hsWrapper
-wrapper "runghc"      = runGhcWrapper
-wrapper "runhaskell"  = runGhcWrapper
+wrapper wrapper_name
+  | "runghc"     `isSuffixOf` wrapper_name = runGhcWrapper
+  | "ghc"        `isSuffixOf` wrapper_name = ghcWrapper
+  | "ghc-pkg"    `isSuffixOf` wrapper_name = ghcPkgWrapper
+  | "ghci"       `isSuffixOf` wrapper_name = ghciScriptWrapper
+  | "haddock"    `isSuffixOf` wrapper_name = haddockWrapper
+  | "hsc2hs"     `isSuffixOf` wrapper_name = hsc2hsWrapper
+  | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper
 wrapper _             = commonWrapper
 
 -- | Wrapper scripts for different programs. Common is default wrapper.
@@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\
 -- | --interactive flag.
 ghciScriptWrapper :: Action String
 ghciScriptWrapper = do
+  prefix <- crossPrefix
   version <- setting ProjectVersion
   pure $ unlines
-    [ "executable=\"$bindir/ghc-" ++ version ++ "\""
+    [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
     , "exec $executable --interactive \"$@\"" ]
 
 -- | When not on Windows, we want to ship the 3 flavours of the iserv program
@@ -548,4 +550,3 @@ createGhcii outDir = do
       [ "#!/bin/sh"
       , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\""
       ]
-


=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
=====================================
@@ -119,6 +119,7 @@ module GHC.Internal.Control.Exception (
   ) where
 
 import GHC.Internal.Control.Exception.Base
+import GHC.Internal.Exception.Type (ExceptionWithContext(..), whileHandling)
 
 import GHC.Internal.Base
 import GHC.Internal.IO (interruptible)
@@ -149,13 +150,15 @@ Instead, we provide a function 'catches', which would be used thus:
 >                     Handler (\ (ex :: IOException)    -> handleIO    ex)]
 -}
 catches :: IO a -> [Handler a] -> IO a
-catches io handlers = io `catch` catchesHandler handlers
-
-catchesHandler :: [Handler a] -> SomeException -> IO a
-catchesHandler handlers e = foldr tryHandler (throw e) handlers
-    where tryHandler (Handler handler) res
-              = case fromException e of
-                Just e' -> handler e'
+catches io handlers = io `catchNoPropagate` catchesHandler handlers
+
+catchesHandler :: [Handler a] -> ExceptionWithContext SomeException -> IO a
+catchesHandler handlers ec@(ExceptionWithContext _ e) =
+    foldr tryHandler (rethrowIO ec) handlers
+    where
+        tryHandler (Handler handler) res =
+            case fromException e of
+                Just e' -> annotateIO (whileHandling ec) (handler e')
                 Nothing -> res
 
 -- -----------------------------------------------------------------------------


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -142,7 +142,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:5:36-49 })
@@ -190,7 +193,10 @@
              (EpaComments
               []))
             (ConDeclH98
-             []
+             (AnnConDeclH98
+              (NoEpUniTok)
+              (NoEpTok)
+              (NoEpUniTok))
              (L
               (EpAnn
                (EpaSpan { Test20239.hs:7:36-48 })
@@ -218,10 +224,11 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaSpan { Test20239.hs:7:50 })
-                   (EpaSpan { Test20239.hs:7:86 }))
+                  ((,)
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:50 }))
+                   (EpTok
+                    (EpaSpan { Test20239.hs:7:86 })))
                   (L
                    (EpAnn
                     (EpaSpan { Test20239.hs:7:51-85 })
@@ -290,10 +297,11 @@
                         (EpaComments
                          []))
                        (HsParTy
-                        (AnnParen
-                         AnnParens
-                         (EpaSpan { Test20239.hs:7:68 })
-                         (EpaSpan { Test20239.hs:7:85 }))
+                        ((,)
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:68 }))
+                         (EpTok
+                          (EpaSpan { Test20239.hs:7:85 })))
                         (L
                          (EpAnn
                           (EpaSpan { Test20239.hs:7:69-84 })


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -972,8 +972,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:23:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:23:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:23:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:23:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1110,11 +1115,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:25:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1348,8 +1354,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:29:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:29:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:29:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:29:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1486,11 +1497,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:31:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -1724,8 +1736,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:35:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:35:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:35:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:35:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1862,11 +1879,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:37:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2100,8 +2118,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:41:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:41:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:41:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:41:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2238,11 +2261,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:43:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2476,8 +2500,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:47:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:47:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:47:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:47:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2614,11 +2643,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:49:10-11 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn
@@ -2852,8 +2882,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { T17544.hs:53:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { T17544.hs:53:18-22 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { T17544.hs:53:1-8 }))
+         (EpTok
+          (EpaSpan { T17544.hs:53:18-22 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -2990,11 +3025,12 @@
                 (EpaComments
                  []))
                (ConDeclGADT
-                ((,)
+                (AnnConDeclGADT
+                 []
+                 []
                  (EpUniTok
                   (EpaSpan { T17544.hs:55:11-12 })
-                  (NormalSyntax))
-                 [])
+                  (NormalSyntax)))
                 (:|
                  (L
                   (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -101,11 +101,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T17544_kw.hs:16:15-16 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -214,11 +215,12 @@
           (EpaComments
            []))
          (ConDeclGADT
-          ((,)
+          (AnnConDeclGADT
+           []
+           []
            (EpUniTok
             (EpaSpan { T17544_kw.hs:19:15-16 })
-            (NormalSyntax))
-           [])
+            (NormalSyntax)))
           (:|
            (L
             (EpAnn


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
=====================================
@@ -90,7 +90,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:5:5-8 })
@@ -151,7 +154,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:7:5-8 })
@@ -211,7 +217,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:9:9-10 })
@@ -339,7 +348,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:12:7-8 })
@@ -467,7 +479,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:16:3-4 })
@@ -637,7 +652,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:23:3-4 })
@@ -807,7 +825,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:28:3-8 })
@@ -844,7 +865,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:28:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:28:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:28:12-13 })
@@ -903,7 +926,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:29:15-16 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:29:15-16 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:29:12-13 })
@@ -1008,7 +1033,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:32:3-8 })
@@ -1045,7 +1073,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:33:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:33:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:33:7-8 })
@@ -1104,7 +1134,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:34:10-11 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:34:10-11 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:34:7-8 })
@@ -1221,7 +1253,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T24221.hs:38:3-8 })
@@ -1258,7 +1293,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:40:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:40:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:40:5-6 })
@@ -1317,7 +1354,9 @@
                 (EpaComments
                  []))
                (ConDeclField
-                [(AddEpAnn AnnDcolon (EpaSpan { T24221.hs:42:8-9 }))]
+                (EpUniTok
+                 (EpaSpan { T24221.hs:42:8-9 })
+                 (NormalSyntax))
                 [(L
                   (EpAnn
                    (EpaSpan { T24221.hs:42:5-6 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -125,7 +125,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:14-17 })
@@ -150,7 +153,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:7:21-24 })
@@ -201,8 +207,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:9:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:9:13-14 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:9:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:9:13-14 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:9:6-11 })
@@ -352,10 +362,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:10 })
-                 (EpaSpan { DumpParsedAst.hs:11:17 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:10 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:17 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:11-16 })
@@ -450,10 +461,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:11:26 })
-                 (EpaSpan { DumpParsedAst.hs:11:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:26 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:11:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:11:27-35 })
@@ -794,7 +806,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { DumpParsedAst.hs:15:21-23 })
@@ -822,10 +837,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { DumpParsedAst.hs:15:25 })
-                 (EpaSpan { DumpParsedAst.hs:15:29 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:25 }))
+                 (EpTok
+                  (EpaSpan { DumpParsedAst.hs:15:29 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpParsedAst.hs:15:26-28 })
@@ -885,8 +901,12 @@
     (KindSigD
      (NoExtField)
      (StandaloneKindSig
-      [(AddEpAnn AnnType (EpaSpan { DumpParsedAst.hs:17:1-4 }))
-      ,(AddEpAnn AnnDcolon (EpaSpan { DumpParsedAst.hs:17:9-10 }))]
+      ((,)
+       (EpTok
+        (EpaSpan { DumpParsedAst.hs:17:1-4 }))
+       (EpUniTok
+        (EpaSpan { DumpParsedAst.hs:17:9-10 })
+        (NormalSyntax)))
       (L
        (EpAnn
         (EpaSpan { DumpParsedAst.hs:17:6-7 })
@@ -960,10 +980,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:17:17 })
-               (EpaSpan { DumpParsedAst.hs:17:27 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:17 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:17:27 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:17:18-26 })
@@ -1604,10 +1625,11 @@
             (EpaComments
              []))
            (HsParTy
-            (AnnParen
-             AnnParens
-             (EpaSpan { DumpParsedAst.hs:22:22 })
-             (EpaSpan { DumpParsedAst.hs:22:37 }))
+            ((,)
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:22 }))
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:22:37 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:22:23-36 })
@@ -1731,10 +1753,11 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaSpan { DumpParsedAst.hs:22:42 })
-               (EpaSpan { DumpParsedAst.hs:22:52 }))
+              ((,)
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:42 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:22:52 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:22:43-51 })
@@ -1814,11 +1837,12 @@
             (EpaComments
              []))
            (ConDeclGADT
-            ((,)
+            (AnnConDeclGADT
+             []
+             []
              (EpUniTok
               (EpaSpan { DumpParsedAst.hs:23:7-8 })
-              (NormalSyntax))
-             [])
+              (NormalSyntax)))
             (:|
              (L
               (EpAnn
@@ -1855,10 +1879,11 @@
                  (EpaComments
                   []))
                 (HsParTy
-                 (AnnParen
-                  AnnParens
-                  (EpaSpan { DumpParsedAst.hs:23:10 })
-                  (EpaSpan { DumpParsedAst.hs:23:34 }))
+                 ((,)
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:10 }))
+                  (EpTok
+                   (EpaSpan { DumpParsedAst.hs:23:34 })))
                  (L
                   (EpAnn
                    (EpaSpan { DumpParsedAst.hs:23:11-33 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -304,10 +304,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:11-16 })
@@ -398,10 +397,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:13:27-35 })
@@ -850,10 +848,9 @@
               (EpaComments
                []))
              (HsParTy
-              (AnnParen
-               AnnParens
-               (EpaDelta {  } (SameLine 0) [])
-               (EpaDelta {  } (SameLine 0) []))
+              ((,)
+               (NoEpTok)
+               (NoEpTok))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:19:23-36 })
@@ -966,10 +963,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:19:43-51 })
@@ -1079,10 +1075,9 @@
                    (EpaComments
                     []))
                   (HsParTy
-                   (AnnParen
-                    AnnParens
-                    (EpaDelta {  } (SameLine 0) [])
-                    (EpaDelta {  } (SameLine 0) []))
+                   ((,)
+                    (NoEpTok)
+                    (NoEpTok))
                    (L
                     (EpAnn
                      (EpaSpan { DumpRenamedAst.hs:20:11-33 })
@@ -1452,10 +1447,9 @@
                   (EpaComments
                    []))
                  (HsParTy
-                  (AnnParen
-                   AnnParens
-                   (EpaDelta {  } (SameLine 0) [])
-                   (EpaDelta {  } (SameLine 0) []))
+                  ((,)
+                   (NoEpTok)
+                   (NoEpTok))
                   (L
                    (EpAnn
                     (EpaSpan { DumpRenamedAst.hs:22:26-28 })
@@ -1955,10 +1949,9 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaDelta {  } (SameLine 0) [])
-                 (EpaDelta {  } (SameLine 0) []))
+                ((,)
+                 (NoEpTok)
+                 (NoEpTok))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:24:18-26 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -831,10 +831,11 @@
              (EpaComments
               []))
             (HsParTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { KindSigs.hs:22:8 })
-              (EpaSpan { KindSigs.hs:22:20 }))
+             ((,)
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:8 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:22:20 })))
              (L
               (EpAnn
                (EpaSpan { KindSigs.hs:22:9-19 })
@@ -924,10 +925,11 @@
                (EpaComments
                 []))
               (HsParTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { KindSigs.hs:22:33 })
-                (EpaSpan { KindSigs.hs:22:44 }))
+               ((,)
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:33 }))
+                (EpTok
+                 (EpaSpan { KindSigs.hs:22:44 })))
                (L
                 (EpAnn
                  (EpaSpan { KindSigs.hs:22:34-43 })
@@ -1643,10 +1645,11 @@
            (EpaComments
             []))
           (HsParTy
-           (AnnParen
-            AnnParens
-            (EpaSpan { KindSigs.hs:34:9 })
-            (EpaSpan { KindSigs.hs:34:22 }))
+           ((,)
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:9 }))
+            (EpTok
+             (EpaSpan { KindSigs.hs:34:22 })))
            (L
             (EpAnn
              (EpaSpan { KindSigs.hs:34:10-21 })


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -167,7 +167,7 @@
                   (EpaComments
                    []))
                  (ConDeclField
-                  []
+                  (NoEpUniTok)
                   [(L
                     (EpAnn
                      (EpaSpan { T14189.hs:6:33 })


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -116,11 +116,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T15323.hs:6:17-18 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn
@@ -196,10 +197,11 @@
                 (EpaComments
                  []))
                (HsParTy
-                (AnnParen
-                 AnnParens
-                 (EpaSpan { T15323.hs:6:31 })
-                 (EpaSpan { T15323.hs:6:36 }))
+                ((,)
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:31 }))
+                 (EpTok
+                  (EpaSpan { T15323.hs:6:36 })))
                 (L
                  (EpAnn
                   (EpaSpan { T15323.hs:6:32-35 })


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -137,7 +137,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:5:26-31 })
@@ -257,7 +260,10 @@
            (EpaComments
             []))
           (ConDeclH98
-           []
+           (AnnConDeclH98
+            (NoEpUniTok)
+            (NoEpTok)
+            (NoEpUniTok))
            (L
             (EpAnn
              (EpaSpan { T20452.hs:6:26-31 })


=====================================
testsuite/tests/printer/T18791.stderr
=====================================
@@ -89,11 +89,12 @@
            (EpaComments
             []))
           (ConDeclGADT
-           ((,)
+           (AnnConDeclGADT
+            []
+            []
             (EpUniTok
              (EpaSpan { T18791.hs:5:7-8 })
-             (NormalSyntax))
-            [])
+             (NormalSyntax)))
            (:|
             (L
              (EpAnn


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -57,7 +57,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:4:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:4:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -449,8 +454,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.hs:14:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.hs:14:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.hs:14:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.hs:14:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -717,7 +727,12 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:3:1-8 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:3:1-8 }))
+         (NoEpTok)
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn
@@ -1036,8 +1051,13 @@
       (ClsInstDecl
        ((,,)
         (Nothing)
-        [(AddEpAnn AnnInstance (EpaSpan { Test24533.ppr.hs:5:1-8 }))
-        ,(AddEpAnn AnnWhere (EpaSpan { Test24533.ppr.hs:5:17-21 }))]
+        (AnnClsInstDecl
+         (EpTok (EpaSpan { Test24533.ppr.hs:5:1-8 }))
+         (EpTok
+          (EpaSpan { Test24533.ppr.hs:5:17-21 }))
+         (NoEpTok)
+         []
+         (NoEpTok))
         (NoAnnSortKey))
        (L
         (EpAnn


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -63,7 +63,6 @@ import Data.Data ( Data )
 import Data.Dynamic
 import Data.Foldable
 import Data.Functor.Const
-import qualified Data.Set as Set
 import Data.Typeable
 import Data.List ( partition, sort, sortBy)
 import qualified Data.List.NonEmpty as NE
@@ -363,11 +362,11 @@ instance HasTrailing Bool where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpUniToken "->" "→") where
+instance HasTrailing (TokForall, EpUniToken "->" "→") where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing (EpUniToken "forall" "∀", EpToken ".") where
+instance HasTrailing (TokForall, EpToken ".") where
   trailing _ = []
   setTrailing a _ = a
 
@@ -646,23 +645,6 @@ flushComments !trailing_anns = do
 
 -- ---------------------------------------------------------------------
 
--- |In order to interleave annotations into the stream, we turn them into
--- comments. They are removed from the annotation to avoid duplication.
-annotationsToComments :: (Monad m, Monoid w)
-  => a -> Lens a [AddEpAnn] -> [AnnKeywordId] -> EP w m a
-annotationsToComments a l kws = do
-  let (newComments, newAnns) = go ([],[]) (view l a)
-  addComments True newComments
-  return (set l (reverse newAnns) a)
-  where
-    keywords = Set.fromList kws
-
-    go :: ([Comment], [AddEpAnn]) -> [AddEpAnn] -> ([Comment], [AddEpAnn])
-    go acc [] = acc
-    go (cs',ans) ((AddEpAnn k ss) : ls)
-      | Set.member k keywords = go ((mkKWComment k (epaToNoCommentsLocation ss)):cs', ans) ls
-      | otherwise             = go (cs', (AddEpAnn k ss):ans)    ls
-
 epTokensToComments :: (Monad m, Monoid w)
   => AnnKeywordId -> [EpToken tok] -> EP w m ()
 epTokensToComments kw toks
@@ -825,10 +807,6 @@ markLensAA' a l = do
 
 -- -------------------------------------
 
-markEpAnnLMS :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS epann l kw ms = markEpAnnLMS'' epann (lepa . l) kw ms
-
 markEpAnnLMS'' :: (Monad m, Monoid w)
   => a -> Lens a [AddEpAnn] -> AnnKeywordId -> Maybe String -> EP w m a
 markEpAnnLMS'' an l kw Nothing = markEpAnnL an l kw
@@ -843,26 +821,6 @@ markEpAnnLMS'' a l kw (Just str) = do
           return (AddEpAnn kw' r')
       | otherwise = return (AddEpAnn kw' r)
 
--- -------------------------------------
-
-markEpAnnLMS' :: (Monad m, Monoid w)
-  => EpAnn a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m (EpAnn a)
-markEpAnnLMS' an l kw ms = markEpAnnLMS0 an (lepa . l) kw ms
-
-markEpAnnLMS0 :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> AnnKeywordId -> Maybe String -> EP w m a
-markEpAnnLMS0 an l _kw Nothing = markLensKwA an l
-markEpAnnLMS0 a l kw (Just str) = do
-  anns <- go (view l a)
-  return (set l anns a)
-  where
-    go :: (Monad m, Monoid w) => AddEpAnn -> EP w m AddEpAnn
-    go (AddEpAnn kw' r)
-      | kw' == kw = do
-          r' <- printStringAtAA r str
-          return (AddEpAnn kw' r')
-      | otherwise = return (AddEpAnn kw' r)
-
 -- ---------------------------------------------------------------------
 
 -- markEpTokenM :: forall m w tok . (Monad m, Monoid w, KnownSymbol tok)
@@ -912,19 +870,8 @@ markArrow (HsExplicitMult (pct, arr) t) = do
 
 -- ---------------------------------------------------------------------
 
-markAnnCloseP :: (Monad m, Monoid w) => EpAnn AnnPragma -> EP w m (EpAnn AnnPragma)
-markAnnCloseP an = markEpAnnLMS' an lapr_close AnnClose (Just "#-}")
-
-markAnnCloseP' :: (Monad m, Monoid w) => AnnPragma -> EP w m AnnPragma
-markAnnCloseP' an = markEpAnnLMS0 an lapr_close AnnClose (Just "#-}")
-
-markAnnOpenP :: (Monad m, Monoid w) => EpAnn AnnPragma -> SourceText -> String -> EP w m (EpAnn AnnPragma)
-markAnnOpenP an NoSourceText txt   = markEpAnnLMS' an lapr_open AnnOpen (Just txt)
-markAnnOpenP an (SourceText txt) _ = markEpAnnLMS' an lapr_open AnnOpen (Just $ unpackFS txt)
-
-markAnnOpenP' :: (Monad m, Monoid w) => AnnPragma -> SourceText -> String -> EP w m AnnPragma
-markAnnOpenP' an NoSourceText txt   = markEpAnnLMS0 an lapr_open AnnOpen (Just txt)
-markAnnOpenP' an (SourceText txt) _ = markEpAnnLMS0 an lapr_open AnnOpen (Just $ unpackFS txt)
+markAnnCloseP'' :: (Monad m, Monoid w) => EpaLocation -> EP w m EpaLocation
+markAnnCloseP'' l = printStringAtAA l "#-}"
 
 markAnnOpen' :: (Monad m, Monoid w)
   => Maybe EpaLocation -> SourceText -> String -> EP w m (Maybe EpaLocation)
@@ -1089,18 +1036,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lapr_rest :: Lens AnnPragma [AddEpAnn]
-lapr_rest k parent = fmap (\newAnns -> parent { apr_rest = newAnns })
-                          (k (apr_rest parent))
-
-lapr_open :: Lens AnnPragma AddEpAnn
-lapr_open k parent = fmap (\new -> parent { apr_open = new })
-                          (k (apr_open parent))
-
-lapr_close :: Lens AnnPragma AddEpAnn
-lapr_close k parent = fmap (\new -> parent { apr_close = new })
-                          (k (apr_close parent))
-
 lidl :: Lens [AddEpAnn] [AddEpAnn]
 lidl k parent = fmap (\new -> new)
                      (k parent)
@@ -1340,12 +1275,6 @@ lepl_case k parent = fmap (\new -> parent { epl_case = new })
 -- End of lenses
 -- ---------------------------------------------------------------------
 
-markLensKwA :: (Monad m, Monoid w)
-  => a -> Lens a AddEpAnn -> EP w m a
-markLensKwA a l = do
-  loc <- markKw (view l a)
-  return (set l loc a)
-
 markLensKw' :: (Monad m, Monoid w)
   => EpAnn a -> Lens a EpaLocation -> AnnKeywordId -> EP w m (EpAnn a)
 markLensKw' (EpAnn anc a cs) l kw = do
@@ -1785,22 +1714,22 @@ instance ExactPrint (LocatedP (WarningTxt GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (WarningTxt mb_cat src ws)) = do
-    an0 <- markAnnOpenP an src "{-# WARNING"
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (WarningTxt mb_cat src ws)) = do
+    o' <- markAnnOpen'' o src "{-# WARNING"
     mb_cat' <- markAnnotated mb_cat
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (WarningTxt mb_cat' src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (WarningTxt mb_cat' src ws'))
 
-  exact (L an (DeprecatedTxt src ws)) = do
-    an0 <- markAnnOpenP an src "{-# DEPRECATED"
-    an1 <- markEpAnnL' an0 lapr_rest AnnOpenS
+  exact (L (EpAnn l (AnnPragma o c (os,cs) l1 l2 t m) css) (DeprecatedTxt src ws)) = do
+    o' <- markAnnOpen'' o src "{-# DEPRECATED"
+    os' <- markEpToken os
     ws' <- markAnnotated ws
-    an2 <- markEpAnnL' an1 lapr_rest AnnCloseS
-    an3 <- markAnnCloseP an2
-    return (L an3 (DeprecatedTxt src ws'))
+    cs' <- markEpToken cs
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' (os',cs') l1 l2 t m) css) (DeprecatedTxt src ws'))
 
 instance ExactPrint InWarningCategory where
   getAnnotationEntry _ = NoEntryVal
@@ -2057,14 +1986,14 @@ instance ExactPrint (DerivDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (DerivDecl (mw, an) typ ms mov) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+  exact (DerivDecl (mw, (td,ti)) typ ms mov) = do
+    td' <- markEpToken td
     ms' <- mapM markAnnotated ms
-    an1 <- markEpAnnL an0 lidl AnnInstance
+    ti' <- markEpToken ti
     mw' <- mapM markAnnotated mw
     mov' <- mapM markAnnotated mov
     typ' <- markAnnotated typ
-    return (DerivDecl (mw', an1) typ' ms' mov')
+    return (DerivDecl (mw', (td',ti')) typ' ms' mov')
 
 -- ---------------------------------------------------------------------
 
@@ -2072,25 +2001,25 @@ instance ExactPrint (ForeignDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ForeignImport an n ty fimport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnImport
+  exact (ForeignImport (tf,ti,td) n ty fimport) = do
+    tf' <- markEpToken tf
+    ti' <- markEpToken ti
 
     fimport' <- markAnnotated fimport
 
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignImport an2 n' ty' fimport')
+    return (ForeignImport (tf',ti',td') n' ty' fimport')
 
-  exact (ForeignExport an n ty fexport) = do
-    an0 <- markEpAnnL an lidl AnnForeign
-    an1 <- markEpAnnL an0 lidl AnnExport
+  exact (ForeignExport (tf,te,td) n ty fexport) = do
+    tf' <- markEpToken tf
+    te' <- markEpToken te
     fexport' <- markAnnotated fexport
     n' <- markAnnotated n
-    an2 <- markEpAnnL an1 lidl AnnDcolon
+    td' <- markEpUniToken td
     ty' <- markAnnotated ty
-    return (ForeignExport an2 n' ty' fexport')
+    return (ForeignExport (tf',te',td') n' ty' fexport')
 
 -- ---------------------------------------------------------------------
 
@@ -2162,24 +2091,22 @@ instance ExactPrint (WarnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (Warning (ns_spec, an) lns  (WarningTxt mb_cat src ls )) = do
+  exact (Warning (ns_spec, (o,c)) lns  (WarningTxt mb_cat src ls )) = do
     mb_cat' <- markAnnotated mb_cat
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns'  (WarningTxt mb_cat' src ls'))
-    -- return (Warning an1 lns'  (WarningTxt mb_cat' src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns'  (WarningTxt mb_cat' src ls'))
 
-  exact (Warning (ns_spec, an) lns (DeprecatedTxt src ls)) = do
+  exact (Warning (ns_spec, (o,c)) lns (DeprecatedTxt src ls)) = do
     ns_spec' <- exactNsSpec ns_spec
     lns' <- markAnnotated lns
-    an0 <- markEpAnnL an lidl AnnOpenS -- "["
+    o' <- markEpToken o
     ls' <- markAnnotated ls
-    an1 <- markEpAnnL an0 lidl AnnCloseS -- "]"
-    return (Warning (ns_spec', an1) lns' (DeprecatedTxt src ls'))
-    -- return (Warning an1 lns' (DeprecatedTxt src ls'))
+    c' <- markEpToken c
+    return (Warning (ns_spec', (o',c')) lns' (DeprecatedTxt src ls'))
 
 exactNsSpec :: (Monad m, Monoid w) => NamespaceSpecifier -> EP w m NamespaceSpecifier
 exactNsSpec NoNamespaceSpecifier = pure NoNamespaceSpecifier
@@ -2306,9 +2233,9 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (RoleAnnotDecl an ltycon roles) = do
-    an0 <- markEpAnnL an lidl AnnType
-    an1 <- markEpAnnL an0 lidl AnnRole
+  exact (RoleAnnotDecl (tt,tr) ltycon roles) = do
+    tt' <- markEpToken tt
+    tr' <- markEpToken tr
     ltycon' <- markAnnotated ltycon
     let markRole (L l (Just r)) = do
           (L l' r') <- markAnnotated (L l r)
@@ -2317,7 +2244,7 @@ instance ExactPrint (RoleAnnotDecl GhcPs) where
           e' <- printStringAtAA  (entry l) "_"
           return (L (l { entry = e'}) Nothing)
     roles' <- mapM markRole roles
-    return (RoleAnnotDecl an1 ltycon' roles')
+    return (RoleAnnotDecl (tt',tr') ltycon' roles')
 
 -- ---------------------------------------------------------------------
 
@@ -2437,28 +2364,28 @@ instance ExactPrint (ClsInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ClsInstDecl { cid_ext = (mbWarn, an, sortKey)
+  exact (ClsInstDecl { cid_ext = (mbWarn, AnnClsInstDecl i w oc semis cc, sortKey)
                      , cid_poly_ty = inst_ty, cid_binds = binds
                      , cid_sigs = sigs, cid_tyfam_insts = ats
                      , cid_overlap_mode = mbOverlap
                      , cid_datafam_insts = adts })
       = do
-          (mbWarn', an0, mbOverlap', inst_ty') <- top_matter
-          an1 <- markEpAnnL an0 lidl AnnOpenC
-          an2 <- markEpAnnAllL' an1 lid AnnSemi
+          (mbWarn', i', w', mbOverlap', inst_ty') <- top_matter
+          oc' <- markEpToken oc
+          semis' <- mapM markEpToken semis
           (sortKey', ds) <- withSortKey sortKey
                                [(ClsAtTag, prepareListAnnotationA ats),
                                 (ClsAtdTag, prepareListAnnotationF adts),
                                 (ClsMethodTag, prepareListAnnotationA binds),
                                 (ClsSigTag, prepareListAnnotationA sigs)
                                ]
-          an3 <- markEpAnnL an2 lidl AnnCloseC -- '}'
+          cc' <- markEpToken cc
           let
             ats'   = undynamic ds
             adts'  = undynamic ds
             binds' = undynamic ds
             sigs'  = undynamic ds
-          return (ClsInstDecl { cid_ext = (mbWarn', an3, sortKey')
+          return (ClsInstDecl { cid_ext = (mbWarn', AnnClsInstDecl i' w' oc' semis' cc', sortKey')
                               , cid_poly_ty = inst_ty', cid_binds = binds'
                               , cid_sigs = sigs', cid_tyfam_insts = ats'
                               , cid_overlap_mode = mbOverlap'
@@ -2466,12 +2393,12 @@ instance ExactPrint (ClsInstDecl GhcPs) where
 
       where
         top_matter = do
-          an0 <- markEpAnnL an lidl AnnInstance
+          i' <- markEpToken i
           mw <- mapM markAnnotated mbWarn
           mo <- mapM markAnnotated mbOverlap
           it <- markAnnotated inst_ty
-          an1 <- markEpAnnL an0 lidl AnnWhere -- Optional
-          return (mw, an1, mo,it)
+          w' <- markEpToken w -- Optional
+          return (mw, i', w', mo,it)
 
 -- ---------------------------------------------------------------------
 
@@ -2492,35 +2419,35 @@ instance ExactPrint (LocatedP OverlapMode) where
   setAnnotationAnchor = setAnchorAn
 
   -- NOTE: NoOverlap is only used in the typechecker
-  exact (L an (NoOverlap src)) = do
-    an0 <- markAnnOpenP an src "{-# NO_OVERLAP"
-    an1 <- markAnnCloseP an0
-    return (L an1 (NoOverlap src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NoOverlap src)) = do
+    o' <- markAnnOpen'' o src "{-# NO_OVERLAP"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (NoOverlap src))
 
-  exact (L an (Overlappable src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPABLE"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlappable src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlappable src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPABLE"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlappable src))
 
-  exact (L an (Overlapping src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPPING"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlapping src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlapping src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPPING"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlapping src))
 
-  exact (L an (Overlaps src)) = do
-    an0 <- markAnnOpenP an src "{-# OVERLAPS"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Overlaps src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Overlaps src)) = do
+    o' <- markAnnOpen'' o src "{-# OVERLAPS"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Overlaps src))
 
-  exact (L an (Incoherent src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (Incoherent src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
-  exact (L an (NonCanonical src)) = do
-    an0 <- markAnnOpenP an src "{-# INCOHERENT"
-    an1 <- markAnnCloseP an0
-    return (L an1 (Incoherent src))
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NonCanonical src)) = do
+    o' <- markAnnOpen'' o src "{-# INCOHERENT"
+    c' <- markAnnCloseP'' c
+    return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
 -- ---------------------------------------------------------------------
 
@@ -2962,12 +2889,12 @@ instance ExactPrint (StandaloneKindSig GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StandaloneKindSig an vars sig) = do
-    an0 <- markEpAnnL an lidl AnnType
+  exact (StandaloneKindSig (tt,td) vars sig) = do
+    tt' <- markEpToken tt
     vars' <- markAnnotated vars
-    an1 <- markEpAnnL an0 lidl AnnDcolon
+    td' <- markEpUniToken td
     sig' <- markAnnotated sig
-    return (StandaloneKindSig an1 vars' sig')
+    return (StandaloneKindSig (tt',td') vars' sig')
 
 -- ---------------------------------------------------------------------
 
@@ -2989,24 +2916,24 @@ instance ExactPrint (AnnDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsAnnotation (an, src) prov e) = do
-    an0 <- markAnnOpenP' an src "{-# ANN"
-    (an1, prov') <-
+  exact (HsAnnotation (AnnPragma o c s l1 l2 t m, src) prov e) = do
+    o' <- markAnnOpen'' o src "{-# ANN"
+    (t', m', prov') <-
       case prov of
         (ValueAnnProvenance n) -> do
           n' <- markAnnotated n
-          return (an0, ValueAnnProvenance n')
+          return (t, m, ValueAnnProvenance n')
         (TypeAnnProvenance n) -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnType
+          t' <- markEpToken t
           n' <- markAnnotated n
-          return (an1, TypeAnnProvenance n')
+          return (t', m, TypeAnnProvenance n')
         ModuleAnnProvenance -> do
-          an1 <- markEpAnnL an0 lapr_rest AnnModule
-          return (an1, prov)
+          m' <- markEpToken m
+          return (t, m', prov)
 
     e' <- markAnnotated e
-    an2 <- markAnnCloseP' an1
-    return (HsAnnotation (an2,src) prov' e')
+    c' <- printStringAtAA c "#-}"
+    return (HsAnnotation (AnnPragma o' c' s l1 l2 t' m',src) prov' e')
 
 -- ---------------------------------------------------------------------
 
@@ -3418,13 +3345,11 @@ instance ExactPrint (HsPragE GhcPs) where
   getAnnotationEntry HsPragSCC{}  = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsPragSCC (an,st) sl) = do
-    an0 <- markAnnOpenP' an st "{-# SCC"
-    let txt = sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl)
-    an1 <- markEpAnnLMS'' an0 lapr_rest AnnVal    (Just txt) -- optional
-    an2 <- markEpAnnLMS'' an1 lapr_rest AnnValStr (Just txt) -- optional
-    an3 <- markAnnCloseP' an2
-    return (HsPragSCC (an3,st) sl)
+  exact (HsPragSCC (AnnPragma o c s l1 l2 t m,st) sl) = do
+    o' <- markAnnOpen'' o st  "{-# SCC"
+    l1' <- printStringAtAA l1 (sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl))
+    c' <- printStringAtAA c "#-}"
+    return (HsPragSCC (AnnPragma o' c' s l1' l2 t m,st) sl)
 
 
 -- ---------------------------------------------------------------------
@@ -4178,11 +4103,11 @@ instance ExactPrint (HsType GhcPs) where
     lo' <- markAnnotated lo
     t2' <- markAnnotated t2
     return (HsOpTy x promoted t1' lo' t2')
-  exact (HsParTy an ty) = do
-    an0 <- markOpeningParen an
+  exact (HsParTy (o,c) ty) = do
+    o' <- markEpToken o
     ty' <- markAnnotated ty
-    an1 <- markClosingParen an0
-    return (HsParTy an1 ty')
+    c' <- markEpToken c
+    return (HsParTy (o',c') ty')
   exact (HsIParamTy an n t) = do
     n' <- markAnnotated n
     an0 <- markEpUniToken an
@@ -4273,7 +4198,7 @@ instance ExactPrint (HsDerivingClause GhcPs) where
   exact (HsDerivingClause { deriv_clause_ext      = an
                           , deriv_clause_strategy = dcs
                           , deriv_clause_tys      = dct }) = do
-    an0 <- markEpAnnL an lidl AnnDeriving
+    an0 <- markEpToken an
     dcs0 <- case dcs of
             Just (L _ ViaStrategy{}) -> return dcs
             _ -> mapM markAnnotated dcs
@@ -4292,16 +4217,16 @@ instance ExactPrint (DerivStrategy GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
   exact (StockStrategy an)    = do
-    an0 <- markEpAnnL an lid AnnStock
+    an0 <- markEpToken an
     return (StockStrategy an0)
   exact (AnyclassStrategy an) = do
-    an0 <- markEpAnnL an lid AnnAnyclass
+    an0 <- markEpToken an
     return (AnyclassStrategy an0)
   exact (NewtypeStrategy an)  = do
-    an0 <- markEpAnnL an lid AnnNewtype
+    an0 <- markEpToken an
     return (NewtypeStrategy an0)
   exact (ViaStrategy (XViaStrategyPs an ty)) = do
-    an0 <- markEpAnnL an lid AnnVia
+    an0 <- markEpToken an
     ty' <- markAnnotated ty
     return (ViaStrategy (XViaStrategyPs an0 ty'))
 
@@ -4468,27 +4393,27 @@ instance ExactPrint (ConDecl GhcPs) where
   setAnnotationAnchor a _ _ _ = a
 
 -- based on pprConDecl
-  exact (ConDeclH98 { con_ext = an
+  exact (ConDeclH98 { con_ext = AnnConDeclH98 tforall tdot tdarrow
                     , con_name = con
                     , con_forall = has_forall
                     , con_ex_tvs = ex_tvs
                     , con_mb_cxt = mcxt
                     , con_args = args
                     , con_doc = doc }) = do
-    an0 <- if has_forall
-      then markEpAnnL an lidl AnnForall
-      else return an
+    tforall' <- if has_forall
+      then markEpUniToken tforall
+      else return tforall
     ex_tvs' <- mapM markAnnotated ex_tvs
-    an1 <- if has_forall
-      then markEpAnnL an0 lidl AnnDot
-      else return an0
+    tdot' <- if has_forall
+      then markEpToken tdot
+      else return tdot
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
+    tdarrow' <- if (isJust mcxt)
+      then markEpUniToken tdarrow
+      else return tdarrow
 
     (con', args') <- exact_details args
-    return (ConDeclH98 { con_ext = an2
+    return (ConDeclH98 { con_ext = AnnConDeclH98 tforall' tdot' tdarrow'
                        , con_name = con'
                        , con_forall = has_forall
                        , con_ex_tvs = ex_tvs'
@@ -4516,14 +4441,15 @@ instance ExactPrint (ConDecl GhcPs) where
 
   -- -----------------------------------
 
-  exact (ConDeclGADT { con_g_ext = (dcol, an)
+  exact (ConDeclGADT { con_g_ext = AnnConDeclGADT ops cps dcol
                      , con_names = cons
                      , con_bndrs = bndrs
                      , con_mb_cxt = mcxt, con_g_args = args
                      , con_res_ty = res_ty, con_doc = doc }) = do
     cons' <- mapM markAnnotated cons
     dcol' <- markEpUniToken dcol
-    an1 <- annotationsToComments an lidl  [AnnOpenP, AnnCloseP]
+    epTokensToComments AnnOpenP ops
+    epTokensToComments AnnCloseP cps
 
     -- Work around https://gitlab.haskell.org/ghc/ghc/-/issues/20558
     bndrs' <- case bndrs of
@@ -4531,9 +4457,6 @@ instance ExactPrint (ConDecl GhcPs) where
       _ -> markAnnotated bndrs
 
     mcxt' <- mapM markAnnotated mcxt
-    an2 <- if (isJust mcxt)
-      then markEpAnnL an1 lidl AnnDarrow
-      else return an1
     args' <-
       case args of
           (PrefixConGADT x args0) -> do
@@ -4544,7 +4467,7 @@ instance ExactPrint (ConDecl GhcPs) where
             rarr' <- markEpUniToken rarr
             return (RecConGADT rarr' fields')
     res_ty' <- markAnnotated res_ty
-    return (ConDeclGADT { con_g_ext = (dcol', an2)
+    return (ConDeclGADT { con_g_ext = AnnConDeclGADT [] [] dcol'
                         , con_names = cons'
                         , con_bndrs = bndrs'
                         , con_mb_cxt = mcxt', con_g_args = args'
@@ -4579,11 +4502,11 @@ instance ExactPrint (ConDeclField GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (ConDeclField an names ftype mdoc) = do
+  exact (ConDeclField td names ftype mdoc) = do
     names' <- markAnnotated names
-    an0 <- markEpAnnL an lidl AnnDcolon
+    td' <- markEpUniToken td
     ftype' <- markAnnotated ftype
-    return (ConDeclField an0 names' ftype' mdoc)
+    return (ConDeclField td' names' ftype' mdoc)
 
 -- ---------------------------------------------------------------------
 
@@ -4610,15 +4533,15 @@ instance ExactPrint (LocatedP CType) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 
-  exact (L an (CType stp mh (stct,ct))) = do
-    an0 <- markAnnOpenP an stp "{-# CTYPE"
-    an1 <- case mh of
-             Nothing -> return an0
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (CType stp mh (stct,ct))) = do
+    o' <- markAnnOpen'' o stp "{-# CTYPE"
+    l1' <- case mh of
+             Nothing -> return l1
              Just (Header srcH _h) ->
-               markEpAnnLMS an0 lapr_rest AnnHeader (Just (toSourceTextWithSuffix srcH "" ""))
-    an2 <- markEpAnnLMS an1 lapr_rest AnnVal (Just (toSourceTextWithSuffix stct (unpackFS ct) ""))
-    an3 <- markAnnCloseP an2
-    return (L an3 (CType stp mh (stct,ct)))
+               printStringAtAA l1 (toSourceTextWithSuffix srcH "" "")
+    l2' <- printStringAtAA l2 (toSourceTextWithSuffix stct (unpackFS ct) "")
+    c' <- printStringAtAA c "#-}"
+    return (L (EpAnn l (AnnPragma o' c' s l1' l2' t m) cs) (CType stp mh (stct,ct)))
 
 -- ---------------------------------------------------------------------
 


=====================================
utils/check-exact/Main.hs
=====================================
@@ -105,7 +105,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Ppr012.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr013.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr014.hs" Nothing
- -- "../../testsuite/tests/printer/Ppr015.hs" Nothing
+ "../../testsuite/tests/printer/Ppr015.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr016.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr017.hs" Nothing
  -- "../../testsuite/tests/printer/Ppr018.hs" Nothing
@@ -212,7 +212,7 @@ _tt = testOneFile changers "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/
  -- "../../testsuite/tests/printer/Test21355.hs" Nothing
 --  "../../testsuite/tests/printer/Test22765.hs" Nothing
  -- "../../testsuite/tests/printer/Test22771.hs" Nothing
- "../../testsuite/tests/printer/Test23465.hs" Nothing
+ -- "../../testsuite/tests/printer/Test23465.hs" Nothing
 
 -- cloneT does not need a test, function can be retired
 


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -1,5 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
 {-# LANGUAGE DerivingStrategies #-}
@@ -820,7 +821,7 @@ type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
 
 type XRecCond a =
-  ( XParTy a ~ AnnParen
+  ( XParTy a ~ (EpToken "(", EpToken ")")
   , NoGhcTc a ~ a
   , MapXRec a
   , UnXRec a
@@ -852,7 +853,7 @@ type instance XListTy DocNameI = EpAnn AnnParen
 type instance XTupleTy DocNameI = EpAnn AnnParen
 type instance XSumTy DocNameI = EpAnn AnnParen
 type instance XOpTy DocNameI = EpAnn [AddEpAnn]
-type instance XParTy DocNameI = AnnParen
+type instance XParTy DocNameI = (EpToken "(", EpToken ")")
 type instance XIParamTy DocNameI = EpAnn [AddEpAnn]
 type instance XKindSig DocNameI = EpAnn [AddEpAnn]
 type instance XSpliceTy DocNameI = DataConCantHappen


=====================================
utils/jsffi/dyld.mjs
=====================================
@@ -1,4 +1,4 @@
-#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --no-turbo-fast-api-calls --wasm-lazy-validation
+#!/usr/bin/env -S node --disable-warning=ExperimentalWarning --experimental-wasm-type-reflection --max-old-space-size=8192 --no-turbo-fast-api-calls --wasm-lazy-validation
 
 // Note [The Wasm Dynamic Linker]
 // ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e54f034315b461c03d8fb2cbf41ca29208df04c0...46c8e121fa45e250b214eaf1fbef2818d1f15e05

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e54f034315b461c03d8fb2cbf41ca29208df04c0...46c8e121fa45e250b214eaf1fbef2818d1f15e05
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 15:22:43 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 21 Oct 2024 11:22:43 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] 83 commits: Fix typo in Prelude doc
 for (>>=)
Message-ID: <671671c3f5a1_291e2bbaa70c13023@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
b75f313b by Rodrigo Mesquita at 2024-10-21T16:21:47+01:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
fff33d40 by Rodrigo Mesquita at 2024-10-21T16:22:29+01:00
Don't log GHC invocation in abi-test

The two abi test invocations would differ because of -dinitial-unique
and -dunique-increment

- - - - -
e94dc2bb by Rodrigo Mesquita at 2024-10-21T16:22:30+01:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80539878902aa787c36d542b19b323793c09db36...e94dc2bbb7742fd86a9326b3b02f51a88b000c07

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80539878902aa787c36d542b19b323793c09db36...e94dc2bbb7742fd86a9326b3b02f51a88b000c07
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 15:57:13 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 21 Oct 2024 11:57:13 -0400
Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass]
 Cleaned up leftover StringLiteral
Message-ID: <671679d94e2ea_3db9ae366b2c8109d@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC


Commits:
927e20ae by Hassan Al-Awwadi at 2024-10-21T16:57:02+01:00
Cleaned up leftover StringLiteral

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1842,7 +1842,7 @@ instance ExactPrint (ImportDecl GhcPs) where
         _ -> return ann1
     ann3 <-
       case mpkg of
-       RawPkgQual (StringLiteral src' v _) ->
+       RawPkgQual (SL src' v _) ->
          printStringAtMLocL ann2 limportDeclAnnPackage (sourceTextToString src' (show v))
        _ -> return ann2
     modname' <- markAnnotated modname
@@ -2175,14 +2175,14 @@ exactNsSpec (DataNamespaceSpecifier data_) = do
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint StringLiteral where
+instance ExactPrint StringLit where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (StringLiteral src fs mcomma) = do
+  exact (SL src fs mcomma) = do
     printSourceTextAA src (show (unpackFS fs))
     mcomma' <- mapM (\r -> printStringAtNC r ",") mcomma
-    return (StringLiteral src fs mcomma')
+    return (SL src fs mcomma')
 
 -- ---------------------------------------------------------------------
 
@@ -3079,7 +3079,7 @@ instance ExactPrint (HsExpr GhcPs) where
     let str = case ol_val ol of
                 HsIntegral   (IL src _ _) -> src
                 HsFractional (FL { fl_text = src }) -> src
-                HsIsString src _          -> src
+                HsIsString   (SL { sl_st = src }) -> src
     case str of
       SourceText s -> printStringAdvance (unpackFS s) >> return ()
       NoSourceText -> withPpr x >> return ()
@@ -4932,7 +4932,7 @@ instance ExactPrint (HsOverLit GhcPs) where
     let str = case ol_val ol of
                 HsIntegral   (IL src _ _) -> src
                 HsFractional (FL{ fl_text = src }) -> src
-                HsIsString src _ -> src
+                HsIsString   (SL{ sl_st = src }) -> src
     in
       case str of
         SourceText s -> printStringAdvance (unpackFS s) >> return ol



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/927e20aee0b0e2031110b633aad35963c2ecfd32

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 17:29:17 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Mon, 21 Oct 2024 13:29:17 -0400
Subject: [Git][ghc/ghc][wip/fix-ghci-wrapper] 6 commits: Interpreter: Add
 locking for communication with external interpreter
Message-ID: <67168f6d58f2c_19eec7484220775f4@gitlab.mail>



Cheng Shao pushed to branch wip/fix-ghci-wrapper at Glasgow Haskell Compiler / GHC


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
b57c2174 by Cheng Shao at 2024-10-21T17:28:09+00:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -


30 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- hadrian/bindist/Makefile
- hadrian/src/Rules/BinaryDist.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- + testsuite/tests/th/T25083.hs
- + testsuite/tests/th/T25083.stdout
- + testsuite/tests/th/T25083_A.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464c0738317a3854bebec467683653307f8f8450...b57c2174cf8b4804d400c7db774565b2be4ff493

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464c0738317a3854bebec467683653307f8f8450...b57c2174cf8b4804d400c7db774565b2be4ff493
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 17:44:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 13:44:15 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Add
 requestTickyCounterSamples to GHC.Internal.Profiling
Message-ID: <671692efcdaf3_19eec772954884939@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
bceb1480 by Simon Peyton Jones at 2024-10-21T13:44:08-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
266a0c9c by Simon Peyton Jones at 2024-10-21T13:44:08-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
ecdc59aa by Andrzej Rybczak at 2024-10-21T13:44:10-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -


8 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46c8e121fa45e250b214eaf1fbef2818d1f15e05...ecdc59aaa6ae8522ee888f5c9b8e416dd05190bf

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46c8e121fa45e250b214eaf1fbef2818d1f15e05...ecdc59aaa6ae8522ee888f5c9b8e416dd05190bf
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 18:32:57 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 21 Oct 2024 14:32:57 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] review suggestions
Message-ID: <67169e5965c44_19eec7c1f73c9918a@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
d22b13c5 by Hassan Al-Awwadi at 2024-10-21T20:32:33+02:00
review suggestions

- - - - -


30 changed files:

- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Basic.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Decls.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 22:26:53 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 21 Oct 2024 18:26:53 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-6
Message-ID: <6716d52d4c3b6_1a24b225a56c327bf@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-6 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-6
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 22:36:01 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 21 Oct 2024 18:36:01 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-6] 9 commits: ci: Add
 support for ONLY_JOBS variable to trigger any validation pipeline
Message-ID: <6716d7515a55d_1a24b231d85032969@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-6 at Glasgow Haskell Compiler / GHC


Commits:
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
f530e5ef by Alan Zimmerman at 2024-10-21T23:35:02+01:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -


13 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/JS/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/980389caf03652a07c89ff342e23dbfe01e992d2...f530e5ef5d1def9a4ff6a8166b4a163ae2dbcceb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/980389caf03652a07c89ff342e23dbfe01e992d2...f530e5ef5d1def9a4ff6a8166b4a163ae2dbcceb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 21 22:36:28 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Mon, 21 Oct 2024 18:36:28 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] wrap expansion statements with
 the statement location instead of genSpan
Message-ID: <6716d76ca73de_1a24b239a198331b4@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
d4905732 by Apoorv Ingle at 2024-10-21T17:35:40-05:00
wrap expansion statements with the statement location instead of genSpan

- - - - -


1 changed file:

- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -578,5 +578,5 @@ mkExpandedStmtAt
   -> HsDoFlavour          -- ^ the flavour of the statement
   -> HsExpr GhcRn         -- ^ expanded expression
   -> LHsExpr GhcRn        -- ^ suitably wrapped located 'XXExprGhcRn'
-mkExpandedStmtAt oStmt flav eExpr
-  = wrapGenSpan $ mkExpandedStmt oStmt flav eExpr
+mkExpandedStmtAt oStmt@(L loc _) flav eExpr
+  = L loc $ mkExpandedStmt oStmt flav eExpr



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 00:54:47 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 20:54:47 -0400
Subject: [Git][ghc/ghc][master] Add requestTickyCounterSamples to
 GHC.Internal.Profiling
Message-ID: <6716f7d74a8f6_1a24b29949e0471d4@gitlab.mail>



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


Commits:
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -


4 changed files:

- libraries/ghc-internal/src/GHC/Internal/Profiling.hs
- rts/RtsSymbols.c
- rts/Ticky.c
- rts/include/rts/Ticky.h


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Profiling.hs
=====================================
@@ -9,6 +9,8 @@ module GHC.Internal.Profiling ( -- * Cost Centre Profiling
                      , startHeapProfTimer
                      , stopHeapProfTimer
                      , requestHeapCensus
+                       -- * Ticky counters (eventlog)
+                     , requestTickyCounterSamples
                      )where
 
 import GHC.Internal.Base
@@ -51,3 +53,11 @@ foreign import ccall startHeapProfTimer :: IO ()
 -- @since base-4.16.0.0
 foreign import ccall stopHeapProfTimer :: IO ()
 
+-- | Request ticky counter samples to be written to the eventlog.
+--
+-- Note: This won't do anything unless you have specified RTS options on
+-- the command line to log ticky samples to the eventlog.
+--
+-- @since base-4.20.0.0
+
+foreign import ccall requestTickyCounterSamples :: IO ()


=====================================
rts/RtsSymbols.c
=====================================
@@ -922,6 +922,7 @@ extern char **environ;
       SymI_HasProto(stopProfTimer)                                      \
       SymI_HasProto(startHeapProfTimer)                                 \
       SymI_HasProto(stopHeapProfTimer)                                  \
+      SymI_HasProto(requestTickyCounterSamples)                         \
       SymI_HasProto(setUserEra)                                         \
       SymI_HasProto(incrementUserEra)                                   \
       SymI_HasProto(getUserEra)                                         \


=====================================
rts/Ticky.c
=====================================
@@ -418,3 +418,12 @@ void emitTickyCounterSamples(void)
 }
 
 #endif /* TICKY_TICKY */
+
+void requestTickyCounterSamples(void)
+{
+#if defined(TICKY_TICKY) && defined(TRACING)
+    if (RtsFlags.TraceFlags.ticky) {
+        emitTickyCounterSamples();
+    }
+#endif
+}


=====================================
rts/include/rts/Ticky.h
=====================================
@@ -32,3 +32,5 @@ typedef struct _StgEntCounter {
     StgInt      allocs;         /* number of allocations by this fun */
     struct _StgEntCounter *link;/* link to chain them all together */
 } StgEntCounter;
+
+void requestTickyCounterSamples(void);



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 00:55:41 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 20:55:41 -0400
Subject: [Git][ghc/ghc][master] 2 commits: Move defaulting code into a new
 module
Message-ID: <6716f80d44d0a_1a24b29d48d8519f1@gitlab.mail>



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


Commits:
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -


8 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d328d173fa54c35b78b1eef5edba797e1fa03fd4...a398227b1a895b9506ced8c4ee63636a3d173491

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d328d173fa54c35b78b1eef5edba797e1fa03fd4...a398227b1a895b9506ced8c4ee63636a3d173491
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 00:56:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 20:56:15 -0400
Subject: [Git][ghc/ghc][master] Adjust catches to properly rethrow exceptions
Message-ID: <6716f82f8af5e_1a24b2b61d045505d@gitlab.mail>



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


Commits:
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/Control/Exception.hs
=====================================
@@ -119,6 +119,7 @@ module GHC.Internal.Control.Exception (
   ) where
 
 import GHC.Internal.Control.Exception.Base
+import GHC.Internal.Exception.Type (ExceptionWithContext(..), whileHandling)
 
 import GHC.Internal.Base
 import GHC.Internal.IO (interruptible)
@@ -149,13 +150,15 @@ Instead, we provide a function 'catches', which would be used thus:
 >                     Handler (\ (ex :: IOException)    -> handleIO    ex)]
 -}
 catches :: IO a -> [Handler a] -> IO a
-catches io handlers = io `catch` catchesHandler handlers
-
-catchesHandler :: [Handler a] -> SomeException -> IO a
-catchesHandler handlers e = foldr tryHandler (throw e) handlers
-    where tryHandler (Handler handler) res
-              = case fromException e of
-                Just e' -> handler e'
+catches io handlers = io `catchNoPropagate` catchesHandler handlers
+
+catchesHandler :: [Handler a] -> ExceptionWithContext SomeException -> IO a
+catchesHandler handlers ec@(ExceptionWithContext _ e) =
+    foldr tryHandler (rethrowIO ec) handlers
+    where
+        tryHandler (Handler handler) res =
+            case fromException e of
+                Just e' -> annotateIO (whileHandling ec) (handler e')
                 Nothing -> res
 
 -- -----------------------------------------------------------------------------



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/148059fea534aced44649c739cd0fad4c25a99f0

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 01:27:21 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Mon, 21 Oct 2024 21:27:21 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Move
 defaulting code into a new module
Message-ID: <6716ff79ea3e1_1a24b21066ae8564e0@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
d3a3cd59 by doyougnu at 2024-10-21T21:27:00-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
fd62bbe6 by doyougnu at 2024-10-21T21:27:00-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
3d31f872 by doyougnu at 2024-10-21T21:27:16-04:00
ghc-internal: strict, unboxed src loc ranges

- closes: #20449
- See CLC proposal: #55

- - - - -
4813cb1d by Cheng Shao at 2024-10-21T21:27:16-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -


9 changed files:

- compiler/GHC/Core/Make.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ecdc59aaa6ae8522ee888f5c9b8e416dd05190bf...4813cb1d29961f0d0a000f73864345bdb665d5af

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ecdc59aaa6ae8522ee888f5c9b8e416dd05190bf...4813cb1d29961f0d0a000f73864345bdb665d5af
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 08:28:20 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 22 Oct 2024 04:28:20 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: linker: add
 --optimistic-linking flag
Message-ID: <6717622495d87_7b74b31d6fc51739@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
867e6115 by doyougnu at 2024-10-22T04:28:09-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
0c6fb1f8 by doyougnu at 2024-10-22T04:28:09-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
73e71758 by Cheng Shao at 2024-10-22T04:28:10-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -


21 changed files:

- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/runtime_control.rst
- hadrian/bindist/Makefile
- hadrian/src/Rules/BinaryDist.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- rts/Linker.c
- rts/RtsFlags.c
- rts/include/rts/Flags.h
- rts/linker/elf_got.c
- + testsuite/tests/ghci/linking/T25240/Makefile
- + testsuite/tests/ghci/linking/T25240/T25240.hs
- + testsuite/tests/ghci/linking/T25240/T25240.stderr
- + testsuite/tests/ghci/linking/T25240/T25240a.hs
- + testsuite/tests/ghci/linking/T25240/all.T
- testsuite/tests/ghci/should_run/T18064.stderr
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32


Changes:

=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -29,6 +29,10 @@ GHCi
 Runtime system
 ~~~~~~~~~~~~~~
 
+- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
+  runtime linker to continue in the presence of unknown symbols. By default this
+  flag is not passed, preserving previous behavior.
+
 Cmm
 ~~~
 


=====================================
docs/users_guide/runtime_control.rst
=====================================
@@ -397,6 +397,11 @@ Miscellaneous RTS options
     heap larger than 1T. ``-xr`` is a no-op if GHC is configured with
     ``--disable-large-address-space`` or if the platform is 32-bit.
 
+.. rts-flag:: --optimistic-linking
+
+    If given, instruct the runtime linker to try to continue linking in the
+    presence of an unresolved symbol.
+
 .. _rts-options-gc:
 
 RTS options to control the garbage collector


=====================================
hadrian/bindist/Makefile
=====================================
@@ -243,7 +243,7 @@ install_wrappers: install_bin_libdir install_hsc2hs_wrapper
 .PHONY: install_hsc2hs_wrapper
 install_hsc2hs_wrapper:
 	@echo Copying hsc2hs wrapper
-	cp mk/hsc2hs wrappers/hsc2hs-ghc-$(ProjectVersion)
+	cp mk/hsc2hs wrappers/$(CrossCompilePrefix)hsc2hs-ghc-$(ProjectVersion)
 
 PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s:   :\0xxx\0:g")
 .PHONY: update_package_db


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -437,13 +437,14 @@ pkgToWrappers pkg = do
       | otherwise     -> pure []
 
 wrapper :: FilePath -> Action String
-wrapper "ghc"         = ghcWrapper
-wrapper "ghc-pkg"     = ghcPkgWrapper
-wrapper "ghci" = ghciScriptWrapper
-wrapper "haddock"     = haddockWrapper
-wrapper "hsc2hs"      = hsc2hsWrapper
-wrapper "runghc"      = runGhcWrapper
-wrapper "runhaskell"  = runGhcWrapper
+wrapper wrapper_name
+  | "runghc"     `isSuffixOf` wrapper_name = runGhcWrapper
+  | "ghc"        `isSuffixOf` wrapper_name = ghcWrapper
+  | "ghc-pkg"    `isSuffixOf` wrapper_name = ghcPkgWrapper
+  | "ghci"       `isSuffixOf` wrapper_name = ghciScriptWrapper
+  | "haddock"    `isSuffixOf` wrapper_name = haddockWrapper
+  | "hsc2hs"     `isSuffixOf` wrapper_name = hsc2hsWrapper
+  | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper
 wrapper _             = commonWrapper
 
 -- | Wrapper scripts for different programs. Common is default wrapper.
@@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\
 -- | --interactive flag.
 ghciScriptWrapper :: Action String
 ghciScriptWrapper = do
+  prefix <- crossPrefix
   version <- setting ProjectVersion
   pure $ unlines
-    [ "executable=\"$bindir/ghc-" ++ version ++ "\""
+    [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
     , "exec $executable --interactive \"$@\"" ]
 
 -- | When not on Windows, we want to ship the 3 flavours of the iserv program
@@ -548,4 +550,3 @@ createGhcii outDir = do
       [ "#!/bin/sh"
       , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\""
       ]
-


=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -162,6 +162,8 @@ data MiscFlags = MiscFlags
     , disableDelayedOsMemoryReturn :: Bool
     , internalCounters      :: Bool
     , linkerAlwaysPic       :: Bool
+    -- TODO: #25354 uncomment to expose this flag to base.
+    -- , linkerOptimistic      :: Bool
     , linkerMemBase         :: Word
       -- ^ address to ask the OS for memory for the linker, 0 ==> off
     , ioManager             :: IoManagerFlag


=====================================
rts/Linker.c
=====================================
@@ -967,10 +967,20 @@ SymbolAddr* lookupSymbol( SymbolName* lbl )
     // lookupDependentSymbol directly.
     SymbolAddr* r = lookupDependentSymbol(lbl, NULL, NULL);
     if (!r) {
-        errorBelch("^^ Could not load '%s', dependency unresolved. "
-                   "See top entry above.\n", lbl);
-        IF_DEBUG(linker, printLoadedObjects());
-        fflush(stderr);
+        if (!RtsFlags.MiscFlags.linkerOptimistic) {
+          errorBelch("^^ Could not load '%s', dependency unresolved. "
+                     "See top entry above. You might consider using --optimistic-linking\n",
+                     lbl);
+          IF_DEBUG(linker, printLoadedObjects());
+          fflush(stderr);
+        } else {
+          // if --optimistic-linking is passed into the RTS we allow the linker
+          // to optimistically continue
+          errorBelch("^^ Could not load '%s', dependency unresolved, "
+                     "optimistically continuing\n",
+                     lbl);
+          r = (void*) 0xDEADBEEF;
+        }
     }
 
     if (!runPendingInitializers()) {


=====================================
rts/RtsFlags.c
=====================================
@@ -269,6 +269,7 @@ void initRtsFlagsDefaults(void)
     RtsFlags.MiscFlags.disableDelayedOsMemoryReturn = false;
     RtsFlags.MiscFlags.internalCounters        = false;
     RtsFlags.MiscFlags.linkerAlwaysPic         = DEFAULT_LINKER_ALWAYS_PIC;
+    RtsFlags.MiscFlags.linkerOptimistic        = false;
     RtsFlags.MiscFlags.linkerMemBase           = 0;
     RtsFlags.MiscFlags.ioManager               = IO_MNGR_FLAG_AUTO;
 #if defined(THREADED_RTS) && defined(mingw32_HOST_OS)
@@ -998,6 +999,11 @@ error = true;
                       OPTION_UNSAFE;
                       RtsFlags.MiscFlags.generate_dump_file = true;
                   }
+                  else if (strequal("optimistic-linking",
+                              &rts_argv[arg][2])) {
+                       OPTION_UNSAFE;
+                       RtsFlags.MiscFlags.linkerOptimistic = true;
+                  }
                   else if (strequal("null-eventlog-writer",
                                &rts_argv[arg][2])) {
                       OPTION_UNSAFE;


=====================================
rts/include/rts/Flags.h
=====================================
@@ -267,6 +267,7 @@ typedef struct _MISC_FLAGS {
                                           there as well. */
     bool internalCounters;       /* See Note [Internal Counters Stats] */
     bool linkerAlwaysPic;        /* Assume the object code is always PIC */
+    bool linkerOptimistic;       /* Should the runtime linker optimistically continue */
     StgWord linkerMemBase;       /* address to ask the OS for memory
                                   * for the linker, NULL ==> off */
     IO_MANAGER_FLAG ioManager;   /* The I/O manager to use.  */


=====================================
rts/linker/elf_got.c
=====================================
@@ -97,9 +97,22 @@ fillGot(ObjectCode * oc) {
                             if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) {
                                 symbol->addr = oc->info->got_start;
                             } else {
-                                errorBelch("Failed to lookup symbol: %s\n",
+                                errorBelch("Failed to lookup symbol: %s,"
+                                           " you might consider using --optimistic-linking\n",
                                            symbol->name);
-                                return EXIT_FAILURE;
+
+                                // if --optimistic-linking is passed into the
+                                // RTS we allow the linker to optimistically
+                                // continue
+                                if (RtsFlags.MiscFlags.linkerOptimistic) {
+                                    errorBelch("Failed to lookup symbol: %s,"
+                                               " optimistically continuing.\n",
+                                               symbol->name);
+                                    symbol->addr = (void*) 0xDEADBEEF;
+                                } else {
+                                    return EXIT_FAILURE;
+                                }
+
                             }
                         }
                     } else {


=====================================
testsuite/tests/ghci/linking/T25240/Makefile
=====================================
@@ -0,0 +1,7 @@
+TOP=../../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+.PHONY: T25240
+T25240:
+	"$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) T25240a.hs T25240.hs +RTS --optimistic-linking -RTS


=====================================
testsuite/tests/ghci/linking/T25240/T25240.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+{-
+
+When the RTS linker loads the T25240a module to run the pure foo splice, it
+tries to resolve the func symbol even if this function isn't required to run the
+splice code, i.e., its dead code. This test checks that by passing the
+--optimistic-linking flag the RTS linker continues to link even in the presence
+of unknown symbols.
+
+-}
+
+module T25240 where
+
+import T25240a
+
+$(pure foo)


=====================================
testsuite/tests/ghci/linking/T25240/T25240.stderr
=====================================
@@ -0,0 +1,2 @@
+ghc: ^^ Could not load 'func', dependency unresolved, optimistically continuing
+


=====================================
testsuite/tests/ghci/linking/T25240/T25240a.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+
+module T25240a
+  ( foo, func
+  ) where
+
+
+foo :: [a]
+foo = []
+
+foreign import ccall "func"
+  func :: Int -> Int


=====================================
testsuite/tests/ghci/linking/T25240/all.T
=====================================
@@ -0,0 +1,3 @@
+# skip on darwin because the leading underscores will make the test fail
+test('T25240', [when(leading_underscore(),skip), req_rts_linker, extra_files(['T25240a.hs'])],
+    makefile_test, ['T25240'])


=====================================
testsuite/tests/ghci/should_run/T18064.stderr
=====================================
@@ -1,2 +1,2 @@
-: ^^ Could not load 'blah', dependency unresolved. See top entry above.
+: ^^ Could not load 'blah', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label


=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32
=====================================
@@ -9,7 +9,7 @@ This could be caused by:
    * Specifying the same object file twice on the GHCi command line
    * An incorrect `package.conf' entry, causing some object to be
      loaded twice.
-ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above.
+ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
 
 
 GHC.ByteCode.Linker: can't find label



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4813cb1d29961f0d0a000f73864345bdb665d5af...73e7175865378652bc12b3af80cb8d6861904e1b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4813cb1d29961f0d0a000f73864345bdb665d5af...73e7175865378652bc12b3af80cb8d6861904e1b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 08:58:00 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 22 Oct 2024 04:58:00 -0400
Subject: [Git][ghc/ghc][wip/fix-centos7] 10 commits: Interpreter: Add locking
 for communication with external interpreter
Message-ID: <67176918628de_7b74b66673c618eb@gitlab.mail>



Cheng Shao pushed to branch wip/fix-centos7 at Glasgow Haskell Compiler / GHC


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
f94510df by Cheng Shao at 2024-10-22T10:57:46+02:00
testsuite: fix process010 for centos7 job

- - - - -


19 changed files:

- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Process.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe4c256705960715e0f1318b44037853ff9faa3f...f94510df6e93b0378aedf730d0caba7a595d1b94

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe4c256705960715e0f1318b44037853ff9faa3f...f94510df6e93b0378aedf730d0caba7a595d1b94
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 09:17:43 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Tue, 22 Oct 2024 05:17:43 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <67176db72ec70_351cf4c47ac3361a@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
d7757719 by Sebastian Graf at 2024-10-22T11:15:29+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                          Baseline
                      Test    Metric          value      New value Change
--------------------------------------------------------------------------------
  ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
            T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
            T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
            T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
           T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
            T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
            T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
             T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
             T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                 geo. mean                                          -0.7%
                 minimum                                           -33.9%
                 maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 09:20:30 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 22 Oct 2024 05:20:30 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/perf-late-ccs
Message-ID: <67176e5ede26e_351cf4218cc03869e@gitlab.mail>



Cheng Shao pushed new branch wip/perf-late-ccs at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/perf-late-ccs
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 10:02:13 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 22 Oct 2024 06:02:13 -0400
Subject: [Git][ghc/ghc][wip/romes/25304] 72 commits: Changed import from Ghc. 
 module to L.H.S module
Message-ID: <6717782549bf4_351cf44ff2f4477c3@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/25304 at Glasgow Haskell Compiler / GHC


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
3ac62a95 by Rodrigo Mesquita at 2024-10-22T11:01:56+01:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
bd6bfe4e by Rodrigo Mesquita at 2024-10-22T11:01:56+01:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -


25 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/JS/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e94dc2bbb7742fd86a9326b3b02f51a88b000c07...bd6bfe4e262e34acbdd075dfdbb71e2a632033c4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e94dc2bbb7742fd86a9326b3b02f51a88b000c07...bd6bfe4e262e34acbdd075dfdbb71e2a632033c4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 22 10:10:23 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 22 Oct 2024 06:10:23 -0400
Subject: [Git][ghc/ghc][wip/perf-late-ccs] hadrian: enable late-CCS for perf
 flavour as well
Message-ID: <67177a0fc5940_b886d8c8445040@gitlab.mail>



Cheng Shao pushed to branch wip/perf-late-ccs at Glasgow Haskell Compiler / GHC


Commits:
2c6cad4b by Cheng Shao at 2024-10-22T12:09:52+02:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -


3 changed files:

- hadrian/doc/flavours.md
- hadrian/src/Settings/Flavours/Performance.hs
- hadrian/src/Settings/Flavours/Release.hs


Changes:

=====================================
hadrian/doc/flavours.md
=====================================
@@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH
     -O2
   
   
-    release (same as perf with -haddock and +late-ccs)
+    release (same as perf with -haddock)
     
     -O
-H64m -O
-H64m @@ -323,7 +323,7 @@ The supported transformers are listed below: late_ccs - Enable -fprof-late in profiled libraries. + Enable -fprof-late in profiled libraries. Enabled in perf and release flavours. dump_stg ===================================== hadrian/src/Settings/Flavours/Performance.hs ===================================== @@ -6,7 +6,7 @@ import {-# SOURCE #-} Settings.Default -- Please update doc/flavours.md when changing this file. performanceFlavour :: Flavour -performanceFlavour = splitSections $ defaultFlavour +performanceFlavour = splitSections $ enableLateCCS $ defaultFlavour { name = "perf" , extraArgs = performanceArgs <> defaultHaddockExtraArgs } ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,4 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableLateCCS $ enableHaddock performanceFlavour { name = "release" } +releaseFlavour = enableHaddock performanceFlavour { name = "release" } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2c6cad4b70cabc4f75ea9cfdd618296ac443c1ef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2c6cad4b70cabc4f75ea9cfdd618296ac443c1ef You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 10:27:15 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 22 Oct 2024 06:27:15 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/ghc-with-debug Message-ID: <67177e035d7df_18e951193818103764@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/ghc-with-debug at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/ghc-with-debug You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 11:54:40 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 22 Oct 2024 07:54:40 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-25406 Message-ID: <67179280c1e4a_149eb3150d24493fb@gitlab.mail> Cheng Shao pushed new branch wip/fix-25406 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-25406 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 13:38:49 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 09:38:49 -0400 Subject: [Git][ghc/ghc][master] 2 commits: linker: add --optimistic-linking flag Message-ID: <6717aae99133f_11f6681544c48336@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 25121dbc by doyougnu at 2024-10-22T09:38:18-04:00 linker: add --optimistic-linking flag This patch adds: - the --optimistic-linking flag which binds unknown symbols in the runtime linker to 0xDEADBEEF instead of exiting with failure - The test T25240 which tests these flags using dead code in the FFI system. - closes #25240 This patch is part of the upstreaming haskell.nix patches project. - - - - - f19e076d by doyougnu at 2024-10-22T09:38:18-04:00 ghc-internal: hide linkerOptimistic in MiscFlags - - - - - 19 changed files: - docs/users_guide/9.14.1-notes.rst - docs/users_guide/runtime_control.rst - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - rts/Linker.c - rts/RtsFlags.c - rts/include/rts/Flags.h - rts/linker/elf_got.c - + testsuite/tests/ghci/linking/T25240/Makefile - + testsuite/tests/ghci/linking/T25240/T25240.hs - + testsuite/tests/ghci/linking/T25240/T25240.stderr - + testsuite/tests/ghci/linking/T25240/T25240a.hs - + testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/should_run/T18064.stderr - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32 Changes: ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -29,6 +29,10 @@ GHCi Runtime system ~~~~~~~~~~~~~~ +- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the + runtime linker to continue in the presence of unknown symbols. By default this + flag is not passed, preserving previous behavior. + Cmm ~~~ ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -397,6 +397,11 @@ Miscellaneous RTS options heap larger than 1T. ``-xr`` is a no-op if GHC is configured with ``--disable-large-address-space`` or if the platform is 32-bit. +.. rts-flag:: --optimistic-linking + + If given, instruct the runtime linker to try to continue linking in the + presence of an unresolved symbol. + .. _rts-options-gc: RTS options to control the garbage collector ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -162,6 +162,8 @@ data MiscFlags = MiscFlags , disableDelayedOsMemoryReturn :: Bool , internalCounters :: Bool , linkerAlwaysPic :: Bool + -- TODO: #25354 uncomment to expose this flag to base. + -- , linkerOptimistic :: Bool , linkerMemBase :: Word -- ^ address to ask the OS for memory for the linker, 0 ==> off , ioManager :: IoManagerFlag ===================================== rts/Linker.c ===================================== @@ -967,10 +967,20 @@ SymbolAddr* lookupSymbol( SymbolName* lbl ) // lookupDependentSymbol directly. SymbolAddr* r = lookupDependentSymbol(lbl, NULL, NULL); if (!r) { - errorBelch("^^ Could not load '%s', dependency unresolved. " - "See top entry above.\n", lbl); - IF_DEBUG(linker, printLoadedObjects()); - fflush(stderr); + if (!RtsFlags.MiscFlags.linkerOptimistic) { + errorBelch("^^ Could not load '%s', dependency unresolved. " + "See top entry above. You might consider using --optimistic-linking\n", + lbl); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); + } else { + // if --optimistic-linking is passed into the RTS we allow the linker + // to optimistically continue + errorBelch("^^ Could not load '%s', dependency unresolved, " + "optimistically continuing\n", + lbl); + r = (void*) 0xDEADBEEF; + } } if (!runPendingInitializers()) { ===================================== rts/RtsFlags.c ===================================== @@ -269,6 +269,7 @@ void initRtsFlagsDefaults(void) RtsFlags.MiscFlags.disableDelayedOsMemoryReturn = false; RtsFlags.MiscFlags.internalCounters = false; RtsFlags.MiscFlags.linkerAlwaysPic = DEFAULT_LINKER_ALWAYS_PIC; + RtsFlags.MiscFlags.linkerOptimistic = false; RtsFlags.MiscFlags.linkerMemBase = 0; RtsFlags.MiscFlags.ioManager = IO_MNGR_FLAG_AUTO; #if defined(THREADED_RTS) && defined(mingw32_HOST_OS) @@ -998,6 +999,11 @@ error = true; OPTION_UNSAFE; RtsFlags.MiscFlags.generate_dump_file = true; } + else if (strequal("optimistic-linking", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.MiscFlags.linkerOptimistic = true; + } else if (strequal("null-eventlog-writer", &rts_argv[arg][2])) { OPTION_UNSAFE; ===================================== rts/include/rts/Flags.h ===================================== @@ -267,6 +267,7 @@ typedef struct _MISC_FLAGS { there as well. */ bool internalCounters; /* See Note [Internal Counters Stats] */ bool linkerAlwaysPic; /* Assume the object code is always PIC */ + bool linkerOptimistic; /* Should the runtime linker optimistically continue */ StgWord linkerMemBase; /* address to ask the OS for memory * for the linker, NULL ==> off */ IO_MANAGER_FLAG ioManager; /* The I/O manager to use. */ ===================================== rts/linker/elf_got.c ===================================== @@ -97,9 +97,22 @@ fillGot(ObjectCode * oc) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; } else { - errorBelch("Failed to lookup symbol: %s\n", + errorBelch("Failed to lookup symbol: %s," + " you might consider using --optimistic-linking\n", symbol->name); - return EXIT_FAILURE; + + // if --optimistic-linking is passed into the + // RTS we allow the linker to optimistically + // continue + if (RtsFlags.MiscFlags.linkerOptimistic) { + errorBelch("Failed to lookup symbol: %s," + " optimistically continuing.\n", + symbol->name); + symbol->addr = (void*) 0xDEADBEEF; + } else { + return EXIT_FAILURE; + } + } } } else { ===================================== testsuite/tests/ghci/linking/T25240/Makefile ===================================== @@ -0,0 +1,7 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +.PHONY: T25240 +T25240: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) T25240a.hs T25240.hs +RTS --optimistic-linking -RTS ===================================== testsuite/tests/ghci/linking/T25240/T25240.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} + +{- + +When the RTS linker loads the T25240a module to run the pure foo splice, it +tries to resolve the func symbol even if this function isn't required to run the +splice code, i.e., its dead code. This test checks that by passing the +--optimistic-linking flag the RTS linker continues to link even in the presence +of unknown symbols. + +-} + +module T25240 where + +import T25240a + +$(pure foo) ===================================== testsuite/tests/ghci/linking/T25240/T25240.stderr ===================================== @@ -0,0 +1,2 @@ +ghc: ^^ Could not load 'func', dependency unresolved, optimistically continuing + ===================================== testsuite/tests/ghci/linking/T25240/T25240a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE TemplateHaskell #-} + + +module T25240a + ( foo, func + ) where + + +foo :: [a] +foo = [] + +foreign import ccall "func" + func :: Int -> Int ===================================== testsuite/tests/ghci/linking/T25240/all.T ===================================== @@ -0,0 +1,3 @@ +# skip on darwin because the leading underscores will make the test fail +test('T25240', [when(leading_underscore(),skip), req_rts_linker, extra_files(['T25240a.hs'])], + makefile_test, ['T25240']) ===================================== testsuite/tests/ghci/should_run/T18064.stderr ===================================== @@ -1,2 +1,2 @@ -: ^^ Could not load 'blah', dependency unresolved. See top entry above. +: ^^ Could not load 'blah', dependency unresolved. See top entry above. You might consider using --optimistic-linking ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/148059fea534aced44649c739cd0fad4c25a99f0...f19e076d7fb10fe1ef1eb83ab23cbf2ec5c3d3be -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/148059fea534aced44649c739cd0fad4c25a99f0...f19e076d7fb10fe1ef1eb83ab23cbf2ec5c3d3be You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 13:39:24 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 09:39:24 -0400 Subject: [Git][ghc/ghc][master] hadrian: fix bindist executable wrapper logic for cross targets Message-ID: <6717ab0c88651_11f66814947011314@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00 hadrian: fix bindist executable wrapper logic for cross targets This commit fixes an oversight of hadrian wrapper generation logic: when doing cross compilation, `wrapper` is called on executable names with cross prefix, therefore we must use `isSuffixOf` when matching to take the cross prefix into account. Also add missing cross prefix to ghci wrapper content and fix hsc2hs wrapper logic. - - - - - 2 changed files: - hadrian/bindist/Makefile - hadrian/src/Rules/BinaryDist.hs Changes: ===================================== hadrian/bindist/Makefile ===================================== @@ -243,7 +243,7 @@ install_wrappers: install_bin_libdir install_hsc2hs_wrapper .PHONY: install_hsc2hs_wrapper install_hsc2hs_wrapper: @echo Copying hsc2hs wrapper - cp mk/hsc2hs wrappers/hsc2hs-ghc-$(ProjectVersion) + cp mk/hsc2hs wrappers/$(CrossCompilePrefix)hsc2hs-ghc-$(ProjectVersion) PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s: :\0xxx\0:g") .PHONY: update_package_db ===================================== hadrian/src/Rules/BinaryDist.hs ===================================== @@ -437,13 +437,14 @@ pkgToWrappers pkg = do | otherwise -> pure [] wrapper :: FilePath -> Action String -wrapper "ghc" = ghcWrapper -wrapper "ghc-pkg" = ghcPkgWrapper -wrapper "ghci" = ghciScriptWrapper -wrapper "haddock" = haddockWrapper -wrapper "hsc2hs" = hsc2hsWrapper -wrapper "runghc" = runGhcWrapper -wrapper "runhaskell" = runGhcWrapper +wrapper wrapper_name + | "runghc" `isSuffixOf` wrapper_name = runGhcWrapper + | "ghc" `isSuffixOf` wrapper_name = ghcWrapper + | "ghc-pkg" `isSuffixOf` wrapper_name = ghcPkgWrapper + | "ghci" `isSuffixOf` wrapper_name = ghciScriptWrapper + | "haddock" `isSuffixOf` wrapper_name = haddockWrapper + | "hsc2hs" `isSuffixOf` wrapper_name = hsc2hsWrapper + | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper wrapper _ = commonWrapper -- | Wrapper scripts for different programs. Common is default wrapper. @@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\ -- | --interactive flag. ghciScriptWrapper :: Action String ghciScriptWrapper = do + prefix <- crossPrefix version <- setting ProjectVersion pure $ unlines - [ "executable=\"$bindir/ghc-" ++ version ++ "\"" + [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\"" , "exec $executable --interactive \"$@\"" ] -- | When not on Windows, we want to ship the 3 flavours of the iserv program @@ -548,4 +550,3 @@ createGhcii outDir = do [ "#!/bin/sh" , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\"" ] - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edc02197b95488e8752c988e0e92ed6253c04b8c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edc02197b95488e8752c988e0e92ed6253c04b8c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 14:54:21 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 22 Oct 2024 10:54:21 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/25397 Message-ID: <6717bc9db0c3f_3e4b0c51056813289@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/25397 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25397 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 15:40:48 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 11:40:48 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: linker: add --optimistic-linking flag Message-ID: <6717c780e0c27_1b289d661d2c112491@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 25121dbc by doyougnu at 2024-10-22T09:38:18-04:00 linker: add --optimistic-linking flag This patch adds: - the --optimistic-linking flag which binds unknown symbols in the runtime linker to 0xDEADBEEF instead of exiting with failure - The test T25240 which tests these flags using dead code in the FFI system. - closes #25240 This patch is part of the upstreaming haskell.nix patches project. - - - - - f19e076d by doyougnu at 2024-10-22T09:38:18-04:00 ghc-internal: hide linkerOptimistic in MiscFlags - - - - - edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00 hadrian: fix bindist executable wrapper logic for cross targets This commit fixes an oversight of hadrian wrapper generation logic: when doing cross compilation, `wrapper` is called on executable names with cross prefix, therefore we must use `isSuffixOf` when matching to take the cross prefix into account. Also add missing cross prefix to ghci wrapper content and fix hsc2hs wrapper logic. - - - - - 20ba7893 by Andreas Klebinger at 2024-10-22T11:40:33-04:00 mkTick: Push ticks through unsafeCoerce#. unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast for the purpose of mkTick. This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we now push the scope part of the cost centre up to `trivial_expr` at which point we can discard it completely if the expression is trivial enough. This fixes #25212. - - - - - c5e1ac81 by Cheng Shao at 2024-10-22T11:40:33-04:00 hadrian: enable late-CCS for perf flavour as well This patch enables late-CCS for perf flavour so that the testsuite can pass for perf as well. Fixes #25308. - - - - - 45657a96 by Cheng Shao at 2024-10-22T11:40:34-04:00 hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling This patch disables internal-interpreter flag for stage0 ghc-bin when not cross compiling, see added comment for explanation. Fixes #25406. - - - - - 27 changed files: - compiler/GHC/Core/Utils.hs - compiler/GHC/Types/Tickish.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/runtime_control.rst - hadrian/bindist/Makefile - hadrian/doc/flavours.md - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - rts/Linker.c - rts/RtsFlags.c - rts/include/rts/Flags.h - rts/linker/elf_got.c - + testsuite/tests/ghci/linking/T25240/Makefile - + testsuite/tests/ghci/linking/T25240/T25240.hs - + testsuite/tests/ghci/linking/T25240/T25240.stderr - + testsuite/tests/ghci/linking/T25240/T25240a.hs - + testsuite/tests/ghci/linking/T25240/all.T - testsuite/tests/ghci/should_run/T18064.stderr - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 - testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32 Changes: ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -305,7 +305,6 @@ mkTick t orig_expr = mkTick' id id orig_expr -- Some ticks (cost-centres) can be split in two, with the -- non-counting part having laxer placement properties. canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t - -- mkTick' handles floating of ticks *into* the expression. -- In this function, `top` is applied after adding the tick, and `rest` before. -- This will result in applications that look like (top $ Tick t $ rest expr). @@ -316,6 +315,10 @@ mkTick t orig_expr = mkTick' id id orig_expr -> CoreExpr -- current expression -> CoreExpr mkTick' top rest expr = case expr of + -- Float ticks into unsafe coerce the same way we would do with a cast. + Case scrut bndr ty alts@[Alt ac abs _rhs] + | Just rhs <- isUnsafeEqualityCase scrut bndr alts + -> top $ mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs -- Cost centre ticks should never be reordered relative to each -- other. Therefore we can stop whenever two collide. @@ -1251,7 +1254,7 @@ Note [Tick trivial] Ticks are only trivial if they are pure annotations. If we treat "tick x" as trivial, it will be inlined inside lambdas and the entry count will be skewed, for example. Furthermore "scc x" will -turn into just "x" in mkTick. +turn into just "x" in mkTick. At least if `x` is not a function. Note [Empty case is trivial] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Tickish.hs ===================================== @@ -295,13 +295,15 @@ tickishCanSplit _ = False mkNoCount :: GenTickish pass -> GenTickish pass mkNoCount n | not (tickishCounts n) = n | not (tickishCanSplit n) = panic "mkNoCount: Cannot split!" -mkNoCount n at ProfNote{} = n {profNoteCount = False} +mkNoCount n at ProfNote{} = let n' = n {profNoteCount = False} + in assert (profNoteCount n) n' mkNoCount _ = panic "mkNoCount: Undefined split!" mkNoScope :: GenTickish pass -> GenTickish pass mkNoScope n | tickishScoped n == NoScope = n | not (tickishCanSplit n) = panic "mkNoScope: Cannot split!" -mkNoScope n at ProfNote{} = n {profNoteScope = False} +mkNoScope n at ProfNote{} = let n' = n {profNoteScope = False} + in assert (profNoteCount n) n' mkNoScope _ = panic "mkNoScope: Undefined split!" -- | Return @True@ if this source annotation compiles to some backend ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -29,6 +29,10 @@ GHCi Runtime system ~~~~~~~~~~~~~~ +- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the + runtime linker to continue in the presence of unknown symbols. By default this + flag is not passed, preserving previous behavior. + Cmm ~~~ ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -397,6 +397,11 @@ Miscellaneous RTS options heap larger than 1T. ``-xr`` is a no-op if GHC is configured with ``--disable-large-address-space`` or if the platform is 32-bit. +.. rts-flag:: --optimistic-linking + + If given, instruct the runtime linker to try to continue linking in the + presence of an unresolved symbol. + .. _rts-options-gc: RTS options to control the garbage collector ===================================== hadrian/bindist/Makefile ===================================== @@ -243,7 +243,7 @@ install_wrappers: install_bin_libdir install_hsc2hs_wrapper .PHONY: install_hsc2hs_wrapper install_hsc2hs_wrapper: @echo Copying hsc2hs wrapper - cp mk/hsc2hs wrappers/hsc2hs-ghc-$(ProjectVersion) + cp mk/hsc2hs wrappers/$(CrossCompilePrefix)hsc2hs-ghc-$(ProjectVersion) PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s: :\0xxx\0:g") .PHONY: update_package_db ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O2 - release (same as perf with -haddock and +late-ccs) + release (same as perf with -haddock) -O
-H64m -O
-H64m @@ -323,7 +323,7 @@ The supported transformers are listed below: late_ccs - Enable -fprof-late in profiled libraries. + Enable -fprof-late in profiled libraries. Enabled in perf and release flavours. dump_stg ===================================== hadrian/src/Rules/BinaryDist.hs ===================================== @@ -437,13 +437,14 @@ pkgToWrappers pkg = do | otherwise -> pure [] wrapper :: FilePath -> Action String -wrapper "ghc" = ghcWrapper -wrapper "ghc-pkg" = ghcPkgWrapper -wrapper "ghci" = ghciScriptWrapper -wrapper "haddock" = haddockWrapper -wrapper "hsc2hs" = hsc2hsWrapper -wrapper "runghc" = runGhcWrapper -wrapper "runhaskell" = runGhcWrapper +wrapper wrapper_name + | "runghc" `isSuffixOf` wrapper_name = runGhcWrapper + | "ghc" `isSuffixOf` wrapper_name = ghcWrapper + | "ghc-pkg" `isSuffixOf` wrapper_name = ghcPkgWrapper + | "ghci" `isSuffixOf` wrapper_name = ghciScriptWrapper + | "haddock" `isSuffixOf` wrapper_name = haddockWrapper + | "hsc2hs" `isSuffixOf` wrapper_name = hsc2hsWrapper + | "runhaskell" `isSuffixOf` wrapper_name = runGhcWrapper wrapper _ = commonWrapper -- | Wrapper scripts for different programs. Common is default wrapper. @@ -473,9 +474,10 @@ runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\ -- | --interactive flag. ghciScriptWrapper :: Action String ghciScriptWrapper = do + prefix <- crossPrefix version <- setting ProjectVersion pure $ unlines - [ "executable=\"$bindir/ghc-" ++ version ++ "\"" + [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\"" , "exec $executable --interactive \"$@\"" ] -- | When not on Windows, we want to ship the 3 flavours of the iserv program @@ -548,4 +550,3 @@ createGhcii outDir = do [ "#!/bin/sh" , "exec \"$(dirname \"$0\")\"/ghc --interactive \"$@\"" ] - ===================================== hadrian/src/Settings/Flavours/Performance.hs ===================================== @@ -6,7 +6,7 @@ import {-# SOURCE #-} Settings.Default -- Please update doc/flavours.md when changing this file. performanceFlavour :: Flavour -performanceFlavour = splitSections $ defaultFlavour +performanceFlavour = splitSections $ enableLateCCS $ defaultFlavour { name = "perf" , extraArgs = performanceArgs <> defaultHaddockExtraArgs } ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,4 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableLateCCS $ enableHaddock performanceFlavour { name = "release" } +releaseFlavour = enableHaddock performanceFlavour { name = "release" } ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -107,7 +107,16 @@ packageArgs = do , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ] , builder (Cabal Flags) ? mconcat - [ expr ghcWithInterpreter `cabalFlag` "internal-interpreter" + [ + -- When cross compiling, enable for stage0 to get ghci + -- support. But when not cross compiling, disable for + -- stage0, otherwise we introduce extra dependencies + -- like haskeline etc, and mixing stageBoot/stage0 libs + -- can cause extra trouble (e.g. #25406) + expr ghcWithInterpreter ? + ifM (expr cross) + (arg "internal-interpreter") + (notStage0 `cabalFlag` "internal-interpreter") , ifM stage0 -- We build a threaded stage 1 if the bootstrapping compiler -- supports it. ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -162,6 +162,8 @@ data MiscFlags = MiscFlags , disableDelayedOsMemoryReturn :: Bool , internalCounters :: Bool , linkerAlwaysPic :: Bool + -- TODO: #25354 uncomment to expose this flag to base. + -- , linkerOptimistic :: Bool , linkerMemBase :: Word -- ^ address to ask the OS for memory for the linker, 0 ==> off , ioManager :: IoManagerFlag ===================================== rts/Linker.c ===================================== @@ -967,10 +967,20 @@ SymbolAddr* lookupSymbol( SymbolName* lbl ) // lookupDependentSymbol directly. SymbolAddr* r = lookupDependentSymbol(lbl, NULL, NULL); if (!r) { - errorBelch("^^ Could not load '%s', dependency unresolved. " - "See top entry above.\n", lbl); - IF_DEBUG(linker, printLoadedObjects()); - fflush(stderr); + if (!RtsFlags.MiscFlags.linkerOptimistic) { + errorBelch("^^ Could not load '%s', dependency unresolved. " + "See top entry above. You might consider using --optimistic-linking\n", + lbl); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); + } else { + // if --optimistic-linking is passed into the RTS we allow the linker + // to optimistically continue + errorBelch("^^ Could not load '%s', dependency unresolved, " + "optimistically continuing\n", + lbl); + r = (void*) 0xDEADBEEF; + } } if (!runPendingInitializers()) { ===================================== rts/RtsFlags.c ===================================== @@ -269,6 +269,7 @@ void initRtsFlagsDefaults(void) RtsFlags.MiscFlags.disableDelayedOsMemoryReturn = false; RtsFlags.MiscFlags.internalCounters = false; RtsFlags.MiscFlags.linkerAlwaysPic = DEFAULT_LINKER_ALWAYS_PIC; + RtsFlags.MiscFlags.linkerOptimistic = false; RtsFlags.MiscFlags.linkerMemBase = 0; RtsFlags.MiscFlags.ioManager = IO_MNGR_FLAG_AUTO; #if defined(THREADED_RTS) && defined(mingw32_HOST_OS) @@ -998,6 +999,11 @@ error = true; OPTION_UNSAFE; RtsFlags.MiscFlags.generate_dump_file = true; } + else if (strequal("optimistic-linking", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.MiscFlags.linkerOptimistic = true; + } else if (strequal("null-eventlog-writer", &rts_argv[arg][2])) { OPTION_UNSAFE; ===================================== rts/include/rts/Flags.h ===================================== @@ -267,6 +267,7 @@ typedef struct _MISC_FLAGS { there as well. */ bool internalCounters; /* See Note [Internal Counters Stats] */ bool linkerAlwaysPic; /* Assume the object code is always PIC */ + bool linkerOptimistic; /* Should the runtime linker optimistically continue */ StgWord linkerMemBase; /* address to ask the OS for memory * for the linker, NULL ==> off */ IO_MANAGER_FLAG ioManager; /* The I/O manager to use. */ ===================================== rts/linker/elf_got.c ===================================== @@ -97,9 +97,22 @@ fillGot(ObjectCode * oc) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; } else { - errorBelch("Failed to lookup symbol: %s\n", + errorBelch("Failed to lookup symbol: %s," + " you might consider using --optimistic-linking\n", symbol->name); - return EXIT_FAILURE; + + // if --optimistic-linking is passed into the + // RTS we allow the linker to optimistically + // continue + if (RtsFlags.MiscFlags.linkerOptimistic) { + errorBelch("Failed to lookup symbol: %s," + " optimistically continuing.\n", + symbol->name); + symbol->addr = (void*) 0xDEADBEEF; + } else { + return EXIT_FAILURE; + } + } } } else { ===================================== testsuite/tests/ghci/linking/T25240/Makefile ===================================== @@ -0,0 +1,7 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +.PHONY: T25240 +T25240: + "$(TEST_HC)" $(TEST_HC_OPTS_INTERACTIVE) T25240a.hs T25240.hs +RTS --optimistic-linking -RTS ===================================== testsuite/tests/ghci/linking/T25240/T25240.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} + +{- + +When the RTS linker loads the T25240a module to run the pure foo splice, it +tries to resolve the func symbol even if this function isn't required to run the +splice code, i.e., its dead code. This test checks that by passing the +--optimistic-linking flag the RTS linker continues to link even in the presence +of unknown symbols. + +-} + +module T25240 where + +import T25240a + +$(pure foo) ===================================== testsuite/tests/ghci/linking/T25240/T25240.stderr ===================================== @@ -0,0 +1,2 @@ +ghc: ^^ Could not load 'func', dependency unresolved, optimistically continuing + ===================================== testsuite/tests/ghci/linking/T25240/T25240a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE TemplateHaskell #-} + + +module T25240a + ( foo, func + ) where + + +foo :: [a] +foo = [] + +foreign import ccall "func" + func :: Int -> Int ===================================== testsuite/tests/ghci/linking/T25240/all.T ===================================== @@ -0,0 +1,3 @@ +# skip on darwin because the leading underscores will make the test fail +test('T25240', [when(leading_underscore(),skip), req_rts_linker, extra_files(['T25240a.hs'])], + makefile_test, ['T25240']) ===================================== testsuite/tests/ghci/should_run/T18064.stderr ===================================== @@ -1,2 +1,2 @@ -: ^^ Could not load 'blah', dependency unresolved. See top entry above. +: ^^ Could not load 'blah', dependency unresolved. See top entry above. You might consider using --optimistic-linking ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label ===================================== testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-64-mingw32 ===================================== @@ -9,7 +9,7 @@ This could be caused by: * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. -ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. +ghc-stage2.exe: ^^ Could not load 'c', dependency unresolved. See top entry above. You might consider using --optimistic-linking GHC.ByteCode.Linker: can't find label View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/73e7175865378652bc12b3af80cb8d6861904e1b...45657a96f5a9420f5f5270fe9aafc2e8bfba81fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/73e7175865378652bc12b3af80cb8d6861904e1b...45657a96f5a9420f5f5270fe9aafc2e8bfba81fa You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 16:31:08 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Tue, 22 Oct 2024 12:31:08 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] 42 commits: SpecConstr: Introduce a separate argument limit for forced specs. Message-ID: <6717d34ca8f4b_2a7fbd1fea3c592b6@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC Commits: da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00 SpecConstr: Introduce a separate argument limit for forced specs. We used to put no limit at all on specializations forced via the SPEC argument. This isn't always reasonable so we introduce a very high limit that applies to forced specializations, a flag to control it, and we now emit a warning if we fail a specialization because we exceed the warning. Fixes #25197 - - - - - 39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00 ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps This will be the new place for functions that would have gone into GHC.Exts in the past but are not stable enough to do so now. Addresses #25242 - - - - - e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00 RTS: cleanup timerfd file descriptors after a fork (#25280) When we init a timerfd-based ticker, we should be careful to cleanup the old file descriptors (e.g. after a fork). - - - - - 64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00 determinism: Deterministic MonadGetUnique LlvmM Update LlvmM to thread a unique deterministic supply (using UniqDSMT), and use it in the MonadGetUnique instance. This makes uniques sampled from LlvmM deterministic, which guarantees object determinism with -fllvm. Fixes #25274 - - - - - 36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00 Bump LLVM upper bound to allow LLVM 19 Also bumps the ci-images commit so that the deb12 images uses LLVM 19 for testing. ------------------------- Metric Decrease: size_hello_artifact_gzip size_hello_unicode_gzip ------------------------- Fixes #25295 - - - - - 0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00 configure: Allow happy-2.0.2 happy-2.0.2 can be used to compile GHC. happy-2.0 and 2.0.1 have bugs which make it unsuitable to use. The version bound is now == 1.20.* || >= 2.0.2 && < 2.1 Fixes #25276 - - - - - 92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00 Use bundled llc/opt on Windows (#22438) - - - - - af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00 Fix registerArch for riscv64 The register allocator doesn't support vector registers on riscv64, therefore advertise as NoVectors. Fixes #25314 - - - - - a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00 riscv: Avoid using csrr instruction to test for vector registers The csrr instruction isn't allowed in qemu user-mode, and raises an illegal instruction error when it is encountered. Therefore for now, we just hard-code that there is no support for vector registers since the rest of the compiler doesn't support vector registers for riscv. Fixes #25312 - - - - - 115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00 Add support for fp min/max to riscv Fixes #25313 - - - - - f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite/perf: Report better error message on malformed note Previously a malformed perf note resulted in very poor errors. Here we slight improve this situation. - - - - - 51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00 testsuite: Handle division-by-zero more gracefully Previously we would fail with an ZeroDivisionError. Fixes #25321 - - - - - 50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00 ci: Add nightly & release ubuntu-22.04 jobs This adds build of bindists on ubuntu-22.04 on nightly and release pipelines. We also update ghcup-metadata to provide ubuntu-22.04 bindists on ubuntu-22.04. Fixes #25317 - - - - - 9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00 haddock: Bump binary interface version to 46. This allows haddock to give good error messages when being used on mismatched interface files. We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6 This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked. - - - - - 2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00 Change versionig of ghc-experimental to follow ghc versions. Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning. This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on. This fixes #25289 - - - - - 876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00 base: Add `HasCallStack` constraint to `ioError` As proposed in core-libraries-committee#275. - - - - - 9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00 Fix toException method for ExceptionWithContext Fixes #25235 - - - - - ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00 Exception rethrowing Basic changes: * Change `catch` function to propagate exceptions using the WhileHandling mechanism. * Introduce `catchNoPropagate`, which does the same as before, but passes an exception which can be rethrown. * Introduce `rethrowIO` combinator, which rethrows an exception with a context and doesn't add a new backtrace. * Introduce `tryWithContext` for a variant of `try` which can rethrow the exception with it's original context. * onException is modified to rethrow the original error rather than creating a new callstack. * Functions which rethrow in GHC.Internal.IO.Handle.FD, GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and GHC.Internal.System.IO.Error are modified to not add a new callstack. Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202> - - - - - bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00 testsuite: remove accidentally checked in debug print logic - - - - - 68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00 Deprecation for WarnCompatUnqualifiedImports Fixes #25330 - - - - - 4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00 Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b) Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86 - - - - - ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00 driver: fix runWorkerLimit on wasm This commit fixes link-time unresolved symbol errors for sem_open etc on wasm, by making runWorkerLimit always behave single-threaded. This avoids introducing the jobserver logic into the final wasm module and thus avoids referencing the posix semaphore symbols. - - - - - 135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00 Parallelize getRootSummary computations in dep analysis downsweep This reuses the upsweep step's infrastructure to process batches of modules in parallel. I benchmarked this by running `ghc -M` on two sets of 10,000 modules; one with a linear dependency chain and the other with a binary tree. Comparing different values for the number of modules per thread suggested an optimum at `length targets `div` (n_cap * 2)`, with results similar to this one (6 cores, 12 threads): ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 1.775 s ± 0.026 s [User: 1.377 s, System: 0.399 s] Range (min … max): 1.757 s … 1.793 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 876.2 ms ± 20.9 ms [User: 1833.2 ms, System: 518.6 ms] Range (min … max): 856.2 ms … 898.0 ms 3 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 793.5 ms ± 23.2 ms [User: 2318.9 ms, System: 718.6 ms] Range (min … max): 771.9 ms … 818.0 ms 3 runs ``` Results don't differ much when the batch size is reduced to a quarter of that, but there's significant thread scheduling overhead for a size of 1: ``` Benchmark 1: linear 1 jobs Time (mean ± σ): 2.611 s ± 0.029 s [User: 2.851 s, System: 0.783 s] Range (min … max): 2.591 s … 2.632 s 2 runs Benchmark 2: linear 6 jobs Time (mean ± σ): 1.189 s ± 0.007 s [User: 2.707 s, System: 1.103 s] Range (min … max): 1.184 s … 1.194 s 2 runs Benchmark 3: linear 12 jobs Time (mean ± σ): 1.097 s ± 0.006 s [User: 2.938 s, System: 1.300 s] Range (min … max): 1.093 s … 1.101 s 2 runs ``` Larger batches also slightly worsen performance. - - - - - 535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00 Clarify the meaning of "exactly once" in LinearTypes Solves documentaion issue #25084. - - - - - 92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00 Only allow (a => b) :: Constraint rather than CONSTRAINT rep Fixes #25243 - - - - - 4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00 EPA: Remove unused hsCaseAnnsRest We never populate it, so remove it. - - - - - 5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00 rts: Fix invocation of __ieee_set_fp_control() on alpha-linux Fixes the following error when building GHC on alpha-linux: rts/posix/Signals.c: In function ‘initDefaultHandlers’: rts/posix/Signals.c:709:5: error: error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration] 709 | ieee_set_fp_control(0); | ^~~~~~~~~~~~~~~~~~~ | 709 | ieee_set_fp_control(0); | - - - - - c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00 Add changelog entries for !12479 - - - - - bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00 javascript: Read fields of ObjectBlock lazily When linking a module with a large dependency footprint too much of the object files were forced during linking. This lead to a large amount of memory taken up by thunks which would never be forced On the PartialDownsweep test this halves the memory required (from 25G to 13G). Towards #25324 ------------------------- Metric Increase: size_hello_obj ------------------------- - - - - - 571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00 ci: Run the i386 validation job when i386 label is set This is helpful when making changes to base and must update the javascript and i386 base exports files. - - - - - e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00 Rewrite partitionByWorkerSize to avoid pattern match checker bug With `-g3` the pattern match checker would warn about these incomplete patterns. This affects the debug_info builds on CI. ``` Pattern match(es) are non-exhaustive In an equation for ‘go’: Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched: (_:_) _ _ | 2514 | go [] small warnings = (small, warnings) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... ``` Workaround for #25338 - - - - - d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00 Remove the wrapper/coercion-passing logic for submultiplicity checks Instead, we use a dedicated DelayedError, which is emitted systematically on submultiplicity checks, but is suppressed if we can indeed solve the submultiplicity constraint with a reflexivity coercion. This way, we don't have to return anything from `tcSubMult`, which now looks like a regular constraint check, the rest is implementation detail. This removes all of the strange boilerplate that I'd been struggling with under the previous implementation. Even if submultiplicity checks are not properly constraints, this way it's contained entirely within a `WantedConstraint`. Much more pleasant. Closes #25128. - - - - - 1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00 AArch64: Implement switch/jump tables (#19912) This improves the performance of Cmm switch statements (compared to a chain of if statements.) - - - - - 3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00 Fixes #25256, missing parens inside TH-printed pattern type signature - - - - - ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00 Better documentation for floatRange function Closes #16479 - - - - - ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00 Adjust progress message for hadrian to include cwd. Fixes #25335 - - - - - 5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00 CCallConv test: Align argument types The C calling convention / standard requires that arguments and their values are of the same type. - - - - - c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00 hadrian: remove unused ghciWithDebugger field from flavour config This patch removes the ghciWithDebugger field from flavour config since it's actually not used anywhere. - - - - - 9c9c790d by sheaf at 2024-10-07T19:27:23-04:00 user's guide: update docs for X86 CPU flags This commit updates the section of the user's guide pertaining to X86 feature flags with the following changes: - the NCG backend now supports SIMD, so remove all text that says the contrary, - the LLVM backend does not "automatically detect" features, so remove any text that makes that claim. - - - - - a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00 ci: RISCV64 cross-compile testing This adds a validation job which tests that we can build a riscv64 cross compiler and build a simple program using it. We do not currently run the whole testsuite. Towards #25254 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00 Remove unused accumulators in partition_errors - - - - - 76dcc2b1 by Torsten Schmits at 2024-10-22T18:30:05+02:00 Link interface bytecode from package DBs if possible Part of #25090. MR !13068 When splices are executed with `-fprefer-byte-code`, the loader will compile Core bindings to bytecode if those are present in interfaces of module dependencies. So far, this only applied to local modules (i.e. home modules in make mode and non-package deps in oneshot mode). This patch extends support to interfaces loaded from a package DB. In `getLinkDeps`, the dependencies chosen for recursion were restricted to `dep_direct_mods`, which has been changed to include `mi_usages`. In order to unify treatment of the different link variants across make/oneshot mode, the algorithm's intermediate results have been abstracted into the data types `LinkDep` and `LinkModule`. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Errors/Ppr.hs - compiler/GHC/HsToCore/Errors/Types.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/196dbea3920369a3f6141c09f9a66b4452189675...76dcc2b10b794c375cd63469aee5b186b05423b6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/196dbea3920369a3f6141c09f9a66b4452189675...76dcc2b10b794c375cd63469aee5b186b05423b6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 17:29:12 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Tue, 22 Oct 2024 13:29:12 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] Link interface bytecode from package DBs if possible Message-ID: <6717e0e875be7_2a7fbd590c4063317@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC Commits: c8ab26a0 by Torsten Schmits at 2024-10-22T19:28:44+02:00 Link interface bytecode from package DBs if possible Part of #25090. MR !13068 When splices are executed with `-fprefer-byte-code`, the loader will compile Core bindings to bytecode if those are present in interfaces of module dependencies. So far, this only applied to local modules (i.e. home modules in make mode and non-package deps in oneshot mode). This patch extends support to interfaces loaded from a package DB. In `getLinkDeps`, the dependencies chosen for recursion were restricted to `dep_direct_mods`, which has been changed to include `mi_usages`. In order to unify treatment of the different link variants across make/oneshot mode, the algorithm's intermediate results have been abstracted into the data types `LinkDep` and `LinkModule`. Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot - - - - - 22 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Module/WholeCoreBindings.hs - docs/users_guide/phases.rst - + testsuite/tests/bytecode/T25090/Dep.hs - + testsuite/tests/bytecode/T25090/DepApi.hs - + testsuite/tests/bytecode/T25090/Local.hs - testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25090/Num.hs - + testsuite/tests/bytecode/T25090/Num.hs-boot - + testsuite/tests/bytecode/T25090/PkgBytecode.hs - + testsuite/tests/bytecode/T25090/PkgBytecode.stdout - testsuite/tests/bytecode/T25090/all.T - + testsuite/tests/bytecode/T25090/dep.conf - + testsuite/tests/bytecode/T25090/prep.bash - + testsuite/tests/bytecode/T25090/run.bash - + testsuite/tests/bytecode/T25090/unit1 - + testsuite/tests/bytecode/T25090/unit2 Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -843,6 +843,7 @@ data GeneralFlag | Opt_BuildDynamicToo | Opt_WriteIfSimplifiedCore | Opt_UseBytecodeRatherThanObjects + | Opt_PackageDbBytecode -- safe haskell flags | Opt_DistrustAllPackages ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2543,6 +2543,7 @@ fFlagsDeps = [ flagSpec "link-rts" Opt_LinkRts, flagSpec "byte-code-and-object-code" Opt_ByteCodeAndObjectCode, flagSpec "prefer-byte-code" Opt_UseBytecodeRatherThanObjects, + flagSpec "package-db-byte-code" Opt_PackageDbBytecode, flagSpec' "compact-unwind" Opt_CompactUnwind (\turn_on -> updM (\dflags -> do unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.Directory import GHC.Driver.Env.KnotVars import {-# source #-} GHC.Driver.Main (loadIfaceByteCode) import GHC.Iface.Errors.Types +import GHC.Runtime.Context (emptyInteractiveContext) import Data.Function ((&)) {- @@ -533,12 +534,18 @@ loadInterface doc_str mod from -- -- See Note [Interface Files with Core Definitions] add_bytecode old - | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls) + | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls) = extendModuleEnv old mod action -- Don't add an entry if the iface doesn't have 'extra_decls' -- so 'get_link_deps' knows that it should load object code. | otherwise = old + where + -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is + -- accessed when the processed module is from a different + -- package. + hydration_env = + purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)} ; warnPprTrace bad_boot "loadInterface" (ppr mod) $ updateEps_ $ \ eps -> ===================================== compiler/GHC/Linker/Deps.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module GHC.Linker.Deps ( LinkDepsOpts (..) @@ -28,6 +29,7 @@ import GHC.Types.Unique.DSet import GHC.Types.Unique.DFM import GHC.Utils.Outputable +import qualified GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Error @@ -47,15 +49,19 @@ import GHC.Utils.Misc import GHC.Unit.Home import GHC.Data.Maybe -import Control.Monad import Control.Applicative +import Control.Monad.IO.Class (MonadIO (liftIO)) +import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE) +import Data.Foldable (traverse_) import qualified Data.Set as Set import qualified Data.Map as M import Data.List (isSuffixOf) import System.FilePath import System.Directory +import GHC.Utils.Logger (Logger) +import Control.Monad ((<$!>)) data LinkDepsOpts = LinkDepsOpts { ldObjSuffix :: !String -- ^ Suffix of .o files @@ -64,19 +70,21 @@ data LinkDepsOpts = LinkDepsOpts , ldUnitEnv :: !UnitEnv , ldPprOpts :: !SDocContext -- ^ Rendering options for error messages , ldUseByteCode :: !Bool -- ^ Use bytecode rather than objects + , ldPkgByteCode :: !Bool -- ^ Use bytecode for external packages , ldMsgOpts :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics , ldWays :: !Ways -- ^ Enabled ways , ldFinderCache :: !FinderCache , ldFinderOpts :: !FinderOpts - , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)) - , ldLoadByteCode :: !(Module -> IO (Maybe Linkable)) + , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation))) + , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable))) + , ldLogger :: !Logger } data LinkDeps = LinkDeps { ldNeededLinkables :: [Linkable] , ldAllLinkables :: [Linkable] - , ldUnits :: [UnitId] - , ldNeededUnits :: UniqDSet UnitId + , ldNeededUnits :: [UnitId] + , ldAllUnits :: UniqDSet UnitId } -- | Find all the packages and linkables that a set of modules depends on @@ -100,9 +108,68 @@ getLinkDeps opts interp pls span mods = do -- then we need to find & link object files built the "normal" way. maybe_normal_osuf <- checkNonStdWay opts interp span - get_link_deps opts pls maybe_normal_osuf span mods - + withTiming (ldLogger opts) (text "getLinkDeps" <+> brackets (ppr span)) (const ()) $ + get_link_deps opts pls maybe_normal_osuf span mods + +data LinkExternalDetails = + -- | A module that should be linked, including its home module and package + -- dependencies. + -- Either a home module in oneshot mode or a package dependency module in + -- either mode. + LinkAllDeps + | + -- | A home module whose package dependencies should be linked, but not the + -- module itself or its home unit dependencies. + -- Can either be a direct target or the non-boot module corresponding to a + -- target boot module, but only in make mode. + -- The 'ModIface' is taken from the 'HomeModInfo', avoiding another lookup in + -- 'external_deps'. + -- The importing module and its home unit dependencies are not processed by + -- 'external_deps', since the readily available 'HomeModInfo's can be linked + -- without further analysis. + LinkOnlyPackages !ModIface + +instance Outputable LinkExternalDetails where + ppr = \case + LinkAllDeps -> text "all" + LinkOnlyPackages _ -> text "only-packages" + +data LinkExternal = + LinkExternal { + le_details :: LinkExternalDetails, + le_module :: !Module + } +instance Outputable LinkExternal where + ppr LinkExternal {..} = ppr le_module <> brackets (ppr le_details) + +data LinkModule = + LinkHomeModule !HomeModInfo + | + LinkObjectModule !ModIface !ModLocation + | + LinkByteCodeModule !ModIface !(IO Linkable) + +link_module_iface :: LinkModule -> ModIface +link_module_iface = \case + LinkHomeModule hmi -> hm_iface hmi + LinkObjectModule iface _ -> iface + LinkByteCodeModule iface _ -> iface + +instance Outputable LinkModule where + ppr = \case + LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI") + LinkObjectModule iface _ -> ppr (mi_module iface) + LinkByteCodeModule iface _ -> ppr (mi_module iface) <+> brackets (text "BC") + +-- | Compute the linkables for the given module set's dependencies. +-- +-- Home modules in make mode are treated separately in a preprocessing step, +-- then all the remaining external deps are processed for both modes. +-- If bytecode is available, transitive external deps are included, otherwise +-- the module's library is linked and processing stops. +-- +-- The results are split into sets of needed/loaded modules/packages. get_link_deps :: LinkDepsOpts -> LoaderState @@ -111,46 +178,36 @@ get_link_deps -> [Module] -> IO LinkDeps get_link_deps opts pls maybe_normal_osuf span mods = do - -- 1. Find the dependent home-pkg-modules/packages from each iface - -- (omitting modules from the interactive package, which is already linked) - (mods_s, pkgs_s) <- - -- Why two code paths here? There is a significant amount of repeated work - -- performed calculating transitive dependencies - -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests) - if ldOneShotMode opts - then follow_deps (filterOut isInteractiveModule mods) - emptyUniqDSet emptyUniqDSet; - else do - (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods - return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs)) - - let - -- 2. Exclude ones already linked - -- Main reason: avoid findModule calls in get_linkable - (mods_needed, links_got) = partitionWith split_mods mods_s - pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls - - split_mods mod = - let is_linked = lookupModuleEnv (objs_loaded pls) mod - <|> lookupModuleEnv (bcos_loaded pls) mod - in case is_linked of - Just linkable -> Right linkable - Nothing -> Left mod - - -- 3. For each dependent module, find its linkable - -- This will either be in the HPT or (in the case of one-shot - -- compilation) we may need to use maybe_getFileLinkable - lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed - - return $ LinkDeps - { ldNeededLinkables = lnks_needed - , ldAllLinkables = links_got ++ lnks_needed - , ldUnits = pkgs_needed - , ldNeededUnits = pkgs_s - } + (link_deps_home, module_deps_external) <- separate_home_deps + link_deps_external <- external_deps opts module_deps_external + let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) = + classify_deps pls link_deps_home link_deps_external + ldNeededLinkables <- mapM module_linkable needed_modules + pure LinkDeps { + ldNeededLinkables, + ldAllLinkables = loaded_modules ++ ldNeededLinkables, + ldNeededUnits, + ldAllUnits + } where mod_graph = ldModuleGraph opts unit_env = ldUnitEnv opts + noninteractive = filterOut isInteractiveModule mods + + -- Preprocess the dependencies in make mode to remove all home modules, + -- since the transitive dependency closure is already cached for those in + -- the HUG (see MultiLayerModulesTH_* tests for the performance impact). + -- + -- Returns the remaining, external, dependencies on the right, which is the + -- entire set for oneshot mode. + separate_home_deps = + if ldOneShotMode opts + then pure ([], LinkExternal LinkAllDeps <$!> noninteractive) + else make_deps + + make_deps = do + (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods + pure (mmods, init_ext ++ dep_ext) -- This code is used in `--make` mode to calculate the home package and unit dependencies -- for a set of modules. @@ -160,9 +217,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- It is also a matter of correctness to use the module graph so that dependencies between home units -- is resolved correctly. - make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey) + make_deps_loop :: ([LinkExternal], Set.Set NodeKey) -> [ModNodeKeyWithUid] -> ([LinkExternal], Set.Set NodeKey) make_deps_loop found [] = found - make_deps_loop found@(found_units, found_mods) (nk:nexts) + make_deps_loop found@(external, found_mods) (nk:nexts) | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts | otherwise = case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of @@ -171,85 +228,27 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- See #936 and the ghci.prog007 test for why we have to continue traversing through -- boot modules. todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps] - in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) + in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) Nothing -> - let (ModNodeKeyWithUid _ uid) = nk - in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts + let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk + mod = Module (RealUnit (Definite uid)) mod_name + in make_deps_loop (LinkExternal LinkAllDeps mod : external, found_mods) nexts mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m) - (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods) + (init_ext, all_deps) = make_deps_loop ([], Set.empty) $ map mkNk noninteractive all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps] get_mod_info (ModNodeKeyWithUid gwib uid) = case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of - Just hmi -> - let iface = (hm_iface hmi) - mmod = case mi_hsc_src iface of - HsBootFile -> link_boot_mod_error (mi_module iface) - _ -> return $ Just (mi_module iface) - - in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$> mmod + Just hmi -> do + let iface = hm_iface hmi + case mi_hsc_src iface of + HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface) + _ -> pure (LinkExternal (LinkOnlyPackages iface) (mi_module iface), hmi) Nothing -> throwProgramError opts $ text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid - - -- This code is used in one-shot mode to traverse downwards through the HPT - -- to find all link dependencies. - -- The ModIface contains the transitive closure of the module dependencies - -- within the current package, *except* for boot modules: if we encounter - -- a boot module, we have to find its real interface and discover the - -- dependencies of that. Hence we need to traverse the dependency - -- tree recursively. See bug #936, testcase ghci/prog007. - follow_deps :: [Module] -- modules to follow - -> UniqDSet Module -- accum. module dependencies - -> UniqDSet UnitId -- accum. package dependencies - -> IO ([Module], UniqDSet UnitId) -- result - follow_deps [] acc_mods acc_pkgs - = return (uniqDSetToList acc_mods, acc_pkgs) - follow_deps (mod:mods) acc_mods acc_pkgs - = do - mb_iface <- ldLoadIface opts msg mod - iface <- case mb_iface of - Failed err -> throwProgramError opts $ - missingInterfaceErrorDiagnostic (ldMsgOpts opts) err - Succeeded iface -> return iface - - when (mi_boot iface == IsBoot) $ link_boot_mod_error mod - - let - pkg = moduleUnit mod - deps = mi_deps iface - - pkg_deps = dep_direct_pkgs deps - (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $ - \case - (_, GWIB m IsBoot) -> Left m - (_, GWIB m NotBoot) -> Right m - - mod_deps' = case ue_homeUnit unit_env of - Nothing -> [] - Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps)) - acc_mods' = case ue_homeUnit unit_env of - Nothing -> acc_mods - Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps) - acc_pkgs' = addListToUniqDSet acc_pkgs (Set.toList pkg_deps) - - case ue_homeUnit unit_env of - Just home_unit | isHomeUnit home_unit pkg -> follow_deps (mod_deps' ++ mods) - acc_mods' acc_pkgs' - _ -> follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg)) - where - msg = text "need to link module" <+> ppr mod <+> - text "due to use of Template Haskell" - - - - link_boot_mod_error :: Module -> IO a - link_boot_mod_error mod = throwProgramError opts $ - text "module" <+> ppr mod <+> - text "cannot be linked; it is only available as a boot module" - no_obj :: Outputable a => a -> IO b no_obj mod = dieWith opts span $ text "cannot find object file for module " <> @@ -258,6 +257,20 @@ get_link_deps opts pls maybe_normal_osuf span mods = do while_linking_expr = text "while linking an interpreted expression" + -- Extract the 'Linkable's for unlinked modules from the intermediate + -- results. + module_linkable = \case + LinkHomeModule hmi -> + adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi)) + + LinkObjectModule iface loc -> do + let mod = mi_module iface + findObjectLinkableMaybe mod loc >>= \case + Nothing -> no_obj mod + Just lnk -> adjust_linkable lnk + + LinkByteCodeModule _ load_bytecode -> + load_bytecode -- See Note [Using Byte Code rather than Object Code for Template Haskell] homeModLinkable :: HomeModInfo -> Maybe Linkable @@ -266,57 +279,247 @@ get_link_deps opts pls maybe_normal_osuf span mods = do then homeModInfoByteCode hmi <|> homeModInfoObject hmi else homeModInfoObject hmi <|> homeModInfoByteCode hmi - get_linkable osuf mod -- A home-package module - | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env) - = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info)) - | otherwise - = do -- It's not in the HPT because we are in one shot mode, - -- so use the Finder to get a ModLocation... - case ue_homeUnit unit_env of - Nothing -> no_obj mod - Just home_unit -> do - from_bc <- ldLoadByteCode opts mod - maybe (fallback_no_bytecode home_unit mod) pure from_bc - where - - fallback_no_bytecode home_unit mod = do - let fc = ldFinderCache opts - let fopts = ldFinderOpts opts - mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod) - case mb_stuff of - Found loc _ -> do - mb_lnk <- findObjectLinkableMaybe mod loc - case mb_lnk of - Nothing -> no_obj mod - Just lnk -> adjust_linkable lnk - _ -> no_obj (moduleName mod) - - adjust_linkable lnk - | Just new_osuf <- maybe_normal_osuf = do - new_parts <- mapM (adjust_part new_osuf) - (linkableParts lnk) - return lnk{ linkableParts=new_parts } - | otherwise = - return lnk - - adjust_part new_osuf part = case part of - DotO file ModuleObject -> do - massert (osuf `isSuffixOf` file) - let file_base = fromJust (stripExtension osuf file) - new_file = file_base <.> new_osuf - ok <- doesFileExist new_file - if (not ok) - then dieWith opts span $ - text "cannot find object file " - <> quotes (text new_file) $$ while_linking_expr - else return (DotO new_file ModuleObject) - DotO file ForeignObject -> pure (DotO file ForeignObject) - DotA fp -> panic ("adjust_ul DotA " ++ show fp) - DotDLL fp -> panic ("adjust_ul DotDLL " ++ show fp) - BCOs {} -> pure part - LazyBCOs{} -> pure part - CoreBindings WholeCoreBindings {wcb_module} -> - pprPanic "Unhydrated core bindings" (ppr wcb_module) + adjust_linkable lnk + | Just new_osuf <- maybe_normal_osuf = do + new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf) + (linkableParts lnk) + return lnk {linkableParts = new_uls} + | otherwise = + return lnk + + adjust_part osuf new_osuf part = case part of + DotO file ModuleObject -> do + massert (osuf `isSuffixOf` file) + let file_base = fromJust (stripExtension osuf file) + new_file = file_base <.> new_osuf + ok <- doesFileExist new_file + if (not ok) + then dieWith opts span $ + text "cannot find object file " + <> quotes (text new_file) $$ while_linking_expr + else return (DotO new_file ModuleObject) + DotO file ForeignObject -> pure (DotO file ForeignObject) + DotA fp -> panic ("adjust_part DotA " ++ show fp) + DotDLL fp -> panic ("adjust_part DotDLL " ++ show fp) + BCOs {} -> pure part + LazyBCOs{} -> pure part + CoreBindings WholeCoreBindings {wcb_module} -> + pprPanic "Unhydrated core bindings" (ppr wcb_module) + +data LinkDep = + LinkModules !(UniqDFM ModuleName LinkModule) + | + LinkLibrary !UnitId + +instance Outputable LinkDep where + ppr = \case + LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods) + LinkLibrary uid -> text "library:" <+> ppr uid + +data OneshotError = + NoLocation !Module + | + NoInterface !MissingInterfaceError + | + LinkBootModule !Module + +-- | Compute the transitive dependency closure of the given modules. +-- +-- Used for all oneshot mode dependencies and for external dependencies of home +-- modules in make mode. +external_deps :: + LinkDepsOpts -> + -- | Modules whose imports to follow + [LinkExternal] -> + IO [LinkDep] +external_deps opts mods = + runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case + Right a -> pure (eltsUDFM a) + Left err -> throwProgramError opts (message err) + where + message = \case + NoLocation mod -> + pprPanic "found iface but no location" (ppr mod) + NoInterface err -> + missingInterfaceErrorDiagnostic (ldMsgOpts opts) err + LinkBootModule mod -> + link_boot_mod_error mod + +external_deps_loop :: + LinkDepsOpts -> + [LinkExternal] -> + UniqDFM UnitId LinkDep -> + ExceptT OneshotError IO (UniqDFM UnitId LinkDep) +external_deps_loop _ [] acc = + pure acc +external_deps_loop opts (job at LinkExternal {le_module = mod, ..} : mods) acc = do + (new_acc, new_mods, action) <- + if already_seen + then done + else process_module le_details + traverse_ debug_log action + external_deps_loop opts (new_mods ++ mods) new_acc + where + debug_log action = + liftIO $ debugTraceMsg (ldLogger opts) 3 $ + text "TH dep" <+> ppr job <+> + brackets (sep (punctuate comma [ + if is_home then text "home" else Outputable.empty, + text action + ])) + + done = pure (acc, [], Nothing) + + -- Decide how this module needs to be processed. + -- We only need an interface if we want to load bytecode or if we have to + -- link an object file (which happens for home unit modules, since those + -- have no libraries). + process_module = \case + LinkAllDeps | is_home || package_bc -> try_iface + | otherwise -> add_library + + -- @LinkOnlyPackages@ is used for make mode home modules, so all imports + -- that are not external are already processed otherwise. + LinkOnlyPackages iface -> with_deps acc iface False "only packages" + + -- Check whether the current module was processed before. + -- Since the accumulator is keyed by unit ID, we have to perform two + -- lookups. + -- If another module from this module's unit has been determined to be + -- linked as a library previously, we skip this module, assuming that no + -- bytecode is available for the entire package. + already_seen + | Just (LinkModules mods) <- mod_dep + = elemUDFM mod_name mods + | Just (LinkLibrary _) <- mod_dep + = True + | otherwise + = False + + -- Load the iface and attempt to get bytecode from Core bindings. + try_iface = + liftIO (ldLoadIface opts load_reason mod) >>= \case + Failed err -> throwE (NoInterface err) + Succeeded (iface, loc) -> do + mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface)) + with_iface iface loc mb_load_bc + + -- Decide how to link this module. + -- If bytecode or an object file is available, use those in that order. + -- Otherwise fall back to linking a library. + with_iface iface loc mb_load_bc + | IsBoot <- mi_boot iface + = throwE (LinkBootModule mod) + + | ldUseByteCode opts && (is_home || package_bc) + , Just load_bc <- mb_load_bc + = add_module iface (LinkByteCodeModule iface load_bc) "bytecode" + + | is_home + , Nothing <- mb_load_bc + = add_module iface (LinkObjectModule iface loc) "object" + + | otherwise + = add_library + + add_library = + pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library") + + add_module iface lmod action = + with_deps with_mod iface True action + where + with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id + + add_package_module lmod = \case + Just (LinkLibrary u) -> Just (LinkLibrary u) + Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod)) + Nothing -> Just (LinkModules (unitUDFM mod_name lmod)) + + with_deps acc iface local action = + pure (addListToUDFM acc link, new_local ++ new_package, Just action) + where + !(!link, !new_package) = package_deps iface + new_local = if local then local_deps iface else [] + + local_deps iface = + [ + LinkExternal LinkAllDeps (mkModule mod_unit m) + | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface)) + ] + + -- If bytecode linking of external dependencies is enabled, add them to the + -- jobs passed to the next iteration of 'external_deps_loop'. + -- Otherwise, link all package deps as libraries. + package_deps iface + | package_bc + = ([], [LinkExternal LinkAllDeps usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface]) + | otherwise + = ([(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))], []) + + mod_dep = lookupUDFM acc mod_unit_id + mod_name = moduleName mod + mod_unit_id = moduleUnitId mod + mod_unit = moduleUnit mod + load_reason = + text "need to link module" <+> ppr mod <+> + text "due to use of Template Haskell" + + package_bc = ldPkgByteCode opts + + -- In multiple home unit mode, this only considers modules from the same + -- unit as the splice's module to be eligible for linking bytecode when + -- @-fpackage-db-byte-code@ is off. + -- For make mode, this is irrelevant, since any bytecode from the HUG is + -- obtained directly, not going through 'external_deps'. + is_home + | Just home <- ue_homeUnit (ldUnitEnv opts) + = homeUnitAsUnit home == mod_unit + | otherwise + = False + +link_boot_mod_error :: Module -> SDoc +link_boot_mod_error mod = + text "module" <+> ppr mod <+> + text "cannot be linked; it is only available as a boot module" + +-- | Split link dependencies into the sets of modules and packages that have +-- been linked previously and those that need to be linked now by checking for +-- their presence in the 'LoaderState': +-- +-- - For module dependencies, in the sets of loaded objects and BCOs +-- ('objs_loaded' and 'bcos_loaded') +-- - For package dependencies, in the set of loaded packages ('pkgs_loaded') +classify_deps :: + LoaderState -> + [HomeModInfo] -> + [LinkDep] -> + ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId]) +classify_deps pls hmis deps = + (loaded_modules' ++ loaded_modules'', needed_modules' ++ needed_modules'', all_packages, needed_packages) + where + (loaded_modules', needed_modules') = partitionWith loaded_or_needed_home_module hmis + (loaded_modules'', needed_modules'') = + partitionWith loaded_or_needed_module (concatMap eltsUDFM modules) + + needed_packages = + eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls) + + all_packages = mkUniqDSet packages + + (modules, packages) = flip partitionWith deps $ \case + LinkModules mods -> Left mods + LinkLibrary lib -> Right lib + + loaded_or_needed_home_module lm = + maybe (Right (LinkHomeModule lm)) Left (loaded_module (mi_module (hm_iface lm))) + + loaded_or_needed_module lm = + maybe (Right lm) Left (loaded_module (mi_module (link_module_iface lm))) + + loaded_module mod = + lookupModuleEnv (objs_loaded pls) mod + <|> + lookupModuleEnv (bcos_loaded pls) mod {- Note [Using Byte Code rather than Object Code for Template Haskell] ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -77,11 +77,13 @@ import GHC.Utils.TmpFs import GHC.Unit.Env import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode)) +import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.State as Packages import qualified GHC.Data.ShortText as ST import GHC.Data.FastString +import qualified GHC.Data.Maybe as Maybe import GHC.Linker.Deps import GHC.Linker.MacOS @@ -94,6 +96,7 @@ import Control.Monad import qualified Data.Set as Set import Data.Char (isSpace) import qualified Data.Foldable as Foldable +import Data.Functor ((<&>)) import Data.IORef import Data.List (intercalate, isPrefixOf, nub, partition) import Data.Maybe @@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - let this_pkgs_needed = ldNeededUnits deps + let this_pkgs_needed = ldAllUnits deps -- Link the packages and modules required - pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls + pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps) let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed all_pkgs_loaded = pkgs_loaded pls2 @@ -646,18 +649,39 @@ initLinkDepsOpts hsc_env = opts , ldFinderCache = hsc_FC hsc_env , ldFinderOpts = initFinderOpts dflags , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags + , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags , ldMsgOpts = initIfaceMessageOpts dflags , ldWays = ways dflags , ldLoadIface , ldLoadByteCode + , ldLogger = hsc_logger hsc_env } dflags = hsc_dflags hsc_env - ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env - $ loadInterface msg mod (ImportByUser NotBoot) + + ldLoadIface msg mod = + initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case + Maybe.Failed err -> pure (Maybe.Failed err) + Maybe.Succeeded iface -> + find_location mod <&> \case + InstalledFound loc _ -> Maybe.Succeeded (iface, loc) + err -> Maybe.Failed $ + cannotFindInterface unit_state home_unit + (targetProfile dflags) (moduleName mod) err + + find_location mod = + liftIO $ + findExactModule (hsc_FC hsc_env) (initFinderOpts dflags) + (initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env) + unit_state home_unit + (toUnitId <$> mod) + + unit_state = hsc_units hsc_env + + home_unit = ue_homeUnit (hsc_unit_env hsc_env) ldLoadByteCode mod = do EPS {eps_iface_bytecode} <- hscEPS hsc_env - sequence (lookupModuleEnv eps_iface_bytecode mod) + pure (lookupModuleEnv eps_iface_bytecode mod) ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -753,7 +753,7 @@ mkStubPaths fopts mod location = do src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location -- ----------------------------------------------------------------------------- --- findLinkable isn't related to the other stuff in here, +-- findObjectLinkable isn't related to the other stuff in here, -- but there's no other obvious place for it findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) ===================================== compiler/GHC/Unit/Module/WholeCoreBindings.hs ===================================== @@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed build artifacts, which can be objects or bytecode, depending on the build settings. -1. In make mode, all eligible modules are part of the dependency graph. +1. In make mode, all eligible home modules are part of the dependency graph. Their interfaces are loaded unconditionally and in dependency order by the compilation manager, and each module's bytecode is prepared before its dependents are compiled, in one of two ways: @@ -88,9 +88,10 @@ settings. 2. In oneshot mode, which compiles individual modules without a shared home unit graph, a previously compiled module is not reprocessed as described for make mode above. - When 'get_link_deps' encounters a dependency on a local module, it requests - its bytecode from the External Package State, who loads the interface - on-demand. + 'get_link_deps' requests the bytecode of dependencies from the External + Package State, who loads the interface on-demand. + This works for modules in local directories (via @-i@ and @-hidir@) as well + as those exposed from a package DB. Since the EPS stores interfaces for all package dependencies in addition to local modules in oneshot mode, it has a substantial memory footprint. @@ -109,6 +110,18 @@ settings. storing the intermediate representation as rehydrated Core bindings, since the latter have a significantly greater memory footprint. +3. In both of the above modes, whenever a module from an external package + (loaded from a package DB) is encountered, the workflow is the same as for + oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object + code is loaded. + Interfaces for external modules are stored together with local oneshot mode + modules, so almost no special treatment is necessary, with the exception of: + - When external package modules are compiled, the @InteractiveContext@ in + @HscEnv@ is accessed, which is not available due to its impact on retention + of outdated build products. + This is solved by writing an empty @InteractiveContext@ to the env used for + compilation. + Note [Size of Interface Files with Core Definitions] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op. Otherwise, the stub objects from the interface are compiled to objects in 'generateByteCode' and added to the 'HomeModLinkable' as well. -Case 3 is not implemented yet (!13042). +In case 3, Core bindings are loaded from the EPS, where stubs only exist in +their serialized form in the interface, so they must be regenerated like in case +2. Problem 3: ===================================== docs/users_guide/phases.rst ===================================== @@ -826,6 +826,17 @@ Options affecting code generation will generate byte-code rather than object code. +.. ghc-flag:: -fpackage-db-byte-code + :shortdesc: Use byte-code from package DB dependencies + :type: dynamic + :category: codegen + + GHC normally only considers local modules to be eligible for loading + bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`. + When this flag is specified additionally, bytecode will be loaded from + interfaces for all external package dependencies that provide it. + + .. _options-linker: Options affecting linking ===================================== testsuite/tests/bytecode/T25090/Dep.hs ===================================== @@ -0,0 +1,15 @@ +module Dep where + +data A = A Int + +used :: Int +used = 9681 + +dep :: A +dep = A used + +unused1 :: A +unused1 = A 1 + +unused2 :: A +unused2 = unused1 ===================================== testsuite/tests/bytecode/T25090/DepApi.hs ===================================== @@ -0,0 +1,7 @@ +module DepApi (A (A), dep) where + +import Dep (A (A)) +import qualified Dep + +dep :: A +dep = Dep.dep ===================================== testsuite/tests/bytecode/T25090/Local.hs ===================================== @@ -0,0 +1,15 @@ +{-# language PackageImports #-} + +module Local where + +import GHC.Prim +import Language.Haskell.TH (ExpQ) +import Language.Haskell.TH.Syntax (lift) +-- just to be sure that the file isn't accidentally picked up locally +import "dep" DepApi (dep, A (A)) +import {-# source #-} Num (num) + +splc :: ExpQ +splc = lift @_ @Int (num + d) + where + A d = dep ===================================== testsuite/tests/bytecode/T25090/Makefile ===================================== @@ -19,3 +19,35 @@ T25090a: T25090b: $(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0 ./exe + +DB := -package-db db -package dep +BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0 +BC := -fprefer-byte-code -fbyte-code-and-object-code +ARGS := $(BASIC) $(BC) + +T25090_pkg: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_empty: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_nolib: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none" + ./run.bash "$(TEST_HC)" "$(ARGS)" + +T25090_pkg_obj_code: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code" + +T25090_pkg_multi_unit: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + mkdir -p unit2-src/ + mv Local.hs Num.hs Num.hs-boot unit2-src/ + "$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -fpackage-db-byte-code -dynamic -unit @unit1 -unit @unit2 + ./PkgBytecode + +T25090_pkg_archive: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive" + ./run.bash "$(TEST_HC)" "$(ARGS)" ===================================== testsuite/tests/bytecode/T25090/Num.hs ===================================== @@ -0,0 +1,4 @@ +module Num where + +num :: Int +num = 48332 ===================================== testsuite/tests/bytecode/T25090/Num.hs-boot ===================================== @@ -0,0 +1,3 @@ +module Num where + +num :: Int ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.hs ===================================== @@ -0,0 +1,12 @@ +{-# language TemplateHaskell #-} + +module Main where + +import GHC.Prim +import Local (splc) + +a :: Int +a = $(splc) + +main :: IO () +main = putStrLn (show a) ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.stdout ===================================== @@ -0,0 +1 @@ +58013 ===================================== testsuite/tests/bytecode/T25090/all.T ===================================== @@ -16,3 +16,33 @@ def test_T25090(name): test_T25090('T25090a') test_T25090('T25090b') + +def test_pkg(name, files = []): + test( + name, + [ + extra_files([ + 'PkgBytecode.hs', + 'Local.hs', + 'Dep.hs', + 'DepApi.hs', + 'Num.hs', + 'Num.hs-boot', + 'dep.conf', + 'prep.bash', + 'run.bash', + ] + files), + use_specs({'stdout': 'PkgBytecode.stdout'}), + ], + makefile_test, + [], + ) + +test_pkg('T25090_pkg') +test_pkg('T25090_pkg_empty') +test_pkg('T25090_pkg_nolib') +test_pkg('T25090_pkg_obj_code') +test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2']) +# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a +# comment says "search for .so libraries _first_" (rather than "only"). +# test_pkg('T25090_pkg_archive') ===================================== testsuite/tests/bytecode/T25090/dep.conf ===================================== @@ -0,0 +1,8 @@ +name: dep +version: 1.0 +id: dep-1.0 +key: dep-1.0 +exposed: True +exposed-modules: DepApi +import-dirs: ${pkgroot}/dep +library-dirs: ${pkgroot}/dep ===================================== testsuite/tests/bytecode/T25090/prep.bash ===================================== @@ -0,0 +1,57 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" +ghc_pkg_cmd="$3" +library="$4" + +base="$PWD" +db="$base/db" +dep="$base/dep" +conf_dep="${dep}/dep.conf" + +mkdir -p "$dep" "$db" +mv Dep.hs DepApi.hs "$dep/" +cp dep.conf "$dep/" + +ghc_pkg() +{ + eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@" +} + +ghc() +{ + eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@" +} + +version=$(ghc "--numeric-version") + +ghc_pkg recache + +ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs" + +if [[ "$library" == 'shared' ]] +then + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'shared-empty' ]] +then + echo 'module Dummy where' > Dummy.hs + ghc "-dynamic-too -c Dummy.hs" + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'archive' ]] +then + $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'none' ]] +then + : +else + echo "Invalid argument for 'library': $library" + exit 1 +fi + +ghc_pkg -v0 register "${conf_dep at Q}" ===================================== testsuite/tests/bytecode/T25090/run.bash ===================================== @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" + +ghc() +{ + eval "${ghc_cmd at Q} $ghc_opts $@" +} + +ghc -c Num.hs-boot Num.hs Local.hs +ghc -fpackage-db-byte-code -c PkgBytecode.hs +ghc PkgBytecode.o -o PkgBytecode +./PkgBytecode ===================================== testsuite/tests/bytecode/T25090/unit1 ===================================== @@ -0,0 +1 @@ +-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2 ===================================== testsuite/tests/bytecode/T25090/unit2 ===================================== @@ -0,0 +1 @@ +-i -i./unit2-src Local Num -this-unit-id unit2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c8ab26a0ea5c3b2a579ba608be5f1fc5bd88d7ce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c8ab26a0ea5c3b2a579ba608be5f1fc5bd88d7ce You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 20:21:59 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Tue, 22 Oct 2024 16:21:59 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] 2 commits: Link interface bytecode from package DBs if possible Message-ID: <67180967a9dac_27dc1e4201448947@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC Commits: 7c9a2b9a by Torsten Schmits at 2024-10-22T22:21:40+02:00 Link interface bytecode from package DBs if possible Part of #25090. MR !13068 When splices are executed with `-fprefer-byte-code`, the loader will compile Core bindings to bytecode if those are present in interfaces of module dependencies. So far, this only applied to local modules (i.e. home modules in make mode and non-package deps in oneshot mode). This patch extends support to interfaces loaded from a package DB. In `getLinkDeps`, the dependencies chosen for recursion were restricted to `dep_direct_mods`, which has been changed to include external dependencies, stored in a new field named `dep_direct_pkg_mods`. In order to unify treatment of the different link variants across make/oneshot mode, the algorithm's intermediate results have been abstracted into the data types `LinkDep` and `LinkModule`. Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot - - - - - 38f1ca4f by Torsten Schmits at 2024-10-22T22:21:40+02:00 add new field to iface for package deps Metric Decrease: MultiLayerModulesTH_Make MultiLayerModulesTH_OneShot - - - - - 23 changed files: - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Module/Deps.hs - compiler/GHC/Unit/Module/WholeCoreBindings.hs - docs/users_guide/phases.rst - + testsuite/tests/bytecode/T25090/Dep.hs - + testsuite/tests/bytecode/T25090/DepApi.hs - + testsuite/tests/bytecode/T25090/Local.hs - testsuite/tests/bytecode/T25090/Makefile - + testsuite/tests/bytecode/T25090/Num.hs - + testsuite/tests/bytecode/T25090/Num.hs-boot - + testsuite/tests/bytecode/T25090/PkgBytecode.hs - + testsuite/tests/bytecode/T25090/PkgBytecode.stdout - testsuite/tests/bytecode/T25090/all.T - + testsuite/tests/bytecode/T25090/dep.conf - + testsuite/tests/bytecode/T25090/prep.bash - + testsuite/tests/bytecode/T25090/run.bash - + testsuite/tests/bytecode/T25090/unit1 - + testsuite/tests/bytecode/T25090/unit2 Changes: ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -843,6 +843,7 @@ data GeneralFlag | Opt_BuildDynamicToo | Opt_WriteIfSimplifiedCore | Opt_UseBytecodeRatherThanObjects + | Opt_PackageDbBytecode -- safe haskell flags | Opt_DistrustAllPackages ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2543,6 +2543,7 @@ fFlagsDeps = [ flagSpec "link-rts" Opt_LinkRts, flagSpec "byte-code-and-object-code" Opt_ByteCodeAndObjectCode, flagSpec "prefer-byte-code" Opt_UseBytecodeRatherThanObjects, + flagSpec "package-db-byte-code" Opt_PackageDbBytecode, flagSpec' "compact-unwind" Opt_CompactUnwind (\turn_on -> updM (\dflags -> do unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.Directory import GHC.Driver.Env.KnotVars import {-# source #-} GHC.Driver.Main (loadIfaceByteCode) import GHC.Iface.Errors.Types +import GHC.Runtime.Context (emptyInteractiveContext) import Data.Function ((&)) {- @@ -533,12 +534,18 @@ loadInterface doc_str mod from -- -- See Note [Interface Files with Core Definitions] add_bytecode old - | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls) + | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls) = extendModuleEnv old mod action -- Don't add an entry if the iface doesn't have 'extra_decls' -- so 'get_link_deps' knows that it should load object code. | otherwise = old + where + -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is + -- accessed when the processed module is from a different + -- package. + hydration_env = + purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)} ; warnPprTrace bad_boot "loadInterface" (ppr mod) $ updateEps_ $ \ eps -> ===================================== compiler/GHC/Linker/Deps.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NamedFieldPuns #-} module GHC.Linker.Deps ( LinkDepsOpts (..) @@ -22,12 +23,12 @@ import GHC.Runtime.Interpreter import GHC.Linker.Types -import GHC.Types.SourceFile import GHC.Types.SrcLoc import GHC.Types.Unique.DSet import GHC.Types.Unique.DFM import GHC.Utils.Outputable +import qualified GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import GHC.Utils.Error @@ -47,15 +48,19 @@ import GHC.Utils.Misc import GHC.Unit.Home import GHC.Data.Maybe -import Control.Monad import Control.Applicative +import Control.Monad.IO.Class (MonadIO (liftIO)) +import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE) +import Data.Foldable (traverse_) import qualified Data.Set as Set import qualified Data.Map as M import Data.List (isSuffixOf) import System.FilePath import System.Directory +import GHC.Utils.Logger (Logger) +import Control.Monad ((<$!>)) data LinkDepsOpts = LinkDepsOpts { ldObjSuffix :: !String -- ^ Suffix of .o files @@ -64,19 +69,23 @@ data LinkDepsOpts = LinkDepsOpts , ldUnitEnv :: !UnitEnv , ldPprOpts :: !SDocContext -- ^ Rendering options for error messages , ldUseByteCode :: !Bool -- ^ Use bytecode rather than objects + , ldPkgByteCode :: !Bool -- ^ Use bytecode for external packages , ldMsgOpts :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics , ldWays :: !Ways -- ^ Enabled ways - , ldFinderCache :: !FinderCache - , ldFinderOpts :: !FinderOpts - , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface)) - , ldLoadByteCode :: !(Module -> IO (Maybe Linkable)) + , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation))) + -- ^ When linking oneshot or package dependencies, we need interfaces and + -- locations to find object files and traverse dependencies. + , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable))) + -- ^ Consult the EPS about the given module, return an action that compiles + -- Core bindings to bytecode if it's available. + , ldLogger :: !Logger } data LinkDeps = LinkDeps { ldNeededLinkables :: [Linkable] , ldAllLinkables :: [Linkable] - , ldUnits :: [UnitId] - , ldNeededUnits :: UniqDSet UnitId + , ldNeededUnits :: [UnitId] + , ldAllUnits :: UniqDSet UnitId } -- | Find all the packages and linkables that a set of modules depends on @@ -100,9 +109,80 @@ getLinkDeps opts interp pls span mods = do -- then we need to find & link object files built the "normal" way. maybe_normal_osuf <- checkNonStdWay opts interp span - get_link_deps opts pls maybe_normal_osuf span mods - + withTiming (ldLogger opts) (text "getLinkDeps" <+> brackets (ppr span)) (const ()) $ + get_link_deps opts pls maybe_normal_osuf span mods + +-- | Determine which parts of a module and its dependencies should be linked +-- when resolving external dependencies. +data LinkExternalDetails = + -- | A module that should be linked, including its dependencies in the home + -- unit and external packages. + -- Can be a home module in oneshot mode or a package dependency module in + -- either mode. + LinkAllDeps + | + -- | A home module whose package dependencies should be linked, but not the + -- module itself or its home unit dependencies. + -- Can either be a direct target or the implementation module corresponding to + -- a target boot module, but only in make mode. + -- The 'ModIface' is taken from the 'HomeModInfo', avoiding another lookup in + -- 'external_deps'. + -- The importing module and its home unit dependencies are not processed by + -- 'external_deps', since the readily available 'HomeModInfo's can be linked + -- without further analysis. + LinkOnlyPackages !ModIface + +instance Outputable LinkExternalDetails where + ppr = \case + LinkAllDeps -> text "all" + LinkOnlyPackages _ -> text "only-packages" + +-- | A module that should be examined by 'external_deps' to decide how to link +-- it and its dependencies. +data LinkExternal = + LinkExternal { + le_details :: LinkExternalDetails, + le_module :: !Module + } +instance Outputable LinkExternal where + ppr LinkExternal {..} = ppr le_module <> brackets (ppr le_details) + +-- | The decision about the linking method used for a given module. +data LinkModule = + -- | In make mode, we can use 'HomeModInfo' without any further analysis. + LinkHomeModule !HomeModInfo + | + -- | A module that must be linked as native code, because bytecode is disabled + -- or unavailable. + LinkObjectModule !Module !ModLocation + | + -- | A module that has bytecode available. + -- The 'IO' that compiles the bytecode from Core bindings is obtained from the + -- EPS. + -- See Note [Interface Files with Core Definitions]. + LinkByteCodeModule !Module !(IO Linkable) + +link_module :: LinkModule -> Module +link_module = \case + LinkHomeModule hmi -> mi_module (hm_iface hmi) + LinkObjectModule mod _ -> mod + LinkByteCodeModule mod _ -> mod + +instance Outputable LinkModule where + ppr = \case + LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI") + LinkObjectModule mod _ -> ppr mod + LinkByteCodeModule mod _ -> ppr mod <+> brackets (text "BC") + +-- | Compute the linkables for the given module set's dependencies. +-- +-- Home modules in make mode are treated separately in a preprocessing step, +-- then all the remaining external deps are processed for both modes. +-- If bytecode is available, transitive external deps are included, otherwise +-- the module's library is linked and processing stops. +-- +-- The results are split into sets of needed/loaded modules/packages. get_link_deps :: LinkDepsOpts -> LoaderState @@ -111,46 +191,36 @@ get_link_deps -> [Module] -> IO LinkDeps get_link_deps opts pls maybe_normal_osuf span mods = do - -- 1. Find the dependent home-pkg-modules/packages from each iface - -- (omitting modules from the interactive package, which is already linked) - (mods_s, pkgs_s) <- - -- Why two code paths here? There is a significant amount of repeated work - -- performed calculating transitive dependencies - -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests) - if ldOneShotMode opts - then follow_deps (filterOut isInteractiveModule mods) - emptyUniqDSet emptyUniqDSet; - else do - (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods - return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs)) - - let - -- 2. Exclude ones already linked - -- Main reason: avoid findModule calls in get_linkable - (mods_needed, links_got) = partitionWith split_mods mods_s - pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls - - split_mods mod = - let is_linked = lookupModuleEnv (objs_loaded pls) mod - <|> lookupModuleEnv (bcos_loaded pls) mod - in case is_linked of - Just linkable -> Right linkable - Nothing -> Left mod - - -- 3. For each dependent module, find its linkable - -- This will either be in the HPT or (in the case of one-shot - -- compilation) we may need to use maybe_getFileLinkable - lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed - - return $ LinkDeps - { ldNeededLinkables = lnks_needed - , ldAllLinkables = links_got ++ lnks_needed - , ldUnits = pkgs_needed - , ldNeededUnits = pkgs_s - } + (link_deps_home, module_deps_external) <- separate_home_deps + link_deps_external <- external_deps opts module_deps_external + let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) = + classify_deps pls link_deps_home link_deps_external + ldNeededLinkables <- mapM module_linkable needed_modules + pure LinkDeps { + ldNeededLinkables, + ldAllLinkables = loaded_modules ++ ldNeededLinkables, + ldNeededUnits, + ldAllUnits + } where mod_graph = ldModuleGraph opts unit_env = ldUnitEnv opts + noninteractive = filterOut isInteractiveModule mods + + -- Preprocess the dependencies in make mode to remove all home modules, + -- since the transitive dependency closure is already cached for those in + -- the HUG (see MultiLayerModulesTH_* tests for the performance impact). + -- + -- Returns the remaining, external, dependencies on the right, which is the + -- entire set for oneshot mode. + separate_home_deps = + if ldOneShotMode opts + then pure ([], LinkExternal LinkAllDeps <$!> noninteractive) + else make_deps + + make_deps = do + (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods + pure (mmods, init_ext ++ dep_ext) -- This code is used in `--make` mode to calculate the home package and unit dependencies -- for a set of modules. @@ -160,9 +230,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- It is also a matter of correctness to use the module graph so that dependencies between home units -- is resolved correctly. - make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey) + make_deps_loop :: ([LinkExternal], Set.Set NodeKey) -> [ModNodeKeyWithUid] -> ([LinkExternal], Set.Set NodeKey) make_deps_loop found [] = found - make_deps_loop found@(found_units, found_mods) (nk:nexts) + make_deps_loop found@(external, found_mods) (nk:nexts) | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts | otherwise = case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of @@ -171,93 +241,46 @@ get_link_deps opts pls maybe_normal_osuf span mods = do -- See #936 and the ghci.prog007 test for why we have to continue traversing through -- boot modules. todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps] - in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) + in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts) Nothing -> - let (ModNodeKeyWithUid _ uid) = nk - in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts + let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk + mod = Module (RealUnit (Definite uid)) mod_name + in make_deps_loop (LinkExternal LinkAllDeps mod : external, found_mods) nexts mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m) - (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods) + (init_ext, all_deps) = make_deps_loop ([], Set.empty) $ map mkNk noninteractive all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps] get_mod_info (ModNodeKeyWithUid gwib uid) = case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of - Just hmi -> - let iface = (hm_iface hmi) - mmod = case mi_hsc_src iface of - HsBootFile -> link_boot_mod_error (mi_module iface) - _ -> return $ Just (mi_module iface) - - in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$> mmod + Just hmi -> do + let iface = hm_iface hmi + pure (LinkExternal (LinkOnlyPackages iface) (mi_module iface), hmi) Nothing -> throwProgramError opts $ text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid - - -- This code is used in one-shot mode to traverse downwards through the HPT - -- to find all link dependencies. - -- The ModIface contains the transitive closure of the module dependencies - -- within the current package, *except* for boot modules: if we encounter - -- a boot module, we have to find its real interface and discover the - -- dependencies of that. Hence we need to traverse the dependency - -- tree recursively. See bug #936, testcase ghci/prog007. - follow_deps :: [Module] -- modules to follow - -> UniqDSet Module -- accum. module dependencies - -> UniqDSet UnitId -- accum. package dependencies - -> IO ([Module], UniqDSet UnitId) -- result - follow_deps [] acc_mods acc_pkgs - = return (uniqDSetToList acc_mods, acc_pkgs) - follow_deps (mod:mods) acc_mods acc_pkgs - = do - mb_iface <- ldLoadIface opts msg mod - iface <- case mb_iface of - Failed err -> throwProgramError opts $ - missingInterfaceErrorDiagnostic (ldMsgOpts opts) err - Succeeded iface -> return iface - - when (mi_boot iface == IsBoot) $ link_boot_mod_error mod - - let - pkg = moduleUnit mod - deps = mi_deps iface - - pkg_deps = dep_direct_pkgs deps - (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $ - \case - (_, GWIB m IsBoot) -> Left m - (_, GWIB m NotBoot) -> Right m - - mod_deps' = case ue_homeUnit unit_env of - Nothing -> [] - Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps)) - acc_mods' = case ue_homeUnit unit_env of - Nothing -> acc_mods - Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps) - acc_pkgs' = addListToUniqDSet acc_pkgs (Set.toList pkg_deps) - - case ue_homeUnit unit_env of - Just home_unit | isHomeUnit home_unit pkg -> follow_deps (mod_deps' ++ mods) - acc_mods' acc_pkgs' - _ -> follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg)) - where - msg = text "need to link module" <+> ppr mod <+> - text "due to use of Template Haskell" - - - - link_boot_mod_error :: Module -> IO a - link_boot_mod_error mod = throwProgramError opts $ - text "module" <+> ppr mod <+> - text "cannot be linked; it is only available as a boot module" - no_obj :: Outputable a => a -> IO b no_obj mod = dieWith opts span $ - text "cannot find object file for module " <> + text "cannot find object file for module" <+> quotes (ppr mod) $$ while_linking_expr while_linking_expr = text "while linking an interpreted expression" + -- Extract the 'Linkable's for unlinked modules from the intermediate + -- results. + module_linkable = \case + LinkHomeModule hmi -> + adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi)) + + LinkObjectModule mod loc -> do + findObjectLinkableMaybe mod loc >>= \case + Nothing -> no_obj mod + Just lnk -> adjust_linkable lnk + + LinkByteCodeModule _ load_bytecode -> + load_bytecode -- See Note [Using Byte Code rather than Object Code for Template Haskell] homeModLinkable :: HomeModInfo -> Maybe Linkable @@ -266,57 +289,244 @@ get_link_deps opts pls maybe_normal_osuf span mods = do then homeModInfoByteCode hmi <|> homeModInfoObject hmi else homeModInfoObject hmi <|> homeModInfoByteCode hmi - get_linkable osuf mod -- A home-package module - | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env) - = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info)) - | otherwise - = do -- It's not in the HPT because we are in one shot mode, - -- so use the Finder to get a ModLocation... - case ue_homeUnit unit_env of - Nothing -> no_obj mod - Just home_unit -> do - from_bc <- ldLoadByteCode opts mod - maybe (fallback_no_bytecode home_unit mod) pure from_bc - where - - fallback_no_bytecode home_unit mod = do - let fc = ldFinderCache opts - let fopts = ldFinderOpts opts - mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod) - case mb_stuff of - Found loc _ -> do - mb_lnk <- findObjectLinkableMaybe mod loc - case mb_lnk of - Nothing -> no_obj mod - Just lnk -> adjust_linkable lnk - _ -> no_obj (moduleName mod) - - adjust_linkable lnk - | Just new_osuf <- maybe_normal_osuf = do - new_parts <- mapM (adjust_part new_osuf) - (linkableParts lnk) - return lnk{ linkableParts=new_parts } - | otherwise = - return lnk - - adjust_part new_osuf part = case part of - DotO file ModuleObject -> do - massert (osuf `isSuffixOf` file) - let file_base = fromJust (stripExtension osuf file) - new_file = file_base <.> new_osuf - ok <- doesFileExist new_file - if (not ok) - then dieWith opts span $ - text "cannot find object file " - <> quotes (text new_file) $$ while_linking_expr - else return (DotO new_file ModuleObject) - DotO file ForeignObject -> pure (DotO file ForeignObject) - DotA fp -> panic ("adjust_ul DotA " ++ show fp) - DotDLL fp -> panic ("adjust_ul DotDLL " ++ show fp) - BCOs {} -> pure part - LazyBCOs{} -> pure part - CoreBindings WholeCoreBindings {wcb_module} -> - pprPanic "Unhydrated core bindings" (ppr wcb_module) + adjust_linkable lnk + | Just new_osuf <- maybe_normal_osuf = do + new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf) + (linkableParts lnk) + return lnk {linkableParts = new_uls} + | otherwise = + return lnk + + adjust_part osuf new_osuf part = case part of + DotO file ModuleObject -> do + massert (osuf `isSuffixOf` file) + let file_base = fromJust (stripExtension osuf file) + new_file = file_base <.> new_osuf + ok <- doesFileExist new_file + if (not ok) + then dieWith opts span $ + text "cannot find object file" + <+> quotes (text new_file) $$ while_linking_expr + else return (DotO new_file ModuleObject) + DotO file ForeignObject -> pure (DotO file ForeignObject) + DotA fp -> panic ("adjust_part DotA " ++ show fp) + DotDLL fp -> panic ("adjust_part DotDLL " ++ show fp) + BCOs {} -> pure part + LazyBCOs{} -> pure part + CoreBindings WholeCoreBindings {wcb_module} -> + pprPanic "Unhydrated core bindings" (ppr wcb_module) + +data LinkDep = + LinkModules !(UniqDFM ModuleName LinkModule) + | + LinkLibrary !UnitId + +instance Outputable LinkDep where + ppr = \case + LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods) + LinkLibrary uid -> text "library:" <+> ppr uid + +data OneshotError = + NoInterface !MissingInterfaceError + | + LinkBootModule !Module + +-- | Compute the transitive dependency closure of the given modules. +-- +-- Used for all oneshot mode dependencies and for external dependencies of home +-- modules in make mode. +external_deps :: + LinkDepsOpts -> + -- | Modules whose imports to follow + [LinkExternal] -> + IO [LinkDep] +external_deps opts mods = + runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case + Right a -> pure (eltsUDFM a) + Left err -> throwProgramError opts (message err) + where + message = \case + NoInterface err -> + missingInterfaceErrorDiagnostic (ldMsgOpts opts) err + LinkBootModule mod -> + link_boot_mod_error mod + +external_deps_loop :: + LinkDepsOpts -> + [LinkExternal] -> + UniqDFM UnitId LinkDep -> + ExceptT OneshotError IO (UniqDFM UnitId LinkDep) +external_deps_loop _ [] acc = + pure acc +external_deps_loop opts (job at LinkExternal {le_module = mod, ..} : mods) acc = do + (new_acc, new_mods, action) <- + if already_seen + then done + else process_module le_details + traverse_ debug_log action + external_deps_loop opts (new_mods ++ mods) new_acc + where + debug_log action = + liftIO $ debugTraceMsg (ldLogger opts) 3 $ + text "TH dep" <+> ppr job <+> + brackets (sep (punctuate comma [ + if is_home then text "home" else Outputable.empty, + text action + ])) + + done = pure (acc, [], Nothing) + + -- Decide how this module needs to be processed. + -- We only need an interface if we want to load bytecode or if we have to + -- link an object file (which happens for home unit modules, since those + -- have no libraries). + process_module = \case + LinkAllDeps | is_home || package_bc -> try_iface + | otherwise -> add_library + + -- @LinkOnlyPackages@ is used for make mode home modules, so all imports + -- that are not external are already processed otherwise. + LinkOnlyPackages iface -> with_deps acc iface False "only packages" + + -- Check whether the current module was processed before. + -- Since the accumulator is keyed by unit ID, we have to perform two + -- lookups. + -- If another module from this module's unit has been determined to be + -- linked as a library previously, we skip this module, assuming that no + -- bytecode is available for the entire package. + already_seen + | Just (LinkModules mods) <- mod_dep + = elemUDFM mod_name mods + | Just (LinkLibrary _) <- mod_dep + = True + | otherwise + = False + + -- Load the iface and attempt to get bytecode from Core bindings. + try_iface = + liftIO (ldLoadIface opts load_reason mod) >>= \case + Failed err -> throwE (NoInterface err) + Succeeded (iface, loc) -> do + mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface)) + with_iface iface loc mb_load_bc + + -- Decide how to link this module. + -- If bytecode or an object file is available, use those in that order. + -- Otherwise fall back to linking a library. + with_iface iface loc mb_load_bc + | IsBoot <- mi_boot iface + = throwE (LinkBootModule mod) + + | ldUseByteCode opts + , is_home || package_bc + , Just load_bc <- mb_load_bc + = add_module iface (LinkByteCodeModule mod load_bc) "bytecode" + + | is_home + = add_module iface (LinkObjectModule mod loc) "object" + + | otherwise + = add_library + + add_library = + pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library") + + add_module iface lmod action = + with_deps with_mod iface True action + where + with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id + + add_package_module lmod = \case + Just (LinkLibrary u) -> Just (LinkLibrary u) + Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod)) + Nothing -> Just (LinkModules (unitUDFM mod_name lmod)) + + with_deps acc iface local action = + pure (addListToUDFM acc link, new_local ++ new_package, Just action) + where + !(!link, !new_package) = package_deps iface + new_local = if local then local_deps iface else [] + + local_deps iface = + [ + LinkExternal LinkAllDeps (mkModule mod_unit m) + | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface)) + ] + + -- If bytecode linking of external dependencies is enabled, add them to the + -- jobs passed to the next iteration of 'external_deps_loop'. + -- Otherwise, link all package deps as libraries. + package_deps iface + | package_bc + = ([], [LinkExternal LinkAllDeps m | m <- Set.toList (dep_direct_pkg_mods (mi_deps iface))]) + | otherwise + = ([(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))], []) + + load_reason = + text "need to link module" <+> ppr mod <+> + text "due to use of Template Haskell" + + package_bc = ldPkgByteCode opts + + -- In multiple home unit mode, this only considers modules from the same + -- unit as the splice's module to be eligible for linking bytecode when + -- @-fpackage-db-byte-code@ is off. + -- For make mode, this is irrelevant, since any bytecode from the HUG is + -- obtained directly, not going through 'external_deps'. + is_home + | Just home <- ue_homeUnit (ldUnitEnv opts) + = homeUnitAsUnit home == mod_unit + | otherwise + = False + + mod_dep = lookupUDFM acc mod_unit_id + mod_name = moduleName mod + mod_unit_id = moduleUnitId mod + mod_unit = moduleUnit mod + +link_boot_mod_error :: Module -> SDoc +link_boot_mod_error mod = + text "module" <+> ppr mod <+> + text "cannot be linked; it is only available as a boot module" + +-- | Split link dependencies into the sets of modules and packages that have +-- been linked previously and those that need to be linked now by checking for +-- their presence in the 'LoaderState': +-- +-- - For module dependencies, in the sets of loaded objects and BCOs +-- ('objs_loaded' and 'bcos_loaded') +-- - For package dependencies, in the set of loaded packages ('pkgs_loaded') +classify_deps :: + LoaderState -> + [HomeModInfo] -> + [LinkDep] -> + ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId]) +classify_deps pls hmis deps = + (loaded_modules' ++ loaded_modules'', needed_modules' ++ needed_modules'', all_packages, needed_packages) + where + (loaded_modules', needed_modules') = partitionWith loaded_or_needed_home_module hmis + (loaded_modules'', needed_modules'') = + partitionWith loaded_or_needed_module (concatMap eltsUDFM modules) + + needed_packages = + eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls) + + all_packages = mkUniqDSet packages + + (modules, packages) = flip partitionWith deps $ \case + LinkModules mods -> Left mods + LinkLibrary lib -> Right lib + + loaded_or_needed_home_module lm = + maybe (Right (LinkHomeModule lm)) Left (loaded_module (mi_module (hm_iface lm))) + + loaded_or_needed_module lm = + maybe (Right lm) Left (loaded_module (link_module lm)) + + loaded_module mod = + lookupModuleEnv (objs_loaded pls) mod + <|> + lookupModuleEnv (bcos_loaded pls) mod {- Note [Using Byte Code rather than Object Code for Template Haskell] ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -77,11 +77,13 @@ import GHC.Utils.TmpFs import GHC.Unit.Env import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode)) +import GHC.Unit.Finder import GHC.Unit.Module import GHC.Unit.State as Packages import qualified GHC.Data.ShortText as ST import GHC.Data.FastString +import qualified GHC.Data.Maybe as Maybe import GHC.Linker.Deps import GHC.Linker.MacOS @@ -94,6 +96,7 @@ import Control.Monad import qualified Data.Set as Set import Data.Char (isSpace) import qualified Data.Foldable as Foldable +import Data.Functor ((<&>)) import Data.IORef import Data.List (intercalate, isPrefixOf, nub, partition) import Data.Maybe @@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - let this_pkgs_needed = ldNeededUnits deps + let this_pkgs_needed = ldAllUnits deps -- Link the packages and modules required - pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls + pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps) let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed all_pkgs_loaded = pkgs_loaded pls2 @@ -643,21 +646,40 @@ initLinkDepsOpts hsc_env = opts , ldModuleGraph = hsc_mod_graph hsc_env , ldUnitEnv = hsc_unit_env hsc_env , ldPprOpts = initSDocContext dflags defaultUserStyle - , ldFinderCache = hsc_FC hsc_env - , ldFinderOpts = initFinderOpts dflags , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags + , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags , ldMsgOpts = initIfaceMessageOpts dflags , ldWays = ways dflags , ldLoadIface , ldLoadByteCode + , ldLogger = hsc_logger hsc_env } dflags = hsc_dflags hsc_env - ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env - $ loadInterface msg mod (ImportByUser NotBoot) + + ldLoadIface msg mod = + initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case + Maybe.Failed err -> pure (Maybe.Failed err) + Maybe.Succeeded iface -> + find_location mod <&> \case + InstalledFound loc _ -> Maybe.Succeeded (iface, loc) + err -> Maybe.Failed $ + cannotFindInterface unit_state home_unit + (targetProfile dflags) (moduleName mod) err + + find_location mod = + liftIO $ + findExactModule (hsc_FC hsc_env) (initFinderOpts dflags) + other_fopts unit_state home_unit (toUnitId <$> mod) + + other_fopts = initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env + + unit_state = hsc_units hsc_env + + home_unit = ue_homeUnit (hsc_unit_env hsc_env) ldLoadByteCode mod = do EPS {eps_iface_bytecode} <- hscEPS hsc_env - sequence (lookupModuleEnv eps_iface_bytecode mod) + pure (lookupModuleEnv eps_iface_bytecode mod) ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -753,7 +753,7 @@ mkStubPaths fopts mod location = do src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location -- ----------------------------------------------------------------------------- --- findLinkable isn't related to the other stuff in here, +-- findObjectLinkable isn't related to the other stuff in here, -- but there's no other obvious place for it findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) ===================================== compiler/GHC/Unit/Module/Deps.hs ===================================== @@ -4,6 +4,7 @@ module GHC.Unit.Module.Deps , mkDependencies , noDependencies , dep_direct_mods + , dep_direct_pkg_mods , dep_direct_pkgs , dep_sig_mods , dep_trusted_pkgs @@ -35,6 +36,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Binary import GHC.Utils.Outputable +import qualified Data.Map.Strict as Map import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set @@ -99,6 +101,9 @@ data Dependencies = Deps -- does NOT include us, unlike 'imp_finsts'. See Note -- [The type family instance consistency story]. + -- TODO strict? + , dep_direct_pkg_mods :: Set Module + } deriving( Eq ) -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints @@ -145,6 +150,8 @@ mkDependencies home_unit mod imports plugin_mods = sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports + dep_direct_pkg_mods = Set.filter ((homeUnitAsUnit home_unit /=) . moduleUnit) (Map.keysSet (imp_mods imports)) + in Deps { dep_direct_mods = direct_mods , dep_direct_pkgs = direct_pkgs , dep_plugin_pkgs = plugin_units @@ -155,6 +162,7 @@ mkDependencies home_unit mod imports plugin_mods = , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) -- sort to get into canonical order -- NB. remember to use lexicographic ordering + , dep_direct_pkg_mods } -- | Update module dependencies containing orphans (used by Backpack) @@ -179,6 +187,7 @@ instance Binary Dependencies where put_ bh (dep_boot_mods deps) put_ bh (dep_orphs deps) put_ bh (dep_finsts deps) + put_ bh (dep_direct_pkg_mods deps) get bh = do dms <- get bh dps <- get bh @@ -188,14 +197,16 @@ instance Binary Dependencies where sms <- get bh os <- get bh fis <- get bh + dep_direct_pkg_mods <- get bh return (Deps { dep_direct_mods = dms , dep_direct_pkgs = dps , dep_plugin_pkgs = plugin_pkgs , dep_sig_mods = hsigms , dep_boot_mods = sms , dep_trusted_pkgs = tps - , dep_orphs = os, - dep_finsts = fis }) + , dep_orphs = os + , dep_finsts = fis + , dep_direct_pkg_mods }) noDependencies :: Dependencies noDependencies = Deps @@ -207,6 +218,7 @@ noDependencies = Deps , dep_trusted_pkgs = Set.empty , dep_orphs = [] , dep_finsts = [] + , dep_direct_pkg_mods = Set.empty } -- | Pretty-print unit dependencies ===================================== compiler/GHC/Unit/Module/WholeCoreBindings.hs ===================================== @@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed build artifacts, which can be objects or bytecode, depending on the build settings. -1. In make mode, all eligible modules are part of the dependency graph. +1. In make mode, all eligible home modules are part of the dependency graph. Their interfaces are loaded unconditionally and in dependency order by the compilation manager, and each module's bytecode is prepared before its dependents are compiled, in one of two ways: @@ -88,9 +88,10 @@ settings. 2. In oneshot mode, which compiles individual modules without a shared home unit graph, a previously compiled module is not reprocessed as described for make mode above. - When 'get_link_deps' encounters a dependency on a local module, it requests - its bytecode from the External Package State, who loads the interface - on-demand. + 'get_link_deps' requests the bytecode of dependencies from the External + Package State, who loads the interface on-demand. + This works for modules in local directories (via @-i@ and @-hidir@) as well + as those exposed from a package DB. Since the EPS stores interfaces for all package dependencies in addition to local modules in oneshot mode, it has a substantial memory footprint. @@ -109,6 +110,18 @@ settings. storing the intermediate representation as rehydrated Core bindings, since the latter have a significantly greater memory footprint. +3. In both of the above modes, whenever a module from an external package + (loaded from a package DB) is encountered, the workflow is the same as for + oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object + code is loaded. + Interfaces for external modules are stored together with local oneshot mode + modules, so almost no special treatment is necessary, with the exception of: + - When external package modules are compiled, the @InteractiveContext@ in + @HscEnv@ is accessed, which is not available due to its impact on retention + of outdated build products. + This is solved by writing an empty @InteractiveContext@ to the env used for + compilation. + Note [Size of Interface Files with Core Definitions] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op. Otherwise, the stub objects from the interface are compiled to objects in 'generateByteCode' and added to the 'HomeModLinkable' as well. -Case 3 is not implemented yet (!13042). +In case 3, Core bindings are loaded from the EPS, where stubs only exist in +their serialized form in the interface, so they must be regenerated like in case +2. Problem 3: ===================================== docs/users_guide/phases.rst ===================================== @@ -826,6 +826,17 @@ Options affecting code generation will generate byte-code rather than object code. +.. ghc-flag:: -fpackage-db-byte-code + :shortdesc: Use byte-code from package DB dependencies + :type: dynamic + :category: codegen + + GHC normally only considers local modules to be eligible for loading + bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`. + When this flag is specified additionally, bytecode will be loaded from + interfaces for all external package dependencies that provide it. + + .. _options-linker: Options affecting linking ===================================== testsuite/tests/bytecode/T25090/Dep.hs ===================================== @@ -0,0 +1,15 @@ +module Dep where + +data A = A Int + +used :: Int +used = 9681 + +dep :: A +dep = A used + +unused1 :: A +unused1 = A 1 + +unused2 :: A +unused2 = unused1 ===================================== testsuite/tests/bytecode/T25090/DepApi.hs ===================================== @@ -0,0 +1,7 @@ +module DepApi (A (A), dep) where + +import Dep (A (A)) +import qualified Dep + +dep :: A +dep = Dep.dep ===================================== testsuite/tests/bytecode/T25090/Local.hs ===================================== @@ -0,0 +1,15 @@ +{-# language PackageImports #-} + +module Local where + +import GHC.Prim +import Language.Haskell.TH (ExpQ) +import Language.Haskell.TH.Syntax (lift) +-- just to be sure that the file isn't accidentally picked up locally +import "dep" DepApi (dep, A (A)) +import {-# source #-} Num (num) + +splc :: ExpQ +splc = lift @_ @Int (num + d) + where + A d = dep ===================================== testsuite/tests/bytecode/T25090/Makefile ===================================== @@ -19,3 +19,35 @@ T25090a: T25090b: $(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0 ./exe + +DB := -package-db db -package dep +BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0 +BC := -fprefer-byte-code -fbyte-code-and-object-code +ARGS := $(BASIC) $(BC) + +T25090_pkg: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_empty: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared-empty" + ./run.bash "$(TEST_HC)" "$(ARGS) -dynamic" + +T25090_pkg_nolib: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "none" + ./run.bash "$(TEST_HC)" "$(ARGS)" + +T25090_pkg_obj_code: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + ./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code" + +T25090_pkg_multi_unit: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "shared" + mkdir -p unit2-src/ + mv Local.hs Num.hs Num.hs-boot unit2-src/ + "$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -fpackage-db-byte-code -dynamic -unit @unit1 -unit @unit2 + ./PkgBytecode + +T25090_pkg_archive: + ./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "archive" + ./run.bash "$(TEST_HC)" "$(ARGS)" ===================================== testsuite/tests/bytecode/T25090/Num.hs ===================================== @@ -0,0 +1,4 @@ +module Num where + +num :: Int +num = 48332 ===================================== testsuite/tests/bytecode/T25090/Num.hs-boot ===================================== @@ -0,0 +1,3 @@ +module Num where + +num :: Int ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.hs ===================================== @@ -0,0 +1,12 @@ +{-# language TemplateHaskell #-} + +module Main where + +import GHC.Prim +import Local (splc) + +a :: Int +a = $(splc) + +main :: IO () +main = putStrLn (show a) ===================================== testsuite/tests/bytecode/T25090/PkgBytecode.stdout ===================================== @@ -0,0 +1 @@ +58013 ===================================== testsuite/tests/bytecode/T25090/all.T ===================================== @@ -16,3 +16,33 @@ def test_T25090(name): test_T25090('T25090a') test_T25090('T25090b') + +def test_pkg(name, files = []): + test( + name, + [ + extra_files([ + 'PkgBytecode.hs', + 'Local.hs', + 'Dep.hs', + 'DepApi.hs', + 'Num.hs', + 'Num.hs-boot', + 'dep.conf', + 'prep.bash', + 'run.bash', + ] + files), + use_specs({'stdout': 'PkgBytecode.stdout'}), + ], + makefile_test, + [], + ) + +test_pkg('T25090_pkg') +test_pkg('T25090_pkg_empty') +test_pkg('T25090_pkg_nolib') +test_pkg('T25090_pkg_obj_code') +test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2']) +# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a +# comment says "search for .so libraries _first_" (rather than "only"). +# test_pkg('T25090_pkg_archive') ===================================== testsuite/tests/bytecode/T25090/dep.conf ===================================== @@ -0,0 +1,8 @@ +name: dep +version: 1.0 +id: dep-1.0 +key: dep-1.0 +exposed: True +exposed-modules: DepApi +import-dirs: ${pkgroot}/dep +library-dirs: ${pkgroot}/dep ===================================== testsuite/tests/bytecode/T25090/prep.bash ===================================== @@ -0,0 +1,57 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" +ghc_pkg_cmd="$3" +library="$4" + +base="$PWD" +db="$base/db" +dep="$base/dep" +conf_dep="${dep}/dep.conf" + +mkdir -p "$dep" "$db" +mv Dep.hs DepApi.hs "$dep/" +cp dep.conf "$dep/" + +ghc_pkg() +{ + eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@" +} + +ghc() +{ + eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@" +} + +version=$(ghc "--numeric-version") + +ghc_pkg recache + +ghc "-dynamic-too -c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs" + +if [[ "$library" == 'shared' ]] +then + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'shared-empty' ]] +then + echo 'module Dummy where' > Dummy.hs + ghc "-dynamic-too -c Dummy.hs" + ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc$version.so Dummy.dyn_o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'archive' ]] +then + $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o" + echo 'hs-libraries: HSdep-1.0' >> "$conf_dep" +elif [[ "$library" == 'none' ]] +then + : +else + echo "Invalid argument for 'library': $library" + exit 1 +fi + +ghc_pkg -v0 register "${conf_dep at Q}" ===================================== testsuite/tests/bytecode/T25090/run.bash ===================================== @@ -0,0 +1,16 @@ +#!/usr/bin/env bash + +set -eu + +ghc_cmd="$1" +ghc_opts="$2" + +ghc() +{ + eval "${ghc_cmd at Q} $ghc_opts $@" +} + +ghc -c Num.hs-boot Num.hs Local.hs +ghc -fpackage-db-byte-code -c PkgBytecode.hs +ghc PkgBytecode.o -o PkgBytecode +./PkgBytecode ===================================== testsuite/tests/bytecode/T25090/unit1 ===================================== @@ -0,0 +1 @@ +-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2 ===================================== testsuite/tests/bytecode/T25090/unit2 ===================================== @@ -0,0 +1 @@ +-i -i./unit2-src Local Num -this-unit-id unit2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8ab26a0ea5c3b2a579ba608be5f1fc5bd88d7ce...38f1ca4f4a6178a76577b68122a5b3653a6a05fc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8ab26a0ea5c3b2a579ba608be5f1fc5bd88d7ce...38f1ca4f4a6178a76577b68122a5b3653a6a05fc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 20:31:17 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 16:31:17 -0400 Subject: [Git][ghc/ghc][master] mkTick: Push ticks through unsafeCoerce#. Message-ID: <67180b95bb17a_27dc1e6525e816420@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00 mkTick: Push ticks through unsafeCoerce#. unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast for the purpose of mkTick. This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we now push the scope part of the cost centre up to `trivial_expr` at which point we can discard it completely if the expression is trivial enough. This fixes #25212. - - - - - 2 changed files: - compiler/GHC/Core/Utils.hs - compiler/GHC/Types/Tickish.hs Changes: ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -305,7 +305,6 @@ mkTick t orig_expr = mkTick' id id orig_expr -- Some ticks (cost-centres) can be split in two, with the -- non-counting part having laxer placement properties. canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t - -- mkTick' handles floating of ticks *into* the expression. -- In this function, `top` is applied after adding the tick, and `rest` before. -- This will result in applications that look like (top $ Tick t $ rest expr). @@ -316,6 +315,10 @@ mkTick t orig_expr = mkTick' id id orig_expr -> CoreExpr -- current expression -> CoreExpr mkTick' top rest expr = case expr of + -- Float ticks into unsafe coerce the same way we would do with a cast. + Case scrut bndr ty alts@[Alt ac abs _rhs] + | Just rhs <- isUnsafeEqualityCase scrut bndr alts + -> top $ mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs -- Cost centre ticks should never be reordered relative to each -- other. Therefore we can stop whenever two collide. @@ -1251,7 +1254,7 @@ Note [Tick trivial] Ticks are only trivial if they are pure annotations. If we treat "tick x" as trivial, it will be inlined inside lambdas and the entry count will be skewed, for example. Furthermore "scc x" will -turn into just "x" in mkTick. +turn into just "x" in mkTick. At least if `x` is not a function. Note [Empty case is trivial] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Tickish.hs ===================================== @@ -295,13 +295,15 @@ tickishCanSplit _ = False mkNoCount :: GenTickish pass -> GenTickish pass mkNoCount n | not (tickishCounts n) = n | not (tickishCanSplit n) = panic "mkNoCount: Cannot split!" -mkNoCount n at ProfNote{} = n {profNoteCount = False} +mkNoCount n at ProfNote{} = let n' = n {profNoteCount = False} + in assert (profNoteCount n) n' mkNoCount _ = panic "mkNoCount: Undefined split!" mkNoScope :: GenTickish pass -> GenTickish pass mkNoScope n | tickishScoped n == NoScope = n | not (tickishCanSplit n) = panic "mkNoScope: Cannot split!" -mkNoScope n at ProfNote{} = n {profNoteScope = False} +mkNoScope n at ProfNote{} = let n' = n {profNoteScope = False} + in assert (profNoteCount n) n' mkNoScope _ = panic "mkNoScope: Undefined split!" -- | Return @True@ if this source annotation compiles to some backend View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edf3bdf57501beb3372eaa0a9602f1094cdf30d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edf3bdf57501beb3372eaa0a9602f1094cdf30d1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 20:32:20 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 16:32:20 -0400 Subject: [Git][ghc/ghc][master] hadrian: enable late-CCS for perf flavour as well Message-ID: <67180bd4222dc_27dc1e5fbe50236c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00 hadrian: enable late-CCS for perf flavour as well This patch enables late-CCS for perf flavour so that the testsuite can pass for perf as well. Fixes #25308. - - - - - 3 changed files: - hadrian/doc/flavours.md - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Release.hs Changes: ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O2 - release (same as perf with -haddock and +late-ccs) + release (same as perf with -haddock) -O
-H64m -O
-H64m @@ -323,7 +323,7 @@ The supported transformers are listed below: late_ccs - Enable -fprof-late in profiled libraries. + Enable -fprof-late in profiled libraries. Enabled in perf and release flavours. dump_stg ===================================== hadrian/src/Settings/Flavours/Performance.hs ===================================== @@ -6,7 +6,7 @@ import {-# SOURCE #-} Settings.Default -- Please update doc/flavours.md when changing this file. performanceFlavour :: Flavour -performanceFlavour = splitSections $ defaultFlavour +performanceFlavour = splitSections $ enableLateCCS $ defaultFlavour { name = "perf" , extraArgs = performanceArgs <> defaultHaddockExtraArgs } ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,4 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableLateCCS $ enableHaddock performanceFlavour { name = "release" } +releaseFlavour = enableHaddock performanceFlavour { name = "release" } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bdb131799a356628e2906c892905b715c722fa0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bdb131799a356628e2906c892905b715c722fa0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Oct 22 20:32:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 22 Oct 2024 16:32:53 -0400 Subject: [Git][ghc/ghc][master] hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling Message-ID: <67180bf511caa_27dc1e549ffc252bf@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00 hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling This patch disables internal-interpreter flag for stage0 ghc-bin when not cross compiling, see added comment for explanation. Fixes #25406. - - - - - 1 changed file: - hadrian/src/Settings/Packages.hs Changes: ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -107,7 +107,16 @@ packageArgs = do , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ] , builder (Cabal Flags) ? mconcat - [ expr ghcWithInterpreter `cabalFlag` "internal-interpreter" + [ + -- When cross compiling, enable for stage0 to get ghci + -- support. But when not cross compiling, disable for + -- stage0, otherwise we introduce extra dependencies + -- like haskeline etc, and mixing stageBoot/stage0 libs + -- can cause extra trouble (e.g. #25406) + expr ghcWithInterpreter ? + ifM (expr cross) + (arg "internal-interpreter") + (notStage0 `cabalFlag` "internal-interpreter") , ifM stage0 -- We build a threaded stage 1 if the bootstrapping compiler -- supports it. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fde12aba9bb2d3ba607548dfba648f2a5ee00b59 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fde12aba9bb2d3ba607548dfba648f2a5ee00b59 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Oct 23 08:38:44 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 23 Oct 2024 04:38:44 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: mkTick: Push ticks through unsafeCoerce#. Message-ID: <6718b6149ef65_3705d571208c938d3@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00 mkTick: Push ticks through unsafeCoerce#. unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast for the purpose of mkTick. This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we now push the scope part of the cost centre up to `trivial_expr` at which point we can discard it completely if the expression is trivial enough. This fixes #25212. - - - - - 1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00 hadrian: enable late-CCS for perf flavour as well This patch enables late-CCS for perf flavour so that the testsuite can pass for perf as well. Fixes #25308. - - - - - fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00 hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling This patch disables internal-interpreter flag for stage0 ghc-bin when not cross compiling, see added comment for explanation. Fixes #25406. - - - - - aec4594a by ignatiusm at 2024-10-23T04:38:27-04:00 Rebases on Master parent d5c2577f12a103dec3c88d2403f59de48269d9c3 author ignatiusm <ignatius.menzies at gmail.com> 1725313252 +1200 committer ignatiusm <ignatius.menzies at gmail.com> 1728459429 +1300 feat: changes heap overflow exception message to point to RTS flags rather than GHC bug feat: adds test for #25198 feat: adds release notes entry for #25198 feat: changes heap overflow exception message to point to RTS flags rather than GHC bug feat: adds test for #25198 Remove makefile from test - - - - - 88628f8c by Rodrigo Mesquita at 2024-10-23T04:38:27-04:00 determinism: Interface re-export list det In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for interface file determinism. This commit introduces 'DetOrdAvails', a newtype that should only be constructed by sorting Avails with 'sortAvails' unless the avails are known to be deterministically ordered. This newtype is used by 'DocStructureItem' where 'Avails' was previously used to ensure the list of avails is deterministically sorted by construction. Note: Even though we order the constructors and avails in the interface file, the order of constructors in the haddock output is still determined from the order of declaration in the source. This was also true before, when the list of constructors in the interface file <docs> section was non-deterministic. Some haddock tests such as "ConstructorArgs" observe this (check the order of constructors in out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file) The updated tests are caused by haddock corners where the order in the source is not preserved (and was non-deterministic before this PR): * Module header in the latex backend * Re-export of pattern synonyms associated to a datatype (#25342) Fixes #25304 - - - - - e055b806 by Rodrigo Mesquita at 2024-10-23T04:38:27-04:00 Revert "ci: Allow abi-test to fail." After #25304, the abi-test with interface and object determinism succeeds. This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Hs/Doc.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Tickish.hs - docs/users_guide/9.14.1-notes.rst - hadrian/doc/flavours.md - hadrian/src/Settings/Flavours/Performance.hs - hadrian/src/Settings/Flavours/Release.hs - hadrian/src/Settings/Packages.hs - + testsuite/tests/determinism/T25304/A.hs - + testsuite/tests/determinism/T25304/B.hs - + testsuite/tests/determinism/T25304/Makefile - + testsuite/tests/determinism/T25304/T25304a.stdout - + testsuite/tests/determinism/T25304/all.T - + testsuite/tests/rts/T25198/T25198.hs - + testsuite/tests/rts/T25198/T25198.stderr - + testsuite/tests/rts/T25198/all.T - testsuite/tests/showIface/DocsInHiFileTH.stdout - testsuite/tests/showIface/NoExportList.stdout - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/html-test/ref/BundledPatterns2.html - utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex - utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex - utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex - utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1007,8 +1007,6 @@ perf: ############################################################ abi-test: - # see #12935 for remaining work - allow_failure: true stage: testing needs: - job: x86_64-linux-fedora33-release ===================================== .gitlab/ci.sh ===================================== @@ -714,11 +714,11 @@ function cabal_abi_test() { start_section "Cabal test: $OUT" mkdir -p "$OUT" - run "$HC" \ + "$HC" \ -hidir tmp -odir tmp -fforce-recomp -haddock \ -iCabal/Cabal/src -XNoPolyKinds Distribution.Simple -j"$cores" \ -fobject-determinism \ - "$@" 2>&1 | tee $OUT/log + "$@" 2>&1 | sed '1d' | tee $OUT/log summarise_hi_files summarise_o_files popd ===================================== compiler/GHC.hs ===================================== @@ -483,6 +483,8 @@ defaultErrorHandler fm (FlushOut flushOut) inner = liftIO $ throwIO UserInterrupt Just StackOverflow -> fm "stack overflow: use +RTS -K to increase it" + Just HeapOverflow -> + fm "heap overflow: use +RTS -M to increase maximum heap size" _ -> case fromException exception of Just (ex :: ExitCode) -> liftIO $ throwIO ex _ -> ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -305,7 +305,6 @@ mkTick t orig_expr = mkTick' id id orig_expr -- Some ticks (cost-centres) can be split in two, with the -- non-counting part having laxer placement properties. canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t - -- mkTick' handles floating of ticks *into* the expression. -- In this function, `top` is applied after adding the tick, and `rest` before. -- This will result in applications that look like (top $ Tick t $ rest expr). @@ -316,6 +315,10 @@ mkTick t orig_expr = mkTick' id id orig_expr -> CoreExpr -- current expression -> CoreExpr mkTick' top rest expr = case expr of + -- Float ticks into unsafe coerce the same way we would do with a cast. + Case scrut bndr ty alts@[Alt ac abs _rhs] + | Just rhs <- isUnsafeEqualityCase scrut bndr alts + -> top $ mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs -- Cost centre ticks should never be reordered relative to each -- other. Therefore we can stop whenever two collide. @@ -1251,7 +1254,7 @@ Note [Tick trivial] Ticks are only trivial if they are pure annotations. If we treat "tick x" as trivial, it will be inlined inside lambdas and the entry count will be skewed, for example. Furthermore "scc x" will -turn into just "x" in mkTick. +turn into just "x" in mkTick. At least if `x` is not a function. Note [Empty case is trivial] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Hs/Doc.hs ===================================== @@ -124,7 +124,7 @@ data DocStructureItem = DsiSectionHeading !Int !(HsDoc GhcRn) | DsiDocChunk !(HsDoc GhcRn) | DsiNamedChunkRef !String - | DsiExports !Avails + | DsiExports !DetOrdAvails | DsiModExport !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple -- modules with a single export declaration. E.g. @@ -136,7 +136,7 @@ data DocStructureItem -- -- Invariant: This list of ModuleNames must be -- sorted to guarantee interface file determinism. - !Avails + !DetOrdAvails -- ^ Invariant: This list of Avails must be sorted -- to guarantee interface file determinism. ===================================== compiler/GHC/HsToCore/Docs.hs ===================================== @@ -163,7 +163,11 @@ mkDocStructureFromExportList mdl import_avails export_list = (IEGroup _ level doc, _) -> DsiSectionHeading level (unLoc doc) (IEDoc _ doc, _) -> DsiDocChunk (unLoc doc) (IEDocNamed _ name, _) -> DsiNamedChunkRef name - (_, avails) -> DsiExports (nubAvails avails) + (IEThingWith{}, avails) -> + DsiExports $ + {- For explicit export lists, use the explicit order. It is deterministic by construction -} + DefinitelyDeterministicAvails (nubAvails avails) + (_, avails) -> DsiExports (sortAvails (nubAvails avails)) moduleExport :: ModuleName -- Alias -> Avails @@ -204,10 +208,10 @@ mkDocStructureFromDecls env all_exports decls = avails :: [Located DocStructureItem] avails = flip fmap all_exports $ \avail -> case M.lookup (availName avail) name_locs of - Just loc -> L loc (DsiExports [avail]) + Just loc -> L loc (DsiExports (sortAvails [avail])) -- FIXME: This is just a workaround that we use when handling e.g. -- associated data families like in the html-test Instances.hs. - Nothing -> noLoc (DsiExports []) + Nothing -> noLoc (DsiExports (sortAvails [])) -- This causes the associated data family to be incorrectly documented -- separately from its class: ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -518,8 +518,8 @@ mkIfaceImports = map go go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env)) go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns) -mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical -mkIfaceExports = sortAvails +mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical +mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas {- Note [Original module] ===================================== compiler/GHC/Types/Avail.hs ===================================== @@ -1,5 +1,7 @@ {-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PatternSynonyms #-} -- -- (c) The University of Glasgow -- @@ -20,6 +22,7 @@ module GHC.Types.Avail ( filterAvails, nubAvails, sortAvails, + DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails) ) where import GHC.Prelude @@ -65,6 +68,20 @@ data AvailInfo -- | A collection of 'AvailInfo' - several things that are \"available\" type Avails = [AvailInfo] +-- | Occurrences of Avails in interface files must be deterministically ordered +-- to guarantee interface file determinism. +-- +-- We guarantee a deterministic order by either using the order explicitly +-- given by the user (e.g. in an explicit constructor export list) or instead +-- by sorting the avails with 'sortAvails'. +newtype DetOrdAvails = DefinitelyDeterministicAvails Avails + deriving newtype (Binary, Outputable, NFData) + +-- | It's always safe to match on 'DetOrdAvails' +pattern DetOrdAvails :: Avails -> DetOrdAvails +pattern DetOrdAvails x <- DefinitelyDeterministicAvails x +{-# COMPLETE DetOrdAvails #-} + {- Note [Representing pattern synonym fields in AvailInfo] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Record pattern synonym fields cannot be represented using AvailTC like fields of @@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns) | otherwise = ns -- | Sort 'Avails'/'AvailInfo's -sortAvails :: Avails -> Avails -sortAvails = sortBy stableAvailCmp . map sort_subs +sortAvails :: Avails -> DetOrdAvails +sortAvails = DefinitelyDeterministicAvails . sortBy stableAvailCmp . map sort_subs where sort_subs :: AvailInfo -> AvailInfo sort_subs (Avail n) = Avail n ===================================== compiler/GHC/Types/Tickish.hs ===================================== @@ -295,13 +295,15 @@ tickishCanSplit _ = False mkNoCount :: GenTickish pass -> GenTickish pass mkNoCount n | not (tickishCounts n) = n | not (tickishCanSplit n) = panic "mkNoCount: Cannot split!" -mkNoCount n at ProfNote{} = n {profNoteCount = False} +mkNoCount n at ProfNote{} = let n' = n {profNoteCount = False} + in assert (profNoteCount n) n' mkNoCount _ = panic "mkNoCount: Undefined split!" mkNoScope :: GenTickish pass -> GenTickish pass mkNoScope n | tickishScoped n == NoScope = n | not (tickishCanSplit n) = panic "mkNoScope: Cannot split!" -mkNoScope n at ProfNote{} = n {profNoteScope = False} +mkNoScope n at ProfNote{} = let n' = n {profNoteScope = False} + in assert (profNoteCount n) n' mkNoScope _ = panic "mkNoScope: Undefined split!" -- | Return @True@ if this source annotation compiles to some backend ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -23,6 +23,8 @@ Language Compiler ~~~~~~~~ +- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198) + GHCi ~~~~ ===================================== hadrian/doc/flavours.md ===================================== @@ -107,7 +107,7 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O2 - release (same as perf with -haddock and +late-ccs) + release (same as perf with -haddock) -O
-H64m -O
-H64m @@ -323,7 +323,7 @@ The supported transformers are listed below: late_ccs - Enable -fprof-late in profiled libraries. + Enable -fprof-late in profiled libraries. Enabled in perf and release flavours. dump_stg ===================================== hadrian/src/Settings/Flavours/Performance.hs ===================================== @@ -6,7 +6,7 @@ import {-# SOURCE #-} Settings.Default -- Please update doc/flavours.md when changing this file. performanceFlavour :: Flavour -performanceFlavour = splitSections $ defaultFlavour +performanceFlavour = splitSections $ enableLateCCS $ defaultFlavour { name = "perf" , extraArgs = performanceArgs <> defaultHaddockExtraArgs } ===================================== hadrian/src/Settings/Flavours/Release.hs ===================================== @@ -4,4 +4,4 @@ import Settings.Flavours.Performance import Flavour releaseFlavour :: Flavour -releaseFlavour = enableLateCCS $ enableHaddock performanceFlavour { name = "release" } +releaseFlavour = enableHaddock performanceFlavour { name = "release" } ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -107,7 +107,16 @@ packageArgs = do , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ] , builder (Cabal Flags) ? mconcat - [ expr ghcWithInterpreter `cabalFlag` "internal-interpreter" + [ + -- When cross compiling, enable for stage0 to get ghci + -- support. But when not cross compiling, disable for + -- stage0, otherwise we introduce extra dependencies + -- like haskeline etc, and mixing stageBoot/stage0 libs + -- can cause extra trouble (e.g. #25406) + expr ghcWithInterpreter ? + ifM (expr cross) + (arg "internal-interpreter") + (notStage0 `cabalFlag` "internal-interpreter") , ifM stage0 -- We build a threaded stage 1 if the bootstrapping compiler -- supports it. ===================================== testsuite/tests/determinism/T25304/A.hs ===================================== @@ -0,0 +1,84 @@ +module A + ( MyType(..) + ) where + +data MyType + = A + | B + | C + | D + | E + | F + | G + | H + | I + | J + | K + | L + | M + | N + | O + | P + | Q + | R + | S + | T + | U + | V + | W + | X + | Y + | Z + | AA + | AB + | AC + | AD + | AE + | AF + | AG + | AH + | AI + | AJ + | AK + | AL + | AM + | AN + | AO + | AP + | AQ + | AR + | AS + | AT + | AU + | AV + | AW + | AX + | AY + | AZ + | BA + | BB + | BC + | BD + | BE + | BF + | BG + | BH + | BI + | BJ + | BK + | BL + | BM + | BN + | BO + | BP + | BQ + | BR + | BS + | BT + | BU + | BV + | BW + | BX + | BY + | BZ + | CA ===================================== testsuite/tests/determinism/T25304/B.hs ===================================== @@ -0,0 +1,86 @@ +module B +( MyType + ( BA + , BB + , BC + , BD + , BE + , BF + , BG + , BH + , BI + , BJ + , BK + , BL + , BM + , BN + , BO + , BP + , BQ + , BR + , BS + , BT + , BU + , BV + , BW + , BX + , BY + , BZ + , CA + , AA + , AB + , AC + , AD + , AE + , AF + , AG + , AH + , AI + , AJ + , AK + , AL + , AM + , AN + , AO + , AP + , AQ + , AR + , AS + , AT + , AU + , AV + , AW + , AX + , AY + , AZ + , A + , B + , C + , D + , E + , F + , G + , H + , I + , J + , K + , L + , M + , N + , O + , P + , Q + , R + , S + , T + , U + , V + , W + , X + , Y + , Z + ) +) where + +import A + ===================================== testsuite/tests/determinism/T25304/Makefile ===================================== @@ -0,0 +1,25 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +T25304: + $(RM) A.hi A.o B.hi B.o + # Use -haddock to get docs: output in the interface file + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs + '$(TEST_HC)' --show-iface A.hi > A_clean_iface + '$(TEST_HC)' --show-iface B.hi > B_clean_iface + '$(TEST_HC)' $(TEST_HC_OPTS) -dinitial-unique=16777215 -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp + '$(TEST_HC)' --show-iface A.hi > A_dirty_iface + '$(TEST_HC)' --show-iface B.hi > B_dirty_iface + diff A_clean_iface A_dirty_iface + diff B_clean_iface B_dirty_iface + +T25304a: + $(RM) A.hi A.o B.hi B.o + # Use -haddock to get docs: output in the interface file + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs + '$(TEST_HC)' --show-iface B.hi > B_clean_iface + # The goal is to see the export list in the documentation structure of the + # interface file preserves the order used in the source + cat B_clean_iface | grep -A7 "documentation structure" + ===================================== testsuite/tests/determinism/T25304/T25304a.stdout ===================================== @@ -0,0 +1,8 @@ + documentation structure: + avails: + [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH, + A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS, + A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC, + A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN, + A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY, + A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L, ===================================== testsuite/tests/determinism/T25304/all.T ===================================== @@ -0,0 +1,2 @@ +test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304']) +test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a']) ===================================== testsuite/tests/rts/T25198/T25198.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} +import Control.Exception +import Language.Haskell.TH + +-- Generate a very large number of declarations +generateDecls :: Int -> Q [Dec] +generateDecls n = mapM (\i -> valD (varP (mkName ("x" ++ show i))) (normalB [| i |]) []) [1..n] + +main :: IO () +main = do + $(generateDecls 1000000) + print x1 ===================================== testsuite/tests/rts/T25198/T25198.stderr ===================================== @@ -0,0 +1 @@ +heap overflow: use +RTS -M to increase maximum heap size ===================================== testsuite/tests/rts/T25198/all.T ===================================== @@ -0,0 +1,4 @@ +test('T25198', + normal, + compile_fail, + ['+RTS -M8M -RTS']) ===================================== testsuite/tests/showIface/DocsInHiFileTH.stdout ===================================== @@ -187,7 +187,7 @@ docs: avails: [i] avails: - [WD11{WD11, WD11Bool, WD11Int, WD11Foo}] + [WD11{WD11, WD11Bool, WD11Foo, WD11Int}] avails: [WD13{WD13}] avails: @@ -221,11 +221,11 @@ docs: avails: [Pretty{Pretty, prettyPrint}] avails: - [Corge{Corge, runCorge, Corge}] + [Corge{Corge, Corge, runCorge}] avails: - [Quuz{Quuz, quuz1_a, Quuz}] + [Quuz{Quuz, Quuz, quuz1_a}] avails: - [Quux{Quux, Quux2, Quux1}] + [Quux{Quux, Quux1, Quux2}] avails: [Tup2] avails: ===================================== testsuite/tests/showIface/NoExportList.stdout ===================================== @@ -32,7 +32,7 @@ docs: -- Actually we have only one type. identifiers: avails: - [R{R, fβ, fα, R}] + [R{R, R, fα, fβ}] section heading, level 1: text: -- * Functions ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -201,7 +201,15 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces -- See Note [Exporting built-in items] let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") []) bonus_ds mods - | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods + | mdl == gHC_PRIM = + [ builtinTys + , DsiExports $ + {- Haddock does not want to sort avails, the order should be + deterministically /derived from the source/. + In this particular case, sorting funAvail would be a no-op anyway. -} + DefinitelyDeterministicAvails + funAvail + ] <> mods | otherwise = mods let @@ -461,11 +469,11 @@ mkExportItems Just hsDoc' -> do doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc' pure [ExportDoc doc] - DsiExports avails -> + DsiExports (DetOrdAvails avails) -> -- TODO: We probably don't need nubAvails here. -- mkDocStructureFromExportList already uses it. concat <$> traverse availExport (nubAvails avails) - DsiModExport mod_names avails -> do + DsiModExport mod_names (DetOrdAvails avails) -> do -- only consider exporting a module if we are sure we are really -- exporting the whole module and not some subset. (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names) ===================================== utils/haddock/html-test/ref/BundledPatterns2.html ===================================== @@ -96,14 +96,6 @@ >wherepattern LR :: a -> BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/45657a96f5a9420f5f5270fe9aafc2e8bfba81fa...e055b8060d8b4641d6946c9ea9c517942a1c4034

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/45657a96f5a9420f5f5270fe9aafc2e8bfba81fa...e055b8060d8b4641d6946c9ea9c517942a1c4034
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 12:48:51 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Wed, 23 Oct 2024 08:48:51 -0400
Subject: [Git][ghc/ghc] Pushed new branch
 wip/andreask/docs-write-if-compression
Message-ID: <6718f0b332b1a_9cf34cbd900827aa@gitlab.mail>



Andreas Klebinger pushed new branch wip/andreask/docs-write-if-compression at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/docs-write-if-compression
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 12:57:06 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Wed, 23 Oct 2024 08:57:06 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-T25413
Message-ID: <6718f2a24b618_9cf34cbb36c9046b@gitlab.mail>



Cheng Shao pushed new branch wip/fix-T25413 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-T25413
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 12:59:32 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Wed, 23 Oct 2024 08:59:32 -0400
Subject: [Git][ghc/ghc][wip/andreask/docs-write-if-compression] Document
 -fwrite-if-compression in release notes.
Message-ID: <6718f33442feb_9cf34da052092260@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/docs-write-if-compression at Glasgow Haskell Compiler / GHC


Commits:
c1864579 by Andreas Klebinger at 2024-10-23T14:40:14+02:00
Document -fwrite-if-compression in release notes.

- - - - -


2 changed files:

- docs/users_guide/9.12.1-notes.rst
- docs/users_guide/using-optimisation.rst


Changes:

=====================================
docs/users_guide/9.12.1-notes.rst
=====================================
@@ -143,6 +143,12 @@ Compiler
   flag doesn't yet ensure determinism across all compilation configurations; we
   anticipate these cases will be addressed in future updates (:ghc-ticket:`12935`).
 
+- GHC now includes a new flag, :ghc-flag:`-fwrite-if-compression`,
+  which controls the level of compression used when writing interface files to disk.
+  While we think the majority of users will be well served by the default setting,
+  the flag allows users to pick their own tradeoff between memory footprint and
+  compilation time when needed.
+
 GHCi
 ~~~~
 


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1850,6 +1850,7 @@ as such you shouldn't need to set any of them explicitly. A flag
     :category: optimization
 
     :default: 2
+    :since: 9.12.1
 
     This flag defines the level of compression of interface files when writing to disk.
     The higher the flag, the more we deduplicate the interface file, at the cost of a higher compilation time.



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 13:01:15 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 23 Oct 2024 09:01:15 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] Temp workaround
Message-ID: <6718f39b10fe6_9cf34cbd8ec95299@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
18bab9dd by Sjoerd Visscher at 2024-10-23T15:01:03+02:00
Temp workaround

- - - - -


1 changed file:

- compiler/GHC/Driver/Make.hs


Changes:

=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1631,7 +1631,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
           -- Add a dependency on the HsBoot file if it exists
           -- This gets passed to the loopImports function which just ignores it if it
           -- can't be found.
-          [(ms_unitid ms, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
+          -- [(ms_unitid ms, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
           [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
 
         logger = hsc_logger hsc_env



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/18bab9ddbc4674db8cb91042473ba325a62c1cd3

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 13:28:22 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 23 Oct 2024 09:28:22 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] Possible fix
Message-ID: <6718f9f623ce5_1b1d88102d90-3ed@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
7c7f3548 by Sjoerd Visscher at 2024-10-23T15:27:03+02:00
Possible fix

- - - - -


1 changed file:

- compiler/GHC/Unit/Finder.hs


Changes:

=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -461,7 +461,7 @@ findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib
    -- special case for GHC.Prim; we won't find it in the filesystem.
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
-   if mod `installedModuleEq` gHC_PRIM
+   if mod `installedModuleEq` gHC_PRIM && is_boot == NotBoot
          then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
@@ -488,13 +488,13 @@ findPackageModule fc unit_state fopts mod = do
 -- The redundancy is to avoid an extra lookup in the package state
 -- for the appropriate config.
 findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModuleWithIsBoot -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod } pkg_conf = do
+findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod, gwib_isBoot = is_boot } pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
   modLocationCache fc gwib $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
-    if mod `installedModuleEq` gHC_PRIM
+    if mod `installedModuleEq` gHC_PRIM && is_boot == NotBoot
           then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c7f3548f80aea40f4ec242335b04e344d6ae1b3

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 13:56:13 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Wed, 23 Oct 2024 09:56:13 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] 2 commits: WIP: Stages for
 imported classes
Message-ID: <6719007d86009_1b1d88269954152e@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
0da5f7f6 by Matthew Pickering at 2024-10-23T13:17:39+01:00
WIP: Stages for imported classes

- - - - -
8e43c366 by Matthew Pickering at 2024-10-23T14:55:48+01:00
Update tests

- - - - -


30 changed files:

- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Unit/Module/Graph.hs
- ghc/GHCi/UI.hs
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00bc8de1e1eb200265825e449e9e614009100176...8e43c366192606df3f0d96ccd1984790b460e065

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00bc8de1e1eb200265825e449e9e614009100176...8e43c366192606df3f0d96ccd1984790b460e065
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 14:17:48 2024
From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits))
Date: Wed, 23 Oct 2024 10:17:48 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] 2
 commits: Link interface bytecode from package DBs if possible
Message-ID: <6719058c3b877_1b1d88347e0c3312@gitlab.mail>



Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC


Commits:
db081c41 by Torsten Schmits at 2024-10-23T16:17:31+02:00
Link interface bytecode from package DBs if possible

Part of #25090.

MR !13068

When splices are executed with `-fprefer-byte-code`, the loader will
compile Core bindings to bytecode if those are present in interfaces of
module dependencies.

So far, this only applied to local modules (i.e. home modules in make
mode and non-package deps in oneshot mode).

This patch extends support to interfaces loaded from a package DB.
In `getLinkDeps`, the dependencies chosen for recursion were restricted
to `dep_direct_mods`, which has been changed to include external
dependencies, stored in a new field named `dep_direct_pkg_mods`.
In order to unify treatment of the different link variants across
make/oneshot mode, the algorithm's intermediate results have been
abstracted into the data types `LinkDep` and `LinkModule`.

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -
e3f8a0a3 by Torsten Schmits at 2024-10-23T16:17:31+02:00
add new field to iface for package deps

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -


23 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- docs/users_guide/phases.rst
- + testsuite/tests/bytecode/T25090/Dep.hs
- + testsuite/tests/bytecode/T25090/DepApi.hs
- + testsuite/tests/bytecode/T25090/Local.hs
- testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/Num.hs
- + testsuite/tests/bytecode/T25090/Num.hs-boot
- + testsuite/tests/bytecode/T25090/PkgBytecode.hs
- + testsuite/tests/bytecode/T25090/PkgBytecode.stdout
- testsuite/tests/bytecode/T25090/all.T
- + testsuite/tests/bytecode/T25090/dep.conf
- + testsuite/tests/bytecode/T25090/prep.bash
- + testsuite/tests/bytecode/T25090/run.bash
- + testsuite/tests/bytecode/T25090/unit1
- + testsuite/tests/bytecode/T25090/unit2


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -843,6 +843,7 @@ data GeneralFlag
    | Opt_BuildDynamicToo
    | Opt_WriteIfSimplifiedCore
    | Opt_UseBytecodeRatherThanObjects
+   | Opt_PackageDbBytecode
 
    -- safe haskell flags
    | Opt_DistrustAllPackages


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2543,6 +2543,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "package-db-byte-code"             Opt_PackageDbBytecode,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.Directory
 import GHC.Driver.Env.KnotVars
 import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
 import GHC.Iface.Errors.Types
+import GHC.Runtime.Context (emptyInteractiveContext)
 import Data.Function ((&))
 
 {-
@@ -533,12 +534,18 @@ loadInterface doc_str mod from
               --
               -- See Note [Interface Files with Core Definitions]
               add_bytecode old
-                | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls)
+                | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls)
                 = extendModuleEnv old mod action
                 -- Don't add an entry if the iface doesn't have 'extra_decls'
                 -- so 'get_link_deps' knows that it should load object code.
                 | otherwise
                 = old
+                where
+                  -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is
+                  -- accessed when the processed module is from a different
+                  -- package.
+                  hydration_env =
+                    purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)}
 
         ; warnPprTrace bad_boot "loadInterface" (ppr mod) $
           updateEps_  $ \ eps ->


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Linker.Deps
   ( LinkDepsOpts (..)
@@ -22,12 +23,12 @@ import GHC.Runtime.Interpreter
 
 import GHC.Linker.Types
 
-import GHC.Types.SourceFile
 import GHC.Types.SrcLoc
 import GHC.Types.Unique.DSet
 import GHC.Types.Unique.DFM
 
 import GHC.Utils.Outputable
+import qualified GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Error
 
@@ -47,15 +48,19 @@ import GHC.Utils.Misc
 import GHC.Unit.Home
 import GHC.Data.Maybe
 
-import Control.Monad
 import Control.Applicative
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
 
+import Data.Foldable (traverse_)
 import qualified Data.Set as Set
 import qualified Data.Map as M
 import Data.List (isSuffixOf)
 
 import System.FilePath
 import System.Directory
+import GHC.Utils.Logger (Logger)
+import Control.Monad ((<$!>))
 
 data LinkDepsOpts = LinkDepsOpts
   { ldObjSuffix   :: !String                        -- ^ Suffix of .o files
@@ -64,19 +69,23 @@ data LinkDepsOpts = LinkDepsOpts
   , ldUnitEnv     :: !UnitEnv
   , ldPprOpts     :: !SDocContext                   -- ^ Rendering options for error messages
   , ldUseByteCode :: !Bool                          -- ^ Use bytecode rather than objects
+  , ldPkgByteCode :: !Bool                          -- ^ Use bytecode for external packages
   , ldMsgOpts     :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics
   , ldWays        :: !Ways                          -- ^ Enabled ways
-  , ldFinderCache :: !FinderCache
-  , ldFinderOpts  :: !FinderOpts
-  , ldLoadIface   :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface))
-  , ldLoadByteCode :: !(Module -> IO (Maybe Linkable))
+  , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)))
+  -- ^ When linking oneshot or package dependencies, we need interfaces and
+  -- locations to find object files and traverse dependencies.
+  , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable)))
+  -- ^ Consult the EPS about the given module, return an action that compiles
+  -- Core bindings to bytecode if it's available.
+  , ldLogger :: !Logger
   }
 
 data LinkDeps = LinkDeps
   { ldNeededLinkables :: [Linkable]
   , ldAllLinkables    :: [Linkable]
-  , ldUnits           :: [UnitId]
-  , ldNeededUnits     :: UniqDSet UnitId
+  , ldNeededUnits     :: [UnitId]
+  , ldAllUnits        :: UniqDSet UnitId
   }
 
 -- | Find all the packages and linkables that a set of modules depends on
@@ -100,9 +109,80 @@ getLinkDeps opts interp pls span mods = do
       -- then we need to find & link object files built the "normal" way.
       maybe_normal_osuf <- checkNonStdWay opts interp span
 
-      get_link_deps opts pls maybe_normal_osuf span mods
-
+      withTiming (ldLogger opts) (text "getLinkDeps" <+> brackets (ppr span)) (const ()) $
+        get_link_deps opts pls maybe_normal_osuf span mods
+
+-- | Determine which parts of a module and its dependencies should be linked
+-- when resolving external dependencies.
+data LinkExternalDetails =
+  -- | A module that should be linked, including its dependencies in the home
+  -- unit and external packages.
+  -- Can be a home module in oneshot mode or a package dependency module in
+  -- either mode.
+  LinkAllDeps
+  |
+  -- | A home module whose package dependencies should be linked, but not the
+  -- module itself or its home unit dependencies.
+  -- Can either be a direct target or the implementation module corresponding to
+  -- a target boot module, but only in make mode.
+  -- The 'ModIface' is taken from the 'HomeModInfo', avoiding another lookup in
+  -- 'external_deps'.
+  -- The importing module and its home unit dependencies are not processed by
+  -- 'external_deps', since the readily available 'HomeModInfo's can be linked
+  -- without further analysis.
+  LinkOnlyPackages !ModIface
+
+instance Outputable LinkExternalDetails where
+  ppr = \case
+    LinkAllDeps -> text "all"
+    LinkOnlyPackages _ -> text "only-packages"
+
+-- | A module that should be examined by 'external_deps' to decide how to link
+-- it and its dependencies.
+data LinkExternal =
+  LinkExternal {
+    le_details :: LinkExternalDetails,
+    le_module :: !Module
+  }
 
+instance Outputable LinkExternal where
+  ppr LinkExternal {..} = ppr le_module <> brackets (ppr le_details)
+
+-- | The decision about the linking method used for a given module.
+data LinkModule =
+  -- | In make mode, we can use 'HomeModInfo' without any further analysis.
+  LinkHomeModule !HomeModInfo
+  |
+  -- | A module that must be linked as native code, because bytecode is disabled
+  -- or unavailable.
+  LinkObjectModule !Module !ModLocation
+  |
+  -- | A module that has bytecode available.
+  -- The 'IO' that compiles the bytecode from Core bindings is obtained from the
+  -- EPS.
+  -- See Note [Interface Files with Core Definitions].
+  LinkByteCodeModule !Module !(IO Linkable)
+
+link_module :: LinkModule -> Module
+link_module = \case
+  LinkHomeModule hmi -> mi_module (hm_iface hmi)
+  LinkObjectModule mod _ -> mod
+  LinkByteCodeModule mod _ -> mod
+
+instance Outputable LinkModule where
+  ppr = \case
+    LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI")
+    LinkObjectModule mod _ -> ppr mod
+    LinkByteCodeModule mod _ -> ppr mod <+> brackets (text "BC")
+
+-- | Compute the linkables for the given module set's dependencies.
+--
+-- Home modules in make mode are treated separately in a preprocessing step,
+-- then all the remaining external deps are processed for both modes.
+-- If bytecode is available, transitive external deps are included, otherwise
+-- the module's library is linked and processing stops.
+--
+-- The results are split into sets of needed/loaded modules/packages.
 get_link_deps
   :: LinkDepsOpts
   -> LoaderState
@@ -111,46 +191,36 @@ get_link_deps
   -> [Module]
   -> IO LinkDeps
 get_link_deps opts pls maybe_normal_osuf span mods = do
-        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-        -- (omitting modules from the interactive package, which is already linked)
-      (mods_s, pkgs_s) <-
-          -- Why two code paths here? There is a significant amount of repeated work
-          -- performed calculating transitive dependencies
-          -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests)
-          if ldOneShotMode opts
-            then follow_deps (filterOut isInteractiveModule mods)
-                              emptyUniqDSet emptyUniqDSet;
-            else do
-              (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
-              return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-
-      let
-        -- 2.  Exclude ones already linked
-        --      Main reason: avoid findModule calls in get_linkable
-            (mods_needed, links_got) = partitionWith split_mods mods_s
-            pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls
-
-            split_mods mod =
-                let is_linked = lookupModuleEnv (objs_loaded pls) mod
-                                <|> lookupModuleEnv (bcos_loaded pls) mod
-                in case is_linked of
-                     Just linkable -> Right linkable
-                     Nothing -> Left mod
-
-        -- 3.  For each dependent module, find its linkable
-        --     This will either be in the HPT or (in the case of one-shot
-        --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
-
-      return $ LinkDeps
-        { ldNeededLinkables = lnks_needed
-        , ldAllLinkables    = links_got ++ lnks_needed
-        , ldUnits           = pkgs_needed
-        , ldNeededUnits     = pkgs_s
-        }
+  (link_deps_home, module_deps_external) <- separate_home_deps
+  link_deps_external <- external_deps opts module_deps_external
+  let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) =
+        classify_deps pls link_deps_home link_deps_external
+  ldNeededLinkables <- mapM module_linkable needed_modules
+  pure LinkDeps {
+    ldNeededLinkables,
+    ldAllLinkables = loaded_modules ++ ldNeededLinkables,
+    ldNeededUnits,
+    ldAllUnits
+  }
   where
     mod_graph = ldModuleGraph opts
     unit_env  = ldUnitEnv     opts
+    noninteractive = filterOut isInteractiveModule mods
+
+    -- Preprocess the dependencies in make mode to remove all home modules,
+    -- since the transitive dependency closure is already cached for those in
+    -- the HUG (see MultiLayerModulesTH_* tests for the performance impact).
+    --
+    -- Returns the remaining, external, dependencies on the right, which is the
+    -- entire set for oneshot mode.
+    separate_home_deps =
+      if ldOneShotMode opts
+      then pure ([], LinkExternal LinkAllDeps <$!> noninteractive)
+      else make_deps
+
+    make_deps = do
+      (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods
+      pure (mmods, init_ext ++ dep_ext)
 
     -- This code is used in `--make` mode to calculate the home package and unit dependencies
     -- for a set of modules.
@@ -160,9 +230,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     -- It is also a matter of correctness to use the module graph so that dependencies between home units
     -- is resolved correctly.
-    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+    make_deps_loop :: ([LinkExternal], Set.Set NodeKey) -> [ModNodeKeyWithUid] -> ([LinkExternal], Set.Set NodeKey)
     make_deps_loop found [] = found
-    make_deps_loop found@(found_units, found_mods) (nk:nexts)
+    make_deps_loop found@(external, found_mods) (nk:nexts)
       | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
       | otherwise =
         case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of
@@ -171,93 +241,46 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   -- See #936 and the ghci.prog007 test for why we have to continue traversing through
                   -- boot modules.
                   todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps]
-              in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
+              in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
             Nothing ->
-              let (ModNodeKeyWithUid _ uid) = nk
-              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+              let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk
+                  mod = Module (RealUnit (Definite uid)) mod_name
+              in make_deps_loop (LinkExternal LinkAllDeps mod : external, found_mods) nexts
 
     mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
-    (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods)
+    (init_ext, all_deps) = make_deps_loop ([], Set.empty) $ map mkNk noninteractive
 
     all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps]
 
     get_mod_info (ModNodeKeyWithUid gwib uid) =
       case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of
-        Just hmi ->
-          let iface = (hm_iface hmi)
-              mmod = case mi_hsc_src iface of
-                      HsBootFile -> link_boot_mod_error (mi_module iface)
-                      _          -> return $ Just (mi_module iface)
-
-          in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$>  mmod
+        Just hmi -> do
+          let iface = hm_iface hmi
+          pure (LinkExternal (LinkOnlyPackages iface) (mi_module iface), hmi)
         Nothing -> throwProgramError opts $
           text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
 
-
-       -- This code is used in one-shot mode to traverse downwards through the HPT
-       -- to find all link dependencies.
-       -- The ModIface contains the transitive closure of the module dependencies
-       -- within the current package, *except* for boot modules: if we encounter
-       -- a boot module, we have to find its real interface and discover the
-       -- dependencies of that.  Hence we need to traverse the dependency
-       -- tree recursively.  See bug #936, testcase ghci/prog007.
-    follow_deps :: [Module]             -- modules to follow
-                -> UniqDSet Module         -- accum. module dependencies
-                -> UniqDSet UnitId          -- accum. package dependencies
-                -> IO ([Module], UniqDSet UnitId) -- result
-    follow_deps []     acc_mods acc_pkgs
-        = return (uniqDSetToList acc_mods, acc_pkgs)
-    follow_deps (mod:mods) acc_mods acc_pkgs
-        = do
-          mb_iface <- ldLoadIface opts msg mod
-          iface <- case mb_iface of
-                    Failed err      -> throwProgramError opts $
-                      missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
-                    Succeeded iface -> return iface
-
-          when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
-
-          let
-            pkg = moduleUnit mod
-            deps  = mi_deps iface
-
-            pkg_deps = dep_direct_pkgs deps
-            (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $
-              \case
-                (_, GWIB m IsBoot)  -> Left m
-                (_, GWIB m NotBoot) -> Right m
-
-            mod_deps' = case ue_homeUnit unit_env of
-                          Nothing -> []
-                          Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps))
-            acc_mods'  = case ue_homeUnit unit_env of
-                          Nothing -> acc_mods
-                          Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps)
-            acc_pkgs'  = addListToUniqDSet acc_pkgs (Set.toList pkg_deps)
-
-          case ue_homeUnit unit_env of
-            Just home_unit | isHomeUnit home_unit pkg ->  follow_deps (mod_deps' ++ mods)
-                                                                      acc_mods' acc_pkgs'
-            _ ->  follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
-        where
-           msg = text "need to link module" <+> ppr mod <+>
-                  text "due to use of Template Haskell"
-
-
-
-    link_boot_mod_error :: Module -> IO a
-    link_boot_mod_error mod = throwProgramError opts $
-            text "module" <+> ppr mod <+>
-            text "cannot be linked; it is only available as a boot module"
-
     no_obj :: Outputable a => a -> IO b
     no_obj mod = dieWith opts span $
-                     text "cannot find object file for module " <>
+                     text "cannot find object file for module" <+>
                         quotes (ppr mod) $$
                      while_linking_expr
 
     while_linking_expr = text "while linking an interpreted expression"
 
+  -- Extract the 'Linkable's for unlinked modules from the intermediate
+  -- results.
+    module_linkable = \case
+      LinkHomeModule hmi ->
+        adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi))
+
+      LinkObjectModule mod loc -> do
+        findObjectLinkableMaybe mod loc >>= \case
+          Nothing  -> no_obj mod
+          Just lnk -> adjust_linkable lnk
+
+      LinkByteCodeModule _ load_bytecode ->
+        load_bytecode
 
     -- See Note [Using Byte Code rather than Object Code for Template Haskell]
     homeModLinkable :: HomeModInfo -> Maybe Linkable
@@ -266,57 +289,244 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
-        | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
-        = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
-        | otherwise
-        = do    -- It's not in the HPT because we are in one shot mode,
-                -- so use the Finder to get a ModLocation...
-             case ue_homeUnit unit_env of
-              Nothing -> no_obj mod
-              Just home_unit -> do
-                from_bc <- ldLoadByteCode opts mod
-                maybe (fallback_no_bytecode home_unit mod) pure from_bc
-        where
-
-            fallback_no_bytecode home_unit mod = do
-              let fc = ldFinderCache opts
-              let fopts = ldFinderOpts opts
-              mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod)
-              case mb_stuff of
-                Found loc _ -> do
-                  mb_lnk <- findObjectLinkableMaybe mod loc
-                  case mb_lnk of
-                    Nothing  -> no_obj mod
-                    Just lnk -> adjust_linkable lnk
-                _ -> no_obj (moduleName mod)
-
-            adjust_linkable lnk
-                | Just new_osuf <- maybe_normal_osuf = do
-                        new_parts <- mapM (adjust_part new_osuf)
-                                        (linkableParts lnk)
-                        return lnk{ linkableParts=new_parts }
-                | otherwise =
-                        return lnk
-
-            adjust_part new_osuf part = case part of
-              DotO file ModuleObject -> do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
-                ok <- doesFileExist new_file
-                if (not ok)
-                   then dieWith opts span $
-                          text "cannot find object file "
-                                <> quotes (text new_file) $$ while_linking_expr
-                   else return (DotO new_file ModuleObject)
-              DotO file ForeignObject -> pure (DotO file ForeignObject)
-              DotA fp    -> panic ("adjust_ul DotA " ++ show fp)
-              DotDLL fp  -> panic ("adjust_ul DotDLL " ++ show fp)
-              BCOs {}    -> pure part
-              LazyBCOs{} -> pure part
-              CoreBindings WholeCoreBindings {wcb_module} ->
-                pprPanic "Unhydrated core bindings" (ppr wcb_module)
+    adjust_linkable lnk
+        | Just new_osuf <- maybe_normal_osuf = do
+                new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf)
+                                (linkableParts lnk)
+                return lnk {linkableParts = new_uls}
+        | otherwise =
+                return lnk
+
+    adjust_part osuf new_osuf part = case part of
+      DotO file ModuleObject -> do
+        massert (osuf `isSuffixOf` file)
+        let file_base = fromJust (stripExtension osuf file)
+            new_file = file_base <.> new_osuf
+        ok <- doesFileExist new_file
+        if (not ok)
+            then dieWith opts span $
+                  text "cannot find object file"
+                        <+> quotes (text new_file) $$ while_linking_expr
+            else return (DotO new_file ModuleObject)
+      DotO file ForeignObject -> pure (DotO file ForeignObject)
+      DotA fp    -> panic ("adjust_part DotA " ++ show fp)
+      DotDLL fp  -> panic ("adjust_part DotDLL " ++ show fp)
+      BCOs {}    -> pure part
+      LazyBCOs{} -> pure part
+      CoreBindings WholeCoreBindings {wcb_module} ->
+        pprPanic "Unhydrated core bindings" (ppr wcb_module)
+
+data LinkDep =
+  LinkModules !(UniqDFM ModuleName LinkModule)
+  |
+  LinkLibrary !UnitId
+
+instance Outputable LinkDep where
+  ppr = \case
+    LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods)
+    LinkLibrary uid -> text "library:" <+> ppr uid
+
+data OneshotError =
+  NoInterface !MissingInterfaceError
+  |
+  LinkBootModule !Module
+
+-- | Compute the transitive dependency closure of the given modules.
+--
+-- Used for all oneshot mode dependencies and for external dependencies of home
+-- modules in make mode.
+external_deps ::
+  LinkDepsOpts ->
+  -- | Modules whose imports to follow
+  [LinkExternal] ->
+  IO [LinkDep]
+external_deps opts mods =
+  runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case
+    Right a -> pure (eltsUDFM a)
+    Left err -> throwProgramError opts (message err)
+  where
+    message = \case
+      NoInterface err ->
+        missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
+      LinkBootModule mod ->
+        link_boot_mod_error mod
+
+external_deps_loop ::
+  LinkDepsOpts ->
+  [LinkExternal] ->
+  UniqDFM UnitId LinkDep ->
+  ExceptT OneshotError IO (UniqDFM UnitId LinkDep)
+external_deps_loop _ [] acc =
+  pure acc
+external_deps_loop opts (job at LinkExternal {le_module = mod, ..} : mods) acc = do
+  (new_acc, new_mods, action) <-
+    if already_seen
+    then done
+    else process_module le_details
+  traverse_ debug_log action
+  external_deps_loop opts (new_mods ++ mods) new_acc
+  where
+    debug_log action =
+      liftIO $ debugTraceMsg (ldLogger opts) 3 $
+      text "TH dep" <+> ppr job <+>
+      brackets (sep (punctuate comma [
+        if is_home then text "home" else Outputable.empty,
+        text action
+      ]))
+
+    done = pure (acc, [], Nothing)
+
+    -- Decide how this module needs to be processed.
+    -- We only need an interface if we want to load bytecode or if we have to
+    -- link an object file (which happens for home unit modules, since those
+    -- have no libraries).
+    process_module = \case
+      LinkAllDeps | is_home || package_bc -> try_iface
+                  | otherwise -> add_library
+
+    -- @LinkOnlyPackages@ is used for make mode home modules, so all imports
+    -- that are not external are already processed otherwise.
+      LinkOnlyPackages iface -> with_deps acc iface False "only packages"
+
+    -- Check whether the current module was processed before.
+    -- Since the accumulator is keyed by unit ID, we have to perform two
+    -- lookups.
+    -- If another module from this module's unit has been determined to be
+    -- linked as a library previously, we skip this module, assuming that no
+    -- bytecode is available for the entire package.
+    already_seen
+      | Just (LinkModules mods) <- mod_dep
+      = elemUDFM mod_name mods
+      | Just (LinkLibrary _) <- mod_dep
+      = True
+      | otherwise
+      = False
+
+    -- Load the iface and attempt to get bytecode from Core bindings.
+    try_iface =
+      liftIO (ldLoadIface opts load_reason mod) >>= \case
+        Failed err -> throwE (NoInterface err)
+        Succeeded (iface, loc) -> do
+          mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface))
+          with_iface iface loc mb_load_bc
+
+    -- Decide how to link this module.
+    -- If bytecode or an object file is available, use those in that order.
+    -- Otherwise fall back to linking a library.
+    with_iface iface loc mb_load_bc
+      | IsBoot <- mi_boot iface
+      = throwE (LinkBootModule mod)
+
+      | ldUseByteCode opts
+      , is_home || package_bc
+      , Just load_bc <- mb_load_bc
+      = add_module iface (LinkByteCodeModule mod load_bc) "bytecode"
+
+      | is_home
+      = add_module iface (LinkObjectModule mod loc) "object"
+
+      | otherwise
+      = add_library
+
+    add_library =
+      pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library")
+
+    add_module iface lmod action =
+      with_deps with_mod iface True action
+      where
+        with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id
+
+    add_package_module lmod = \case
+      Just (LinkLibrary u) -> Just (LinkLibrary u)
+      Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod))
+      Nothing -> Just (LinkModules (unitUDFM mod_name lmod))
+
+    with_deps acc iface local action =
+      pure (addListToUDFM acc link, new_local ++ new_package, Just action)
+      where
+        !(!link, !new_package) = package_deps iface
+        new_local = if local then local_deps iface else []
+
+    local_deps iface =
+      [
+        LinkExternal LinkAllDeps (mkModule mod_unit m)
+        | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface))
+      ]
+
+    -- If bytecode linking of external dependencies is enabled, add them to the
+    -- jobs passed to the next iteration of 'external_deps_loop'.
+    -- Otherwise, link all package deps as libraries.
+    package_deps iface
+      | package_bc
+      = ([], [LinkExternal LinkAllDeps m | m <- Set.toList (dep_direct_pkg_mods (mi_deps iface))])
+      | otherwise
+      = ([(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))], [])
+
+    load_reason =
+      text "need to link module" <+> ppr mod <+>
+      text "due to use of Template Haskell"
+
+    package_bc = ldPkgByteCode opts
+
+    -- In multiple home unit mode, this only considers modules from the same
+    -- unit as the splice's module to be eligible for linking bytecode when
+    -- @-fpackage-db-byte-code@ is off.
+    -- For make mode, this is irrelevant, since any bytecode from the HUG is
+    -- obtained directly, not going through 'external_deps'.
+    is_home
+      | Just home <- ue_homeUnit (ldUnitEnv opts)
+      = homeUnitAsUnit home == mod_unit
+      | otherwise
+      = False
+
+    mod_dep = lookupUDFM acc mod_unit_id
+    mod_name = moduleName mod
+    mod_unit_id = moduleUnitId mod
+    mod_unit = moduleUnit mod
+
+link_boot_mod_error :: Module -> SDoc
+link_boot_mod_error mod =
+  text "module" <+> ppr mod <+>
+  text "cannot be linked; it is only available as a boot module"
+
+-- | Split link dependencies into the sets of modules and packages that have
+-- been linked previously and those that need to be linked now by checking for
+-- their presence in the 'LoaderState':
+--
+-- - For module dependencies, in the sets of loaded objects and BCOs
+--   ('objs_loaded' and 'bcos_loaded')
+-- - For package dependencies, in the set of loaded packages ('pkgs_loaded')
+classify_deps ::
+  LoaderState ->
+  [HomeModInfo] ->
+  [LinkDep] ->
+  ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId])
+classify_deps pls hmis deps =
+  (loaded_modules' ++ loaded_modules'', needed_modules' ++ needed_modules'', all_packages, needed_packages)
+  where
+    (loaded_modules', needed_modules') = partitionWith loaded_or_needed_home_module hmis
+    (loaded_modules'', needed_modules'') =
+      partitionWith loaded_or_needed_module (concatMap eltsUDFM modules)
+
+    needed_packages =
+      eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls)
+
+    all_packages = mkUniqDSet packages
+
+    (modules, packages) = flip partitionWith deps $ \case
+      LinkModules mods -> Left mods
+      LinkLibrary lib -> Right lib
+
+    loaded_or_needed_home_module lm =
+      maybe (Right (LinkHomeModule lm)) Left (loaded_module (mi_module (hm_iface lm)))
+
+    loaded_or_needed_module lm =
+      maybe (Right lm) Left (loaded_module (link_module lm))
+
+    loaded_module mod =
+      lookupModuleEnv (objs_loaded pls) mod
+      <|>
+      lookupModuleEnv (bcos_loaded pls) mod
 
 {-
 Note [Using Byte Code rather than Object Code for Template Haskell]


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -77,11 +77,13 @@ import GHC.Utils.TmpFs
 
 import GHC.Unit.Env
 import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
+import GHC.Unit.Finder
 import GHC.Unit.Module
 import GHC.Unit.State as Packages
 
 import qualified GHC.Data.ShortText as ST
 import GHC.Data.FastString
+import qualified GHC.Data.Maybe as Maybe
 
 import GHC.Linker.Deps
 import GHC.Linker.MacOS
@@ -94,6 +96,7 @@ import Control.Monad
 import qualified Data.Set as Set
 import Data.Char (isSpace)
 import qualified Data.Foldable as Foldable
+import Data.Functor ((<&>))
 import Data.IORef
 import Data.List (intercalate, isPrefixOf, nub, partition)
 import Data.Maybe
@@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do
    -- Find what packages and linkables are required
    deps <- getLinkDeps opts interp pls span needed_mods
 
-   let this_pkgs_needed = ldNeededUnits deps
+   let this_pkgs_needed = ldAllUnits deps
 
    -- Link the packages and modules required
-   pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
+   pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls
    (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
    let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
        all_pkgs_loaded = pkgs_loaded pls2
@@ -643,21 +646,40 @@ initLinkDepsOpts hsc_env = opts
             , ldModuleGraph = hsc_mod_graph hsc_env
             , ldUnitEnv     = hsc_unit_env hsc_env
             , ldPprOpts     = initSDocContext dflags defaultUserStyle
-            , ldFinderCache = hsc_FC hsc_env
-            , ldFinderOpts  = initFinderOpts dflags
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
+            , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
             , ldLoadIface
             , ldLoadByteCode
+            , ldLogger = hsc_logger hsc_env
             }
     dflags = hsc_dflags hsc_env
-    ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env
-                          $ loadInterface msg mod (ImportByUser NotBoot)
+
+    ldLoadIface msg mod =
+      initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case
+        Maybe.Failed err -> pure (Maybe.Failed err)
+        Maybe.Succeeded iface ->
+          find_location mod <&> \case
+            InstalledFound loc _ -> Maybe.Succeeded (iface, loc)
+            err -> Maybe.Failed $
+                   cannotFindInterface unit_state home_unit
+                   (targetProfile dflags) (moduleName mod) err
+
+    find_location mod =
+      liftIO $
+      findExactModule (hsc_FC hsc_env) (initFinderOpts dflags)
+      other_fopts unit_state home_unit (toUnitId <$> mod)
+
+    other_fopts = initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env
+
+    unit_state = hsc_units hsc_env
+
+    home_unit = ue_homeUnit (hsc_unit_env hsc_env)
 
     ldLoadByteCode mod = do
       EPS {eps_iface_bytecode} <- hscEPS hsc_env
-      sequence (lookupModuleEnv eps_iface_bytecode mod)
+      pure (lookupModuleEnv eps_iface_bytecode mod)
 
 
 


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -753,7 +753,7 @@ mkStubPaths fopts mod location = do
     src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
 
 -- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
+-- findObjectLinkable isn't related to the other stuff in here,
 -- but there's no other obvious place for it
 
 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)


=====================================
compiler/GHC/Unit/Module/Deps.hs
=====================================
@@ -4,6 +4,7 @@ module GHC.Unit.Module.Deps
    , mkDependencies
    , noDependencies
    , dep_direct_mods
+   , dep_direct_pkg_mods
    , dep_direct_pkgs
    , dep_sig_mods
    , dep_trusted_pkgs
@@ -35,6 +36,7 @@ import GHC.Utils.Fingerprint
 import GHC.Utils.Binary
 import GHC.Utils.Outputable
 
+import qualified Data.Map.Strict as Map
 import Data.List (sortBy, sort, partition)
 import Data.Set (Set)
 import qualified Data.Set as Set
@@ -99,6 +101,9 @@ data Dependencies = Deps
       -- does NOT include us, unlike 'imp_finsts'. See Note
       -- [The type family instance consistency story].
 
+   -- TODO strict?
+   , dep_direct_pkg_mods :: Set Module
+
    }
    deriving( Eq )
         -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
@@ -145,6 +150,8 @@ mkDependencies home_unit mod imports plugin_mods =
 
       sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports
 
+      dep_direct_pkg_mods = Set.filter ((homeUnitAsUnit home_unit /=) . moduleUnit) (Map.keysSet (imp_mods imports))
+
   in Deps { dep_direct_mods  = direct_mods
           , dep_direct_pkgs  = direct_pkgs
           , dep_plugin_pkgs  = plugin_units
@@ -155,6 +162,7 @@ mkDependencies home_unit mod imports plugin_mods =
           , dep_finsts       = sortBy stableModuleCmp (imp_finsts imports)
             -- sort to get into canonical order
             -- NB. remember to use lexicographic ordering
+          , dep_direct_pkg_mods
           }
 
 -- | Update module dependencies containing orphans (used by Backpack)
@@ -179,6 +187,7 @@ instance Binary Dependencies where
                       put_ bh (dep_boot_mods deps)
                       put_ bh (dep_orphs deps)
                       put_ bh (dep_finsts deps)
+                      put_ bh (dep_direct_pkg_mods deps)
 
     get bh = do dms <- get bh
                 dps <- get bh
@@ -188,14 +197,16 @@ instance Binary Dependencies where
                 sms <- get bh
                 os <- get bh
                 fis <- get bh
+                dep_direct_pkg_mods <- get bh
                 return (Deps { dep_direct_mods = dms
                              , dep_direct_pkgs = dps
                              , dep_plugin_pkgs = plugin_pkgs
                              , dep_sig_mods = hsigms
                              , dep_boot_mods = sms
                              , dep_trusted_pkgs = tps
-                             , dep_orphs = os,
-                               dep_finsts = fis })
+                             , dep_orphs = os
+                             , dep_finsts = fis
+                             , dep_direct_pkg_mods })
 
 noDependencies :: Dependencies
 noDependencies = Deps
@@ -207,6 +218,7 @@ noDependencies = Deps
   , dep_trusted_pkgs = Set.empty
   , dep_orphs        = []
   , dep_finsts       = []
+  , dep_direct_pkg_mods = Set.empty
   }
 
 -- | Pretty-print unit dependencies


=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed
 build artifacts, which can be objects or bytecode, depending on the build
 settings.
 
-1. In make mode, all eligible modules are part of the dependency graph.
+1. In make mode, all eligible home modules are part of the dependency graph.
    Their interfaces are loaded unconditionally and in dependency order by the
    compilation manager, and each module's bytecode is prepared before its
    dependents are compiled, in one of two ways:
@@ -88,9 +88,10 @@ settings.
 2. In oneshot mode, which compiles individual modules without a shared home unit
    graph, a previously compiled module is not reprocessed as described for make
    mode above.
-   When 'get_link_deps' encounters a dependency on a local module, it requests
-   its bytecode from the External Package State, who loads the interface
-   on-demand.
+   'get_link_deps' requests the bytecode of dependencies from the External
+   Package State, who loads the interface on-demand.
+   This works for modules in local directories (via @-i@ and @-hidir@) as well
+   as those exposed from a package DB.
 
    Since the EPS stores interfaces for all package dependencies in addition to
    local modules in oneshot mode, it has a substantial memory footprint.
@@ -109,6 +110,18 @@ settings.
    storing the intermediate representation as rehydrated Core bindings, since
    the latter have a significantly greater memory footprint.
 
+3. In both of the above modes, whenever a module from an external package
+   (loaded from a package DB) is encountered, the workflow is the same as for
+   oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object
+   code is loaded.
+   Interfaces for external modules are stored together with local oneshot mode
+   modules, so almost no special treatment is necessary, with the exception of:
+   - When external package modules are compiled, the @InteractiveContext@ in
+     @HscEnv@ is accessed, which is not available due to its impact on retention
+     of outdated build products.
+     This is solved by writing an empty @InteractiveContext@ to the env used for
+     compilation.
+
 Note [Size of Interface Files with Core Definitions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op.
 Otherwise, the stub objects from the interface are compiled to objects in
 'generateByteCode' and added to the 'HomeModLinkable' as well.
 
-Case 3 is not implemented yet (!13042).
+In case 3, Core bindings are loaded from the EPS, where stubs only exist in
+their serialized form in the interface, so they must be regenerated like in case
+2.
 
 Problem 3:
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -826,6 +826,17 @@ Options affecting code generation
     will generate byte-code rather than object code.
 
 
+.. ghc-flag:: -fpackage-db-byte-code
+    :shortdesc: Use byte-code from package DB dependencies
+    :type: dynamic
+    :category: codegen
+
+    GHC normally only considers local modules to be eligible for loading
+    bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`.
+    When this flag is specified additionally, bytecode will be loaded from
+    interfaces for all external package dependencies that provide it.
+
+
 .. _options-linker:
 
 Options affecting linking


=====================================
testsuite/tests/bytecode/T25090/Dep.hs
=====================================
@@ -0,0 +1,15 @@
+module Dep where
+
+data A = A Int
+
+used :: Int
+used = 9681
+
+dep :: A
+dep = A used
+
+unused1 :: A
+unused1 = A 1
+
+unused2 :: A
+unused2 = unused1


=====================================
testsuite/tests/bytecode/T25090/DepApi.hs
=====================================
@@ -0,0 +1,7 @@
+module DepApi (A (A), dep) where
+
+import Dep (A (A))
+import qualified Dep
+
+dep :: A
+dep = Dep.dep


=====================================
testsuite/tests/bytecode/T25090/Local.hs
=====================================
@@ -0,0 +1,15 @@
+{-# language PackageImports #-}
+
+module Local where
+
+import GHC.Prim
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+-- just to be sure that the file isn't accidentally picked up locally
+import "dep" DepApi (dep, A (A))
+import {-# source #-} Num (num)
+
+splc :: ExpQ
+splc = lift @_ @Int (num + d)
+  where
+    A d = dep


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -19,3 +19,35 @@ T25090a:
 T25090b:
 	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe
+
+DB := -package-db db -package dep
+BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0
+BC := -fprefer-byte-code -fbyte-code-and-object-code
+ARGS := $(BASIC) $(BC)
+
+T25090_pkg:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_empty:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared-empty"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_nolib:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "none"
+	./run.bash "$(TEST_HC)" "$(ARGS)"
+
+T25090_pkg_obj_code:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code"
+
+T25090_pkg_multi_unit:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	mkdir -p unit2-src/
+	mv Local.hs Num.hs Num.hs-boot unit2-src/
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -fpackage-db-byte-code -dynamic -unit @unit1 -unit @unit2
+	./PkgBytecode
+
+T25090_pkg_archive:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "archive"
+	./run.bash "$(TEST_HC)" "$(ARGS)"


=====================================
testsuite/tests/bytecode/T25090/Num.hs
=====================================
@@ -0,0 +1,4 @@
+module Num where
+
+num :: Int
+num = 48332


=====================================
testsuite/tests/bytecode/T25090/Num.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module Num where
+
+num :: Int


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.hs
=====================================
@@ -0,0 +1,12 @@
+{-# language TemplateHaskell #-}
+
+module Main where
+
+import GHC.Prim
+import Local (splc)
+
+a :: Int
+a = $(splc)
+
+main :: IO ()
+main = putStrLn (show a)


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.stdout
=====================================
@@ -0,0 +1 @@
+58013


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -16,3 +16,33 @@ def test_T25090(name):
 
 test_T25090('T25090a')
 test_T25090('T25090b')
+
+def test_pkg(name, files = []):
+    test(
+        name,
+        [
+            extra_files([
+                'PkgBytecode.hs',
+                'Local.hs',
+                'Dep.hs',
+                'DepApi.hs',
+                'Num.hs',
+                'Num.hs-boot',
+                'dep.conf',
+                'prep.bash',
+                'run.bash',
+            ] + files),
+            use_specs({'stdout': 'PkgBytecode.stdout'}),
+        ],
+        makefile_test,
+        [],
+    )
+
+test_pkg('T25090_pkg')
+test_pkg('T25090_pkg_empty')
+test_pkg('T25090_pkg_nolib')
+test_pkg('T25090_pkg_obj_code')
+test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2'])
+# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a
+# comment says "search for .so libraries _first_" (rather than "only").
+# test_pkg('T25090_pkg_archive')


=====================================
testsuite/tests/bytecode/T25090/dep.conf
=====================================
@@ -0,0 +1,8 @@
+name: dep
+version: 1.0
+id: dep-1.0
+key: dep-1.0
+exposed: True
+exposed-modules: DepApi
+import-dirs: ${pkgroot}/dep
+library-dirs: ${pkgroot}/dep


=====================================
testsuite/tests/bytecode/T25090/prep.bash
=====================================
@@ -0,0 +1,59 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+ghc_pkg_cmd="$3"
+so_ext="$4"
+library="$5"
+
+base="$PWD"
+db="$base/db"
+dep="$base/dep"
+conf_dep="${dep}/dep.conf"
+
+mkdir -p "$dep" "$db"
+mv Dep.hs DepApi.hs "$dep/"
+cp dep.conf "$dep/"
+
+ghc_pkg()
+{
+  eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@"
+}
+
+ghc()
+{
+  eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@"
+}
+
+version=$(ghc "--numeric-version")
+
+ghc_pkg recache
+
+ghc "-c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+ghc "-dynamic -c -osuf dyn_o -hisuf dyn_hi ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+
+if [[ "$library" == 'shared' ]]
+then
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'shared-empty' ]]
+then
+  echo 'module Dummy where' > Dummy.hs
+  ghc "-dynamic-too -c Dummy.hs"
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} Dummy.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'archive' ]]
+then
+  $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'none' ]]
+then
+  :
+else
+  echo "Invalid argument for 'library': $library"
+  exit 1
+fi
+
+ghc_pkg -v0 register "${conf_dep at Q}"


=====================================
testsuite/tests/bytecode/T25090/run.bash
=====================================
@@ -0,0 +1,16 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+
+ghc()
+{
+  eval "${ghc_cmd at Q} $ghc_opts $@"
+}
+
+ghc -c Num.hs-boot Num.hs Local.hs
+ghc -fpackage-db-byte-code -c PkgBytecode.hs
+ghc PkgBytecode.o -o PkgBytecode
+./PkgBytecode


=====================================
testsuite/tests/bytecode/T25090/unit1
=====================================
@@ -0,0 +1 @@
+-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2


=====================================
testsuite/tests/bytecode/T25090/unit2
=====================================
@@ -0,0 +1 @@
+-i -i./unit2-src Local Num -this-unit-id unit2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38f1ca4f4a6178a76577b68122a5b3653a6a05fc...e3f8a0a3682e4937d28fae627f335fb04fe48b9f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38f1ca4f4a6178a76577b68122a5b3653a6a05fc...e3f8a0a3682e4937d28fae627f335fb04fe48b9f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 15:52:46 2024
From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani))
Date: Wed, 23 Oct 2024 11:52:46 -0400
Subject: [Git][ghc/ghc][wip/spj-apporv-Oct24] fix bugs, let stmt pop in the
 right place
Message-ID: <67191bce4da61_1b1d888de91083ad@gitlab.mail>



Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC


Commits:
43b80d2f by Apoorv Ingle at 2024-10-23T10:52:06-05:00
fix bugs, let stmt pop in the right place

- - - - -


1 changed file:

- compiler/GHC/Tc/Gen/Do.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/Do.hs
=====================================
@@ -95,8 +95,8 @@ expand_do_stmts doFlavour (stmt@(L _loc (LetStmt _ bs)) : lstmts) =
 --    ------------------------------------------------
 --       let x = e ; stmts ~~> let x = e in stmts'
   do expand_stmts <- expand_do_stmts doFlavour lstmts
-     let expansion = genPopErrCtxtExpr (wrapGenSpan $ genHsLet bs expand_stmts)
-     return $ mkExpandedStmtAt stmt doFlavour (unLoc expansion)
+     let expansion = genHsLet bs (genPopErrCtxtExpr expand_stmts)
+     return $ mkExpandedStmtAt stmt doFlavour expansion
 
 expand_do_stmts doFlavour (stmt@(L _loc (BindStmt xbsrn pat e)): lstmts)
   | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn
@@ -107,8 +107,8 @@ expand_do_stmts doFlavour (stmt@(L _loc (BindStmt xbsrn pat e)): lstmts)
 --                                   _   -> fail "Pattern match failure .."
 --    -------------------------------------------------------
 --       pat <- e ; stmts   ~~> (>>=) e f
-  = do expand_stmts <- genPopErrCtxtExpr <$> expand_do_stmts doFlavour lstmts
-       failable_expr <- mk_failable_expr doFlavour pat expand_stmts fail_op
+  = do expand_stmts <- expand_do_stmts doFlavour lstmts
+       failable_expr <- mk_failable_expr doFlavour pat (genPopErrCtxtExpr expand_stmts) fail_op
        let expansion = genHsExpApps bind_op  -- (>>=)
                        [ e
                        , failable_expr ]
@@ -254,10 +254,7 @@ mk_failable_expr doFlav lpat@(L loc pat) expr@(L _exprloc _) fail_op =
                                         ])
      ; if irrf_pat -- don't wrap with fail block if
                    -- the pattern is irrefutable
-       then case pat of
-              (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr
-              _ -> return $ genHsLamDoExp doFlav [lpat] expr
-
+       then return $ genHsLamDoExp doFlav [lpat] expr
        else L loc <$> mk_fail_block doFlav lpat expr fail_op
      }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/43b80d2f1bd3131b00a4c6813a8d5c6d7f52cbee

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 18:18:54 2024
From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits))
Date: Wed, 23 Oct 2024 14:18:54 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] 2
 commits: Link interface bytecode from package DBs if possible
Message-ID: <67193e0eaf062_2f906858e15c311b@gitlab.mail>



Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC


Commits:
60413ac9 by Torsten Schmits at 2024-10-23T20:18:36+02:00
Link interface bytecode from package DBs if possible

Part of #25090.

MR !13068

When splices are executed with `-fprefer-byte-code`, the loader will
compile Core bindings to bytecode if those are present in interfaces of
module dependencies.

So far, this only applied to local modules (i.e. home modules in make
mode and non-package deps in oneshot mode).

This patch extends support to interfaces loaded from a package DB.
In `getLinkDeps`, the dependencies chosen for recursion were restricted
to `dep_direct_mods`, which has been changed to include external
dependencies, stored in a new field named `dep_direct_pkg_mods`.
In order to unify treatment of the different link variants across
make/oneshot mode, the algorithm's intermediate results have been
abstracted into the data types `LinkDep` and `LinkModule`.

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -
ca0cef6d by Torsten Schmits at 2024-10-23T20:18:36+02:00
add new field to iface for package deps

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -


23 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- docs/users_guide/phases.rst
- + testsuite/tests/bytecode/T25090/Dep.hs
- + testsuite/tests/bytecode/T25090/DepApi.hs
- + testsuite/tests/bytecode/T25090/Local.hs
- testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/Num.hs
- + testsuite/tests/bytecode/T25090/Num.hs-boot
- + testsuite/tests/bytecode/T25090/PkgBytecode.hs
- + testsuite/tests/bytecode/T25090/PkgBytecode.stdout
- testsuite/tests/bytecode/T25090/all.T
- + testsuite/tests/bytecode/T25090/dep.conf
- + testsuite/tests/bytecode/T25090/prep.bash
- + testsuite/tests/bytecode/T25090/run.bash
- + testsuite/tests/bytecode/T25090/unit1
- + testsuite/tests/bytecode/T25090/unit2


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -843,6 +843,7 @@ data GeneralFlag
    | Opt_BuildDynamicToo
    | Opt_WriteIfSimplifiedCore
    | Opt_UseBytecodeRatherThanObjects
+   | Opt_PackageDbBytecode
 
    -- safe haskell flags
    | Opt_DistrustAllPackages


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2543,6 +2543,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "package-db-byte-code"             Opt_PackageDbBytecode,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.Directory
 import GHC.Driver.Env.KnotVars
 import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
 import GHC.Iface.Errors.Types
+import GHC.Runtime.Context (emptyInteractiveContext)
 import Data.Function ((&))
 
 {-
@@ -533,12 +534,18 @@ loadInterface doc_str mod from
               --
               -- See Note [Interface Files with Core Definitions]
               add_bytecode old
-                | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls)
+                | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls)
                 = extendModuleEnv old mod action
                 -- Don't add an entry if the iface doesn't have 'extra_decls'
                 -- so 'get_link_deps' knows that it should load object code.
                 | otherwise
                 = old
+                where
+                  -- @dontLeakTheHUG@ purges @InteractiveContext@, but it is
+                  -- accessed when the processed module is from a different
+                  -- package.
+                  hydration_env =
+                    purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)}
 
         ; warnPprTrace bad_boot "loadInterface" (ppr mod) $
           updateEps_  $ \ eps ->


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Linker.Deps
   ( LinkDepsOpts (..)
@@ -22,12 +23,12 @@ import GHC.Runtime.Interpreter
 
 import GHC.Linker.Types
 
-import GHC.Types.SourceFile
 import GHC.Types.SrcLoc
 import GHC.Types.Unique.DSet
 import GHC.Types.Unique.DFM
 
 import GHC.Utils.Outputable
+import qualified GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Error
 
@@ -47,15 +48,19 @@ import GHC.Utils.Misc
 import GHC.Unit.Home
 import GHC.Data.Maybe
 
-import Control.Monad
 import Control.Applicative
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
 
+import Data.Foldable (traverse_)
 import qualified Data.Set as Set
 import qualified Data.Map as M
 import Data.List (isSuffixOf)
 
 import System.FilePath
 import System.Directory
+import GHC.Utils.Logger (Logger)
+import Control.Monad ((<$!>))
 
 data LinkDepsOpts = LinkDepsOpts
   { ldObjSuffix   :: !String                        -- ^ Suffix of .o files
@@ -64,19 +69,23 @@ data LinkDepsOpts = LinkDepsOpts
   , ldUnitEnv     :: !UnitEnv
   , ldPprOpts     :: !SDocContext                   -- ^ Rendering options for error messages
   , ldUseByteCode :: !Bool                          -- ^ Use bytecode rather than objects
+  , ldPkgByteCode :: !Bool                          -- ^ Use bytecode for external packages
   , ldMsgOpts     :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics
   , ldWays        :: !Ways                          -- ^ Enabled ways
-  , ldFinderCache :: !FinderCache
-  , ldFinderOpts  :: !FinderOpts
-  , ldLoadIface   :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface))
-  , ldLoadByteCode :: !(Module -> IO (Maybe Linkable))
+  , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)))
+  -- ^ When linking oneshot or package dependencies, we need interfaces and
+  -- locations to find object files and traverse dependencies.
+  , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable)))
+  -- ^ Consult the EPS about the given module, return an action that compiles
+  -- Core bindings to bytecode if it's available.
+  , ldLogger :: !Logger
   }
 
 data LinkDeps = LinkDeps
   { ldNeededLinkables :: [Linkable]
   , ldAllLinkables    :: [Linkable]
-  , ldUnits           :: [UnitId]
-  , ldNeededUnits     :: UniqDSet UnitId
+  , ldNeededUnits     :: [UnitId]
+  , ldAllUnits        :: UniqDSet UnitId
   }
 
 -- | Find all the packages and linkables that a set of modules depends on
@@ -100,9 +109,80 @@ getLinkDeps opts interp pls span mods = do
       -- then we need to find & link object files built the "normal" way.
       maybe_normal_osuf <- checkNonStdWay opts interp span
 
-      get_link_deps opts pls maybe_normal_osuf span mods
-
+      withTiming (ldLogger opts) (text "getLinkDeps" <+> brackets (ppr span)) (const ()) $
+        get_link_deps opts pls maybe_normal_osuf span mods
+
+-- | Determine which parts of a module and its dependencies should be linked
+-- when resolving external dependencies.
+data LinkExternalDetails =
+  -- | A module that should be linked, including its dependencies in the home
+  -- unit and external packages.
+  -- Can be a home module in oneshot mode or a package dependency module in
+  -- either mode.
+  LinkAllDeps
+  |
+  -- | A home module whose package dependencies should be linked, but not the
+  -- module itself or its home unit dependencies.
+  -- Can either be a direct target or the implementation module corresponding to
+  -- a target boot module, but only in make mode.
+  -- The 'ModIface' is taken from the 'HomeModInfo', avoiding another lookup in
+  -- 'external_deps'.
+  -- The importing module and its home unit dependencies are not processed by
+  -- 'external_deps', since the readily available 'HomeModInfo's can be linked
+  -- without further analysis.
+  LinkOnlyPackages !ModIface
+
+instance Outputable LinkExternalDetails where
+  ppr = \case
+    LinkAllDeps -> text "all"
+    LinkOnlyPackages _ -> text "only-packages"
+
+-- | A module that should be examined by 'external_deps' to decide how to link
+-- it and its dependencies.
+data LinkExternal =
+  LinkExternal {
+    le_details :: LinkExternalDetails,
+    le_module :: !Module
+  }
 
+instance Outputable LinkExternal where
+  ppr LinkExternal {..} = ppr le_module <> brackets (ppr le_details)
+
+-- | The decision about the linking method used for a given module.
+data LinkModule =
+  -- | In make mode, we can use 'HomeModInfo' without any further analysis.
+  LinkHomeModule !HomeModInfo
+  |
+  -- | A module that must be linked as native code, because bytecode is disabled
+  -- or unavailable.
+  LinkObjectModule !Module !ModLocation
+  |
+  -- | A module that has bytecode available.
+  -- The 'IO' that compiles the bytecode from Core bindings is obtained from the
+  -- EPS.
+  -- See Note [Interface Files with Core Definitions].
+  LinkByteCodeModule !Module !(IO Linkable)
+
+link_module :: LinkModule -> Module
+link_module = \case
+  LinkHomeModule hmi -> mi_module (hm_iface hmi)
+  LinkObjectModule mod _ -> mod
+  LinkByteCodeModule mod _ -> mod
+
+instance Outputable LinkModule where
+  ppr = \case
+    LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI")
+    LinkObjectModule mod _ -> ppr mod
+    LinkByteCodeModule mod _ -> ppr mod <+> brackets (text "BC")
+
+-- | Compute the linkables for the given module set's dependencies.
+--
+-- Home modules in make mode are treated separately in a preprocessing step,
+-- then all the remaining external deps are processed for both modes.
+-- If bytecode is available, transitive external deps are included, otherwise
+-- the module's library is linked and processing stops.
+--
+-- The results are split into sets of needed/loaded modules/packages.
 get_link_deps
   :: LinkDepsOpts
   -> LoaderState
@@ -111,46 +191,36 @@ get_link_deps
   -> [Module]
   -> IO LinkDeps
 get_link_deps opts pls maybe_normal_osuf span mods = do
-        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-        -- (omitting modules from the interactive package, which is already linked)
-      (mods_s, pkgs_s) <-
-          -- Why two code paths here? There is a significant amount of repeated work
-          -- performed calculating transitive dependencies
-          -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests)
-          if ldOneShotMode opts
-            then follow_deps (filterOut isInteractiveModule mods)
-                              emptyUniqDSet emptyUniqDSet;
-            else do
-              (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
-              return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-
-      let
-        -- 2.  Exclude ones already linked
-        --      Main reason: avoid findModule calls in get_linkable
-            (mods_needed, links_got) = partitionWith split_mods mods_s
-            pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls
-
-            split_mods mod =
-                let is_linked = lookupModuleEnv (objs_loaded pls) mod
-                                <|> lookupModuleEnv (bcos_loaded pls) mod
-                in case is_linked of
-                     Just linkable -> Right linkable
-                     Nothing -> Left mod
-
-        -- 3.  For each dependent module, find its linkable
-        --     This will either be in the HPT or (in the case of one-shot
-        --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
-
-      return $ LinkDeps
-        { ldNeededLinkables = lnks_needed
-        , ldAllLinkables    = links_got ++ lnks_needed
-        , ldUnits           = pkgs_needed
-        , ldNeededUnits     = pkgs_s
-        }
+  (link_deps_home, module_deps_external) <- separate_home_deps
+  link_deps_external <- external_deps opts module_deps_external
+  let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) =
+        classify_deps pls link_deps_home link_deps_external
+  ldNeededLinkables <- mapM module_linkable needed_modules
+  pure LinkDeps {
+    ldNeededLinkables,
+    ldAllLinkables = loaded_modules ++ ldNeededLinkables,
+    ldNeededUnits,
+    ldAllUnits
+  }
   where
     mod_graph = ldModuleGraph opts
     unit_env  = ldUnitEnv     opts
+    noninteractive = filterOut isInteractiveModule mods
+
+    -- Preprocess the dependencies in make mode to remove all home modules,
+    -- since the transitive dependency closure is already cached for those in
+    -- the HUG (see MultiLayerModulesTH_* tests for the performance impact).
+    --
+    -- Returns the remaining, external, dependencies on the right, which is the
+    -- entire set for oneshot mode.
+    separate_home_deps =
+      if ldOneShotMode opts
+      then pure ([], LinkExternal LinkAllDeps <$!> noninteractive)
+      else make_deps
+
+    make_deps = do
+      (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods
+      pure (mmods, init_ext ++ dep_ext)
 
     -- This code is used in `--make` mode to calculate the home package and unit dependencies
     -- for a set of modules.
@@ -160,9 +230,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     -- It is also a matter of correctness to use the module graph so that dependencies between home units
     -- is resolved correctly.
-    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+    make_deps_loop :: ([LinkExternal], Set.Set NodeKey) -> [ModNodeKeyWithUid] -> ([LinkExternal], Set.Set NodeKey)
     make_deps_loop found [] = found
-    make_deps_loop found@(found_units, found_mods) (nk:nexts)
+    make_deps_loop found@(external, found_mods) (nk:nexts)
       | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
       | otherwise =
         case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of
@@ -171,93 +241,46 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   -- See #936 and the ghci.prog007 test for why we have to continue traversing through
                   -- boot modules.
                   todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps]
-              in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
+              in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
             Nothing ->
-              let (ModNodeKeyWithUid _ uid) = nk
-              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+              let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk
+                  mod = Module (RealUnit (Definite uid)) mod_name
+              in make_deps_loop (LinkExternal LinkAllDeps mod : external, found_mods) nexts
 
     mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
-    (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods)
+    (init_ext, all_deps) = make_deps_loop ([], Set.empty) $ map mkNk noninteractive
 
     all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps]
 
     get_mod_info (ModNodeKeyWithUid gwib uid) =
       case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of
-        Just hmi ->
-          let iface = (hm_iface hmi)
-              mmod = case mi_hsc_src iface of
-                      HsBootFile -> link_boot_mod_error (mi_module iface)
-                      _          -> return $ Just (mi_module iface)
-
-          in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$>  mmod
+        Just hmi -> do
+          let iface = hm_iface hmi
+          pure (LinkExternal (LinkOnlyPackages iface) (mi_module iface), hmi)
         Nothing -> throwProgramError opts $
           text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
 
-
-       -- This code is used in one-shot mode to traverse downwards through the HPT
-       -- to find all link dependencies.
-       -- The ModIface contains the transitive closure of the module dependencies
-       -- within the current package, *except* for boot modules: if we encounter
-       -- a boot module, we have to find its real interface and discover the
-       -- dependencies of that.  Hence we need to traverse the dependency
-       -- tree recursively.  See bug #936, testcase ghci/prog007.
-    follow_deps :: [Module]             -- modules to follow
-                -> UniqDSet Module         -- accum. module dependencies
-                -> UniqDSet UnitId          -- accum. package dependencies
-                -> IO ([Module], UniqDSet UnitId) -- result
-    follow_deps []     acc_mods acc_pkgs
-        = return (uniqDSetToList acc_mods, acc_pkgs)
-    follow_deps (mod:mods) acc_mods acc_pkgs
-        = do
-          mb_iface <- ldLoadIface opts msg mod
-          iface <- case mb_iface of
-                    Failed err      -> throwProgramError opts $
-                      missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
-                    Succeeded iface -> return iface
-
-          when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
-
-          let
-            pkg = moduleUnit mod
-            deps  = mi_deps iface
-
-            pkg_deps = dep_direct_pkgs deps
-            (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $
-              \case
-                (_, GWIB m IsBoot)  -> Left m
-                (_, GWIB m NotBoot) -> Right m
-
-            mod_deps' = case ue_homeUnit unit_env of
-                          Nothing -> []
-                          Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps))
-            acc_mods'  = case ue_homeUnit unit_env of
-                          Nothing -> acc_mods
-                          Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps)
-            acc_pkgs'  = addListToUniqDSet acc_pkgs (Set.toList pkg_deps)
-
-          case ue_homeUnit unit_env of
-            Just home_unit | isHomeUnit home_unit pkg ->  follow_deps (mod_deps' ++ mods)
-                                                                      acc_mods' acc_pkgs'
-            _ ->  follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
-        where
-           msg = text "need to link module" <+> ppr mod <+>
-                  text "due to use of Template Haskell"
-
-
-
-    link_boot_mod_error :: Module -> IO a
-    link_boot_mod_error mod = throwProgramError opts $
-            text "module" <+> ppr mod <+>
-            text "cannot be linked; it is only available as a boot module"
-
     no_obj :: Outputable a => a -> IO b
     no_obj mod = dieWith opts span $
-                     text "cannot find object file for module " <>
+                     text "cannot find object file for module" <+>
                         quotes (ppr mod) $$
                      while_linking_expr
 
     while_linking_expr = text "while linking an interpreted expression"
 
+  -- Extract the 'Linkable's for unlinked modules from the intermediate
+  -- results.
+    module_linkable = \case
+      LinkHomeModule hmi ->
+        adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi))
+
+      LinkObjectModule mod loc -> do
+        findObjectLinkableMaybe mod loc >>= \case
+          Nothing  -> no_obj mod
+          Just lnk -> adjust_linkable lnk
+
+      LinkByteCodeModule _ load_bytecode ->
+        load_bytecode
 
     -- See Note [Using Byte Code rather than Object Code for Template Haskell]
     homeModLinkable :: HomeModInfo -> Maybe Linkable
@@ -266,57 +289,244 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
-        | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
-        = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
-        | otherwise
-        = do    -- It's not in the HPT because we are in one shot mode,
-                -- so use the Finder to get a ModLocation...
-             case ue_homeUnit unit_env of
-              Nothing -> no_obj mod
-              Just home_unit -> do
-                from_bc <- ldLoadByteCode opts mod
-                maybe (fallback_no_bytecode home_unit mod) pure from_bc
-        where
-
-            fallback_no_bytecode home_unit mod = do
-              let fc = ldFinderCache opts
-              let fopts = ldFinderOpts opts
-              mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod)
-              case mb_stuff of
-                Found loc _ -> do
-                  mb_lnk <- findObjectLinkableMaybe mod loc
-                  case mb_lnk of
-                    Nothing  -> no_obj mod
-                    Just lnk -> adjust_linkable lnk
-                _ -> no_obj (moduleName mod)
-
-            adjust_linkable lnk
-                | Just new_osuf <- maybe_normal_osuf = do
-                        new_parts <- mapM (adjust_part new_osuf)
-                                        (linkableParts lnk)
-                        return lnk{ linkableParts=new_parts }
-                | otherwise =
-                        return lnk
-
-            adjust_part new_osuf part = case part of
-              DotO file ModuleObject -> do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
-                ok <- doesFileExist new_file
-                if (not ok)
-                   then dieWith opts span $
-                          text "cannot find object file "
-                                <> quotes (text new_file) $$ while_linking_expr
-                   else return (DotO new_file ModuleObject)
-              DotO file ForeignObject -> pure (DotO file ForeignObject)
-              DotA fp    -> panic ("adjust_ul DotA " ++ show fp)
-              DotDLL fp  -> panic ("adjust_ul DotDLL " ++ show fp)
-              BCOs {}    -> pure part
-              LazyBCOs{} -> pure part
-              CoreBindings WholeCoreBindings {wcb_module} ->
-                pprPanic "Unhydrated core bindings" (ppr wcb_module)
+    adjust_linkable lnk
+        | Just new_osuf <- maybe_normal_osuf = do
+                new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf)
+                                (linkableParts lnk)
+                return lnk {linkableParts = new_uls}
+        | otherwise =
+                return lnk
+
+    adjust_part osuf new_osuf part = case part of
+      DotO file ModuleObject -> do
+        massert (osuf `isSuffixOf` file)
+        let file_base = fromJust (stripExtension osuf file)
+            new_file = file_base <.> new_osuf
+        ok <- doesFileExist new_file
+        if (not ok)
+            then dieWith opts span $
+                  text "cannot find object file"
+                        <+> quotes (text new_file) $$ while_linking_expr
+            else return (DotO new_file ModuleObject)
+      DotO file ForeignObject -> pure (DotO file ForeignObject)
+      DotA fp    -> panic ("adjust_part DotA " ++ show fp)
+      DotDLL fp  -> panic ("adjust_part DotDLL " ++ show fp)
+      BCOs {}    -> pure part
+      LazyBCOs{} -> pure part
+      CoreBindings WholeCoreBindings {wcb_module} ->
+        pprPanic "Unhydrated core bindings" (ppr wcb_module)
+
+data LinkDep =
+  LinkModules !(UniqDFM ModuleName LinkModule)
+  |
+  LinkLibrary !UnitId
+
+instance Outputable LinkDep where
+  ppr = \case
+    LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods)
+    LinkLibrary uid -> text "library:" <+> ppr uid
+
+data OneshotError =
+  NoInterface !MissingInterfaceError
+  |
+  LinkBootModule !Module
+
+-- | Compute the transitive dependency closure of the given modules.
+--
+-- Used for all oneshot mode dependencies and for external dependencies of home
+-- modules in make mode.
+external_deps ::
+  LinkDepsOpts ->
+  -- | Modules whose imports to follow
+  [LinkExternal] ->
+  IO [LinkDep]
+external_deps opts mods =
+  runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case
+    Right a -> pure (eltsUDFM a)
+    Left err -> throwProgramError opts (message err)
+  where
+    message = \case
+      NoInterface err ->
+        missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
+      LinkBootModule mod ->
+        link_boot_mod_error mod
+
+external_deps_loop ::
+  LinkDepsOpts ->
+  [LinkExternal] ->
+  UniqDFM UnitId LinkDep ->
+  ExceptT OneshotError IO (UniqDFM UnitId LinkDep)
+external_deps_loop _ [] acc =
+  pure acc
+external_deps_loop opts (job at LinkExternal {le_module = mod, ..} : mods) acc = do
+  (new_acc, new_mods, action) <-
+    if already_seen
+    then done
+    else process_module le_details
+  traverse_ debug_log action
+  external_deps_loop opts (new_mods ++ mods) new_acc
+  where
+    debug_log action =
+      liftIO $ debugTraceMsg (ldLogger opts) 3 $
+      text "TH dep" <+> ppr job <+>
+      brackets (sep (punctuate comma [
+        if is_home then text "home" else Outputable.empty,
+        text action
+      ]))
+
+    done = pure (acc, [], Nothing)
+
+    -- Decide how this module needs to be processed.
+    -- We only need an interface if we want to load bytecode or if we have to
+    -- link an object file (which happens for home unit modules, since those
+    -- have no libraries).
+    process_module = \case
+      LinkAllDeps | is_home || package_bc -> try_iface
+                  | otherwise -> add_library
+
+    -- @LinkOnlyPackages@ is used for make mode home modules, so all imports
+    -- that are not external are already processed otherwise.
+      LinkOnlyPackages iface -> with_deps acc iface False "only packages"
+
+    -- Check whether the current module was processed before.
+    -- Since the accumulator is keyed by unit ID, we have to perform two
+    -- lookups.
+    -- If another module from this module's unit has been determined to be
+    -- linked as a library previously, we skip this module, assuming that no
+    -- bytecode is available for the entire package.
+    already_seen
+      | Just (LinkModules mods) <- mod_dep
+      = elemUDFM mod_name mods
+      | Just (LinkLibrary _) <- mod_dep
+      = True
+      | otherwise
+      = False
+
+    -- Load the iface and attempt to get bytecode from Core bindings.
+    try_iface =
+      liftIO (ldLoadIface opts load_reason mod) >>= \case
+        Failed err -> throwE (NoInterface err)
+        Succeeded (iface, loc) -> do
+          mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface))
+          with_iface iface loc mb_load_bc
+
+    -- Decide how to link this module.
+    -- If bytecode or an object file is available, use those in that order.
+    -- Otherwise fall back to linking a library.
+    with_iface iface loc mb_load_bc
+      | IsBoot <- mi_boot iface
+      = throwE (LinkBootModule mod)
+
+      | ldUseByteCode opts
+      , is_home || package_bc
+      , Just load_bc <- mb_load_bc
+      = add_module iface (LinkByteCodeModule mod load_bc) "bytecode"
+
+      | is_home
+      = add_module iface (LinkObjectModule mod loc) "object"
+
+      | otherwise
+      = add_library
+
+    add_library =
+      pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library")
+
+    add_module iface lmod action =
+      with_deps with_mod iface True action
+      where
+        with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id
+
+    add_package_module lmod = \case
+      Just (LinkLibrary u) -> Just (LinkLibrary u)
+      Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod))
+      Nothing -> Just (LinkModules (unitUDFM mod_name lmod))
+
+    with_deps acc iface local action =
+      pure (addListToUDFM acc link, new_local ++ new_package, Just action)
+      where
+        !(!link, !new_package) = package_deps iface
+        new_local = if local then local_deps iface else []
+
+    local_deps iface =
+      [
+        LinkExternal LinkAllDeps (mkModule mod_unit m)
+        | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface))
+      ]
+
+    -- If bytecode linking of external dependencies is enabled, add them to the
+    -- jobs passed to the next iteration of 'external_deps_loop'.
+    -- Otherwise, link all package deps as libraries.
+    package_deps iface
+      | package_bc
+      = ([], [LinkExternal LinkAllDeps m | m <- Set.toList (dep_direct_pkg_mods (mi_deps iface))])
+      | otherwise
+      = ([(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))], [])
+
+    load_reason =
+      text "need to link module" <+> ppr mod <+>
+      text "due to use of Template Haskell"
+
+    package_bc = ldPkgByteCode opts
+
+    -- In multiple home unit mode, this only considers modules from the same
+    -- unit as the splice's module to be eligible for linking bytecode when
+    -- @-fpackage-db-byte-code@ is off.
+    -- For make mode, this is irrelevant, since any bytecode from the HUG is
+    -- obtained directly, not going through 'external_deps'.
+    is_home
+      | Just home <- ue_homeUnit (ldUnitEnv opts)
+      = homeUnitAsUnit home == mod_unit
+      | otherwise
+      = False
+
+    mod_dep = lookupUDFM acc mod_unit_id
+    mod_name = moduleName mod
+    mod_unit_id = moduleUnitId mod
+    mod_unit = moduleUnit mod
+
+link_boot_mod_error :: Module -> SDoc
+link_boot_mod_error mod =
+  text "module" <+> ppr mod <+>
+  text "cannot be linked; it is only available as a boot module"
+
+-- | Split link dependencies into the sets of modules and packages that have
+-- been linked previously and those that need to be linked now by checking for
+-- their presence in the 'LoaderState':
+--
+-- - For module dependencies, in the sets of loaded objects and BCOs
+--   ('objs_loaded' and 'bcos_loaded')
+-- - For package dependencies, in the set of loaded packages ('pkgs_loaded')
+classify_deps ::
+  LoaderState ->
+  [HomeModInfo] ->
+  [LinkDep] ->
+  ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId])
+classify_deps pls hmis deps =
+  (loaded_modules' ++ loaded_modules'', needed_modules' ++ needed_modules'', all_packages, needed_packages)
+  where
+    (loaded_modules', needed_modules') = partitionWith loaded_or_needed_home_module hmis
+    (loaded_modules'', needed_modules'') =
+      partitionWith loaded_or_needed_module (concatMap eltsUDFM modules)
+
+    needed_packages =
+      eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls)
+
+    all_packages = mkUniqDSet packages
+
+    (modules, packages) = flip partitionWith deps $ \case
+      LinkModules mods -> Left mods
+      LinkLibrary lib -> Right lib
+
+    loaded_or_needed_home_module lm =
+      maybe (Right (LinkHomeModule lm)) Left (loaded_module (mi_module (hm_iface lm)))
+
+    loaded_or_needed_module lm =
+      maybe (Right lm) Left (loaded_module (link_module lm))
+
+    loaded_module mod =
+      lookupModuleEnv (objs_loaded pls) mod
+      <|>
+      lookupModuleEnv (bcos_loaded pls) mod
 
 {-
 Note [Using Byte Code rather than Object Code for Template Haskell]


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -77,11 +77,13 @@ import GHC.Utils.TmpFs
 
 import GHC.Unit.Env
 import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
+import GHC.Unit.Finder
 import GHC.Unit.Module
 import GHC.Unit.State as Packages
 
 import qualified GHC.Data.ShortText as ST
 import GHC.Data.FastString
+import qualified GHC.Data.Maybe as Maybe
 
 import GHC.Linker.Deps
 import GHC.Linker.MacOS
@@ -94,6 +96,7 @@ import Control.Monad
 import qualified Data.Set as Set
 import Data.Char (isSpace)
 import qualified Data.Foldable as Foldable
+import Data.Functor ((<&>))
 import Data.IORef
 import Data.List (intercalate, isPrefixOf, nub, partition)
 import Data.Maybe
@@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do
    -- Find what packages and linkables are required
    deps <- getLinkDeps opts interp pls span needed_mods
 
-   let this_pkgs_needed = ldNeededUnits deps
+   let this_pkgs_needed = ldAllUnits deps
 
    -- Link the packages and modules required
-   pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
+   pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls
    (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
    let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
        all_pkgs_loaded = pkgs_loaded pls2
@@ -643,21 +646,40 @@ initLinkDepsOpts hsc_env = opts
             , ldModuleGraph = hsc_mod_graph hsc_env
             , ldUnitEnv     = hsc_unit_env hsc_env
             , ldPprOpts     = initSDocContext dflags defaultUserStyle
-            , ldFinderCache = hsc_FC hsc_env
-            , ldFinderOpts  = initFinderOpts dflags
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
+            , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
             , ldLoadIface
             , ldLoadByteCode
+            , ldLogger = hsc_logger hsc_env
             }
     dflags = hsc_dflags hsc_env
-    ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env
-                          $ loadInterface msg mod (ImportByUser NotBoot)
+
+    ldLoadIface msg mod =
+      initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case
+        Maybe.Failed err -> pure (Maybe.Failed err)
+        Maybe.Succeeded iface ->
+          find_location mod <&> \case
+            InstalledFound loc _ -> Maybe.Succeeded (iface, loc)
+            err -> Maybe.Failed $
+                   cannotFindInterface unit_state home_unit
+                   (targetProfile dflags) (moduleName mod) err
+
+    find_location mod =
+      liftIO $
+      findExactModule (hsc_FC hsc_env) (initFinderOpts dflags)
+      other_fopts unit_state home_unit (toUnitId <$> mod)
+
+    other_fopts = initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env
+
+    unit_state = hsc_units hsc_env
+
+    home_unit = ue_homeUnit (hsc_unit_env hsc_env)
 
     ldLoadByteCode mod = do
       EPS {eps_iface_bytecode} <- hscEPS hsc_env
-      sequence (lookupModuleEnv eps_iface_bytecode mod)
+      pure (lookupModuleEnv eps_iface_bytecode mod)
 
 
 


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -753,7 +753,7 @@ mkStubPaths fopts mod location = do
     src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
 
 -- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
+-- findObjectLinkable isn't related to the other stuff in here,
 -- but there's no other obvious place for it
 
 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)


=====================================
compiler/GHC/Unit/Module/Deps.hs
=====================================
@@ -4,6 +4,7 @@ module GHC.Unit.Module.Deps
    , mkDependencies
    , noDependencies
    , dep_direct_mods
+   , dep_direct_pkg_mods
    , dep_direct_pkgs
    , dep_sig_mods
    , dep_trusted_pkgs
@@ -35,6 +36,7 @@ import GHC.Utils.Fingerprint
 import GHC.Utils.Binary
 import GHC.Utils.Outputable
 
+import qualified Data.Map.Strict as Map
 import Data.List (sortBy, sort, partition)
 import Data.Set (Set)
 import qualified Data.Set as Set
@@ -99,6 +101,9 @@ data Dependencies = Deps
       -- does NOT include us, unlike 'imp_finsts'. See Note
       -- [The type family instance consistency story].
 
+   -- TODO strict?
+   , dep_direct_pkg_mods :: Set Module
+
    }
    deriving( Eq )
         -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
@@ -145,6 +150,8 @@ mkDependencies home_unit mod imports plugin_mods =
 
       sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports
 
+      dep_direct_pkg_mods = Set.filter ((homeUnitAsUnit home_unit /=) . moduleUnit) (Map.keysSet (imp_mods imports))
+
   in Deps { dep_direct_mods  = direct_mods
           , dep_direct_pkgs  = direct_pkgs
           , dep_plugin_pkgs  = plugin_units
@@ -155,6 +162,7 @@ mkDependencies home_unit mod imports plugin_mods =
           , dep_finsts       = sortBy stableModuleCmp (imp_finsts imports)
             -- sort to get into canonical order
             -- NB. remember to use lexicographic ordering
+          , dep_direct_pkg_mods
           }
 
 -- | Update module dependencies containing orphans (used by Backpack)
@@ -179,6 +187,7 @@ instance Binary Dependencies where
                       put_ bh (dep_boot_mods deps)
                       put_ bh (dep_orphs deps)
                       put_ bh (dep_finsts deps)
+                      put_ bh (dep_direct_pkg_mods deps)
 
     get bh = do dms <- get bh
                 dps <- get bh
@@ -188,14 +197,16 @@ instance Binary Dependencies where
                 sms <- get bh
                 os <- get bh
                 fis <- get bh
+                dep_direct_pkg_mods <- get bh
                 return (Deps { dep_direct_mods = dms
                              , dep_direct_pkgs = dps
                              , dep_plugin_pkgs = plugin_pkgs
                              , dep_sig_mods = hsigms
                              , dep_boot_mods = sms
                              , dep_trusted_pkgs = tps
-                             , dep_orphs = os,
-                               dep_finsts = fis })
+                             , dep_orphs = os
+                             , dep_finsts = fis
+                             , dep_direct_pkg_mods })
 
 noDependencies :: Dependencies
 noDependencies = Deps
@@ -207,6 +218,7 @@ noDependencies = Deps
   , dep_trusted_pkgs = Set.empty
   , dep_orphs        = []
   , dep_finsts       = []
+  , dep_direct_pkg_mods = Set.empty
   }
 
 -- | Pretty-print unit dependencies


=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed
 build artifacts, which can be objects or bytecode, depending on the build
 settings.
 
-1. In make mode, all eligible modules are part of the dependency graph.
+1. In make mode, all eligible home modules are part of the dependency graph.
    Their interfaces are loaded unconditionally and in dependency order by the
    compilation manager, and each module's bytecode is prepared before its
    dependents are compiled, in one of two ways:
@@ -88,9 +88,10 @@ settings.
 2. In oneshot mode, which compiles individual modules without a shared home unit
    graph, a previously compiled module is not reprocessed as described for make
    mode above.
-   When 'get_link_deps' encounters a dependency on a local module, it requests
-   its bytecode from the External Package State, who loads the interface
-   on-demand.
+   'get_link_deps' requests the bytecode of dependencies from the External
+   Package State, who loads the interface on-demand.
+   This works for modules in local directories (via @-i@ and @-hidir@) as well
+   as those exposed from a package DB.
 
    Since the EPS stores interfaces for all package dependencies in addition to
    local modules in oneshot mode, it has a substantial memory footprint.
@@ -109,6 +110,18 @@ settings.
    storing the intermediate representation as rehydrated Core bindings, since
    the latter have a significantly greater memory footprint.
 
+3. In both of the above modes, whenever a module from an external package
+   (loaded from a package DB) is encountered, the workflow is the same as for
+   oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object
+   code is loaded.
+   Interfaces for external modules are stored together with local oneshot mode
+   modules, so almost no special treatment is necessary, with the exception of:
+   - When external package modules are compiled, the @InteractiveContext@ in
+     @HscEnv@ is accessed, which is not available due to its impact on retention
+     of outdated build products.
+     This is solved by writing an empty @InteractiveContext@ to the env used for
+     compilation.
+
 Note [Size of Interface Files with Core Definitions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op.
 Otherwise, the stub objects from the interface are compiled to objects in
 'generateByteCode' and added to the 'HomeModLinkable' as well.
 
-Case 3 is not implemented yet (!13042).
+In case 3, Core bindings are loaded from the EPS, where stubs only exist in
+their serialized form in the interface, so they must be regenerated like in case
+2.
 
 Problem 3:
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -826,6 +826,17 @@ Options affecting code generation
     will generate byte-code rather than object code.
 
 
+.. ghc-flag:: -fpackage-db-byte-code
+    :shortdesc: Use byte-code from package DB dependencies
+    :type: dynamic
+    :category: codegen
+
+    GHC normally only considers local modules to be eligible for loading
+    bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`.
+    When this flag is specified additionally, bytecode will be loaded from
+    interfaces for all external package dependencies that provide it.
+
+
 .. _options-linker:
 
 Options affecting linking


=====================================
testsuite/tests/bytecode/T25090/Dep.hs
=====================================
@@ -0,0 +1,15 @@
+module Dep where
+
+data A = A Int
+
+used :: Int
+used = 9681
+
+dep :: A
+dep = A used
+
+unused1 :: A
+unused1 = A 1
+
+unused2 :: A
+unused2 = unused1


=====================================
testsuite/tests/bytecode/T25090/DepApi.hs
=====================================
@@ -0,0 +1,7 @@
+module DepApi (A (A), dep) where
+
+import Dep (A (A))
+import qualified Dep
+
+dep :: A
+dep = Dep.dep


=====================================
testsuite/tests/bytecode/T25090/Local.hs
=====================================
@@ -0,0 +1,15 @@
+{-# language PackageImports #-}
+
+module Local where
+
+import GHC.Prim
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+-- just to be sure that the file isn't accidentally picked up locally
+import "dep" DepApi (dep, A (A))
+import {-# source #-} Num (num)
+
+splc :: ExpQ
+splc = lift @_ @Int (num + d)
+  where
+    A d = dep


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -19,3 +19,35 @@ T25090a:
 T25090b:
 	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe
+
+DB := -package-db db -package dep
+BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0
+BC := -fprefer-byte-code -fbyte-code-and-object-code
+ARGS := $(BASIC) $(BC)
+
+T25090_pkg:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_empty:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared-empty"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_nolib:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "none"
+	./run.bash "$(TEST_HC)" "$(ARGS)"
+
+T25090_pkg_obj_code:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code"
+
+T25090_pkg_multi_unit:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	mkdir -p unit2-src/
+	mv Local.hs Num.hs Num.hs-boot unit2-src/
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -fpackage-db-byte-code -dynamic -unit @unit1 -unit @unit2
+	./PkgBytecode
+
+T25090_pkg_archive:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "archive"
+	./run.bash "$(TEST_HC)" "$(ARGS)"


=====================================
testsuite/tests/bytecode/T25090/Num.hs
=====================================
@@ -0,0 +1,4 @@
+module Num where
+
+num :: Int
+num = 48332


=====================================
testsuite/tests/bytecode/T25090/Num.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module Num where
+
+num :: Int


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.hs
=====================================
@@ -0,0 +1,12 @@
+{-# language TemplateHaskell #-}
+
+module Main where
+
+import GHC.Prim
+import Local (splc)
+
+a :: Int
+a = $(splc)
+
+main :: IO ()
+main = putStrLn (show a)


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.stdout
=====================================
@@ -0,0 +1 @@
+58013


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -16,3 +16,36 @@ def test_T25090(name):
 
 test_T25090('T25090a')
 test_T25090('T25090b')
+
+def test_pkg(name, files = []):
+    test(
+        name,
+        [
+            extra_files([
+                'PkgBytecode.hs',
+                'Local.hs',
+                'Dep.hs',
+                'DepApi.hs',
+                'Num.hs',
+                'Num.hs-boot',
+                'dep.conf',
+                'prep.bash',
+                'run.bash',
+            ] + files),
+            req_th,
+            js_skip,
+            windows_skip,
+            use_specs({'stdout': 'PkgBytecode.stdout'}),
+        ],
+        makefile_test,
+        [],
+    )
+
+test_pkg('T25090_pkg')
+test_pkg('T25090_pkg_empty')
+test_pkg('T25090_pkg_nolib')
+test_pkg('T25090_pkg_obj_code')
+test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2'])
+# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a
+# comment says "search for .so libraries _first_" (rather than "only").
+# test_pkg('T25090_pkg_archive')


=====================================
testsuite/tests/bytecode/T25090/dep.conf
=====================================
@@ -0,0 +1,8 @@
+name: dep
+version: 1.0
+id: dep-1.0
+key: dep-1.0
+exposed: True
+exposed-modules: DepApi
+import-dirs: ${pkgroot}/dep
+library-dirs: ${pkgroot}/dep


=====================================
testsuite/tests/bytecode/T25090/prep.bash
=====================================
@@ -0,0 +1,59 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+ghc_pkg_cmd="$3"
+so_ext="$4"
+library="$5"
+
+base="$PWD"
+db="$base/db"
+dep="$base/dep"
+conf_dep="${dep}/dep.conf"
+
+mkdir -p "$dep" "$db"
+mv Dep.hs DepApi.hs "$dep/"
+cp dep.conf "$dep/"
+
+ghc_pkg()
+{
+  eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@"
+}
+
+ghc()
+{
+  eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@"
+}
+
+version=$(ghc "--numeric-version")
+
+ghc_pkg recache
+
+ghc "-c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+ghc "-dynamic -c -osuf dyn_o -hisuf dyn_hi ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+
+if [[ "$library" == 'shared' ]]
+then
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'shared-empty' ]]
+then
+  echo 'module Dummy where' > Dummy.hs
+  ghc "-dynamic-too -c Dummy.hs"
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} Dummy.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'archive' ]]
+then
+  $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'none' ]]
+then
+  :
+else
+  echo "Invalid argument for 'library': $library"
+  exit 1
+fi
+
+ghc_pkg -v0 register "${conf_dep at Q}"


=====================================
testsuite/tests/bytecode/T25090/run.bash
=====================================
@@ -0,0 +1,16 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+
+ghc()
+{
+  eval "${ghc_cmd at Q} $ghc_opts $@"
+}
+
+ghc -c Num.hs-boot Num.hs Local.hs
+ghc -fpackage-db-byte-code -c PkgBytecode.hs
+ghc PkgBytecode.o -o PkgBytecode
+./PkgBytecode


=====================================
testsuite/tests/bytecode/T25090/unit1
=====================================
@@ -0,0 +1 @@
+-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2


=====================================
testsuite/tests/bytecode/T25090/unit2
=====================================
@@ -0,0 +1 @@
+-i -i./unit2-src Local Num -this-unit-id unit2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3f8a0a3682e4937d28fae627f335fb04fe48b9f...ca0cef6d45cef6ff7cf5ff772b82207f02f845fa

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3f8a0a3682e4937d28fae627f335fb04fe48b9f...ca0cef6d45cef6ff7cf5ff772b82207f02f845fa
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 18:46:46 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 23 Oct 2024 14:46:46 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-6] 11 commits: Add
 requestTickyCounterSamples to GHC.Internal.Profiling
Message-ID: <67194496a97bc_2f9068754db0350cc@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-6 at Glasgow Haskell Compiler / GHC


Commits:
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
484c7999 by Alan Zimmerman at 2024-10-23T19:46:07+01:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -


25 changed files:

- compiler/GHC/Core/Utils.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f530e5ef5d1def9a4ff6a8166b4a163ae2dbcceb...484c7999dd9cec81d6ed9f49b8322b5aa5e687dc

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f530e5ef5d1def9a4ff6a8166b4a163ae2dbcceb...484c7999dd9cec81d6ed9f49b8322b5aa5e687dc
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 19:13:38 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Wed, 23 Oct 2024 15:13:38 -0400
Subject: [Git][ghc/ghc][wip/T20749] 266 commits: JS: fake support for native
 adjustors (#25159)
Message-ID: <67194ae222c9c_27ca5cbe6b82981e@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
03055c71 by Sylvain Henry at 2024-09-09T14:58:15-04:00
JS: fake support for native adjustors (#25159)

The JS backend doesn't support adjustors (I believe) and in any case if
it ever supports them it will be a native support, not one via libffi.

- - - - -
5bf0e6bc by Sylvain Henry at 2024-09-09T14:58:56-04:00
JS: remove redundant h$lstat

It was introduced a second time by mistake in
27dceb42376c34b99a38e36a33b2abc346ed390f (cf #25190)

- - - - -
ffbc2ab0 by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Refactor only newSysLocalDs

* Change newSysLocalDs to take a scaled type
* Add newSysLocalMDs that takes a type and makes a ManyTy local

Lots of files touched, nothing deep.

- - - - -
7124e4ad by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Don't introduce 'nospec' on the LHS of a RULE

This patch address #25160.  The main payload is:

* When desugaring the LHS of a RULE, do not introduce the `nospec` call
  for non-canonical evidence.  See GHC.Core.InstEnv
  Note [Coherence and specialisation: overview]

  The `nospec` call usually introdued in `dsHsWrapper`, but we don't want it
  on the LHS of a RULE (that's what caused #25160).  So now `dsHsWrapper` takes
  a flag to say if it's on the LHS of a RULE.  See wrinkle (NC1) in
  `Note [Desugaring non-canonical evidence]` in GHC.HsToCore.Binds.

But I think this flag will go away again when I have finished with my
(entirely separate) speciaise-on-values patch (#24359).

All this meant I had to re-understand the `nospec` stuff and coherence, and
that in turn made me do some refactoring, and add a lot of new documentation

The big change is that in GHC.Core.InstEnv, I changed
  the /type synonym/ `Canonical` into
  a /data type/ `CanonicalEvidence`
and documented it a lot better.

That in turn made me realise that CalLStacks were being treated with a
bit of a hack, which I documented in `Note [CallStack and ExecptionContext hack]`.

- - - - -
663daf8d by Simon Peyton Jones at 2024-09-10T00:40:37-04:00
Add defaulting of equalities

This MR adds one new defaulting strategy to the top-level
defaulting story: see Note [Defaulting equalities] in GHC.Tc.Solver.

This resolves #25029 and #25125, which showed that users were
accidentally relying on a GHC bug, which was fixed by

    commit 04f5bb85c8109843b9ac2af2a3e26544d05e02f4
    Author: Simon Peyton Jones <simon.peytonjones at gmail.com>
    Date:   Wed Jun 12 17:44:59 2024 +0100

    Fix untouchability test

    This MR fixes #24938.  The underlying problem was tha the test for
    "does this implication bring in scope any equalities" was plain wrong.

This fix gave rise to a number of user complaints; but the improved
defaulting story of this MR largely resolves them.

On the way I did a bit of refactoring, of course

* Completely restructure the extremely messy top-level defaulting
  code. The new code is in GHC.Tc.Solver.tryDefaulting, and is much,
  much, much esaier to grok.

- - - - -
e28cd021 by Andrzej Rybczak at 2024-09-10T00:41:18-04:00
Don't name a binding pattern

It's a keyword when PatternSynonyms are set.

- - - - -
b09571e2 by Simon Peyton Jones at 2024-09-10T00:41:54-04:00
Do not use an error thunk for an absent dictionary

In worker/wrapper we were using an error thunk for an absent dictionary,
but that works very badly for -XDictsStrict, or even (as #24934 showed)
in some complicated cases involving strictness analysis and unfoldings.

This MR just uses RubbishLit for dictionaries. Simple.

No test case, sadly because our only repro case is rather complicated.

- - - - -
8bc9f5f6 by Hécate Kleidukos at 2024-09-10T00:42:34-04:00
haddock: Remove support for applehelp format in the Manual

- - - - -
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
a65f99a7 by Sebastian Graf at 2024-10-23T20:20:09+02:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
2417ce35 by Sebastian Graf at 2024-10-23T21:13:26+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                          Baseline
                      Test    Metric          value      New value Change
--------------------------------------------------------------------------------
  ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
            T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
            T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
            T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
           T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
            T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
            T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
             T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
             T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                 geo. mean                                          -0.7%
                 minimum                                           -33.9%
                 maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors

- - - - -


14 changed files:

- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- cabal.project-reinstall
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7757719dc6b2dc59dad84a804910ad1f820c834...2417ce35b8e1ce33ec23516cc6f5f85ab9e9917e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7757719dc6b2dc59dad84a804910ad1f820c834...2417ce35b8e1ce33ec23516cc6f5f85ab9e9917e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 20:13:28 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 23 Oct 2024 16:13:28 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Improve heap
 overflow exception message (#25198)
Message-ID: <671958e86dd93_27ca5c5ec360392aa@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
a4672096 by ignatiusm at 2024-10-23T16:13:14-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
a69f45ed by Rodrigo Mesquita at 2024-10-23T16:13:14-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
238783c2 by Rodrigo Mesquita at 2024-10-23T16:13:14-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -


24 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Types/Avail.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout
- + testsuite/tests/determinism/T25304/all.T
- + testsuite/tests/rts/T25198/T25198.hs
- + testsuite/tests/rts/T25198/T25198.stderr
- + testsuite/tests/rts/T25198/all.T
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/NoExportList.stdout
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
- utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
- utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
- utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1007,8 +1007,6 @@ perf:
 ############################################################
 
 abi-test:
-  # see #12935 for remaining work
-  allow_failure: true
   stage: testing
   needs:
     - job: x86_64-linux-fedora33-release


=====================================
.gitlab/ci.sh
=====================================
@@ -714,11 +714,11 @@ function cabal_abi_test() {
 
   start_section "Cabal test: $OUT"
   mkdir -p "$OUT"
-  run "$HC" \
+  "$HC" \
     -hidir tmp -odir tmp -fforce-recomp -haddock \
     -iCabal/Cabal/src -XNoPolyKinds Distribution.Simple -j"$cores" \
     -fobject-determinism \
-    "$@" 2>&1 | tee $OUT/log
+    "$@" 2>&1 | sed '1d' | tee $OUT/log
   summarise_hi_files
   summarise_o_files
   popd


=====================================
compiler/GHC.hs
=====================================
@@ -483,6 +483,8 @@ defaultErrorHandler fm (FlushOut flushOut) inner =
                          liftIO $ throwIO UserInterrupt
                      Just StackOverflow ->
                          fm "stack overflow: use +RTS -K to increase it"
+                     Just HeapOverflow ->
+                         fm "heap overflow: use +RTS -M to increase maximum heap size"
                      _ -> case fromException exception of
                           Just (ex :: ExitCode) -> liftIO $ throwIO ex
                           _ ->


=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -124,7 +124,7 @@ data DocStructureItem
   = DsiSectionHeading !Int !(HsDoc GhcRn)
   | DsiDocChunk !(HsDoc GhcRn)
   | DsiNamedChunkRef !String
-  | DsiExports !Avails
+  | DsiExports !DetOrdAvails
   | DsiModExport
       !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple
                             -- modules with a single export declaration. E.g.
@@ -136,7 +136,7 @@ data DocStructureItem
                             --
                             -- Invariant: This list of ModuleNames must be
                             -- sorted to guarantee interface file determinism.
-      !Avails
+      !DetOrdAvails
                             -- ^ Invariant: This list of Avails must be sorted
                             -- to guarantee interface file determinism.
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -163,7 +163,11 @@ mkDocStructureFromExportList mdl import_avails export_list =
       (IEGroup _ level doc, _)         -> DsiSectionHeading level (unLoc doc)
       (IEDoc _ doc, _)                 -> DsiDocChunk (unLoc doc)
       (IEDocNamed _ name, _)           -> DsiNamedChunkRef name
-      (_, avails)                      -> DsiExports (nubAvails avails)
+      (IEThingWith{}, avails)          ->
+        DsiExports $
+          {- For explicit export lists, use the explicit order. It is deterministic by construction -}
+          DefinitelyDeterministicAvails (nubAvails avails)
+      (_, avails)                      -> DsiExports (sortAvails (nubAvails avails))
 
     moduleExport :: ModuleName -- Alias
                  -> Avails
@@ -204,10 +208,10 @@ mkDocStructureFromDecls env all_exports decls =
     avails :: [Located DocStructureItem]
     avails = flip fmap all_exports $ \avail ->
       case M.lookup (availName avail) name_locs of
-        Just loc -> L loc (DsiExports [avail])
+        Just loc -> L loc (DsiExports (sortAvails [avail]))
         -- FIXME: This is just a workaround that we use when handling e.g.
         -- associated data families like in the html-test Instances.hs.
-        Nothing -> noLoc (DsiExports [])
+        Nothing -> noLoc (DsiExports (sortAvails []))
 
         -- This causes the associated data family to be incorrectly documented
         -- separately from its class:


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -518,8 +518,8 @@ mkIfaceImports = map go
     go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
     go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
 
-mkIfaceExports :: [AvailInfo] -> [IfaceExport]  -- Sort to make canonical
-mkIfaceExports = sortAvails
+mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
+mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas
 
 {-
 Note [Original module]


=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -1,5 +1,7 @@
 
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE PatternSynonyms #-}
 --
 -- (c) The University of Glasgow
 --
@@ -20,6 +22,7 @@ module GHC.Types.Avail (
     filterAvails,
     nubAvails,
     sortAvails,
+    DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails)
   ) where
 
 import GHC.Prelude
@@ -65,6 +68,20 @@ data AvailInfo
 -- | A collection of 'AvailInfo' - several things that are \"available\"
 type Avails = [AvailInfo]
 
+-- | Occurrences of Avails in interface files must be deterministically ordered
+-- to guarantee interface file determinism.
+--
+-- We guarantee a deterministic order by either using the order explicitly
+-- given by the user (e.g. in an explicit constructor export list) or instead
+-- by sorting the avails with 'sortAvails'.
+newtype DetOrdAvails = DefinitelyDeterministicAvails Avails
+  deriving newtype (Binary, Outputable, NFData)
+
+-- | It's always safe to match on 'DetOrdAvails'
+pattern DetOrdAvails :: Avails -> DetOrdAvails
+pattern DetOrdAvails x <- DefinitelyDeterministicAvails x
+{-# COMPLETE DetOrdAvails #-}
+
 {- Note [Representing pattern synonym fields in AvailInfo]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Record pattern synonym fields cannot be represented using AvailTC like fields of
@@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns)
   | otherwise              = ns
 
 -- | Sort 'Avails'/'AvailInfo's
-sortAvails :: Avails -> Avails
-sortAvails = sortBy stableAvailCmp . map sort_subs
+sortAvails :: Avails -> DetOrdAvails
+sortAvails = DefinitelyDeterministicAvails . sortBy stableAvailCmp . map sort_subs
   where
     sort_subs :: AvailInfo -> AvailInfo
     sort_subs (Avail n) = Avail n


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -23,6 +23,8 @@ Language
 Compiler
 ~~~~~~~~
 
+- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
+
 GHCi
 ~~~~
 


=====================================
testsuite/tests/determinism/T25304/A.hs
=====================================
@@ -0,0 +1,84 @@
+module A
+  ( MyType(..)
+  ) where
+
+data MyType
+    = A
+    | B
+    | C
+    | D
+    | E
+    | F
+    | G
+    | H
+    | I
+    | J
+    | K
+    | L
+    | M
+    | N
+    | O
+    | P
+    | Q
+    | R
+    | S
+    | T
+    | U
+    | V
+    | W
+    | X
+    | Y
+    | Z
+    | AA
+    | AB
+    | AC
+    | AD
+    | AE
+    | AF
+    | AG
+    | AH
+    | AI
+    | AJ
+    | AK
+    | AL
+    | AM
+    | AN
+    | AO
+    | AP
+    | AQ
+    | AR
+    | AS
+    | AT
+    | AU
+    | AV
+    | AW
+    | AX
+    | AY
+    | AZ
+    | BA
+    | BB
+    | BC
+    | BD
+    | BE
+    | BF
+    | BG
+    | BH
+    | BI
+    | BJ
+    | BK
+    | BL
+    | BM
+    | BN
+    | BO
+    | BP
+    | BQ
+    | BR
+    | BS
+    | BT
+    | BU
+    | BV
+    | BW
+    | BX
+    | BY
+    | BZ
+    | CA


=====================================
testsuite/tests/determinism/T25304/B.hs
=====================================
@@ -0,0 +1,86 @@
+module B
+( MyType
+    ( BA
+    , BB
+    , BC
+    , BD
+    , BE
+    , BF
+    , BG
+    , BH
+    , BI
+    , BJ
+    , BK
+    , BL
+    , BM
+    , BN
+    , BO
+    , BP
+    , BQ
+    , BR
+    , BS
+    , BT
+    , BU
+    , BV
+    , BW
+    , BX
+    , BY
+    , BZ
+    , CA
+    , AA
+    , AB
+    , AC
+    , AD
+    , AE
+    , AF
+    , AG
+    , AH
+    , AI
+    , AJ
+    , AK
+    , AL
+    , AM
+    , AN
+    , AO
+    , AP
+    , AQ
+    , AR
+    , AS
+    , AT
+    , AU
+    , AV
+    , AW
+    , AX
+    , AY
+    , AZ
+    , A
+    , B
+    , C
+    , D
+    , E
+    , F
+    , G
+    , H
+    , I
+    , J
+    , K
+    , L
+    , M
+    , N
+    , O
+    , P
+    , Q
+    , R
+    , S
+    , T
+    , U
+    , V
+    , W
+    , X
+    , Y
+    , Z
+    )
+) where
+
+import A
+


=====================================
testsuite/tests/determinism/T25304/Makefile
=====================================
@@ -0,0 +1,25 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25304:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface A.hi > A_clean_iface
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	'$(TEST_HC)' $(TEST_HC_OPTS) -dinitial-unique=16777215 -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp
+	'$(TEST_HC)' --show-iface A.hi > A_dirty_iface
+	'$(TEST_HC)' --show-iface B.hi > B_dirty_iface
+	diff A_clean_iface A_dirty_iface
+	diff B_clean_iface B_dirty_iface
+
+T25304a:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	# The goal is to see the export list in the documentation structure of the
+	# interface file preserves the order used in the source
+	cat B_clean_iface | grep -A7 "documentation structure"
+


=====================================
testsuite/tests/determinism/T25304/T25304a.stdout
=====================================
@@ -0,0 +1,8 @@
+       documentation structure:
+         avails:
+           [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH,
+                     A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS,
+                     A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC,
+                     A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN,
+                     A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY,
+                     A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L,


=====================================
testsuite/tests/determinism/T25304/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304'])
+test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a'])


=====================================
testsuite/tests/rts/T25198/T25198.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+import Control.Exception
+import Language.Haskell.TH
+
+-- Generate a very large number of declarations
+generateDecls :: Int -> Q [Dec]
+generateDecls n = mapM (\i -> valD (varP (mkName ("x" ++ show i))) (normalB [| i |]) []) [1..n]
+
+main :: IO ()
+main = do
+  $(generateDecls 1000000)
+  print x1


=====================================
testsuite/tests/rts/T25198/T25198.stderr
=====================================
@@ -0,0 +1 @@
+heap overflow: use +RTS -M to increase maximum heap size


=====================================
testsuite/tests/rts/T25198/all.T
=====================================
@@ -0,0 +1,4 @@
+test('T25198',
+     normal,
+     compile_fail,
+     ['+RTS -M8M -RTS'])


=====================================
testsuite/tests/showIface/DocsInHiFileTH.stdout
=====================================
@@ -187,7 +187,7 @@ docs:
          avails:
            [i]
          avails:
-           [WD11{WD11, WD11Bool, WD11Int, WD11Foo}]
+           [WD11{WD11, WD11Bool, WD11Foo, WD11Int}]
          avails:
            [WD13{WD13}]
          avails:
@@ -221,11 +221,11 @@ docs:
          avails:
            [Pretty{Pretty, prettyPrint}]
          avails:
-           [Corge{Corge, runCorge, Corge}]
+           [Corge{Corge, Corge, runCorge}]
          avails:
-           [Quuz{Quuz, quuz1_a, Quuz}]
+           [Quuz{Quuz, Quuz, quuz1_a}]
          avails:
-           [Quux{Quux, Quux2, Quux1}]
+           [Quux{Quux, Quux1, Quux2}]
          avails:
            [Tup2]
          avails:


=====================================
testsuite/tests/showIface/NoExportList.stdout
=====================================
@@ -32,7 +32,7 @@ docs:
 -- Actually we have only one type.
            identifiers:
          avails:
-           [R{R, fβ, fα, R}]
+           [R{R, R, fα, fβ}]
          section heading, level 1:
            text:
              -- * Functions


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -201,7 +201,15 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
   -- See Note [Exporting built-in items]
   let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") [])
       bonus_ds mods
-        | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods
+        | mdl == gHC_PRIM =
+            [ builtinTys
+            , DsiExports $
+                {- Haddock does not want to sort avails, the order should be
+                    deterministically /derived from the source/.
+                   In this particular case, sorting funAvail would be a no-op anyway. -}
+                DefinitelyDeterministicAvails
+                  funAvail
+            ] <> mods
         | otherwise = mods
 
   let
@@ -461,11 +469,11 @@ mkExportItems
             Just hsDoc' -> do
               doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc'
               pure [ExportDoc doc]
-        DsiExports avails ->
+        DsiExports (DetOrdAvails avails) ->
           -- TODO: We probably don't need nubAvails here.
           -- mkDocStructureFromExportList already uses it.
           concat <$> traverse availExport (nubAvails avails)
-        DsiModExport mod_names avails -> do
+        DsiModExport mod_names (DetOrdAvails avails) -> do
           -- only consider exporting a module if we are sure we are really
           -- exporting the whole module and not some subset.
           (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names)


=====================================
utils/haddock/html-test/ref/BundledPatterns2.html
=====================================
@@ -96,14 +96,6 @@
 	      >wherepattern LR :: a ->  BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e055b8060d8b4641d6946c9ea9c517942a1c4034...238783c24644a6dd4eda700427c52a1b0dd77e1b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e055b8060d8b4641d6946c9ea9c517942a1c4034...238783c24644a6dd4eda700427c52a1b0dd77e1b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 23 22:37:55 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 23 Oct 2024 18:37:55 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-7
Message-ID: <67197ac3d59c7_27ca5ce10a50494e4@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-7 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 01:06:27 2024
From: gitlab at gitlab.haskell.org (Brandon S. Allbery (@geekosaur))
Date: Wed, 23 Oct 2024 21:06:27 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/geekosaur/clarify-cpp-2
Message-ID: <67199d931f87c_1eac63608038966c5@gitlab.mail>



Brandon S. Allbery pushed new branch wip/geekosaur/clarify-cpp-2 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/geekosaur/clarify-cpp-2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 01:10:43 2024
From: gitlab at gitlab.haskell.org (Brandon S. Allbery (@geekosaur))
Date: Wed, 23 Oct 2024 21:10:43 -0400
Subject: [Git][ghc/ghc][wip/geekosaur/clarify-cpp-2] 19 commits: ci: Add
 support for ONLY_JOBS variable to trigger any validation pipeline
Message-ID: <67199e93c747e_1eac636f29941004c7@gitlab.mail>



Brandon S. Allbery pushed to branch wip/geekosaur/clarify-cpp-2 at Glasgow Haskell Compiler / GHC


Commits:
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
69b6c8e7 by brandon s allbery kf8nh at 2024-10-24T01:10:40+00:00
further explanations of CPP options

It was missing the ANSI "token pasting" behavior, which affects
users of -XMagicHash. It also explains why clang's -traditional
isn't sufficient for preprocessing Haskell code.

- - - - -


9 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/JS/Ppr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bf2122f6b70ea5bff3b673166ea1a34be3c74602...69b6c8e72c63a5fedb61aa4da06e3c4948a9f2cc

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bf2122f6b70ea5bff3b673166ea1a34be3c74602...69b6c8e72c63a5fedb61aa4da06e3c4948a9f2cc
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 05:24:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 01:24:02 -0400
Subject: [Git][ghc/ghc][master] Improve heap overflow exception message
 (#25198)
Message-ID: <6719d9f2339b0_41c5b3290458f5@gitlab.mail>



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


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -


5 changed files:

- compiler/GHC.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/rts/T25198/T25198.hs
- + testsuite/tests/rts/T25198/T25198.stderr
- + testsuite/tests/rts/T25198/all.T


Changes:

=====================================
compiler/GHC.hs
=====================================
@@ -483,6 +483,8 @@ defaultErrorHandler fm (FlushOut flushOut) inner =
                          liftIO $ throwIO UserInterrupt
                      Just StackOverflow ->
                          fm "stack overflow: use +RTS -K to increase it"
+                     Just HeapOverflow ->
+                         fm "heap overflow: use +RTS -M to increase maximum heap size"
                      _ -> case fromException exception of
                           Just (ex :: ExitCode) -> liftIO $ throwIO ex
                           _ ->


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -23,6 +23,8 @@ Language
 Compiler
 ~~~~~~~~
 
+- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
+
 GHCi
 ~~~~
 


=====================================
testsuite/tests/rts/T25198/T25198.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+import Control.Exception
+import Language.Haskell.TH
+
+-- Generate a very large number of declarations
+generateDecls :: Int -> Q [Dec]
+generateDecls n = mapM (\i -> valD (varP (mkName ("x" ++ show i))) (normalB [| i |]) []) [1..n]
+
+main :: IO ()
+main = do
+  $(generateDecls 1000000)
+  print x1


=====================================
testsuite/tests/rts/T25198/T25198.stderr
=====================================
@@ -0,0 +1 @@
+heap overflow: use +RTS -M to increase maximum heap size


=====================================
testsuite/tests/rts/T25198/all.T
=====================================
@@ -0,0 +1,4 @@
+test('T25198',
+     normal,
+     compile_fail,
+     ['+RTS -M8M -RTS'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ab8d751aabe37a1c141615bc80e310d14ae3e17

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 05:24:44 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 01:24:44 -0400
Subject: [Git][ghc/ghc][master] 2 commits: determinism: Interface re-export
 list det
Message-ID: <6719da1cded8e_41c63f01050654@gitlab.mail>



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


Commits:
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -


19 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Types/Avail.hs
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout
- + testsuite/tests/determinism/T25304/all.T
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/NoExportList.stdout
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
- utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
- utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
- utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1007,8 +1007,6 @@ perf:
 ############################################################
 
 abi-test:
-  # see #12935 for remaining work
-  allow_failure: true
   stage: testing
   needs:
     - job: x86_64-linux-fedora33-release


=====================================
.gitlab/ci.sh
=====================================
@@ -714,11 +714,11 @@ function cabal_abi_test() {
 
   start_section "Cabal test: $OUT"
   mkdir -p "$OUT"
-  run "$HC" \
+  "$HC" \
     -hidir tmp -odir tmp -fforce-recomp -haddock \
     -iCabal/Cabal/src -XNoPolyKinds Distribution.Simple -j"$cores" \
     -fobject-determinism \
-    "$@" 2>&1 | tee $OUT/log
+    "$@" 2>&1 | sed '1d' | tee $OUT/log
   summarise_hi_files
   summarise_o_files
   popd


=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -124,7 +124,7 @@ data DocStructureItem
   = DsiSectionHeading !Int !(HsDoc GhcRn)
   | DsiDocChunk !(HsDoc GhcRn)
   | DsiNamedChunkRef !String
-  | DsiExports !Avails
+  | DsiExports !DetOrdAvails
   | DsiModExport
       !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple
                             -- modules with a single export declaration. E.g.
@@ -136,7 +136,7 @@ data DocStructureItem
                             --
                             -- Invariant: This list of ModuleNames must be
                             -- sorted to guarantee interface file determinism.
-      !Avails
+      !DetOrdAvails
                             -- ^ Invariant: This list of Avails must be sorted
                             -- to guarantee interface file determinism.
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -163,7 +163,11 @@ mkDocStructureFromExportList mdl import_avails export_list =
       (IEGroup _ level doc, _)         -> DsiSectionHeading level (unLoc doc)
       (IEDoc _ doc, _)                 -> DsiDocChunk (unLoc doc)
       (IEDocNamed _ name, _)           -> DsiNamedChunkRef name
-      (_, avails)                      -> DsiExports (nubAvails avails)
+      (IEThingWith{}, avails)          ->
+        DsiExports $
+          {- For explicit export lists, use the explicit order. It is deterministic by construction -}
+          DefinitelyDeterministicAvails (nubAvails avails)
+      (_, avails)                      -> DsiExports (sortAvails (nubAvails avails))
 
     moduleExport :: ModuleName -- Alias
                  -> Avails
@@ -204,10 +208,10 @@ mkDocStructureFromDecls env all_exports decls =
     avails :: [Located DocStructureItem]
     avails = flip fmap all_exports $ \avail ->
       case M.lookup (availName avail) name_locs of
-        Just loc -> L loc (DsiExports [avail])
+        Just loc -> L loc (DsiExports (sortAvails [avail]))
         -- FIXME: This is just a workaround that we use when handling e.g.
         -- associated data families like in the html-test Instances.hs.
-        Nothing -> noLoc (DsiExports [])
+        Nothing -> noLoc (DsiExports (sortAvails []))
 
         -- This causes the associated data family to be incorrectly documented
         -- separately from its class:


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -518,8 +518,8 @@ mkIfaceImports = map go
     go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
     go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
 
-mkIfaceExports :: [AvailInfo] -> [IfaceExport]  -- Sort to make canonical
-mkIfaceExports = sortAvails
+mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
+mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas
 
 {-
 Note [Original module]


=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -1,5 +1,7 @@
 
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE PatternSynonyms #-}
 --
 -- (c) The University of Glasgow
 --
@@ -20,6 +22,7 @@ module GHC.Types.Avail (
     filterAvails,
     nubAvails,
     sortAvails,
+    DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails)
   ) where
 
 import GHC.Prelude
@@ -65,6 +68,20 @@ data AvailInfo
 -- | A collection of 'AvailInfo' - several things that are \"available\"
 type Avails = [AvailInfo]
 
+-- | Occurrences of Avails in interface files must be deterministically ordered
+-- to guarantee interface file determinism.
+--
+-- We guarantee a deterministic order by either using the order explicitly
+-- given by the user (e.g. in an explicit constructor export list) or instead
+-- by sorting the avails with 'sortAvails'.
+newtype DetOrdAvails = DefinitelyDeterministicAvails Avails
+  deriving newtype (Binary, Outputable, NFData)
+
+-- | It's always safe to match on 'DetOrdAvails'
+pattern DetOrdAvails :: Avails -> DetOrdAvails
+pattern DetOrdAvails x <- DefinitelyDeterministicAvails x
+{-# COMPLETE DetOrdAvails #-}
+
 {- Note [Representing pattern synonym fields in AvailInfo]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Record pattern synonym fields cannot be represented using AvailTC like fields of
@@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns)
   | otherwise              = ns
 
 -- | Sort 'Avails'/'AvailInfo's
-sortAvails :: Avails -> Avails
-sortAvails = sortBy stableAvailCmp . map sort_subs
+sortAvails :: Avails -> DetOrdAvails
+sortAvails = DefinitelyDeterministicAvails . sortBy stableAvailCmp . map sort_subs
   where
     sort_subs :: AvailInfo -> AvailInfo
     sort_subs (Avail n) = Avail n


=====================================
testsuite/tests/determinism/T25304/A.hs
=====================================
@@ -0,0 +1,84 @@
+module A
+  ( MyType(..)
+  ) where
+
+data MyType
+    = A
+    | B
+    | C
+    | D
+    | E
+    | F
+    | G
+    | H
+    | I
+    | J
+    | K
+    | L
+    | M
+    | N
+    | O
+    | P
+    | Q
+    | R
+    | S
+    | T
+    | U
+    | V
+    | W
+    | X
+    | Y
+    | Z
+    | AA
+    | AB
+    | AC
+    | AD
+    | AE
+    | AF
+    | AG
+    | AH
+    | AI
+    | AJ
+    | AK
+    | AL
+    | AM
+    | AN
+    | AO
+    | AP
+    | AQ
+    | AR
+    | AS
+    | AT
+    | AU
+    | AV
+    | AW
+    | AX
+    | AY
+    | AZ
+    | BA
+    | BB
+    | BC
+    | BD
+    | BE
+    | BF
+    | BG
+    | BH
+    | BI
+    | BJ
+    | BK
+    | BL
+    | BM
+    | BN
+    | BO
+    | BP
+    | BQ
+    | BR
+    | BS
+    | BT
+    | BU
+    | BV
+    | BW
+    | BX
+    | BY
+    | BZ
+    | CA


=====================================
testsuite/tests/determinism/T25304/B.hs
=====================================
@@ -0,0 +1,86 @@
+module B
+( MyType
+    ( BA
+    , BB
+    , BC
+    , BD
+    , BE
+    , BF
+    , BG
+    , BH
+    , BI
+    , BJ
+    , BK
+    , BL
+    , BM
+    , BN
+    , BO
+    , BP
+    , BQ
+    , BR
+    , BS
+    , BT
+    , BU
+    , BV
+    , BW
+    , BX
+    , BY
+    , BZ
+    , CA
+    , AA
+    , AB
+    , AC
+    , AD
+    , AE
+    , AF
+    , AG
+    , AH
+    , AI
+    , AJ
+    , AK
+    , AL
+    , AM
+    , AN
+    , AO
+    , AP
+    , AQ
+    , AR
+    , AS
+    , AT
+    , AU
+    , AV
+    , AW
+    , AX
+    , AY
+    , AZ
+    , A
+    , B
+    , C
+    , D
+    , E
+    , F
+    , G
+    , H
+    , I
+    , J
+    , K
+    , L
+    , M
+    , N
+    , O
+    , P
+    , Q
+    , R
+    , S
+    , T
+    , U
+    , V
+    , W
+    , X
+    , Y
+    , Z
+    )
+) where
+
+import A
+


=====================================
testsuite/tests/determinism/T25304/Makefile
=====================================
@@ -0,0 +1,25 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25304:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface A.hi > A_clean_iface
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	'$(TEST_HC)' $(TEST_HC_OPTS) -dinitial-unique=16777215 -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp
+	'$(TEST_HC)' --show-iface A.hi > A_dirty_iface
+	'$(TEST_HC)' --show-iface B.hi > B_dirty_iface
+	diff A_clean_iface A_dirty_iface
+	diff B_clean_iface B_dirty_iface
+
+T25304a:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	# The goal is to see the export list in the documentation structure of the
+	# interface file preserves the order used in the source
+	cat B_clean_iface | grep -A7 "documentation structure"
+


=====================================
testsuite/tests/determinism/T25304/T25304a.stdout
=====================================
@@ -0,0 +1,8 @@
+       documentation structure:
+         avails:
+           [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH,
+                     A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS,
+                     A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC,
+                     A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN,
+                     A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY,
+                     A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L,


=====================================
testsuite/tests/determinism/T25304/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304'])
+test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a'])


=====================================
testsuite/tests/showIface/DocsInHiFileTH.stdout
=====================================
@@ -187,7 +187,7 @@ docs:
          avails:
            [i]
          avails:
-           [WD11{WD11, WD11Bool, WD11Int, WD11Foo}]
+           [WD11{WD11, WD11Bool, WD11Foo, WD11Int}]
          avails:
            [WD13{WD13}]
          avails:
@@ -221,11 +221,11 @@ docs:
          avails:
            [Pretty{Pretty, prettyPrint}]
          avails:
-           [Corge{Corge, runCorge, Corge}]
+           [Corge{Corge, Corge, runCorge}]
          avails:
-           [Quuz{Quuz, quuz1_a, Quuz}]
+           [Quuz{Quuz, Quuz, quuz1_a}]
          avails:
-           [Quux{Quux, Quux2, Quux1}]
+           [Quux{Quux, Quux1, Quux2}]
          avails:
            [Tup2]
          avails:


=====================================
testsuite/tests/showIface/NoExportList.stdout
=====================================
@@ -32,7 +32,7 @@ docs:
 -- Actually we have only one type.
            identifiers:
          avails:
-           [R{R, fβ, fα, R}]
+           [R{R, R, fα, fβ}]
          section heading, level 1:
            text:
              -- * Functions


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -201,7 +201,15 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
   -- See Note [Exporting built-in items]
   let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") [])
       bonus_ds mods
-        | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods
+        | mdl == gHC_PRIM =
+            [ builtinTys
+            , DsiExports $
+                {- Haddock does not want to sort avails, the order should be
+                    deterministically /derived from the source/.
+                   In this particular case, sorting funAvail would be a no-op anyway. -}
+                DefinitelyDeterministicAvails
+                  funAvail
+            ] <> mods
         | otherwise = mods
 
   let
@@ -461,11 +469,11 @@ mkExportItems
             Just hsDoc' -> do
               doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc'
               pure [ExportDoc doc]
-        DsiExports avails ->
+        DsiExports (DetOrdAvails avails) ->
           -- TODO: We probably don't need nubAvails here.
           -- mkDocStructureFromExportList already uses it.
           concat <$> traverse availExport (nubAvails avails)
-        DsiModExport mod_names avails -> do
+        DsiModExport mod_names (DetOrdAvails avails) -> do
           -- only consider exporting a module if we are sure we are really
           -- exporting the whole module and not some subset.
           (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names)


=====================================
utils/haddock/html-test/ref/BundledPatterns2.html
=====================================
@@ -96,14 +96,6 @@
 	      >wherepattern LR :: a ->  BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ab8d751aabe37a1c141615bc80e310d14ae3e17...e39c8c993c1da534c5893ca418d1fa4cbb9e0a0a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ab8d751aabe37a1c141615bc80e310d14ae3e17...e39c8c993c1da534c5893ca418d1fa4cbb9e0a0a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 06:17:04 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Thu, 24 Oct 2024 02:17:04 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <6719e6608da34_41ca771dc54448@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
ad39e0ed by Sebastian Graf at 2024-10-24T08:15:36+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 06:54:37 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Thu, 24 Oct 2024 02:54:37 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <6719ef2d4db1d_41cdaeef457293@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
5df99e8e by Sebastian Graf at 2024-10-24T08:54:27+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5df99e8ebaee981a28668e3f774a3a07ab9cf98b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 08:56:40 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 24 Oct 2024 04:56:40 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T20264
Message-ID: <671a0bc835c98_309a232bc8c058544@gitlab.mail>



Simon Peyton Jones pushed new branch wip/T20264 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T20264
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 08:57:57 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 24 Oct 2024 04:57:57 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25387
Message-ID: <671a0c158731_309a232c61e058782@gitlab.mail>



Simon Peyton Jones pushed new branch wip/T25387 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25387
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 09:26:56 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 05:26:56 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Improve heap
 overflow exception message (#25198)
Message-ID: <671a12e03fa82_309a233d359c645ed@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
d2764fb7 by Alan Zimmerman at 2024-10-24T05:26:50-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
b0207d72 by Rodrigo Mesquita at 2024-10-24T05:26:51-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Avail.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/238783c24644a6dd4eda700427c52a1b0dd77e1b...b0207d72bf70ea6888d7851e108e9676b4a58d7b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/238783c24644a6dd4eda700427c52a1b0dd77e1b...b0207d72bf70ea6888d7851e108e9676b4a58d7b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 09:38:22 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 24 Oct 2024 05:38:22 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/testsuite-test-hc-opts
Message-ID: <671a158e96be5_309a235c20ec7604a@gitlab.mail>



Matthew Pickering pushed new branch wip/testsuite-test-hc-opts at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/testsuite-test-hc-opts
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 09:54:21 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 24 Oct 2024 05:54:21 -0400
Subject: [Git][ghc/ghc][wip/testsuite-test-hc-opts] 2 commits: testsuite: Pass
 TEST_HC_OPTS to T24634
Message-ID: <671a194d3766_16ac93f95106401a@gitlab.mail>



Matthew Pickering pushed to branch wip/testsuite-test-hc-opts at Glasgow Haskell Compiler / GHC


Commits:
7869cd96 by Matthew Pickering at 2024-10-24T10:41:21+01:00
testsuite: Pass TEST_HC_OPTS to T24634

- - - - -
994923a7 by Matthew Pickering at 2024-10-24T10:54:00+01:00
testsuite: Pass TEST_HC_OPTS to T25166

- - - - -


2 changed files:

- testsuite/tests/bytecode/T24634/Makefile
- testsuite/tests/codeGen/should_compile/Makefile


Changes:

=====================================
testsuite/tests/bytecode/T24634/Makefile
=====================================
@@ -4,14 +4,14 @@ include $(TOP)/mk/test.mk
 
 # This case loads bytecode from the interface file written in the second invocation.
 T24634a:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
 	./Main
 
 # This case uses the bytecode generated in 'runHscBackendPhase', not involving the interface, since 'Hello' is compiled
 # in the same invocation as 'Main'.
 T24634b:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
 	./Main


=====================================
testsuite/tests/codeGen/should_compile/Makefile
=====================================
@@ -79,4 +79,4 @@ T17648:
 		grep -F 'f :: T GHC.Types.Int -> ()  [TagSig' >/dev/null
 
 T25166:
-	'$(TEST_HC)' -O2 -dno-typeable-binds -ddump-cmm T25166.hs | awk '/foo_closure/{flag=1}/}]/{flag=0}flag'
+	'$(TEST_HC)' $(TEST_HC_OPTS) -O2 -dno-typeable-binds -ddump-cmm T25166.hs | awk '/foo_closure/{flag=1}/}]/{flag=0}flag'



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4652a1a4d9ba7d2656b4bf9d39b7ce3936b728b3...994923a7ed31db7a5bb4c1b46337c8ad48df3397

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4652a1a4d9ba7d2656b4bf9d39b7ce3936b728b3...994923a7ed31db7a5bb4c1b46337c8ad48df3397
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 10:23:29 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 24 Oct 2024 06:23:29 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-b] More boot-file awareness in Finder
Message-ID: <671a2021905f5_16ac932d8e08663b5@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-b at Glasgow Haskell Compiler / GHC


Commits:
9bab00b6 by Sjoerd Visscher at 2024-10-24T12:23:15+02:00
More boot-file awareness in Finder

Finishes work started in fff55592

Adds findImportedModuleWithIsBoot and findHomeModuleWithIsBoot so that callers don't have to call addBootSuffix on the result.

Removes InstalledModule field from InstalledFound constructor since it's already part of the key that was searched for.

- - - - -


13 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Location.hs
- + testsuite/tests/driver/boot-target/C.hs
- + testsuite/tests/driver/boot-target/D.hs
- testsuite/tests/driver/boot-target/Makefile
- testsuite/tests/driver/boot-target/all.T
- + testsuite/tests/driver/boot-target/boot4.stderr


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -771,7 +771,7 @@ summariseRequirement pn mod_name = do
     let fopts = initFinderOpts dflags
 
     let PackageName pn_fs = pn
-    let location = mkHomeModLocation2 fopts mod_name
+    let location = mkHomeModLocation2 fopts (notBoot mod_name)
                     (unsafeEncodeUtf $ unpackFS pn_fs  moduleNameSlashes mod_name) (os "hsig")
 
     env <- getBkpEnv
@@ -848,23 +848,20 @@ hsModuleToModSummary home_keys pn hsc_src modname
     let PackageName unit_fs = pn
         dflags = hsc_dflags hsc_env
         fopts = initFinderOpts dflags
+        modWithIsBoot = GWIB modname (hscSourceToIsBoot hsc_src)
     -- Unfortunately, we have to define a "fake" location in
     -- order to appease the various code which uses the file
     -- name to figure out where to put, e.g. object files.
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation2 fopts modWithIsBoot
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
                               (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
@@ -893,7 +890,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modWithIsBoot location
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2126,31 +2126,21 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
               ".lhs-boot" -> IsBoot
               _ -> NotBoot
 
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
-
-            -- Make a ModLocation for this file, adding the @-boot@ suffix to
-            -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            modWithIsBoot = GWIB pi_mod_name is_boot
+
+            hsc_src
+              | IsBoot <- is_boot = HsBootFile
+              | isHaskellSigFilename src_fn = HsigFile
+              | otherwise = HsSrcFile
+
+            location = mkHomeModLocation fopts modWithIsBoot src_path
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit modWithIsBoot location
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2180,14 +2170,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
            _ <- do
               let fc = hsc_FC hsc_env
                   gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+              addModuleToFinder fc gwib location
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
@@ -2239,7 +2225,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env (GWIB wanted_mod is_boot) mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2243,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2253,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env (GWIB imp is_boot) pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,19 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+        modWithIsBoot = GWIB mod_name (hscSourceToIsBoot src_flavour)
+    let location1 = mkHomeModLocation2 fopts modWithIsBoot (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -804,15 +799,15 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     -- above
     let expl_o_file = outputFile_ dflags
         expl_dyn_o_file  = dynOutputFile_ dflags
-        location5 | Just ofile <- expl_o_file
+        location4 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
-    return location5
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
+    return location4
     where
       fopts = initFinderOpts dflags
 


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -317,7 +317,7 @@ loadSrcInterface_maybe doc mod want_boot maybe_pkg
   -- interface; it will call the Finder again, but the ModLocation will be
   -- cached from the first search.
   = do hsc_env <- getTopEnv
-       res <- liftIO $ findImportedModule hsc_env mod maybe_pkg
+       res <- liftIO $ findImportedModuleWithIsBoot hsc_env (GWIB mod want_boot) maybe_pkg
        case res of
            Found _ mod -> initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
            -- TODO: Make sure this error message is good
@@ -895,9 +895,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit (GWIB mod hi_boot_file))
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,9 +15,11 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
+    findHomeModuleWithIsBoot,
     findExposedPackageModule,
     mkHomeModLocation,
     mkHomeModLocation2,
@@ -148,7 +150,10 @@ initFinderCache = do
 -- that package is searched for the module.
 
 findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult
-findImportedModule hsc_env mod pkg_qual =
+findImportedModule hsc_env = findImportedModuleWithIsBoot hsc_env . notBoot
+
+findImportedModuleWithIsBoot :: HscEnv -> ModuleNameWithIsBoot -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod pkg_qual =
   let fc        = hsc_FC hsc_env
       mhome_unit = hsc_home_unit_maybe hsc_env
       dflags    = hsc_dflags hsc_env
@@ -161,10 +166,10 @@ findImportedModuleNoHsc
   -> FinderOpts
   -> UnitEnv
   -> Maybe HomeUnit
-  -> ModuleName
+  -> ModuleNameWithIsBoot
   -> PkgQual
   -> IO FindResult
-findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
+findImportedModuleNoHsc fc fopts ue mhome_unit gwib at GWIB { gwib_mod = mod_name } mb_pkg =
   case mb_pkg of
     NoPkgQual  -> unqual_import
     ThisPkg uid | (homeUnitId <$> mhome_unit) == Just uid -> home_import
@@ -178,7 +183,7 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
 
 
     home_import = case mhome_unit of
-                   Just home_unit -> findHomeModule fc fopts home_unit mod_name
+                   Just home_unit -> findHomeModuleWithIsBoot fc fopts home_unit gwib
                    Nothing -> pure $ NoPackage (panic "findImportedModule: no home-unit")
 
 
@@ -186,11 +191,11 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
       -- If the module is reexported, then look for it as if it was from the perspective
       -- of that package which reexports it.
       | Just real_mod_name <- mod_name `M.lookup` finder_reexportedModules opts =
-        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) real_mod_name NoPkgQual
+        findImportedModuleNoHsc fc opts ue (Just $ DefiniteHomeUnit uid Nothing) gwib{ gwib_mod = real_mod_name } NoPkgQual
       | mod_name `Set.member` finder_hiddenModules opts =
         return (mkHomeHidden uid)
       | otherwise =
-        findHomePackageModule fc opts uid mod_name
+        findHomePackageModule fc opts uid gwib
 
     -- Do not be smart and change this to `foldr orIfNotFound home_import hs` as
     -- that is not the same!! home_import is first because we need to look within ourselves
@@ -228,15 +233,15 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModuleWithIsBoot -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit gwib at GWIB { gwib_mod = mod } = do
   case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
-        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
+        -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName <$> gwib)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
-        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
-    _ -> findPackageModule fc unit_state fopts mod
+        -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName <$> gwib)
+    _ -> findPackageModule fc unit_state fopts gwib
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -271,10 +276,10 @@ orIfNotFound this or_this = do
 -- been done.  Otherwise, do the lookup (with the IO action) and save
 -- the result in the finder cache and the module location cache (if it
 -- was successful.)
-homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
+homeSearchCache :: FinderCache -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
-  let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  let mod = mkModule home_unit <$> mod_name
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -290,13 +295,13 @@ findLookupResult :: FinderCache -> FinderOpts -> LookupResult -> IO FindResult
 findLookupResult fc fopts r = case r of
      LookupFound m pkg_conf -> do
        let im = fst (getModuleInstantiation m)
-       r' <- findPackageModule_ fc fopts im (fst pkg_conf)
+       r' <- findPackageModule_ fc fopts (notBoot im) (fst pkg_conf)
        case r' of
         -- TODO: ghc -M is unlikely to do the right thing
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -344,24 +349,27 @@ modLocationCache fc mod do_this = do
 addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
 addModuleToFinder fc mod loc = do
   let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+  addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
 addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
 addHomeModuleToFinder fc home_unit mod_name loc = do
   let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
+  addToFinderCache fc mod (InstalledFound loc)
   return (mkHomeModule home_unit (gwib_mod mod_name))
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
 
 findHomeModule :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
-findHomeModule fc fopts  home_unit mod_name = do
+findHomeModule fc fopts home_unit = findHomeModuleWithIsBoot fc fopts home_unit . notBoot
+
+findHomeModuleWithIsBoot :: FinderCache -> FinderOpts -> HomeUnit -> ModuleNameWithIsBoot -> IO FindResult
+findHomeModuleWithIsBoot fc fopts home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -381,12 +389,12 @@ mkHomeHidden uid =
            , fr_unusables = []
            , fr_suggestions = []}
 
-findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO FindResult
+findHomePackageModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO FindResult
 findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid (gwib_mod mod_name))
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -414,35 +422,33 @@ findHomePackageModule fc fopts  home_unit mod_name = do
 --
 --  4. Some special-case code in GHCi (ToDo: Figure out why that needs to
 --  call this.)
-findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleName -> IO InstalledFindResult
-findInstalledHomeModule fc fopts home_unit mod_name = do
-  homeSearchCache fc home_unit mod_name $
+findInstalledHomeModule :: FinderCache -> FinderOpts -> UnitId -> ModuleNameWithIsBoot -> IO InstalledFindResult
+findInstalledHomeModule fc fopts home_unit gwib at GWIB { gwib_mod = mod_name, gwib_isBoot = is_boot } = do
+  homeSearchCache fc home_unit gwib $
    let
      maybe_working_dir = finder_workingDirectory fopts
      home_path = case maybe_working_dir of
                   Nothing -> finder_importPaths fopts
                   Just fp -> augmentImports fp (finder_importPaths fopts)
+     mod = mkModule home_unit mod_name
      hi_dir_path =
       case finder_hiDir fopts of
         Just hiDir -> case maybe_working_dir of
           Nothing -> [hiDir]
           Just fp -> [fp  hiDir]
         Nothing -> home_path
-     hisuf = finder_hiSuf fopts
-     mod = mkModule home_unit mod_name
 
-     source_exts =
-      [ (os "hs",    mkHomeModLocationSearched fopts mod_name $ os "hs")
-      , (os "lhs",   mkHomeModLocationSearched fopts mod_name $ os "lhs")
-      , (os "hsig",  mkHomeModLocationSearched fopts mod_name $ os "hsig")
-      , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig")
-      ]
+     sufs = case is_boot of
+       NotBoot -> ["hs", "lhs", "hsig", "lhsig"]
+       IsBoot -> ["hs-boot", "lhs-boot"]
+     source_exts = [ (ext, mkHomeModLocationSearched fopts gwib ext) | ext <- map os sufs ]
 
+     hisuf = case is_boot of
+       NotBoot -> finder_hiSuf fopts
+       IsBoot -> addBootSuffix $ finder_hiSuf fopts
      -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that
      -- when hiDir field is set in dflags, we know to look there (see #16500)
-     hi_exts = [ (hisuf,                mkHomeModHiOnlyLocation fopts mod_name)
-               , (addBootSuffix hisuf,  mkHomeModHiOnlyLocation fopts mod_name)
-               ]
+     hi_exts = [ (hisuf, mkHomeModHiOnlyLocation fopts gwib) ]
 
         -- In compilation manager modes, we look for source files in the home
         -- package because we can compile these automatically.  In one-shot
@@ -455,8 +461,8 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- special case for GHC.Prim; we won't find it in the filesystem.
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
-   if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+   if mod `installedModuleEq` gHC_PRIM && is_boot == NotBoot
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -467,9 +473,9 @@ augmentImports work_dir (fp:fps)
   | otherwise            = (work_dir  fp) : augmentImports work_dir fps
 
 -- | Search for a module in external packages only.
-findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult
+findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModuleWithIsBoot -> IO InstalledFindResult
 findPackageModule fc unit_state fopts mod = do
-  let pkg_id = moduleUnit mod
+  let pkg_id = moduleUnit (gwib_mod mod)
   case lookupUnitId unit_state pkg_id of
      Nothing -> return (InstalledNoPackage pkg_id)
      Just u  -> findPackageModule_ fc fopts mod u
@@ -481,15 +487,15 @@ findPackageModule fc unit_state fopts mod = do
 -- the 'UnitInfo' must be consistent with the unit id in the 'Module'.
 -- The redundancy is to avoid an extra lookup in the package state
 -- for the appropriate config.
-findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -> IO InstalledFindResult
-findPackageModule_ fc fopts mod pkg_conf = do
+findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModuleWithIsBoot -> UnitInfo -> IO InstalledFindResult
+findPackageModule_ fc fopts gwib at GWIB { gwib_mod = mod, gwib_isBoot = is_boot } pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc gwib $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
-    if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+    if mod `installedModuleEq` gHC_PRIM && is_boot == NotBoot
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +519,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,10 +553,10 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
-mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt
+mkHomeModLocationSearched :: FinderOpts -> ModuleNameWithIsBoot -> FileExt
                           -> OsPath -> BaseName -> ModLocation
 mkHomeModLocationSearched fopts mod suff path basename =
   mkHomeModLocation2 fopts mod (path  basename) suff
@@ -589,34 +595,35 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
+mkHomeModLocation :: FinderOpts -> ModuleNameWithIsBoot -> OsPath -> ModLocation
 mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
+   let (basename, extension) = OsPath.splitExtension src_filename
    in mkHomeModLocation2 dflags mod basename extension
 
 mkHomeModLocation2 :: FinderOpts
-                   -> ModuleName
+                   -> ModuleNameWithIsBoot
                    -> OsPath  -- Of source module, without suffix
                    -> FileExt    -- Suffix
                    -> ModLocation
-mkHomeModLocation2 fopts mod src_basename ext =
+mkHomeModLocation2 fopts (GWIB mod is_boot) src_basename ext =
    let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod
-
-       obj_fn = mkObjPath  fopts src_basename mod_basename
-       dyn_obj_fn = mkDynObjPath  fopts src_basename mod_basename
-       hi_fn  = mkHiPath   fopts src_basename mod_basename
-       dyn_hi_fn  = mkDynHiPath   fopts src_basename mod_basename
-       hie_fn = mkHiePath  fopts src_basename mod_basename
-
-   in (OsPathModLocation{ ml_hs_file_ospath   = Just (src_basename <.> ext),
-                          ml_hi_file_ospath   = hi_fn,
-                          ml_dyn_hi_file_ospath = dyn_hi_fn,
-                          ml_obj_file_ospath  = obj_fn,
+       bootify = if is_boot == IsBoot then addBootSuffix else id
+
+       obj_fn     = bootify $ mkObjPath    fopts src_basename mod_basename
+       dyn_obj_fn = bootify $ mkDynObjPath fopts src_basename mod_basename
+       hi_fn      = bootify $ mkHiPath     fopts src_basename mod_basename
+       dyn_hi_fn  = bootify $ mkDynHiPath  fopts src_basename mod_basename
+       hie_fn     = bootify $ mkHiePath    fopts src_basename mod_basename
+
+   in (OsPathModLocation{ ml_hs_file_ospath      = Just (src_basename <.> ext),
+                          ml_hi_file_ospath      = hi_fn,
+                          ml_dyn_hi_file_ospath  = dyn_hi_fn,
+                          ml_obj_file_ospath     = obj_fn,
                           ml_dyn_obj_file_ospath = dyn_obj_fn,
-                          ml_hie_file_ospath  = hie_fn })
+                          ml_hie_file_ospath     = hie_fn })
 
 mkHomeModHiOnlyLocation :: FinderOpts
-                        -> ModuleName
+                        -> ModuleNameWithIsBoot
                         -> OsPath
                         -> BaseName
                         -> ModLocation


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,10 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
-   , addBootSuffixLocn
-   , addBootSuffixLocnOut
    , removeBootSuffix
    , mkFileSrcSpan
    )
@@ -25,7 +21,6 @@ where
 import GHC.Prelude
 
 import GHC.Data.OsPath
-import GHC.Unit.Types
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Data.FastString (mkFastString)
@@ -99,38 +94,6 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
--- | Add the @-boot@ suffix to all file paths associated with the module
-addBootSuffixLocn :: ModLocation -> ModLocation
-addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
-
--- | Add the @-boot@ suffix to all output file paths associated with the
--- module, not including the input file itself
-addBootSuffixLocnOut :: ModLocation -> ModLocation
-addBootSuffixLocnOut locn
-  = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn)
-         }
-
 -- | Compute a 'SrcSpan' from a 'ModLocation'.
 mkFileSrcSpan :: ModLocation -> SrcSpan
 mkFileSrcSpan mod_loc


=====================================
testsuite/tests/driver/boot-target/C.hs
=====================================
@@ -0,0 +1,5 @@
+module C where
+
+import {-# source #-} D
+
+data C = C D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/D.hs
=====================================
@@ -0,0 +1,3 @@
+module D where
+
+data D = D
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/Makefile
=====================================
@@ -5,4 +5,7 @@ boot2:
 	$(TEST_HC) A.hs-boot A.hs B.hs -v0
 
 boot3:
-	$(TEST_HC) A.hs-boot B.hs -v0
\ No newline at end of file
+	$(TEST_HC) A.hs-boot B.hs -v0
+
+boot4:
+	$(TEST_HC) C.hs -v0
\ No newline at end of file


=====================================
testsuite/tests/driver/boot-target/all.T
=====================================
@@ -8,3 +8,9 @@ def test_boot(name):
 test_boot('boot1')
 test_boot('boot2')
 test_boot('boot3')
+
+test('boot4',
+     [extra_files(['C.hs', 'D.hs']),
+      exit_code(2)],
+     makefile_test,
+     [])


=====================================
testsuite/tests/driver/boot-target/boot4.stderr
=====================================
@@ -0,0 +1,8 @@
+C.hs:3:1: [GHC-87110]
+    Could not find module ‘D’.
+    Use -v to see a list of the files searched for.
+  |
+3 | import {-# source #-} D
+  | ^^^^^^^^^^^^^^^^^^^^^^^
+
+gmake: *** [Makefile:11: boot4] Error 1
\ No newline at end of file



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9bab00b6af4775447966222ccaa5ccfa40856128

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 10:27:06 2024
From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo))
Date: Thu, 24 Oct 2024 06:27:06 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/teo/th-reify-docs-link-to-ticket
Message-ID: <671a20fa2a54b_16ac93f95106739c@gitlab.mail>



Teo Camarasu pushed new branch wip/teo/th-reify-docs-link-to-ticket at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/th-reify-docs-link-to-ticket
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 10:28:53 2024
From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo))
Date: Thu, 24 Oct 2024 06:28:53 -0400
Subject: [Git][ghc/ghc] Deleted branch wip/teo/th-reify-docs-link-to-ticket
Message-ID: <671a2165d963f_16ac933135d0675e5@gitlab.mail>



Teo Camarasu deleted branch wip/teo/th-reify-docs-link-to-ticket at Glasgow Haskell Compiler / GHC

-- 

You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 10:29:23 2024
From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo))
Date: Thu, 24 Oct 2024 06:29:23 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/teo/th-reify-docs-link-to-ticket
Message-ID: <671a2183ea699_16ac932f4914677fc@gitlab.mail>



Teo Camarasu pushed new branch wip/teo/th-reify-docs-link-to-ticket at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/th-reify-docs-link-to-ticket
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 11:37:44 2024
From: gitlab at gitlab.haskell.org (Teo Camarasu (@teo))
Date: Thu, 24 Oct 2024 07:37:44 -0400
Subject: [Git][ghc/ghc][wip/teo/th-reify-docs-link-to-ticket] docs: link to
 #14474 in the template-haskell docs
Message-ID: <671a3188a0355_16ac937b6fc487931@gitlab.mail>



Teo Camarasu pushed to branch wip/teo/th-reify-docs-link-to-ticket at Glasgow Haskell Compiler / GHC


Commits:
5221cf86 by Teo Camarasu at 2024-10-24T12:37:27+01:00
docs: link to #14474 in the template-haskell docs

- - - - -


1 changed file:

- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs


Changes:

=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -1534,9 +1534,11 @@ data Info
   The @Maybe Dec@ field contains @Just@ the declaration which
   defined the variable - including the RHS of the declaration -
   or else @Nothing@, in the case where the RHS is unavailable to
-  the compiler. At present, this value is /always/ @Nothing@:
-  returning the RHS has not yet been implemented because of
-  lack of interest.
+  the compiler.
+
+  At present, this value is /always/ @Nothing@:
+  returning the RHS has not yet been implemented and is tracked by
+  [GHC #14474](https://gitlab.haskell.org/ghc/ghc/-/issues/14474).
   -}
   | VarI
        Name



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5221cf8640d3ced6fa613214d7eadc0a6ffb28b5

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 11:52:09 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Thu, 24 Oct 2024 07:52:09 -0400
Subject: [Git][ghc/ghc][wip/andreask/docs-write-if-compression] Document
 -fwrite-if-compression in release notes.
Message-ID: <671a34e9ce411_16ac9390f3949269b@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/docs-write-if-compression at Glasgow Haskell Compiler / GHC


Commits:
93335a25 by Andreas Klebinger at 2024-10-24T13:32:50+02:00
Document -fwrite-if-compression in release notes.

- - - - -


2 changed files:

- docs/users_guide/9.12.1-notes.rst
- docs/users_guide/using-optimisation.rst


Changes:

=====================================
docs/users_guide/9.12.1-notes.rst
=====================================
@@ -143,6 +143,12 @@ Compiler
   flag doesn't yet ensure determinism across all compilation configurations; we
   anticipate these cases will be addressed in future updates (:ghc-ticket:`12935`).
 
+- GHC now includes a new flag, :ghc-flag:`-fwrite-if-compression=⟨n⟩`,
+  which controls the level of compression used when writing interface files to disk.
+  While we think the majority of users will be well served by the default setting,
+  the flag allows users to pick their own tradeoff between memory footprint and
+  compilation time when needed.
+
 GHCi
 ~~~~
 


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1850,6 +1850,7 @@ as such you shouldn't need to set any of them explicitly. A flag
     :category: optimization
 
     :default: 2
+    :since: 9.12.1
 
     This flag defines the level of compression of interface files when writing to disk.
     The higher the flag, the more we deduplicate the interface file, at the cost of a higher compilation time.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/93335a250347ed0591d240701a56ff171a9a5561

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 11:52:29 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Thu, 24 Oct 2024 07:52:29 -0400
Subject: [Git][ghc/ghc][wip/buildplan] 84 commits: GHCi: fix improper location
 of ghci_history file
Message-ID: <671a34fd5601f_16ac938e0918930ef@gitlab.mail>



Cheng Shao pushed to branch wip/buildplan at Glasgow Haskell Compiler / GHC


Commits:
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
d6a81905 by Cheng Shao at 2024-10-24T13:32:25+02:00
driver: make UsageFile distinguish hs/nonhs deps

- - - - -
342883cb by Cheng Shao at 2024-10-24T13:32:46+02:00
driver: implement --buildplan major mode to extract BuildPlan info from dependency analysis

- - - - -
8052b031 by Cheng Shao at 2024-10-24T13:52:15+02:00
track non-hs deps

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9b7829c6c2cf3189606f7c779f38a431a998dfed...8052b03196c1746762d77c296f215cffa9d659a1

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9b7829c6c2cf3189606f7c779f38a431a998dfed...8052b03196c1746762d77c296f215cffa9d659a1
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 12:26:48 2024
From: gitlab at gitlab.haskell.org (Brandon S. Allbery (@geekosaur))
Date: Thu, 24 Oct 2024 08:26:48 -0400
Subject: [Git][ghc/ghc][wip/geekosaur/clarify-cpp-2] 4 commits: Improve heap
 overflow exception message (#25198)
Message-ID: <671a3d084e2a_16ac93aee430100520@gitlab.mail>



Brandon S. Allbery pushed to branch wip/geekosaur/clarify-cpp-2 at Glasgow Haskell Compiler / GHC


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
c20fc3dd by brandon s allbery kf8nh at 2024-10-24T08:26:27-04:00
further explanations of CPP options

It was missing the ANSI "token pasting" behavior, which affects
users of -XMagicHash. It also explains why clang's -traditional
isn't sufficient for preprocessing Haskell code.

- - - - -


25 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Types/Avail.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout
- + testsuite/tests/determinism/T25304/all.T
- + testsuite/tests/rts/T25198/T25198.hs
- + testsuite/tests/rts/T25198/T25198.stderr
- + testsuite/tests/rts/T25198/all.T
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/NoExportList.stdout
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/html-test/ref/BundledPatterns2.html
- utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
- utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
- utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
- utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -1007,8 +1007,6 @@ perf:
 ############################################################
 
 abi-test:
-  # see #12935 for remaining work
-  allow_failure: true
   stage: testing
   needs:
     - job: x86_64-linux-fedora33-release


=====================================
.gitlab/ci.sh
=====================================
@@ -714,11 +714,11 @@ function cabal_abi_test() {
 
   start_section "Cabal test: $OUT"
   mkdir -p "$OUT"
-  run "$HC" \
+  "$HC" \
     -hidir tmp -odir tmp -fforce-recomp -haddock \
     -iCabal/Cabal/src -XNoPolyKinds Distribution.Simple -j"$cores" \
     -fobject-determinism \
-    "$@" 2>&1 | tee $OUT/log
+    "$@" 2>&1 | sed '1d' | tee $OUT/log
   summarise_hi_files
   summarise_o_files
   popd


=====================================
compiler/GHC.hs
=====================================
@@ -483,6 +483,8 @@ defaultErrorHandler fm (FlushOut flushOut) inner =
                          liftIO $ throwIO UserInterrupt
                      Just StackOverflow ->
                          fm "stack overflow: use +RTS -K to increase it"
+                     Just HeapOverflow ->
+                         fm "heap overflow: use +RTS -M to increase maximum heap size"
                      _ -> case fromException exception of
                           Just (ex :: ExitCode) -> liftIO $ throwIO ex
                           _ ->


=====================================
compiler/GHC/Hs/Doc.hs
=====================================
@@ -124,7 +124,7 @@ data DocStructureItem
   = DsiSectionHeading !Int !(HsDoc GhcRn)
   | DsiDocChunk !(HsDoc GhcRn)
   | DsiNamedChunkRef !String
-  | DsiExports !Avails
+  | DsiExports !DetOrdAvails
   | DsiModExport
       !(NonEmpty ModuleName) -- ^ We might re-export avails from multiple
                             -- modules with a single export declaration. E.g.
@@ -136,7 +136,7 @@ data DocStructureItem
                             --
                             -- Invariant: This list of ModuleNames must be
                             -- sorted to guarantee interface file determinism.
-      !Avails
+      !DetOrdAvails
                             -- ^ Invariant: This list of Avails must be sorted
                             -- to guarantee interface file determinism.
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -163,7 +163,11 @@ mkDocStructureFromExportList mdl import_avails export_list =
       (IEGroup _ level doc, _)         -> DsiSectionHeading level (unLoc doc)
       (IEDoc _ doc, _)                 -> DsiDocChunk (unLoc doc)
       (IEDocNamed _ name, _)           -> DsiNamedChunkRef name
-      (_, avails)                      -> DsiExports (nubAvails avails)
+      (IEThingWith{}, avails)          ->
+        DsiExports $
+          {- For explicit export lists, use the explicit order. It is deterministic by construction -}
+          DefinitelyDeterministicAvails (nubAvails avails)
+      (_, avails)                      -> DsiExports (sortAvails (nubAvails avails))
 
     moduleExport :: ModuleName -- Alias
                  -> Avails
@@ -204,10 +208,10 @@ mkDocStructureFromDecls env all_exports decls =
     avails :: [Located DocStructureItem]
     avails = flip fmap all_exports $ \avail ->
       case M.lookup (availName avail) name_locs of
-        Just loc -> L loc (DsiExports [avail])
+        Just loc -> L loc (DsiExports (sortAvails [avail]))
         -- FIXME: This is just a workaround that we use when handling e.g.
         -- associated data families like in the html-test Instances.hs.
-        Nothing -> noLoc (DsiExports [])
+        Nothing -> noLoc (DsiExports (sortAvails []))
 
         -- This causes the associated data family to be incorrectly documented
         -- separately from its class:


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -518,8 +518,8 @@ mkIfaceImports = map go
     go (ImpUserSpec decl (ImpUserExplicit env)) = IfaceImport decl (ImpIfaceExplicit (forceGlobalRdrEnv env))
     go (ImpUserSpec decl (ImpUserEverythingBut ns)) = IfaceImport decl (ImpIfaceEverythingBut ns)
 
-mkIfaceExports :: [AvailInfo] -> [IfaceExport]  -- Sort to make canonical
-mkIfaceExports = sortAvails
+mkIfaceExports :: [AvailInfo] -> [IfaceExport] -- Sort to make canonical
+mkIfaceExports as = case sortAvails as of DefinitelyDeterministicAvails sas -> sas
 
 {-
 Note [Original module]


=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -72,17 +72,25 @@ Haskell source. This avoids the following situations:
 
   * Errors due to an ANSI C preprocessor lexing the source and failing on
     names with single quotes (TH quotes, ticked promoted constructors,
-    names with primes in them).
+    names with primes in them);
 
-  Both of those cases may be subtle: gcc and clang permit C++-style //
-  comments in C code, and Data.Array and Data.Vector both export a //
-  operator whose type is such that a removed "comment" may leave code that
-  typechecks but does the wrong thing. Another example is that, since ANSI
-  C permits long character constants, an expression involving multiple
-  functions with primes in their names may not expand macros properly when
-  they occur between the primed functions.
+  * Errors due to ANSI "token pasting" semantics, which are triggered by
+    "#" characters (which affects code using -XMagicHash).
 
-Third special type of preprocessor for JavaScript was added laterly due to
+All of those cases may be subtle: gcc and clang permit C++-style //
+comments in C code, and Data.Array and Data.Vector both export a //
+operator whose type is such that a removed "comment" may leave code that
+typechecks but does the wrong thing. Another example is that, since ANSI
+C permits long character constants, an expression involving multiple
+functions with primes in their names may not expand macros properly when
+they occur between the primed functions.
+
+It should be noted that clang's -traditional doesn't disable // or token
+pasting; as a result, the ghc runtime installer tries very hard to find a
+gcc in order to use its preprocessor. If one can't be found, a programmer's
+only recourse is to use "-pgmP cpphs" (cpphs is on Hackage).
+
+A third special type of preprocessor for JavaScript was added later, due to
 needing to keep JSDoc comments and multiline comments. Various third party
 minifying software (for example, Google Closure Compiler) uses JSDoc
 information to apply more strict rules to code reduction which results in


=====================================
compiler/GHC/Types/Avail.hs
=====================================
@@ -1,5 +1,7 @@
 
 {-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE PatternSynonyms #-}
 --
 -- (c) The University of Glasgow
 --
@@ -20,6 +22,7 @@ module GHC.Types.Avail (
     filterAvails,
     nubAvails,
     sortAvails,
+    DetOrdAvails(DetOrdAvails, DefinitelyDeterministicAvails)
   ) where
 
 import GHC.Prelude
@@ -65,6 +68,20 @@ data AvailInfo
 -- | A collection of 'AvailInfo' - several things that are \"available\"
 type Avails = [AvailInfo]
 
+-- | Occurrences of Avails in interface files must be deterministically ordered
+-- to guarantee interface file determinism.
+--
+-- We guarantee a deterministic order by either using the order explicitly
+-- given by the user (e.g. in an explicit constructor export list) or instead
+-- by sorting the avails with 'sortAvails'.
+newtype DetOrdAvails = DefinitelyDeterministicAvails Avails
+  deriving newtype (Binary, Outputable, NFData)
+
+-- | It's always safe to match on 'DetOrdAvails'
+pattern DetOrdAvails :: Avails -> DetOrdAvails
+pattern DetOrdAvails x <- DefinitelyDeterministicAvails x
+{-# COMPLETE DetOrdAvails #-}
+
 {- Note [Representing pattern synonym fields in AvailInfo]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Record pattern synonym fields cannot be represented using AvailTC like fields of
@@ -133,8 +150,8 @@ availSubordinateNames avail@(AvailTC _ ns)
   | otherwise              = ns
 
 -- | Sort 'Avails'/'AvailInfo's
-sortAvails :: Avails -> Avails
-sortAvails = sortBy stableAvailCmp . map sort_subs
+sortAvails :: Avails -> DetOrdAvails
+sortAvails = DefinitelyDeterministicAvails . sortBy stableAvailCmp . map sort_subs
   where
     sort_subs :: AvailInfo -> AvailInfo
     sort_subs (Avail n) = Avail n


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -23,6 +23,8 @@ Language
 Compiler
 ~~~~~~~~
 
+- An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
+
 GHCi
 ~~~~
 


=====================================
testsuite/tests/determinism/T25304/A.hs
=====================================
@@ -0,0 +1,84 @@
+module A
+  ( MyType(..)
+  ) where
+
+data MyType
+    = A
+    | B
+    | C
+    | D
+    | E
+    | F
+    | G
+    | H
+    | I
+    | J
+    | K
+    | L
+    | M
+    | N
+    | O
+    | P
+    | Q
+    | R
+    | S
+    | T
+    | U
+    | V
+    | W
+    | X
+    | Y
+    | Z
+    | AA
+    | AB
+    | AC
+    | AD
+    | AE
+    | AF
+    | AG
+    | AH
+    | AI
+    | AJ
+    | AK
+    | AL
+    | AM
+    | AN
+    | AO
+    | AP
+    | AQ
+    | AR
+    | AS
+    | AT
+    | AU
+    | AV
+    | AW
+    | AX
+    | AY
+    | AZ
+    | BA
+    | BB
+    | BC
+    | BD
+    | BE
+    | BF
+    | BG
+    | BH
+    | BI
+    | BJ
+    | BK
+    | BL
+    | BM
+    | BN
+    | BO
+    | BP
+    | BQ
+    | BR
+    | BS
+    | BT
+    | BU
+    | BV
+    | BW
+    | BX
+    | BY
+    | BZ
+    | CA


=====================================
testsuite/tests/determinism/T25304/B.hs
=====================================
@@ -0,0 +1,86 @@
+module B
+( MyType
+    ( BA
+    , BB
+    , BC
+    , BD
+    , BE
+    , BF
+    , BG
+    , BH
+    , BI
+    , BJ
+    , BK
+    , BL
+    , BM
+    , BN
+    , BO
+    , BP
+    , BQ
+    , BR
+    , BS
+    , BT
+    , BU
+    , BV
+    , BW
+    , BX
+    , BY
+    , BZ
+    , CA
+    , AA
+    , AB
+    , AC
+    , AD
+    , AE
+    , AF
+    , AG
+    , AH
+    , AI
+    , AJ
+    , AK
+    , AL
+    , AM
+    , AN
+    , AO
+    , AP
+    , AQ
+    , AR
+    , AS
+    , AT
+    , AU
+    , AV
+    , AW
+    , AX
+    , AY
+    , AZ
+    , A
+    , B
+    , C
+    , D
+    , E
+    , F
+    , G
+    , H
+    , I
+    , J
+    , K
+    , L
+    , M
+    , N
+    , O
+    , P
+    , Q
+    , R
+    , S
+    , T
+    , U
+    , V
+    , W
+    , X
+    , Y
+    , Z
+    )
+) where
+
+import A
+


=====================================
testsuite/tests/determinism/T25304/Makefile
=====================================
@@ -0,0 +1,25 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+T25304:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface A.hi > A_clean_iface
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	'$(TEST_HC)' $(TEST_HC_OPTS) -dinitial-unique=16777215 -dunique-increment=-1 -v0 -haddock A.hs B.hs -fforce-recomp
+	'$(TEST_HC)' --show-iface A.hi > A_dirty_iface
+	'$(TEST_HC)' --show-iface B.hi > B_dirty_iface
+	diff A_clean_iface A_dirty_iface
+	diff B_clean_iface B_dirty_iface
+
+T25304a:
+	$(RM) A.hi A.o B.hi B.o
+	# Use -haddock to get docs: output in the interface file
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 -haddock B.hs
+	'$(TEST_HC)' --show-iface B.hi > B_clean_iface
+	# The goal is to see the export list in the documentation structure of the
+	# interface file preserves the order used in the source
+	cat B_clean_iface | grep -A7 "documentation structure"
+


=====================================
testsuite/tests/determinism/T25304/T25304a.stdout
=====================================
@@ -0,0 +1,8 @@
+       documentation structure:
+         avails:
+           [A.MyType{A.MyType, A.BA, A.BB, A.BC, A.BD, A.BE, A.BF, A.BG, A.BH,
+                     A.BI, A.BJ, A.BK, A.BL, A.BM, A.BN, A.BO, A.BP, A.BQ, A.BR, A.BS,
+                     A.BT, A.BU, A.BV, A.BW, A.BX, A.BY, A.BZ, A.CA, A.AA, A.AB, A.AC,
+                     A.AD, A.AE, A.AF, A.AG, A.AH, A.AI, A.AJ, A.AK, A.AL, A.AM, A.AN,
+                     A.AO, A.AP, A.AQ, A.AR, A.AS, A.AT, A.AU, A.AV, A.AW, A.AX, A.AY,
+                     A.AZ, A.A, A.B, A.C, A.D, A.E, A.F, A.G, A.H, A.I, A.J, A.K, A.L,


=====================================
testsuite/tests/determinism/T25304/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T25304', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304'])
+test('T25304a', [extra_files(['A.hs', 'B.hs'])], makefile_test, ['T25304a'])


=====================================
testsuite/tests/rts/T25198/T25198.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+import Control.Exception
+import Language.Haskell.TH
+
+-- Generate a very large number of declarations
+generateDecls :: Int -> Q [Dec]
+generateDecls n = mapM (\i -> valD (varP (mkName ("x" ++ show i))) (normalB [| i |]) []) [1..n]
+
+main :: IO ()
+main = do
+  $(generateDecls 1000000)
+  print x1


=====================================
testsuite/tests/rts/T25198/T25198.stderr
=====================================
@@ -0,0 +1 @@
+heap overflow: use +RTS -M to increase maximum heap size


=====================================
testsuite/tests/rts/T25198/all.T
=====================================
@@ -0,0 +1,4 @@
+test('T25198',
+     normal,
+     compile_fail,
+     ['+RTS -M8M -RTS'])


=====================================
testsuite/tests/showIface/DocsInHiFileTH.stdout
=====================================
@@ -187,7 +187,7 @@ docs:
          avails:
            [i]
          avails:
-           [WD11{WD11, WD11Bool, WD11Int, WD11Foo}]
+           [WD11{WD11, WD11Bool, WD11Foo, WD11Int}]
          avails:
            [WD13{WD13}]
          avails:
@@ -221,11 +221,11 @@ docs:
          avails:
            [Pretty{Pretty, prettyPrint}]
          avails:
-           [Corge{Corge, runCorge, Corge}]
+           [Corge{Corge, Corge, runCorge}]
          avails:
-           [Quuz{Quuz, quuz1_a, Quuz}]
+           [Quuz{Quuz, Quuz, quuz1_a}]
          avails:
-           [Quux{Quux, Quux2, Quux1}]
+           [Quux{Quux, Quux1, Quux2}]
          avails:
            [Tup2]
          avails:


=====================================
testsuite/tests/showIface/NoExportList.stdout
=====================================
@@ -32,7 +32,7 @@ docs:
 -- Actually we have only one type.
            identifiers:
          avails:
-           [R{R, fβ, fα, R}]
+           [R{R, R, fα, fβ}]
          section heading, level 1:
            text:
              -- * Functions


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
=====================================
@@ -201,7 +201,15 @@ createInterface1' flags unit_state dflags hie_file mod_iface ifaces inst_ifaces
   -- See Note [Exporting built-in items]
   let builtinTys = DsiSectionHeading 1 (WithHsDocIdentifiers (mkGeneratedHsDocString "Builtin syntax") [])
       bonus_ds mods
-        | mdl == gHC_PRIM = [builtinTys, DsiExports funAvail] <> mods
+        | mdl == gHC_PRIM =
+            [ builtinTys
+            , DsiExports $
+                {- Haddock does not want to sort avails, the order should be
+                    deterministically /derived from the source/.
+                   In this particular case, sorting funAvail would be a no-op anyway. -}
+                DefinitelyDeterministicAvails
+                  funAvail
+            ] <> mods
         | otherwise = mods
 
   let
@@ -461,11 +469,11 @@ mkExportItems
             Just hsDoc' -> do
               doc <- processDocStringParas parserOpts sDocContext pkgName hsDoc'
               pure [ExportDoc doc]
-        DsiExports avails ->
+        DsiExports (DetOrdAvails avails) ->
           -- TODO: We probably don't need nubAvails here.
           -- mkDocStructureFromExportList already uses it.
           concat <$> traverse availExport (nubAvails avails)
-        DsiModExport mod_names avails -> do
+        DsiModExport mod_names (DetOrdAvails avails) -> do
           -- only consider exporting a module if we are sure we are really
           -- exporting the whole module and not some subset.
           (unrestricted_mods, remaining_avails) <- unrestrictedModExports sDocContext thisMod modMap instIfaceMap avails (NE.toList mod_names)


=====================================
utils/haddock/html-test/ref/BundledPatterns2.html
=====================================
@@ -96,14 +96,6 @@
 	      >wherepattern LR :: a ->  BR :: RTree 0 a d a -> RTree d a -> RTree (d + 1) a

Leaf of a perfect depth tree

Branch of a perfect depth tree

>>> LR 1
+		      >BR (LR 1) (LR 2)
 1
+		    ><1,2>
 >>> let x = LR 1
+		      >let x = BR (LR 1) (LR 2)
 :t x
 x :: Num a => RTree 0 a
+		    >x :: Num a => RTree 1 a
 

Can be used as a pattern:

Case be used a pattern:

>>> let f (LR a) (LR b) = a + b
+		      >let f (BR (LR a) (LR b)) = LR (a + b)
 :t f
 f :: Num a => RTree 0 a -> RTree 0 a -> a
+		    >f :: Num a => RTree 1 a -> RTree 0 a
 >>> f (LR 1) (LR 2)
+		      >f (BR (LR 1) (LR 2))
 3
@@ -384,34 +390,28 @@
 	      >pattern BR :: RTree d a -> RTree d a ->  LR :: a -> RTree (d + 1) a 0 a

Branch of a perfect depth tree

Leaf of a perfect depth tree

>>> BR (LR 1) (LR 2)
+		      >LR 1
 <1,2>
+		    >1
 >>> let x = BR (LR 1) (LR 2)
+		      >let x = LR 1
 :t x
 x :: Num a => RTree 1 a
+		    >x :: Num a => RTree 0 a
 

Case be used a pattern:

Can be used as a pattern:

>>> let f (BR (LR a) (LR b)) = LR (a + b)
+		      >let f (LR a) (LR b) = a + b
 :t f
 f :: Num a => RTree 1 a -> RTree 0 a
+		    >f :: Num a => RTree 0 a -> RTree 0 a -> a
 >>> f (BR (LR 1) (LR 2))
+		      >f (LR 1) (LR 2)
 3


=====================================
utils/haddock/latex-test/ref/ConstructorArgs/ConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module ConstructorArgs (
-    Foo((:|), Rec, x, y, Baz, Boa, (:*)), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
+    Foo((:*), (:|), Baz, Boa, Rec, x, y), Boo(Foo, Foa, Fo, Fo'), pattern Bo,
     pattern Bo'
   ) where\end{verbatim}}
 \haddockendheader


=====================================
utils/haddock/latex-test/ref/DefaultSignatures/DefaultSignatures.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module DefaultSignatures (
-    Foo(baz', baz, bar)
+    Foo(bar, baz, baz')
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/GadtConstructorArgs/GadtConstructorArgs.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module GadtConstructorArgs (
-    Boo(Fot, x, y, Fob, w, z)
+    Boo(Fob, Fot, w, x, y, z)
   ) where\end{verbatim}}
 \haddockendheader
 


=====================================
utils/haddock/latex-test/ref/TypeFamilies3/TypeFamilies3.tex
=====================================
@@ -3,7 +3,7 @@
 \haddockbeginheader
 {\haddockverb\begin{verbatim}
 module TypeFamilies3 (
-    Foo, Bar, Baz(Baz3, Baz2, Baz1)
+    Foo, Bar, Baz(Baz1, Baz2, Baz3)
   ) where\end{verbatim}}
 \haddockendheader
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69b6c8e72c63a5fedb61aa4da06e3c4948a9f2cc...c20fc3ddc7538e01ff2039dc5ba4f64b8cf2344f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/69b6c8e72c63a5fedb61aa4da06e3c4948a9f2cc...c20fc3ddc7538e01ff2039dc5ba4f64b8cf2344f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 12:58:08 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 24 Oct 2024 08:58:08 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] 5 commits: testsuite: T25090
 test, pass TEST_HC_OPTS when calling GHC
Message-ID: <671a446073db7_8343e1829c8398c@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
caf3ae71 by Matthew Pickering at 2024-10-24T10:35:27+01:00
testsuite: T25090 test, pass TEST_HC_OPTS when calling GHC

These options should be passed to that the commands don't print out
debug output.

- - - - -
4c8dd8e8 by Matthew Pickering at 2024-10-24T10:40:28+01:00
wip

- - - - -
22f25643 by Matthew Pickering at 2024-10-24T10:40:49+01:00
testsuite: Pass TEST_HC_OPTS to T24634

- - - - -
e3a49e33 by Matthew Pickering at 2024-10-24T10:42:36+01:00
testsuite: Pass TEST_HC_OPTS to T25166

- - - - -
3a654716 by Matthew Pickering at 2024-10-24T13:57:36+01:00
wip

- - - - -


26 changed files:

- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Unit/Module/Graph.hs
- testsuite/tests/bytecode/T24634/Makefile
- testsuite/tests/bytecode/T25090/Makefile
- testsuite/tests/codeGen/should_compile/Makefile
- testsuite/tests/splice-imports/SI03.stderr
- testsuite/tests/splice-imports/SI05.stderr
- testsuite/tests/splice-imports/SI07.stderr
- testsuite/tests/splice-imports/SI08.hs
- testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI11.stderr
- + testsuite/tests/splice-imports/SI12.stderr
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- testsuite/tests/splice-imports/all.T
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Core/InstEnv.hs
=====================================
@@ -1205,7 +1205,7 @@ lookupInstEnv check_overlap_safe
                         , ie_visible = vis_mods })
               cls
               tys
-  = pprTrace "lookup" (ppr home_ie) $ (final_matches, final_unifs, unsafe_overlapped)
+  = (final_matches, final_unifs, unsafe_overlapped)
   where
     (home_matches, home_unifs) = lookupInstEnv' home_ie vis_mods cls tys
     (pkg_matches,  pkg_unifs)  = lookupInstEnv' pkg_ie  vis_mods cls tys


=====================================
compiler/GHC/Driver/Env.hs
=====================================
@@ -239,13 +239,13 @@ hptAllInstances hsc_env
 hptInstancesBelow :: HscEnv -> UnitId -> ModuleStage -> ModuleNameWithIsBoot -> (NameEnv (Set.Set ThLevel), InstEnv, [FamInst])
 hptInstancesBelow hsc_env uid lvl mnwib =
   let
-    mk_bind_env clvl ie = mkNameEnv $ flip zip (repeat (Set.singleton clvl)) $ map is_dfun_name (instEnvElts ie)
+    mk_bind_env clvl ie = mkNameEnv $ flip zip (repeat (Set.singleton (moduleStageToThLevel clvl))) $ map is_dfun_name (instEnvElts ie)
     mn = gwib_mod mnwib
     (bind_env, insts, famInsts) =
         unzip3 $ hptSomeThingsBelowUs (\mlvl mod_info ->
                                      let details = hm_details mod_info
                                      -- Don't include instances for the current module
-                                     in pprTrace "lvl" (ppr mlvl) $ if moduleName (mi_module (hm_iface mod_info)) == mn
+                                     in if moduleName (mi_module (hm_iface mod_info)) == mn
                                           then []
                                           else [(mk_bind_env mlvl (md_insts details), md_insts details, md_fam_insts details)])
                              True -- Include -hi-boot
@@ -255,7 +255,7 @@ hptInstancesBelow hsc_env uid lvl mnwib =
                              mnwib
     -- Horrible horrible
     hack = mkInstEnv (nubBy (\c1 c2 -> instanceDFunId c1 == instanceDFunId c2) (concatMap instEnvElts insts))
-  in (foldl' (plusNameEnv_C Set.union) emptyNameEnv bind_env, hack, concat famInsts)
+  in ((foldl' (plusNameEnv_C Set.union) emptyNameEnv bind_env), hack, concat famInsts)
 
 -- | Get rules from modules "below" this one (in the dependency sense)
 hptRules :: HscEnv -> UnitId -> ModuleStage -> ModuleNameWithIsBoot -> [CoreRule]


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -667,8 +667,8 @@ createBuildPlan mod_graph maybe_top_mod =
 
   in
 
-    assertPpr (sum (map countMods build_plan) == length (collapseModuleGraph $ mgModSummaries' mod_graph))
-              (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (length (collapseModuleGraph $ mgModSummaries' mod_graph )))])
+    assertPpr (sum (map countMods build_plan) == length (collapseModuleGraphNodes $ mgModSummaries' mod_graph))
+              (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (length (collapseModuleGraphNodes $ mgModSummaries' mod_graph )))])
               build_plan
 
 mkWorkerLimit :: DynFlags -> IO WorkerLimit
@@ -1478,7 +1478,7 @@ topSortModuleGraph
 topSortModuleGraph drop_hs_boot_nodes module_graph mb_root_mod =
     -- stronglyConnCompG flips the original order, so if we reverse
     -- the summaries we get a stable topological sort.
-  topSortModules drop_hs_boot_nodes (reverse $ collapseModuleGraph $ mgModSummaries' module_graph) mb_root_mod
+  topSortModules drop_hs_boot_nodes (reverse $ collapseModuleGraphNodes $ mgModSummaries' module_graph) mb_root_mod
 
 topSortModules :: Bool -> [ModuleGraphNode] -> Maybe HomeUnitModule -> [SCC ModuleGraphNode]
 topSortModules drop_hs_boot_nodes summaries mb_root_mod
@@ -1637,8 +1637,8 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
           [(ms_unitid ms, offsetStage lvl st, b, c) | (st, b, c) <- msDeps ms ]
 
         offsetStage lvl NormalStage = lvl
-        offsetStage lvl QuoteStage  = lvl + 1
-        offsetStage lvl SpliceStage = lvl - 1
+        offsetStage lvl QuoteStage  = incModuleStage lvl
+        offsetStage lvl SpliceStage = decModuleStage lvl
 
         logger = hsc_logger hsc_env
 


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -123,6 +123,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
             else do
               (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
               return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
+      pprTraceM "ld" (ppr (all_home_mods, mods_s, pkgs_s))
 
       let
         -- 2.  Exclude ones already linked


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -111,6 +111,7 @@ import System.Win32.Info (getSystemDirectory)
 #endif
 
 import GHC.Utils.Exception
+import GHC.Unit.Module.Graph
 
 -- Note [Linkers and loaders]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -640,7 +641,10 @@ initLinkDepsOpts hsc_env = opts
     opts = LinkDepsOpts
             { ldObjSuffix   = objectSuf dflags
             , ldOneShotMode = isOneShot (ghcMode dflags)
-            , ldModuleGraph = hsc_mod_graph hsc_env
+            -- MP: This is very inefficient as it destroys sharing of
+            -- calculating transitive dependencies. it would be better if we
+            -- were explicit about requesting modules at a specific stage.
+            , ldModuleGraph = collapseModuleGraph $ hsc_mod_graph hsc_env
             , ldUnitEnv     = hsc_unit_env hsc_env
             , ldPprOpts     = initSDocContext dflags defaultUserStyle
             , ldFinderCache = hsc_FC hsc_env


=====================================
compiler/GHC/Rename/Splice.hs
=====================================
@@ -974,7 +974,7 @@ checkThLocalName name
   = return ()
 
   | otherwise
-  = do  { pprTraceM "checkThLocalName" (ppr name)
+  = do  { --pprTraceM "checkThLocalName" (ppr name)
         ; mb_local_use <- getStageAndBindLevel name
         ; case mb_local_use of {
              Nothing -> return () ;  -- Not a locally-bound thing
@@ -983,9 +983,9 @@ checkThLocalName name
         ; cur_mod <- extractModule <$> getGblEnv
         ; let is_local = nameIsLocalOrFrom cur_mod name
        -- ; checkWellStaged (StageCheckSplice name) bind_lvl use_lvl
-        ; pprTraceM "checkThLocalName" (ppr name <+> ppr bind_lvl
-                                               <+> ppr use_stage
-                                               <+> ppr use_lvl)
+        --; pprTraceM "checkThLocalName" (ppr name <+> ppr bind_lvl
+        --                                       <+> ppr use_stage
+        --                                       <+> ppr use_lvl)
         ; dflags <- getDynFlags
         ; checkCrossStageLifting dflags (StageCheckSplice name) top_lvl is_local bind_lvl use_stage use_lvl name } } }
 


=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -1060,7 +1060,7 @@ checkThLocalId :: Id -> TcM ()
 -- Here we just add constraints for cross-stage lifting
 checkThLocalId id
   = do  { mb_local_use <- getStageAndBindLevel (idName id)
-        ; pprTraceM "local" (ppr id $$ ppr mb_local_use)
+--        ; pprTraceM "local" (ppr id $$ ppr mb_local_use)
         ; case mb_local_use of
              Just (top_lvl, bind_lvl, use_stage)
                 | thLevel use_stage `notElem` bind_lvl


=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -1455,10 +1455,10 @@ checkWellStagedInstanceWhat what
     = do
         cur_mod <- extractModule <$> getGblEnv
         gbl_env <- getGblEnv
-        pprTraceM "checkWellStaged" (ppr what)
-        pprTraceM "checkWellStaged" (ppr (tcg_bind_env gbl_env))
-        pprTraceM "checkWellStaged"
-          (ppr (lookupNameEnv   (tcg_bind_env gbl_env) (idName dfun_id)))
+--        pprTraceM "checkWellStaged" (ppr what)
+--        pprTraceM "checkWellStaged" (ppr (tcg_bind_env gbl_env))
+--        pprTraceM "checkWellStaged"
+--          (ppr (lookupNameEnv   (tcg_bind_env gbl_env) (idName dfun_id)))
         return $ (,isLocalId dfun_id)  <$> (lookupNameEnv   (tcg_bind_env gbl_env) (idName dfun_id))
         return $ case  lookupNameEnv (tcg_bind_env gbl_env) (idName dfun_id) of
           -- The instance comes from HPT imported module
@@ -1466,7 +1466,9 @@ checkWellStagedInstanceWhat what
           Nothing ->
             if isLocalId dfun_id
               then Just ( (Set.singleton outerLevel, True) )
-              else Just ( (Set.singleton impLevel, False) )
+              -- TODO: Instances coming from external packages also need somehow
+              -- to deal with splice imports
+              else Just ( (Set.fromList [impLevel, outerLevel], False) )
 --        return $ Just (TcM.topIdLvl dfun_id)
   | BuiltinTypeableInstance tc <- what
     = do


=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -2082,16 +2082,27 @@ getStageAndBindLevel name
        ; case lookupNameEnv (getLclEnvThBndrs env) name of
            Nothing                  -> do
               lvls <- getExternalBindLvl name
-              pprTraceM "lvls" (ppr name $$ ppr lvls $$ ppr (getLclEnvThStage env))
-              return (Just (TopLevel, lvls, getLclEnvThStage env))
+              if Set.empty == lvls
+                -- This case happens when code is generated for identifiers which are not
+                -- in scope.
+                --
+                -- TODO: What happens if someone generates [|| GHC.Magic.dataToTag# ||]
+                then do
+                  env <- getGlobalRdrEnv
+                  pprTrace "NO_LVLS" (ppr env $$ ppr name) (return Nothing)
+                else return (Just (TopLevel, lvls, getLclEnvThStage env))
            Just (top_lvl, bind_lvl) -> return (Just (top_lvl, Set.singleton bind_lvl, getLclEnvThStage env)) }
 
 getExternalBindLvl :: Name -> TcRn (Set.Set ThLevel)
 getExternalBindLvl name = do
   env <- getGlobalRdrEnv
+  mod <- getModule
   case lookupGRE_Name env name of
     Just gre -> return $ (Set.map convert_lvl (greStages gre))
-    Nothing -> return Set.empty
+    Nothing ->
+      if nameIsLocalOrFrom mod name
+        then return $ Set.singleton outerLevel
+        else pprTrace "NO LVLS" (ppr name) (return Set.empty) -- pprPanic "getExternalBindLvl" (ppr env $$ ppr name $$ ppr (nameSrcSpan name))
   where
     convert_lvl NormalStage = thLevel topStage
     convert_lvl SpliceStage = thLevel topSpliceStage


=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -630,7 +630,9 @@ greInfo :: GlobalRdrElt -> GREInfo
 greInfo = gre_info
 
 greStages :: GlobalRdrElt -> Set.Set ImportStage
-greStages g = Set.fromList (bagToList (fmap (is_staged . is_decl) (gre_imp g)))
+greStages g =
+  if gre_lcl g then Set.singleton NormalStage
+                 else Set.fromList (bagToList (fmap (is_staged . is_decl) (gre_imp g)))
 
 -- | See Note [Parents]
 data Parent = NoParent


=====================================
compiler/GHC/Unit/Module/Graph.hs
=====================================
@@ -43,7 +43,11 @@ module GHC.Unit.Module.Graph
    , ModuleStage
    , zeroStage
    , todoStage
+   , moduleStageToThLevel
+   , incModuleStage
+   , decModuleStage
    , collapseModuleGraph
+   , collapseModuleGraphNodes
    )
 where
 
@@ -141,21 +145,28 @@ nodeKeyModName :: NodeKey -> Maybe ModuleName
 nodeKeyModName (NodeKey_Module mk) = Just (gwib_mod $ mnkModuleName mk)
 nodeKeyModName _ = Nothing
 
-type ModuleStage = Int
+newtype ModuleStage = ModuleStage Int deriving (Eq, Ord)
+
+instance Outputable ModuleStage where
+  ppr (ModuleStage p) = ppr p
 
 zeroStage :: ModuleStage
-zeroStage = 0
+zeroStage = ModuleStage 1
 
 todoStage :: HasCallStack => ModuleStage
 todoStage = pprTrace "todoStage" callStackDoc zeroStage
 
+moduleStageToThLevel (ModuleStage m) = m
+incModuleStage (ModuleStage m) = ModuleStage (m + 1)
+decModuleStage (ModuleStage m) = ModuleStage (m - 1)
+
 data ModNodeKeyWithUid = ModNodeKeyWithUid { mnkModuleName :: !ModuleNameWithIsBoot
                                            , mnkLevel      :: !ModuleStage
                                            , mnkUnitId     :: !UnitId } deriving (Eq, Ord)
 
 instance Outputable ModNodeKeyWithUid where
   ppr (ModNodeKeyWithUid mnwib lvl uid)
-    | lvl == 0 = ppr uid <> colon <> ppr mnwib
+    | lvl == zeroStage = ppr uid <> colon <> ppr mnwib
     | otherwise = ppr uid <> colon <> ppr mnwib <> text "@" <> ppr lvl
 
 -- | A '@ModuleGraph@' contains all the nodes from the home package (only). See
@@ -256,9 +267,11 @@ extendMG' mg = \case
 mkModuleGraph :: [ModuleGraphNode] -> ModuleGraph
 mkModuleGraph = foldr (flip extendMG') emptyMG
 
+collapseModuleGraph = mkModuleGraph . collapseModuleGraphNodes . mgModSummaries'
+
 -- Collapse information about levels and map everything to level 0
-collapseModuleGraph :: [ModuleGraphNode] -> [ModuleGraphNode]
-collapseModuleGraph m = nub $ map go m
+collapseModuleGraphNodes :: [ModuleGraphNode] -> [ModuleGraphNode]
+collapseModuleGraphNodes m = nub $ map go m
   where
     go (ModuleNode deps _lvl ms) = ModuleNode (nub $ map collapseNodeKey deps) zeroStage ms
     go (LinkNode deps uid) = LinkNode (nub $ map collapseNodeKey deps) uid
@@ -311,7 +324,7 @@ showModMsg dflags recomp (ModuleNode _ lvl mod_summary) =
       then text mod_str
       else hsep $
          [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
-         , int lvl
+         , (if lvl == zeroStage then empty else ppr lvl)
          , char '('
          , text (op $ msHsFilePath mod_summary) <> char ','
          , message, char ')' ]
@@ -351,7 +364,7 @@ nodeDependencies :: Bool -> ModuleGraphNode -> [NodeKey]
 nodeDependencies drop_hs_boot_nodes = \case
     LinkNode deps _uid -> deps
     InstantiationNode uid iuid ->
-      NodeKey_Module . (\mod -> ModNodeKeyWithUid (GWIB mod NotBoot) 0 uid)  <$> uniqDSetToList (instUnitHoles iuid)
+      NodeKey_Module . (\mod -> ModNodeKeyWithUid (GWIB mod NotBoot) zeroStage uid)  <$> uniqDSetToList (instUnitHoles iuid)
     ModuleNode deps _lvl _ms ->
       map drop_hs_boot deps
   where


=====================================
testsuite/tests/bytecode/T24634/Makefile
=====================================
@@ -4,14 +4,14 @@ include $(TOP)/mk/test.mk
 
 # This case loads bytecode from the interface file written in the second invocation.
 T24634a:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code -fno-omit-interface-pragmas Hello.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Main.hs
 	./Main
 
 # This case uses the bytecode generated in 'runHscBackendPhase', not involving the interface, since 'Hello' is compiled
 # in the same invocation as 'Main'.
 T24634b:
-	$(TEST_HC) -c hello_c.c -o hello_c.o
-	$(TEST_HC) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c hello_c.c -o hello_c.o
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fprefer-byte-code -fbyte-code-and-object-code -fno-ignore-interface-pragmas hello_c.o Hello.hs Main.hs
 	./Main


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -4,18 +4,18 @@ include $(TOP)/mk/test.mk
 
 # Verify that the object files aren't linked by clobbering them.
 T25090a:
-	$(TEST_HC) -c -fbyte-code-and-object-code C.hs-boot
-	$(TEST_HC) -c -fbyte-code-and-object-code B.hs
-	$(TEST_HC) -c -fbyte-code-and-object-code C.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code C.hs-boot
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code B.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code C.hs
 	echo 'corrupt' > B.o
 	echo 'corrupt' > C.o
 	echo 'corrupt' > C.o-boot
-	$(TEST_HC) -c -fbyte-code-and-object-code D.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code D.hs
 	echo 'corrupt' > D.o
-	$(TEST_HC) -c -fbyte-code-and-object-code -fprefer-byte-code A.hs
-	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A.o -o exe
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -fbyte-code-and-object-code -fprefer-byte-code A.hs
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fbyte-code-and-object-code -fprefer-byte-code A.o -o exe
 	./exe
 
 T25090b:
-	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
+	'$(TEST_HC)' $(TEST_HC_OPTS) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe


=====================================
testsuite/tests/codeGen/should_compile/Makefile
=====================================
@@ -79,4 +79,4 @@ T17648:
 		grep -F 'f :: T GHC.Types.Int -> ()  [TagSig' >/dev/null
 
 T25166:
-	'$(TEST_HC)' -O2 -dno-typeable-binds -ddump-cmm T25166.hs | awk '/foo_closure/{flag=1}/}]/{flag=0}flag'
+	'$(TEST_HC)' $(TEST_HC_OPTS) -O2 -dno-typeable-binds -ddump-cmm T25166.hs | awk '/foo_closure/{flag=1}/}]/{flag=0}flag'


=====================================
testsuite/tests/splice-imports/SI03.stderr
=====================================
@@ -1,7 +1,5 @@
-
-SI03.hs:8:11: error:
-    • Splice import
-      sid
-        imported from ‘SI01A’ at SI03.hs:5:1-12
-        (and originally defined at SI01A.hs:3:1-3)
+SI03.hs:8:11: error: [GHC-28914]
+    • Stage error: ‘sid’ is bound at stage {1} but used at stage 0
+      Hint: quoting [| sid |] or an enclosing expression would allow the quotation to be used in an earlier stage
     • In the untyped splice: $(sid [| pure () |])
+


=====================================
testsuite/tests/splice-imports/SI05.stderr
=====================================
@@ -1,11 +1,16 @@
+SI05.hs:9:11: error: [GHC-28914]
+    • Stage error: ‘SI01A.sid’ is bound at stage {1} but used at stage 0
+      Hint: quoting [| SI01A.sid |] or an enclosing expression would allow the quotation to be used in an earlier stage
+    • In the untyped splice: $(sid [| pure () |])
 
-SI05.hs:9:11: error:
-    • Ambiguous occurrence ‘sid’
+SI05.hs:9:11: error: [GHC-87543]
+    • Ambiguous occurrence ‘sid’.
       It could refer to
          either ‘SI01A.sid’,
                 imported from ‘SI01A’ at SI05.hs:5:1-12
-                (and originally defined at SI01A.hs:3:1-3)
+                (and originally defined at SI01A.hs:3:1-3),
              or ‘SI05A.sid’,
                 imported from ‘SI05A’ at SI05.hs:6:1-19
-                (and originally defined at SI05A.hs:3:1-3)
+                (and originally defined at SI05A.hs:3:1-3).
     • In the untyped splice: $(sid [| pure () |])
+


=====================================
testsuite/tests/splice-imports/SI07.stderr
=====================================
@@ -1,3 +1,3 @@
-[1 of 3] Compiling SI05A            ( SI05A.hs, SI05A.o, SI05A.dyn_o )
-[2 of 3] Compiling SI07A            ( SI07A.hs, nothing, SI07A.dyn_o )
-[3 of 3] Compiling SI07             ( SI07.hs, SI07.o, SI07.dyn_o )
+[1 of 3] Compiling SI05A            ( SI05A.hs, SI05A.o )
+[2 of 3] Compiling SI07A            ( SI07A.hs, SI07A.o )
+[3 of 3] Compiling SI07             ( SI07.hs, nothing )


=====================================
testsuite/tests/splice-imports/SI08.hs
=====================================
@@ -4,6 +4,8 @@ module SI08 where
 
 import InstanceA ()
 import splice ClassA
+import ClassA
+import splice Prelude (const)
 
 e :: X
 -- Uses a non-splice imported instance


=====================================
testsuite/tests/splice-imports/SI08.stderr
=====================================
@@ -1,6 +1,6 @@
-
-SI08.hs:10:25: error:
-    • No instance for (C X) arising from a use of ‘x’
+SI08.hs:12:25: error: [GHC-28914]
+    • Stage error: instance for ‘C X’ is bound at stage {1} but used at stage 0
     • In the second argument of ‘const’, namely ‘(x vx)’
       In the expression: const [| x vx |] (x vx)
       In the untyped splice: $(const [| x vx |] (x vx))
+


=====================================
testsuite/tests/splice-imports/SI11.stderr
=====================================
@@ -0,0 +1,5 @@
+SI11.hs:11:10: error: [GHC-28914]
+    • Stage error: ‘X’ is bound at stage {1} but used at stage 2
+      Hint: quoting [| X |] or an enclosing expression would allow the quotation to be used in an earlier stage
+    • In the Template Haskell quotation [| X |]
+


=====================================
testsuite/tests/splice-imports/SI12.stderr
=====================================
@@ -0,0 +1,5 @@
+SI12.hs:6:22: error: [GHC-28914]
+    • Stage error: ‘t’ is bound at stage {1} but used at stage 2
+      Hint: quoting [| t |] or an enclosing expression would allow the quotation to be used in an earlier stage
+    • In the Template Haskell quotation [| t |]
+


=====================================
testsuite/tests/splice-imports/SI14.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE DeriveLift #-}
+{-# LANGUAGE ExplicitStageImports #-}
+module SI14 where
+
+import Language.Haskell.TH.Syntax (Lift)
+
+data A = A deriving Lift


=====================================
testsuite/tests/splice-imports/SI14.stderr
=====================================
@@ -0,0 +1,10 @@
+SI14.hs:7:21: error: [GHC-28914]
+    • Stage error: ‘A’ is bound at stage {1} but used at stage 2
+      Hint: quoting [| A |] or an enclosing expression would allow the quotation to be used in an earlier stage
+    • In the Template Haskell typed quotation [|| A ||]
+
+SI14.hs:7:21: error: [GHC-28914]
+    • Stage error: ‘A’ is bound at stage {1} but used at stage 2
+      Hint: quoting [| A |] or an enclosing expression would allow the quotation to be used in an earlier stage
+    • In the Template Haskell quotation [| A |]
+


=====================================
testsuite/tests/splice-imports/SI15.hs
=====================================
@@ -0,0 +1,7 @@
+{-# LANGUAGE NoPathCSP #-}
+{-# LANGUAGE DeriveLift #-}
+module SI15 where
+
+import Language.Haskell.TH.Syntax (Lift)
+
+data A = A deriving Lift


=====================================
testsuite/tests/splice-imports/all.T
=====================================
@@ -17,4 +17,6 @@ test('SI10', [extra_files(["ClassA.hs", "InstanceA.hs"])], multimod_compile, ['S
 test('SI11', normal,  compile_fail, [''])
 test('SI12', normal,  compile_fail, [''])
 test('SI13', normal,  compile, [''])
+test('SI14', normal,  compile_fail, [''])
+test('SI15', normal,  compile_fail, [''])
 


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1840,7 +1840,7 @@ instance ExactPrint (ImportDecl GhcPs) where
                     = (ideclExt idecl) { ideclAnn = setAnchorEpa (ideclAnn $ ideclExt idecl) anc ts cs} }
 
   exact (ImportDecl (XImportDeclPass ann msrc impl)
-                     modname mpkg src safeflag qualFlag mAs hiding) = do
+                     modname mpkg src st safeflag qualFlag mAs hiding) = do
 
     ann0 <- markLensKw' ann limportDeclAnnImport AnnImport
     let (EpAnn _anc an _cs) = ann0
@@ -1902,7 +1902,7 @@ instance ExactPrint (ImportDecl GhcPs) where
                   }
 
     return (ImportDecl (XImportDeclPass (EpAnn anc' an2 cs') msrc impl)
-                     modname' mpkg src safeflag qualFlag mAs' hiding')
+                     modname' mpkg src st safeflag qualFlag mAs' hiding')
 
 
 -- ---------------------------------------------------------------------



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8e43c366192606df3f0d96ccd1984790b460e065...3a654716d968a18b1fec755886f7c03e94a02eb3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8e43c366192606df3f0d96ccd1984790b460e065...3a654716d968a18b1fec755886f7c03e94a02eb3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 12:59:33 2024
From: gitlab at gitlab.haskell.org (Brandon S. Allbery (@geekosaur))
Date: Thu, 24 Oct 2024 08:59:33 -0400
Subject: [Git][ghc/ghc][wip/geekosaur/clarify-cpp-2] further explanations of
 CPP options
Message-ID: <671a44b5c7293_8343e1a4ab44119@gitlab.mail>



Brandon S. Allbery pushed to branch wip/geekosaur/clarify-cpp-2 at Glasgow Haskell Compiler / GHC


Commits:
fdceb680 by brandon s allbery kf8nh at 2024-10-24T08:59:23-04:00
further explanations of CPP options

It was missing the ANSI "token pasting" behavior, which affects
users of -XMagicHash. It also explains why clang's -traditional
isn't sufficient for preprocessing Haskell code.

- - - - -


1 changed file:

- compiler/GHC/SysTools/Cpp.hs


Changes:

=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -72,17 +72,26 @@ Haskell source. This avoids the following situations:
 
   * Errors due to an ANSI C preprocessor lexing the source and failing on
     names with single quotes (TH quotes, ticked promoted constructors,
-    names with primes in them).
-
-  Both of those cases may be subtle: gcc and clang permit C++-style //
-  comments in C code, and Data.Array and Data.Vector both export a //
-  operator whose type is such that a removed "comment" may leave code that
-  typechecks but does the wrong thing. Another example is that, since ANSI
-  C permits long character constants, an expression involving multiple
-  functions with primes in their names may not expand macros properly when
-  they occur between the primed functions.
-
-Third special type of preprocessor for JavaScript was added laterly due to
+    names with primes in them);
+
+  * Errors due to ANSI "token pasting" semantics, which are triggered by
+    "#" characters (which affects code using -XMagicHash).
+
+All of those cases may be subtle: gcc and clang permit C++-style //
+comments in C code, and Data.Array and Data.Vector both export a //
+operator whose type is such that a removed "comment" may leave code that
+typechecks but does the wrong thing. Another example is that, since ANSI
+C permits long character constants, an expression involving multiple
+functions with primes in their names may not expand macros properly when
+they occur between the primed functions. Token pasting means # characters
+may be stripped and surrounding identifiers combined into single words.
+
+It should be noted that clang's -traditional doesn't disable // or token
+pasting; as a result, the ghc runtime installer tries very hard to find a
+gcc in order to use its preprocessor. If one can't be found, a programmer's
+only recourse is to use "-pgmP cpphs" (cpphs is on Hackage).
+
+A third special type of preprocessor for JavaScript was added later, due to
 needing to keep JSDoc comments and multiline comments. Various third party
 minifying software (for example, Google Closure Compiler) uses JSDoc
 information to apply more strict rules to code reduction which results in



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 13:04:13 2024
From: gitlab at gitlab.haskell.org (Brandon S. Allbery (@geekosaur))
Date: Thu, 24 Oct 2024 09:04:13 -0400
Subject: [Git][ghc/ghc][wip/geekosaur/clarify-cpp-2] further explanations of
 CPP options
Message-ID: <671a45cd2dc7d_8343e2917244932@gitlab.mail>



Brandon S. Allbery pushed to branch wip/geekosaur/clarify-cpp-2 at Glasgow Haskell Compiler / GHC


Commits:
0664f6b9 by brandon s allbery kf8nh at 2024-10-24T09:04:04-04:00
further explanations of CPP options

It was missing the ANSI "token pasting" behavior, which affects
users of -XMagicHash. It also explains why clang's -traditional
isn't sufficient for preprocessing Haskell code.

- - - - -


1 changed file:

- compiler/GHC/SysTools/Cpp.hs


Changes:

=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -72,17 +72,28 @@ Haskell source. This avoids the following situations:
 
   * Errors due to an ANSI C preprocessor lexing the source and failing on
     names with single quotes (TH quotes, ticked promoted constructors,
-    names with primes in them).
-
-  Both of those cases may be subtle: gcc and clang permit C++-style //
-  comments in C code, and Data.Array and Data.Vector both export a //
-  operator whose type is such that a removed "comment" may leave code that
-  typechecks but does the wrong thing. Another example is that, since ANSI
-  C permits long character constants, an expression involving multiple
-  functions with primes in their names may not expand macros properly when
-  they occur between the primed functions.
-
-Third special type of preprocessor for JavaScript was added laterly due to
+    names with primes in them);
+
+  * Errors due to ANSI "stringizing" (https://gcc.gnu.org/onlinedocs/cpp/Stringizing.html)
+    and token pasting (https://gcc.gnu.org/onlinedocs/cpp/Concatenation.html)
+    semantics, which are triggered by "#" characters (which affects code
+    using -XMagicHash).
+
+All of those cases may be subtle: gcc and clang permit C++-style //
+comments in C code, and Data.Array and Data.Vector both export a //
+operator whose type is such that a removed "comment" may leave code that
+typechecks but does the wrong thing. Another example is that, since ANSI
+C permits long character constants, an expression involving multiple
+functions with primes in their names may not expand macros properly when
+they occur between the primed functions. Token pasting means # characters
+may be stripped and surrounding identifiers combined into single words.
+
+It should be noted that clang's -traditional doesn't disable // or token
+pasting; as a result, the ghc runtime installer tries very hard to find a
+gcc in order to use its preprocessor. If one can't be found, a programmer's
+only recourse is to use "-pgmP cpphs" (cpphs is on Hackage).
+
+A third special type of preprocessor for JavaScript was added later, due to
 needing to keep JSDoc comments and multiline comments. Various third party
 minifying software (for example, Google Closure Compiler) uses JSDoc
 information to apply more strict rules to code reduction which results in



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0664f6b9b86c1c5c79253a0e1aca63a6cf2c603f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 13:24:22 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 24 Oct 2024 09:24:22 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] 82 commits: GHCi: fix improper
 location of ghci_history file
Message-ID: <671a4a8687ea2_8343e436804798a@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
fdf0adff by Sjoerd Visscher at 2024-10-24T15:01:22+02:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -


25 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9151799fbc754b204ddaff5f228d3f3fb19e8b3a...fdf0adfff2e860f265749f646baf5737d98cbc09

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9151799fbc754b204ddaff5f228d3f3fb19e8b3a...fdf0adfff2e860f265749f646baf5737d98cbc09
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 13:29:30 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Thu, 24 Oct 2024 09:29:30 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/rm-hscDecls
Message-ID: <671a4bba9f553_8343e552da08323@gitlab.mail>



Cheng Shao pushed new branch wip/rm-hscDecls at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rm-hscDecls
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 15:15:24 2024
From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge))
Date: Thu, 24 Oct 2024 11:15:24 -0400
Subject: [Git][ghc/ghc][wip/T23479] 84 commits: Changed import from Ghc. 
 module to L.H.S module
Message-ID: <671a648cc8835_314a551893687959c@gitlab.mail>



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


Commits:
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
cb4aaee1 by Serge S. Gulin at 2024-10-24T18:14:50+03:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -


25 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d0c0ea515c2e1d865240cfa4dec564a9d6442fb...cb4aaee1003053c65cc39454600d9d2c35b3acb7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d0c0ea515c2e1d865240cfa4dec564a9d6442fb...cb4aaee1003053c65cc39454600d9d2c35b3acb7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 15:43:21 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 24 Oct 2024 11:43:21 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/base-unit-hash
Message-ID: <671a6b192ba73_241dae19ec681264d@gitlab.mail>



Matthew Pickering pushed new branch wip/base-unit-hash at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/base-unit-hash
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 15:49:54 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 24 Oct 2024 11:49:54 -0400
Subject: [Git][ghc/ghc][wip/T25387] 11 commits: linker: add
 --optimistic-linking flag
Message-ID: <671a6ca21adcc_241dae2281c0178ab@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25387 at Glasgow Haskell Compiler / GHC


Commits:
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
00f0ef67 by Simon Peyton Jones at 2024-10-24T11:01:10+01:00
Fix optimisation of InstCo

- - - - -
fb9fe152 by Simon Peyton Jones at 2024-10-24T16:49:35+01:00
More wibbles

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Tickish.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/runtime_control.rst
- hadrian/bindist/Makefile
- hadrian/doc/flavours.md
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Settings/Flavours/Performance.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- rts/Linker.c
- rts/RtsFlags.c
- rts/include/rts/Flags.h
- rts/linker/elf_got.c
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs
- + testsuite/tests/determinism/T25304/Makefile
- + testsuite/tests/determinism/T25304/T25304a.stdout


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bca7e5f2c70ab6dca419a6852007da48f6610f6...fb9fe1522599542b8564339babbf64a06b24af3a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bca7e5f2c70ab6dca419a6852007da48f6610f6...fb9fe1522599542b8564339babbf64a06b24af3a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 16:02:20 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Thu, 24 Oct 2024 12:02:20 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <671a6f8c40483_158dc5bca7010068c@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
5d20a113 by Sebastian Graf at 2024-10-24T18:02:13+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d20a113f1843f5fc39443e3b8b504345e917435

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 16:09:15 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Thu, 24 Oct 2024 12:09:15 -0400
Subject: [Git][ghc/ghc][wip/T20749] Make DataCon workers strict in strict
 fields (#20749)
Message-ID: <671a712b676fe_158dc53e9ab81129b4@gitlab.mail>



Sebastian Graf pushed to branch wip/T20749 at Glasgow Haskell Compiler / GHC


Commits:
d034204a by Sebastian Graf at 2024-10-24T18:09:06+02:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Info.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 16:19:14 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 24 Oct 2024 12:19:14 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Concentrate boot extension logic in
 Finder
Message-ID: <671a738255b8c_158dc56163a41182c8@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
4d3d3a7d by Sjoerd Visscher at 2024-10-24T18:19:03+02:00
Concentrate boot extension logic in Finder

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Location.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -854,16 +854,14 @@ hsModuleToModSummary home_keys pn hsc_src modname
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation fopts modname
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
-                              (case hsc_src of
+                             (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
+                             hsc_src
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2123,31 +2123,16 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = unsafeEncodeUtf src_fn
+            (basename, extension) = splitExtension src_fn
 
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
+            hsc_src
+              | isHaskellSigSuffix (drop 1 extension) = HsigFile
+              | isHaskellBootSuffix (drop 1 extension) = HsBootFile
+              | otherwise = HsSrcFile
 
             -- Make a ModLocation for this file, adding the @-boot@ suffix to
             -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf extension) hsc_src
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
@@ -2239,7 +2224,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2242,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2252,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env imp is_boot pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Phases.hs
=====================================
@@ -23,6 +23,7 @@ module GHC.Driver.Phases (
    isDynLibSuffix,
    isHaskellUserSrcSuffix,
    isHaskellSigSuffix,
+   isHaskellBootSuffix,
    isSourceSuffix,
 
    isHaskellishTarget,
@@ -247,7 +248,8 @@ js_suffixes                  = [ "js" ]
 
 -- Will not be deleted as temp files:
 haskellish_user_src_suffixes =
-  haskellish_sig_suffixes ++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+  haskellish_sig_suffixes ++ haskellish_boot_suffixes ++ [ "hs", "lhs" ]
+haskellish_boot_suffixes     = [ "hs-boot", "lhs-boot" ]
 haskellish_sig_suffixes      = [ "hsig", "lhsig" ]
 backpackish_suffixes         = [ "bkp" ]
 
@@ -270,6 +272,7 @@ isHaskellishSuffix, isBackpackishSuffix, isHaskellSrcSuffix, isCishSuffix,
 isHaskellishSuffix     s = s `elem` haskellish_suffixes
 isBackpackishSuffix    s = s `elem` backpackish_suffixes
 isHaskellSigSuffix     s = s `elem` haskellish_sig_suffixes
+isHaskellBootSuffix    s = s `elem` haskellish_boot_suffixes
 isHaskellSrcSuffix     s = s `elem` haskellish_src_suffixes
 isCishSuffix           s = s `elem` cish_suffixes
 isJsSuffix             s = s `elem` js_suffixes


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,18 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+    let location1 = mkHomeModLocation fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) src_flavour
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -807,11 +801,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
         location5 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
     return location5
     where
       fopts = initFinderOpts dflags


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -896,9 +896,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,6 +15,7 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
@@ -157,6 +158,13 @@ findImportedModule hsc_env mod pkg_qual =
   in do
     findImportedModuleNoHsc fc fopts (hsc_unit_env hsc_env) mhome_unit mod pkg_qual
 
+findImportedModuleWithIsBoot :: HscEnv -> ModuleName -> IsBootInterface -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod is_boot pkg_qual = do
+  res <- findImportedModule hsc_env mod pkg_qual
+  case (res, is_boot) of
+    (Found loc mod, IsBoot) -> return (Found (addBootSuffixLocn loc) mod)
+    _ -> return res
+
 findImportedModuleNoHsc
   :: FinderCache
   -> FinderOpts
@@ -229,15 +237,19 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
-  case mhome_unit of
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
+  res <- case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
         -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
         -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
     _ -> findPackageModule fc unit_state fopts mod
+  case (res, is_boot) of
+    (InstalledFound loc, IsBoot) -> return (InstalledFound (addBootSuffixLocn loc))
+    _ -> return res
+
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -592,10 +604,12 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
-mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
-   in mkHomeModLocation2 dflags mod basename extension
+mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> FileExt -> HscSource -> ModLocation
+mkHomeModLocation dflags mod src_basename ext hsc_src =
+   let loc = mkHomeModLocation2 dflags mod src_basename ext
+   in case hsc_src of
+     HsBootFile -> addBootSuffixLocnOut loc
+     _ -> loc
 
 mkHomeModLocation2 :: FinderOpts
                    -> ModuleName


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,8 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
    , addBootSuffixLocn
    , addBootSuffixLocnOut
    , removeBootSuffix
@@ -99,26 +97,10 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
 -- | Add the @-boot@ suffix to all file paths associated with the module
 addBootSuffixLocn :: ModLocation -> ModLocation
 addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
+  = addBootSuffixLocnOut locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) }
 
 -- | Add the @-boot@ suffix to all output file paths associated with the
 -- module, not including the input file itself



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d3d3a7dc98a78db4c420acb1f107b6656397480

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 17:07:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 13:07:25 -0400
Subject: [Git][ghc/ghc][master] EPA: reduce [AddEpann] in AnnList
Message-ID: <671a7ecd5f969_158dc5872134124562@gitlab.mail>



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


Commits:
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T20718.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b1b0c6deab87bfc4d2b4ddfda40ed735c28cd53

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 17:08:02 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 13:08:02 -0400
Subject: [Git][ghc/ghc][master] Fix -fobject-determinism flag definition
Message-ID: <671a7ef267bc8_158dc5ad9d501291de@gitlab.mail>



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


Commits:
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -


1 changed file:

- compiler/GHC/Driver/Session.hs


Changes:

=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1291,8 +1291,6 @@ dynamic_flags_deps = [
         (NoArg (unSetGeneralFlag Opt_KeepOFiles))
 
         ------- Miscellaneous ----------------------------------------------
-  , make_ord_flag defGhcFlag "fobject-determinism"
-        (NoArg (setGeneralFlag Opt_ObjectDeterminism))
   , make_ord_flag defGhcFlag "no-auto-link-packages"
         (NoArg (unSetGeneralFlag Opt_AutoLinkPackages))
   , make_ord_flag defGhcFlag "no-hs-main"
@@ -2544,6 +2542,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "object-determinism"               Opt_ObjectDeterminism,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4a00731eda964ec551f920b0319b24db2073687c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 19:08:09 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Thu, 24 Oct 2024 15:08:09 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-bytecode-stubs
Message-ID: <671a9b1939fe7_158dc5f5319c138533@gitlab.mail>



Cheng Shao pushed new branch wip/fix-bytecode-stubs at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-bytecode-stubs
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 20:27:13 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Thu, 24 Oct 2024 16:27:13 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-7] 11 commits: Improve heap
 overflow exception message (#25198)
Message-ID: <671aada120f9c_158dc5152b97014654e@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-7 at Glasgow Haskell Compiler / GHC


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
3ea14480 by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

- - - - -
174e35b1 by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

- - - - -
af41b408 by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

- - - - -
5e20f1b5 by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

- - - - -
30b2afa3 by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Remove AddEpAnn from HsRuleAnn

- - - - -
2814fb1e by Alan Zimmerman at 2024-10-24T21:24:23+01:00
EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Avail.hs
- docs/users_guide/9.14.1-notes.rst
- + testsuite/tests/determinism/T25304/A.hs
- + testsuite/tests/determinism/T25304/B.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f333f133202deb7545ea0f83a633cba885fd4bf7...2814fb1e6c5b8c2ae92df12b966936ed130a907d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f333f133202deb7545ea0f83a633cba885fd4bf7...2814fb1e6c5b8c2ae92df12b966936ed130a907d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 24 22:10:51 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 24 Oct 2024 18:10:51 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: EPA: reduce
 [AddEpann] in AnnList
Message-ID: <671ac5eb94bb4_16778d3c7670103d1@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
c4a7510c by Sebastian Graf at 2024-10-24T18:10:41-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
a2b5152f by Sebastian Graf at 2024-10-24T18:10:42-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
bc67e7f7 by Simon Peyton Jones at 2024-10-24T18:10:45-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
07ff51df by Ryan Hendrickson at 2024-10-24T18:10:45-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b0207d72bf70ea6888d7851e108e9676b4a58d7b...07ff51dfc1052f1850abc997925acc414f604fbe

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b0207d72bf70ea6888d7851e108e9676b4a58d7b...07ff51dfc1052f1850abc997925acc414f604fbe
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 06:31:52 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 25 Oct 2024 02:31:52 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: CorePrep:
 Attach evaldUnfolding to floats to detect more values
Message-ID: <671b3b587f13f_2ce90e16a0e442738@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
7e50910d by Sebastian Graf at 2024-10-25T02:31:44-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
5307ec26 by Sebastian Graf at 2024-10-25T02:31:44-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
62997ea2 by Simon Peyton Jones at 2024-10-25T02:31:45-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
16a5f47e by Ryan Hendrickson at 2024-10-25T02:31:45-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07ff51dfc1052f1850abc997925acc414f604fbe...16a5f47eb265075cedd86888a5e5da6f167fcb21

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07ff51dfc1052f1850abc997925acc414f604fbe...16a5f47eb265075cedd86888a5e5da6f167fcb21
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 09:45:56 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 25 Oct 2024 05:45:56 -0400
Subject: [Git][ghc/ghc][wip/T25387] 3 commits: EPA: reduce [AddEpann] in
 AnnList
Message-ID: <671b68d44ca1a_26e245471ddc393aa@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25387 at Glasgow Haskell Compiler / GHC


Commits:
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
625b2609 by Simon Peyton Jones at 2024-10-25T10:45:22+01:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -


30 changed files:

- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Types/Basic.hs
- + testsuite/tests/dependent/should_compile/T25387.hs
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb9fe1522599542b8564339babbf64a06b24af3a...625b2609396c83117c73e72e24360bd130575bf9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb9fe1522599542b8564339babbf64a06b24af3a...625b2609396c83117c73e72e24360bd130575bf9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 09:51:45 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 25 Oct 2024 05:51:45 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T25391
Message-ID: <671b6a314c873_26e24556b8784112@gitlab.mail>



Simon Peyton Jones pushed new branch wip/T25391 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25391
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 11:02:29 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 25 Oct 2024 07:02:29 -0400
Subject: [Git][ghc/ghc][master] 2 commits: CorePrep: Attach evaldUnfolding to
 floats to detect more values
Message-ID: <671b7ac59007_26e245875ca85497@gitlab.mail>



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


Commits:
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs
- compiler/GHC/Stg/InferTags/Types.hs → compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/Pipeline.hs
- compiler/GHC/Stg/Syntax.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a00731eda964ec551f920b0319b24db2073687c...9f57c96d09dcafa8da4e6577a1226599d52c9955

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a00731eda964ec551f920b0319b24db2073687c...9f57c96d09dcafa8da4e6577a1226599d52c9955
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 11:02:53 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Fri, 25 Oct 2024 07:02:53 -0400
Subject: [Git][ghc/ghc][master] 2 commits: Some renaming
Message-ID: <671b7adde1051_26e24586bf28584eb@gitlab.mail>



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


Commits:
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- + testsuite/tests/deriving/should_compile/T20815.hs
- testsuite/tests/deriving/should_fail/T8851.hs → testsuite/tests/deriving/should_compile/T8851.hs
- testsuite/tests/deriving/should_compile/all.T
- + testsuite/tests/deriving/should_fail/T12768.hs
- + testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- + testsuite/tests/deriving/should_fail/T20815a.hs
- + testsuite/tests/deriving/should_fail/T20815a.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- − testsuite/tests/deriving/should_fail/T8851.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f57c96d09dcafa8da4e6577a1226599d52c9955...15a3456ba704c120f58816cab60264fd45e3413d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f57c96d09dcafa8da4e6577a1226599d52c9955...15a3456ba704c120f58816cab60264fd45e3413d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 16:36:04 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 25 Oct 2024 12:36:04 -0400
Subject: [Git][ghc/ghc][wip/T20264] Wibbles
Message-ID: <671bc8f4342f7_1cd39b18b8ac805d9@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
d0f30cc2 by Simon Peyton Jones at 2024-10-25T17:35:48+01:00
Wibbles

- - - - -


2 changed files:

- compiler/GHC/Core/Lint.hs
- compiler/GHC/Types/Id.hs


Changes:

=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -208,7 +208,7 @@ in GHC.Core.Opt.WorkWrap.Utils.  (Maybe there are other "clients" of this featur
   returns a substituted type.
 
 * When we encounter a binder (like x::a) we must apply the substitution
-  to the type of the binding variable.  lintBinders does this.
+  to the type of the binding variable.  lintLocalBinders does this.
 
 * Clearly we need to clone tyvar binders as we go.
 
@@ -554,7 +554,7 @@ Check a core binding, returning the list of variables bound.
 lintRecBindings :: TopLevelFlag -> [(Id, CoreExpr)]
                 -> ([LintedId] -> LintM a) -> LintM (a, [UsageEnv])
 lintRecBindings top_lvl pairs thing_inside
-  = lintIdBndrs top_lvl bndrs $ \ bndrs' ->
+  = lintBinders top_lvl LetBind bndrs $ \ bndrs' ->
     do { ues <- zipWithM lint_pair bndrs' rhss
        ; a <- thing_inside bndrs'
        ; return (a, ues) }
@@ -572,11 +572,16 @@ lintLetBody loc bndrs body
        ; mapM_ (lintJoinBndrType body_ty) bndrs
        ; return (body_ty, body_ue) }
 
-lintLetBind :: TopLevelFlag -> RecFlag -> LintedId
-              -> CoreExpr -> LintedType -> LintM ()
+lintLetBind :: TopLevelFlag -> RecFlag -> Var
+            -> CoreExpr -> LintedType -> LintM ()
 -- Binder's type, and the RHS, have already been linted
 -- This function checks other invariants
 lintLetBind top_lvl rec_flag binder rhs rhs_ty
+  | isTyVar binder
+  = pprTrace "lintLetBind: fill in" (ppr binder) $
+    return ()  -- Fill in!
+
+  | otherwise
   = do { let binder_ty = idType binder
        ; ensureEqTys binder_ty rhs_ty (mkRhsMsg binder (text "RHS") rhs_ty)
 
@@ -668,10 +673,14 @@ lintRhs :: Id -> CoreExpr -> LintM (LintedType, UsageEnv)
 -- NB: the Id can be Linted or not -- it's only used for
 --     its OccInfo and join-pointer-hood
 lintRhs bndr rhs
-    | JoinPoint arity <- idJoinPointHood bndr
-    = lintJoinLams arity (Just bndr) rhs
-    | AlwaysTailCalled arity <- tailCallInfo (idOccInfo bndr)
-    = lintJoinLams arity Nothing rhs
+  | isTyVar bndr
+  = pprTrace "lintRhs:fill in" (ppr bndr) $
+    return (varType bndr, zeroUE)  -- ToDo: fill in
+
+  | JoinPoint arity <- idJoinPointHood bndr
+  = lintJoinLams arity (Just bndr) rhs
+  | AlwaysTailCalled arity <- tailCallInfo (idOccInfo bndr)
+  = lintJoinLams arity Nothing rhs
 
 -- Allow applications of the data constructor @StaticPtr@ at the top
 -- but produce errors otherwise.
@@ -937,7 +946,7 @@ lintCoreExpr (Let (NonRec bndr rhs) body)
 
           -- See Note [Multiplicity of let binders] in Var
          -- Now lint the binder
-       ; lintBinder LetBind bndr $ \bndr' ->
+       ; lintLocalBinder LetBind bndr $ \bndr' ->
     do { lintLetBind NotTopLevel NonRecursive bndr' rhs rhs_ty
        ; addAliasUE bndr let_ue (lintLetBody (BodyOfLet bndr') [bndr'] body) } }
 
@@ -1090,7 +1099,7 @@ lintCoreFun expr nargs
 lintLambda :: Var -> LintM (Type, UsageEnv) -> LintM (Type, UsageEnv)
 lintLambda var lintBody =
     addLoc (LambdaBodyOf var) $
-    lintBinder LambdaBind var $ \ var' ->
+    lintLocalBinder LambdaBind var $ \ var' ->
     do { (body_ty, ue) <- lintBody
        ; ue' <- checkLinearity ue var'
        ; return (mkLamType var' body_ty, ue') }
@@ -1664,7 +1673,7 @@ lintCaseExpr scrut var alt_ty alts =
      ; ensureEqTys var_ty scrut_ty (mkScrutMsg var var_ty scrut_ty subst)
        -- See GHC.Core Note [Case expression invariants] item (7)
 
-     ; lintBinder CaseBind var $ \_ ->
+     ; lintLocalBinder CaseBind var $ \_ ->
        do { -- Check the alternatives
           ; alt_ues <- mapM (lintCoreAlt var scrut_ty scrut_mult alt_ty) alts
           ; let case_ue = (scaleUE scrut_mult scrut_ue) `addUE` supUEs alt_ues
@@ -1764,7 +1773,7 @@ lintCoreAlt case_bndr scrut_ty _scrut_mult alt_ty alt@(Alt (DataAlt con) args rh
           ; multiplicities = map binderMult $ fst $ splitPiTys con_payload_ty }
 
         -- And now bring the new binders into scope
-    ; lintBinders CasePatBind args $ \ args' -> do
+    ; lintLocalBinders CasePatBind args $ \ args' -> do
       {
         rhs_ue <- lintAltExpr rhs alt_ty
       ; rhs_ue' <- addLoc (CasePat alt) (lintAltBinders rhs_ue case_bndr scrut_ty con_payload_ty (zipEqual "lintCoreAlt" multiplicities  args'))
@@ -1808,22 +1817,32 @@ lintLinearBinder doc actual_usage described_usage
 ************************************************************************
 -}
 
+lintLocalBinders :: BindingSite -> [Var] -> ([Var] -> LintM a) -> LintM a
+lintLocalBinders = lintBinders NotTopLevel
+
+lintLocalBinder :: BindingSite -> Var -> (Var -> LintM a) -> LintM a
+lintLocalBinder = lintBinder NotTopLevel
+
+lintBinders :: TopLevelFlag -> BindingSite -> [Var] -> ([Var] -> LintM a) -> LintM a
 -- When we lint binders, we (one at a time and in order):
 --  1. Lint var types or kinds (possibly substituting)
 --  2. Add the binder to the in scope set, and if its a coercion var,
 --     we may extend the substitution to reflect its (possibly) new kind
-lintBinders :: BindingSite -> [Var] -> ([Var] -> LintM a) -> LintM a
-lintBinders _    []         linterF = linterF []
-lintBinders site (var:vars) linterF = lintBinder site var $ \var' ->
-                                      lintBinders site vars $ \ vars' ->
-                                      linterF (var':vars')
+lintBinders top_lvl site vars thing_inside
+  = go vars thing_inside
+  where
+    go :: [Var] -> ([Var] -> LintM a) -> LintM a
+    go []       thing_inside = thing_inside []
+    go (var:vars) thing_inside = lintBinder top_lvl site var $ \var' ->
+                                 go vars                     $ \vars' ->
+                                 thing_inside (var' : vars')
 
 -- If you edit this function, you may need to update the GHC formalism
 -- See Note [GHC Formalism]
-lintBinder :: BindingSite -> Var -> (Var -> LintM a) -> LintM a
-lintBinder site var linterF
+lintBinder :: TopLevelFlag -> BindingSite -> Var -> (Var -> LintM a) -> LintM a
+lintBinder top_lvl site var linterF
   | isTyCoVar var = lintTyCoBndr var linterF
-  | otherwise     = lintIdBndr NotTopLevel site var linterF
+  | otherwise     = lintIdBndr top_lvl site var linterF
 
 lintTyBndr :: TyVar -> (LintedTyCoVar -> LintM a) -> LintM a
 lintTyBndr = lintTyCoBndr  -- We could specialise it, I guess
@@ -1849,16 +1868,6 @@ lintTyCoBndr tcv thing_inside
 
        ; updateSubst subst' (thing_inside tcv') }
 
-lintIdBndrs :: forall a. TopLevelFlag -> [Id] -> ([LintedId] -> LintM a) -> LintM a
-lintIdBndrs top_lvl ids thing_inside
-  = go ids thing_inside
-  where
-    go :: [Id] -> ([Id] -> LintM a) -> LintM a
-    go []       thing_inside = thing_inside []
-    go (id:ids) thing_inside = lintIdBndr top_lvl LetBind id  $ \id' ->
-                               go ids                         $ \ids' ->
-                               thing_inside (id' : ids')
-
 lintIdBndr :: TopLevelFlag -> BindingSite
            -> InVar -> (OutVar -> LintM a) -> LintM a
 -- Do substitution on the type of a binder and add the var with this
@@ -2203,7 +2212,7 @@ lintCoreRule _ _ (BuiltinRule {})
 
 lintCoreRule fun fun_ty rule@(Rule { ru_name = name, ru_bndrs = bndrs
                                    , ru_args = args, ru_rhs = rhs })
-  = lintBinders LambdaBind bndrs $ \ _ ->
+  = lintLocalBinders LambdaBind bndrs $ \ _ ->
     do { (lhs_ty, _) <- lintCoreArgs (fun_ty, zeroUE) args
        ; (rhs_ty, _) <- case idJoinPointHood fun of
                      JoinPoint join_arity
@@ -2849,7 +2858,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches
 lint_branch :: TyCon -> CoAxBranch -> LintM ()
 lint_branch ax_tc (CoAxBranch { cab_tvs = tvs, cab_cvs = cvs
                               , cab_lhs = lhs_args, cab_rhs = rhs })
-  = lintBinders LambdaBind (tvs ++ cvs) $ \_ ->
+  = lintLocalBinders LambdaBind (tvs ++ cvs) $ \_ ->
     do { let lhs = mkTyConApp ax_tc lhs_args
        ; lhs' <- lintType lhs
        ; rhs' <- lintType rhs


=====================================
compiler/GHC/Types/Id.hs
=====================================
@@ -921,7 +921,7 @@ setIdLFInfo id lf = modifyIdInfo (`setLFInfo` lf) id
 
         ---------------------------------
         -- Occurrence INFO
-idOccInfo :: Id -> OccInfo
+idOccInfo :: HasDebugCallStack => Id -> OccInfo
 idOccInfo id = occInfo (idInfo id)
 
 setIdOccInfo :: Id -> OccInfo -> Id



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 16:37:53 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Fri, 25 Oct 2024 12:37:53 -0400
Subject: [Git][ghc/ghc][wip/T25387] Fix optimisation of InstCo
Message-ID: <671bc96196eb6_1cd39b1c2cd080733@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T25387 at Glasgow Haskell Compiler / GHC


Commits:
0740c45f by Simon Peyton Jones at 2024-10-25T17:37:17+01:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -


9 changed files:

- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/Types/Basic.hs
- + testsuite/tests/dependent/should_compile/T25387.hs
- testsuite/tests/dependent/should_compile/all.T


Changes:

=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -30,7 +30,7 @@ module GHC.Core.Coercion (
         coercionRole, coercionKindRole,
 
         -- ** Constructing coercions
-        mkGReflCo, mkReflCo, mkRepReflCo, mkNomReflCo,
+        mkGReflCo, mkGReflMCo, mkReflCo, mkRepReflCo, mkNomReflCo,
         mkCoVarCo, mkCoVarCos,
         mkAxInstCo, mkUnbranchedAxInstCo,
         mkAxInstRHS, mkUnbranchedAxInstRHS,
@@ -334,8 +334,23 @@ isGReflMCo _ = False
 mkGReflCo :: Role -> Type -> MCoercionN -> Coercion
 mkGReflCo r ty mco
   | isGReflMCo mco = if r == Nominal then Refl ty
-                     else GRefl r ty MRefl
-  | otherwise    = GRefl r ty mco
+                                     else GRefl r ty MRefl
+  | otherwise
+  = -- I'd like to have this assert, but sadly it's not true during type
+    -- inference because the types are not fully zonked
+    -- assertPpr (case mco of
+    --              MCo co -> typeKind ty `eqType` coercionLKind co
+    --              MRefl  -> True)
+    --          (vcat [ text "ty" <+> ppr ty <+> dcolon <+> ppr (typeKind ty)
+    --                , case mco of
+    --                     MCo co -> text "co" <+> ppr co
+    --                                  <+> dcolon <+> ppr (coercionKind co)
+    --                     MRefl  -> text "MRefl"
+    --                , callStackDoc ]) $
+    GRefl r ty mco
+
+mkGReflMCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion
+mkGReflMCo r ty co = mkGReflCo r ty (MCo co)
 
 -- | Compose two MCoercions via transitivity
 mkTransMCo :: MCoercion -> MCoercion -> MCoercion
@@ -1129,14 +1144,19 @@ mkSymCo co@(ForAllCo { fco_kind = kco, fco_body = body_co })
   | isReflCo kco           = co { fco_body = mkSymCo body_co }
 mkSymCo co                 = SymCo co
 
--- | Create a new 'Coercion' by composing the two given 'Coercion's transitively.
---   (co1 ; co2)
-mkTransCo :: Coercion -> Coercion -> Coercion
-mkTransCo co1 co2 | isReflCo co1 = co2
-                  | isReflCo co2 = co1
-mkTransCo (GRefl r t1 (MCo co1)) (GRefl _ _ (MCo co2))
-  = GRefl r t1 (MCo $ mkTransCo co1 co2)
-mkTransCo co1 co2                = TransCo co1 co2
+-- | mkTransCo creates a new 'Coercion' by composing the two
+--   given 'Coercion's transitively: (co1 ; co2)
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+mkTransCo co1 co2
+   | isReflCo co1 = co2
+   | isReflCo co2 = co1
+
+   | GRefl r t1 (MCo kco1) <- co1
+   , GRefl _ _  (MCo kco2) <- co2
+   = GRefl r t1 (MCo $ mkTransCo kco1 kco2)
+
+   | otherwise
+   = TransCo co1 co2
 
 --------------------
 {- Note [mkSelCo precondition]
@@ -1296,7 +1316,7 @@ mkGReflRightCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise = GRefl r ty (MCo co)
+  | otherwise = mkGReflMCo r ty co
 
 -- | Given @r@, @ty :: k1@, and @co :: k1 ~N k2@,
 -- produces @co' :: (ty |> co) ~r ty@
@@ -1305,7 +1325,7 @@ mkGReflLeftCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise    = mkSymCo $ GRefl r ty (MCo co)
+  | otherwise    = mkSymCo $ mkGReflMCo r ty co
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty ~r ty'@,
 -- produces @co' :: (ty |> co) ~r ty'
@@ -1314,16 +1334,16 @@ mkGReflLeftCo r ty co
 mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceLeftCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = (mkSymCo $ GRefl r ty (MCo co)) `mkTransCo` co2
+  | otherwise    = (mkSymCo $ mkGReflMCo r ty co) `mkTransCo` co2
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty' ~r ty@,
 -- produces @co' :: ty' ~r (ty |> co)
 -- It is not only a utility function, but it saves allocation when co
 -- is a GRefl coercion.
-mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
+mkCoherenceRightCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceRightCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = co2 `mkTransCo` GRefl r ty (MCo co)
+  | otherwise    = co2 `mkTransCo` mkGReflMCo r ty co
 
 -- | Given @co :: (a :: k) ~ (b :: k')@ produce @co' :: k ~ k'@.
 mkKindCo :: Coercion -> Coercion
@@ -1682,8 +1702,8 @@ castCoercionKind1 g r t1 t2 h
                  mkNomReflCo (mkCastTy t2 h)
       GRefl _ _ mco -> case mco of
            MRefl       -> mkReflCo r (mkCastTy t2 h)
-           MCo kind_co -> GRefl r (mkCastTy t1 h) $
-                          MCo (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
+           MCo kind_co -> mkGReflMCo r (mkCastTy t1 h)
+                               (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
       _ -> castCoercionKind2 g r t1 t2 h h
 
 -- | Creates a new coercion with both of its types casted by different casts
@@ -2110,10 +2130,10 @@ zapLiftingContext :: LiftingContext -> LiftingContext
 zapLiftingContext (LC subst _) = LC (zapSubst subst) emptyVarEnv
 
 -- | Like 'substForAllCoBndr', but works on a lifting context
-substForAllCoBndrUsingLC :: Bool
-                            -> (Coercion -> Coercion)
-                            -> LiftingContext -> TyCoVar -> Coercion
-                            -> (LiftingContext, TyCoVar, Coercion)
+substForAllCoBndrUsingLC :: SwapFlag
+                         -> (Coercion -> Coercion)
+                         -> LiftingContext -> TyCoVar -> Coercion
+                         -> (LiftingContext, TyCoVar, Coercion)
 substForAllCoBndrUsingLC sym sco (LC subst lc_env) tv co
   = (LC subst' lc_env, tv', co')
   where
@@ -2691,7 +2711,7 @@ mkNomPrimEqPred k ty1 ty2 = mkTyConApp eqPrimTyCon [k, k, ty1, ty2]
 -- transitivity over coercion applications, where splitting two
 -- AppCos might yield different kinds. See Note [EtaAppCo] in
 -- "GHC.Core.Coercion.Opt".
-buildCoercion :: Type -> Type -> CoercionN
+buildCoercion :: HasDebugCallStack => Type -> Type -> CoercionN
 buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
   where
     go ty1 ty2 | Just ty1' <- coreView ty1 = go ty1' ty2
@@ -2719,7 +2739,10 @@ buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
         mkFunCo Nominal af1 (go w1 w2) (go arg1 arg2) (go res1 res2)
 
     go (TyConApp tc1 args1) (TyConApp tc2 args2)
-      = assert (tc1 == tc2) $
+      = assertPpr (tc1 == tc2) (vcat [ ppr tc1 <+> ppr tc2
+                                     , text "orig_ty1:" <+> ppr orig_ty1
+                                     , text "orig_ty2:" <+> ppr orig_ty2
+                                     ]) $
         mkTyConAppCo Nominal tc1 (zipWith go args1 args2)
 
     go (AppTy ty1a ty1b) ty2


=====================================
compiler/GHC/Core/Coercion.hs-boot
=====================================
@@ -24,7 +24,7 @@ mkCoVarCo :: CoVar -> Coercion
 mkPhantomCo :: Coercion -> Type -> Type -> Coercion
 mkUnivCo :: UnivCoProvenance -> [Coercion] -> Role -> Type -> Type -> Coercion
 mkSymCo :: Coercion -> Coercion
-mkTransCo :: Coercion -> Coercion -> Coercion
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
 mkSelCo :: HasDebugCallStack => CoSel -> Coercion -> Coercion
 mkLRCo :: LeftOrRight -> Coercion -> Coercion
 mkInstCo :: Coercion -> Coercion -> Coercion


=====================================
compiler/GHC/Core/Coercion/Opt.hs
=====================================
@@ -21,6 +21,7 @@ import GHC.Core.TyCon
 import GHC.Core.Coercion.Axiom
 import GHC.Core.Unify
 
+import GHC.Types.Basic( SwapFlag(..), flipSwap, isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -66,32 +67,55 @@ opt_co2.
 
 Note [Optimising InstCo]
 ~~~~~~~~~~~~~~~~~~~~~~~~
-(1) tv is a type variable
-When we have (InstCo (ForAllCo tv h g) g2), we want to optimise.
+Optimising InstCo is pretty subtle: #15725, #25387.
 
-Let's look at the typing rules.
+(1) tv is a type variable. We want to optimise
 
-h : k1 ~ k2
-tv:k1 |- g : t1 ~ t2
------------------------------
-ForAllCo tv h g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym h])
+  InstCo (ForAllCo tv kco g) g2  -->   S(g)
 
-g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
-g2 : s1 ~ s2
---------------------
-InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+where S is some substitution. Let's look at the typing rules.
 
-We thus want some coercion proving this:
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    -----------------------------
+    ForAllCo tv kco g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym kco])
+
+    g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+
+Putting these two together
 
-  (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym h])
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo (ForAllCo tv kco g) g2 : t1[tv |-> s1] ~ t2[tv |-> s2 |> sym kco]
 
-If we substitute the *type* tv for the *coercion*
-(g2 ; t2 ~ t2 |> sym h) in g, we'll get this result exactly.
-This is bizarre,
-though, because we're substituting a type variable with a coercion. However,
-this operation already exists: it's called *lifting*, and defined in GHC.Core.Coercion.
-We just need to enhance the lifting operation to be able to deal with
-an ambient substitution, which is why a LiftingContext stores a TCvSubst.
+We thus want S(g) to have kind
+
+  S(g) :: (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym kco])
+
+All we need do is to substitute the coercion tv_co for tv:
+  S = [tv :-> tv_co]
+where
+  tv_co : s1 ~ (s2 |> sym kco)
+This looks bizarre, because we're substituting a /type variable/ with a
+/coercion/. However, this operation already exists: it's called *lifting*, and
+defined in GHC.Core.Coercion.  We just need to enhance the lifting operation to
+be able to deal with an ambient substitution, which is why a LiftingContext
+stores a TCvSubst.
+
+In general if
+  S = [tv :-> tv_co]
+  tv_co : r1 ~ r2
+  g     : t1 ~ t2
+then
+  S(g) : t1[tv :-> r1] ~ t2[tv :-> r2]
+
+The substitution S is embodied in the LiftingContext argument of `opt_co4`;
+See Note [The LiftingContext in optCoercion]
 
 (2) cv is a coercion variable
 Now consider we have (InstCo (ForAllCo cv h g) g2), we want to optimise.
@@ -117,6 +141,27 @@ We thus want some coercion proving this:
 
 So we substitute the coercion variable c for the coercion
 (h1 ~N (n1; h2; sym n2)) in g.
+
+Note [The LiftingContext in optCoercion]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+To suppport Note [Optimising InstCo] the coercion optimiser carries a
+GHC.Core.Coercion.LiftingContext, which comprises
+  * An ordinary Subst
+  * The `lc_env`: a mapping from /type variables/ to /coercions/
+
+We don't actually have a separate function
+   liftCoSubstCo :: LiftingContext -> Coercion -> Coercion
+The substitution of a type variable by a coercion is done by the calls to
+`liftCoSubst` (on a type) in the Refl and GRefl cases of `opt_co4`.
+
+We use the following invariants:
+ (LC1) The coercions in the range of `lc_env` have already had all substitutions
+       applied; they are "OutCoercions".  If you re-optimise these coercions, you
+       must zap the LiftingContext first.
+
+ (LC2) However they have /not/ had the "ambient sym" (the second argument of
+       `opt_co4`) applied.  The ambient sym applies to the entire coercion not
+       to the little bits being substituted.
 -}
 
 -- | Coercion optimisation options
@@ -147,7 +192,7 @@ optCoercion opts env co
 optCoercion' :: Subst -> Coercion -> NormalCo
 optCoercion' env co
   | debugIsOn
-  = let out_co = opt_co1 lc False co
+  = let out_co = opt_co1 lc NotSwapped co
         (Pair in_ty1  in_ty2,  in_role)  = coercionKindRole co
         (Pair out_ty1 out_ty2, out_role) = coercionKindRole out_co
 
@@ -170,7 +215,7 @@ optCoercion' env co
     out_co
 
   | otherwise
-  = opt_co1 lc False co
+  = opt_co1 lc NotSwapped co
   where
     lc = mkSubstLiftingContext env
 --    ppr_one cv = ppr cv <+> dcolon <+> ppr (coVarKind cv)
@@ -184,41 +229,38 @@ type NormalCo    = Coercion
 
 type NormalNonIdCo = NormalCo  -- Extra invariant: not the identity
 
--- | Do we apply a @sym@ to the result?
-type SymFlag = Bool
-
 -- | Do we force the result to be representational?
 type ReprFlag = Bool
 
 -- | Optimize a coercion, making no assumptions. All coercions in
 -- the lifting context are already optimized (and sym'd if nec'y)
 opt_co1 :: LiftingContext
-        -> SymFlag
+        -> SwapFlag   -- IsSwapped => apply Sym to the result
         -> Coercion -> NormalCo
 opt_co1 env sym co = opt_co2 env sym (coercionRole co) co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's role. No other assumptions.
 opt_co2 :: LiftingContext
-        -> SymFlag
-        -> Role   -- ^ The role of the input coercion
+        -> SwapFlag   -- ^IsSwapped => apply Sym to the result
+        -> Role       -- ^ The role of the input coercion
         -> Coercion -> NormalCo
 opt_co2 env sym Phantom co = opt_phantom env sym co
-opt_co2 env sym r       co = opt_co4_wrap env sym False r co
+opt_co2 env sym r       co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's non-Phantom role,
 --   and with an optional downgrade
-opt_co3 :: LiftingContext -> SymFlag -> Maybe Role -> Role -> Coercion -> NormalCo
+opt_co3 :: LiftingContext -> SwapFlag -> Maybe Role -> Role -> Coercion -> NormalCo
 opt_co3 env sym (Just Phantom)          _ co = opt_phantom env sym co
-opt_co3 env sym (Just Representational) r co = opt_co4_wrap env sym True  r co
+opt_co3 env sym (Just Representational) r co = opt_co4 env sym True  r co
   -- if mrole is Just Nominal, that can't be a downgrade, so we can ignore
-opt_co3 env sym _                       r co = opt_co4_wrap env sym False r co
+opt_co3 env sym _                       r co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a non-phantom coercion.
-opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
-                      -> Role -> Coercion -> NormalCo
+opt_co4, opt_co4' :: LiftingContext -> SwapFlag -> ReprFlag
+                  -> Role -> Coercion -> NormalCo
 -- Precondition:  In every call (opt_co4 lc sym rep role co)
 --                we should have role = coercionRole co
 -- Precondition:  role is not Phantom
@@ -227,20 +269,20 @@ opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
 --                 where wrapsym is SymCo if sym=True
 --                       wrapsub is SubCo if rep=True
 
--- opt_co4_wrap is there just to support tracing, when debugging
--- Usually it just goes straight to opt_co4
-opt_co4_wrap = opt_co4
+-- opt_co4 is there just to support tracing, when debugging
+-- Usually it just goes straight to opt_co4'
+opt_co4 = opt_co4'
 
 {-
-opt_co4_wrap env sym rep r co
-  = pprTrace "opt_co4_wrap {"
+opt_co4 env sym rep r co
+  = pprTrace "opt_co4 {"
    ( vcat [ text "Sym:" <+> ppr sym
           , text "Rep:" <+> ppr rep
           , text "Role:" <+> ppr r
           , text "Co:" <+> ppr co ]) $
    assert (r == coercionRole co )    $
-   let result = opt_co4 env sym rep r co in
-   pprTrace "opt_co4_wrap }" (ppr co $$ text "---" $$ ppr result) $
+   let result = opt_co4' env sym rep r co in
+   pprTrace "opt_co4 }" (ppr co $$ text "---" $$ ppr result) $
    assertPpr (res_role == coercionRole result)
              (vcat [ text "Role:" <+> ppr r
                    , text "Result: " <+>  ppr result
@@ -252,40 +294,45 @@ opt_co4_wrap env sym rep r co
              | otherwise = r
 -}
 
-opt_co4 env _   rep r (Refl ty)
+opt_co4' env sym rep r (Refl ty)
   = assertPpr (r == Nominal)
               (text "Expected role:" <+> ppr r    $$
                text "Found role:" <+> ppr Nominal $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env _   rep r (GRefl _r ty MRefl)
+opt_co4' env sym rep r (GRefl _r ty MRefl)
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env sym  rep r (GRefl _r ty (MCo co))
+opt_co4' env sym  rep r (GRefl _r ty (MCo kco))
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    if isGReflCo co || isGReflCo co'
-    then liftCoSubst r' env ty
-    else wrapSym sym $ mkCoherenceRightCo r' ty' co' (liftCoSubst r' env ty)
+    if isGReflCo kco || isGReflCo kco'
+    then wrapSym sym ty_co
+    else wrapSym sym $ mk_coherence_right_co r' (coercionRKind ty_co) kco' ty_co
+            -- ty :: k1
+            -- kco :: k1 ~ k2
+            -- Desired result coercion:   ty ~ ty |> co
   where
-    r'  = chooseRole rep r
-    ty' = substTy (lcSubstLeft env) ty
-    co' = opt_co4 env False False Nominal co
+    r'    = chooseRole rep r
+    ty_co = liftCoSubst r' env ty
+    kco'  = opt_co4 env NotSwapped False Nominal kco
 
-opt_co4 env sym rep r (SymCo co)  = opt_co4_wrap env (not sym) rep r co
+opt_co4' env sym rep r (SymCo co)  = opt_co4 env (flipSwap sym) rep r co
   -- surprisingly, we don't have to do anything to the env here. This is
   -- because any "lifting" substitutions in the env are tied to ForAllCos,
   -- which treat their left and right sides differently. We don't want to
   -- exchange them.
 
-opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
+opt_co4' env sym rep r g@(TyConAppCo _r tc cos)
   = assert (r == _r) $
     case (rep, r) of
       (True, Nominal) ->
@@ -295,7 +342,7 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                (repeat Nominal)
                                cos)
       (False, Nominal) ->
-        mkTyConAppCo Nominal tc (map (opt_co4_wrap env sym False Nominal) cos)
+        mkTyConAppCo Nominal tc (map (opt_co4 env sym False Nominal) cos)
       (_, Representational) ->
                       -- must use opt_co2 here, because some roles may be P
                       -- See Note [Optimising coercion optimisation]
@@ -304,34 +351,35 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                    cos)
       (_, Phantom) -> pprPanic "opt_co4 sees a phantom!" (ppr g)
 
-opt_co4 env sym rep r (AppCo co1 co2)
-  = mkAppCo (opt_co4_wrap env sym rep r co1)
-            (opt_co4_wrap env sym False Nominal co2)
+opt_co4' env sym rep r (AppCo co1 co2)
+  = mkAppCo (opt_co4 env sym rep r co1)
+            (opt_co4 env sym False Nominal co2)
 
-opt_co4 env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
+opt_co4' env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
                                 , fco_kind = k_co, fco_body = co })
   = case optForAllCoBndr env sym tv k_co of
       (env', tv', k_co') -> mkForAllCo tv' visL' visR' k_co' $
-                            opt_co4_wrap env' sym rep r co
+                            opt_co4 env' sym rep r co
      -- Use the "mk" functions to check for nested Refls
   where
     !(visL', visR') = swapSym sym (visL, visR)
 
-opt_co4 env sym rep r (FunCo _r afl afr cow co1 co2)
+opt_co4' env sym rep r (FunCo _r afl afr cow co1 co2)
   = assert (r == _r) $
     mkFunCo2 r' afl' afr' cow' co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     cow' = opt_co1 env sym cow
     !r' | rep       = Representational
         | otherwise = r
     !(afl', afr') = swapSym sym (afl, afr)
 
-opt_co4 env sym rep r (CoVarCo cv)
+opt_co4' env sym rep r (CoVarCo cv)
   | Just co <- lcLookupCoVar env cv   -- see Note [Forall over coercion] for why
                                       -- this is the right thing here
-  = opt_co4_wrap (zapLiftingContext env) sym rep r co
+  = -- pprTrace "CoVarCo" (ppr cv $$ ppr co) $
+    opt_co4 (zapLiftingContext env) sym rep r co
 
   | ty1 `eqType` ty2   -- See Note [Optimise CoVarCo to Refl]
   = mkReflCo (chooseRole rep r) ty1
@@ -352,10 +400,10 @@ opt_co4 env sym rep r (CoVarCo cv)
                           cv
           -- cv1 might have a substituted kind!
 
-opt_co4 _ _ _ _ (HoleCo h)
+opt_co4' _ _ _ _ (HoleCo h)
   = pprPanic "opt_univ fell into a hole" (ppr h)
 
-opt_co4 env sym rep r (AxiomCo con cos)
+opt_co4' env sym rep r (AxiomCo con cos)
     -- Do *not* push sym inside top-level axioms
     -- e.g. if g is a top-level axiom
     --   g a : f a ~ a
@@ -365,25 +413,25 @@ opt_co4 env sym rep r (AxiomCo con cos)
     wrapSym sym $
                        -- some sub-cos might be P: use opt_co2
                        -- See Note [Optimising coercion optimisation]
-    AxiomCo con (zipWith (opt_co2 env False)
+    AxiomCo con (zipWith (opt_co2 env NotSwapped)
                          (coAxiomRuleArgRoles con)
                          cos)
       -- Note that the_co does *not* have sym pushed into it
 
-opt_co4 env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
+opt_co4' env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
                               , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps (chooseRole rep r) t1 t2
 
-opt_co4 env sym rep r (TransCo co1 co2)
-                      -- sym (g `o` h) = sym h `o` sym g
-  | sym       = opt_trans in_scope co2' co1'
-  | otherwise = opt_trans in_scope co1' co2'
+opt_co4' env sym rep r (TransCo co1 co2)
+  -- sym (g `o` h) = sym h `o` sym g
+  | isSwapped sym = opt_trans in_scope co2' co1'
+  | otherwise     = opt_trans in_scope co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     in_scope = lcInScopeSet env
 
-opt_co4 env sym rep r (SelCo cs co)
+opt_co4' env sym rep r (SelCo cs co)
   -- Historical note 1: we used to check `co` for Refl, TyConAppCo etc
   -- before optimising `co`; but actually the SelCo will have been built
   -- with mkSelCo, so these tests always fail.
@@ -393,19 +441,19 @@ opt_co4 env sym rep r (SelCo cs co)
   -- and (b) wrapRole uses mkSubCo which does much the same job
   = wrapRole rep r $ mkSelCo cs $ opt_co1 env sym co
 
-opt_co4 env sym rep r (LRCo lr co)
+opt_co4' env sym rep r (LRCo lr co)
   | Just pr_co <- splitAppCo_maybe co
   = assert (r == Nominal )
-    opt_co4_wrap env sym rep Nominal (pick_lr lr pr_co)
+    opt_co4 env sym rep Nominal (pick_lr lr pr_co)
   | Just pr_co <- splitAppCo_maybe co'
   = assert (r == Nominal) $
     if rep
-    then opt_co4_wrap (zapLiftingContext env) False True Nominal (pick_lr lr pr_co)
+    then opt_co4 (zapLiftingContext env) NotSwapped True Nominal (pick_lr lr pr_co)
     else pick_lr lr pr_co
   | otherwise
   = wrapRole rep Nominal $ LRCo lr co'
   where
-    co' = opt_co4_wrap env sym False Nominal co
+    co' = opt_co4 env sym False Nominal co
 
     pick_lr CLeft  (l, _) = l
     pick_lr CRight (_, r) = r
@@ -445,66 +493,68 @@ So we extend the environment binding cv to arg's left-hand type.
 -}
 
 -- See Note [Optimising InstCo]
-opt_co4 env sym rep r (InstCo co1 arg)
+opt_co4' env sym rep r (InstCo fun_co arg_co)
     -- forall over type...
-  | Just (tv, _visL, _visR, kind_co, co_body) <- splitForAllCo_ty_maybe co1
-  = opt_co4_wrap (extendLiftingContext env tv
-                    (mkCoherenceRightCo Nominal t2 (mkSymCo kind_co) sym_arg))
-                   -- mkSymCo kind_co :: k1 ~ k2
-                   -- sym_arg :: (t1 :: k1) ~ (t2 :: k2)
-                   -- tv |-> (t1 :: k1) ~ (((t2 :: k2) |> (sym kind_co)) :: k1)
-                 sym rep r co_body
+  | Just (tv, _visL, _visR, k_co, body_co) <- splitForAllCo_ty_maybe fun_co
+    -- tv      :: k1
+    -- k_co    :: k1 ~ k2
+    -- body_co :: t1 ~ t2
+    -- arg_co  :: (s1:k1) ~ (s2:k2)
+  , let arg_co'  = opt_co4 env NotSwapped False Nominal arg_co
+                  -- Do /not/ push Sym into the arg_co, hence sym=False
+                  -- see (LC2) of Note [The LiftingContext in optCoercion]
+        k_co' = opt_co4 env NotSwapped False Nominal k_co
+        s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+                   -- mkSymCo kind_co :: k2 ~ k1
+                   -- tv_co   :: (s1 :: k1) ~ (((s2 :: k2) |> (sym kind_co)) :: k1)
+  = opt_co4 (extendLiftingContext env tv tv_co) sym rep r body_co
 
     -- See Note [Forall over coercion]
-  | Just (cv, _visL, _visR, _kind_co, co_body) <- splitForAllCo_co_maybe co1
-  , CoercionTy h1 <- t1
-  = opt_co4_wrap (extendLiftingContextCvSubst env cv h1) sym rep r co_body
+  | Just (cv, _visL, _visR, _kind_co, body_co) <- splitForAllCo_co_maybe fun_co
+  , CoercionTy h1 <- coercionLKind arg_co
+  , let h1' = opt_co4 env NotSwapped False Nominal h1
+  = opt_co4 (extendLiftingContextCvSubst env cv h1') sym rep r body_co
 
-    -- See if it is a forall after optimization
-    -- If so, do an inefficient one-variable substitution, then re-optimize
+  -- OK so those cases didn't work.  See if it is a forall /after/ optimization
+  -- If so, do an inefficient one-variable substitution, then re-optimize
 
     -- forall over type...
-  | Just (tv', _visL, _visR, kind_co', co_body') <- splitForAllCo_ty_maybe co1'
-  = opt_co4_wrap (extendLiftingContext (zapLiftingContext env) tv'
-                    (mkCoherenceRightCo Nominal t2' (mkSymCo kind_co') arg'))
-            False False r' co_body'
+  | Just (tv', _visL, _visR, k_co', body_co') <- splitForAllCo_ty_maybe fun_co'
+  , let s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+        env'  = extendLiftingContext (zapLiftingContext env) tv' tv_co
+  = opt_co4 env' NotSwapped False r' body_co'
 
     -- See Note [Forall over coercion]
-  | Just (cv', _visL, _visR, _kind_co', co_body') <- splitForAllCo_co_maybe co1'
-  , CoercionTy h1' <- t1'
-  = opt_co4_wrap (extendLiftingContextCvSubst (zapLiftingContext env) cv' h1')
-                    False False r' co_body'
+  | Just (cv', _visL, _visR, _kind_co', body_co') <- splitForAllCo_co_maybe fun_co'
+  , CoercionTy h1' <- coercionLKind arg_co'
+  , let env' = extendLiftingContextCvSubst (zapLiftingContext env) cv' h1'
+  = opt_co4 env' NotSwapped False r' body_co'
+
+  -- Those cases didn't work either, so rebuild the InstCo
+  -- Push Sym into /both/ function /and/ arg_coument
+  | otherwise = InstCo fun_co' arg_co'
 
-  | otherwise = InstCo co1' arg'
   where
-    co1'    = opt_co4_wrap env sym rep r co1
-    r'      = chooseRole rep r
-    arg'    = opt_co4_wrap env sym False Nominal arg
-    sym_arg = wrapSym sym arg'
-
-    -- Performance note: don't be alarmed by the two calls to coercionKind
-    -- here, as only one call to coercionKind is actually demanded per guard.
-    -- t1/t2 are used when checking if co1 is a forall, and t1'/t2' are used
-    -- when checking if co1' (i.e., co1 post-optimization) is a forall.
-    --
-    -- t1/t2 must come from sym_arg, not arg', since it's possible that arg'
-    -- might have an extra Sym at the front (after being optimized) that co1
-    -- lacks, so we need to use sym_arg to balance the number of Syms. (#15725)
-    Pair t1  t2  = coercionKind sym_arg
-    Pair t1' t2' = coercionKind arg'
-
-opt_co4 env sym _rep r (KindCo co)
+    -- fun_co' arg_co' are both optimised, /and/ we have pushed `sym` into both
+    -- So no more sym'ing on th results of fun_co' arg_co'
+    fun_co' = opt_co4 env sym rep r fun_co
+    arg_co' = opt_co4 env sym False Nominal arg_co
+    r'   = chooseRole rep r
+
+opt_co4' env sym _rep r (KindCo co)
   = assert (r == Nominal) $
     let kco' = promoteCoercion co in
     case kco' of
       KindCo co' -> promoteCoercion (opt_co1 env sym co')
-      _          -> opt_co4_wrap env sym False Nominal kco'
+      _          -> opt_co4 env sym False Nominal kco'
   -- This might be able to be optimized more to do the promotion
   -- and substitution/optimization at the same time
 
-opt_co4 env sym _ r (SubCo co)
+opt_co4' env sym _ r (SubCo co)
   = assert (r == Representational) $
-    opt_co4_wrap env sym True Nominal co
+    opt_co4 env sym True Nominal co
 
 {- Note [Optimise CoVarCo to Refl]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -518,7 +568,7 @@ in GHC.Core.Coercion.
 -------------
 -- | Optimize a phantom coercion. The input coercion may not necessarily
 -- be a phantom, but the output sure will be.
-opt_phantom :: LiftingContext -> SymFlag -> Coercion -> NormalCo
+opt_phantom :: LiftingContext -> SwapFlag -> Coercion -> NormalCo
 opt_phantom env sym (UnivCo { uco_prov = prov, uco_lty = t1
                             , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps Phantom t1 t2
@@ -559,7 +609,7 @@ See #19509.
 
  -}
 
-opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance
+opt_univ :: LiftingContext -> SwapFlag -> UnivCoProvenance
          -> [Coercion]
          -> Role -> Type -> Type -> Coercion
 opt_univ env sym prov deps role ty1 ty2
@@ -640,11 +690,19 @@ opt_transList :: HasDebugCallStack => InScopeSet -> [NormalCo] -> [NormalCo] ->
 opt_transList is = zipWithEqual "opt_transList" (opt_trans is)
   -- The input lists must have identical length.
 
-opt_trans, opt_trans' :: InScopeSet -> NormalCo -> NormalCo -> NormalCo
+opt_trans :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 
 -- opt_trans just allows us to add some debug tracing
 -- Usually it just goes to opt_trans'
-opt_trans is co1 co2 = opt_trans' is co1 co2
+opt_trans is co1 co2
+  = -- (if coercionRKind co1 `eqType` coercionLKind co2
+    --  then (\x -> x) else
+    --  pprTrace "opt_trans" (vcat [ text "co1" <+> ppr co1
+    --                             , text "co2" <+> ppr co2
+    --                             , text "co1 kind" <+> ppr (coercionKind co1)
+    --                             , text "co2 kind" <+> ppr (coercionKind co2)
+    --                             , callStackDoc ])) $
+    opt_trans' is co1 co2
 
 {-
 opt_trans is co1 co2
@@ -658,19 +716,20 @@ opt_trans is co1 co2
     r2 = coercionRole co1
 -}
 
+opt_trans' :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 opt_trans' is co1 co2
   | isReflCo co1 = co2
     -- optimize when co1 is a Refl Co
   | otherwise    = opt_trans1 is co1 co2
 
-opt_trans1 :: InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
+opt_trans1 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
 -- First arg is not the identity
 opt_trans1 is co1 co2
   | isReflCo co2 = co1
     -- optimize when co2 is a Refl Co
   | otherwise    = opt_trans2 is co1 co2
 
-opt_trans2 :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
+opt_trans2 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
 -- Neither arg is the identity
 opt_trans2 is (TransCo co1a co1b) co2
     -- Don't know whether the sub-coercions are the identity
@@ -687,16 +746,27 @@ opt_trans2 is co1 (TransCo co2a co2b)
     else opt_trans1 is co1_2a co2b
 
 opt_trans2 _ co1 co2
-  = mkTransCo co1 co2
+  = mk_trans_co co1 co2
+
 
 ------
 -- Optimize coercions with a top-level use of transitivity.
-opt_trans_rule :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
-
-opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _ (MCo co2))
+opt_trans_rule :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
+
+opt_trans_rule _ in_co1 in_co2
+  | assertPpr (coercionRKind in_co1 `eqType` coercionLKind in_co2)
+              (vcat [ text "in_co1" <+> ppr in_co1
+                   , text "in_co2" <+> ppr in_co2
+                   , text "in_co1 kind" <+> ppr (coercionKind in_co1)
+                   , text "in_co2 kind" <+> ppr (coercionKind in_co2)
+                   , callStackDoc ]) $
+    False
+  = panic "opt_trans_rule"  -- This entire equation is purely assertion checking
+
+opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _t2 (MCo co2))
   = assert (r1 == r2) $
     fireTransRule "GRefl" in_co1 in_co2 $
-    mkGReflRightCo r1 t1 (opt_trans is co1 co2)
+    mk_grefl_right_co r1 t1 (opt_trans is co1 co2)
 
 -- Push transitivity through matching destructors
 opt_trans_rule is in_co1@(SelCo d1 co1) in_co2@(SelCo d2 co2)
@@ -818,8 +888,8 @@ opt_trans_rule is co1 co2
       eta1' = downgradeRole role Nominal eta1
       n1   = mkSelCo (SelTyCon 2 role) eta1'
       n2   = mkSelCo (SelTyCon 3 role) eta1'
-      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mkTransCo`
-                                        (mkCoVarCo cv1) `mkTransCo` n2])
+      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mk_trans_co`
+                                        (mkCoVarCo cv1) `mk_trans_co` n2])
                     r2
 
 -- Push transitivity inside axioms
@@ -836,15 +906,15 @@ opt_trans_rule is co1 co2
   | Just (sym1, axr1, cos1) <- isAxiomCo_maybe co1
   , Just (sym2, axr2, cos2) <- isAxiomCo_maybe co2
   , axr1 == axr2
-  , sym1 == not sym2
+  , sym1 == flipSwap sym2
   , Just (tc, role, branch) <- coAxiomRuleBranch_maybe axr1
   , let qtvs   = coAxBranchTyVars branch ++ coAxBranchCoVars branch
         lhs    = mkTyConApp tc (coAxBranchLHS branch)
         rhs    = coAxBranchRHS branch
-        pivot_tvs = exactTyCoVarsOfType (if sym2 then rhs else lhs)
+        pivot_tvs = exactTyCoVarsOfType (pickSwap sym2 lhs rhs)
   , all (`elemVarSet` pivot_tvs) qtvs
   = fireTransRule "TrPushAxSym" co1 co2 $
-    if sym2
+    if isSwapped sym2
        -- TrPushAxSym
     then liftCoSubstWith role qtvs (opt_transList is cos1 (map mkSymCo cos2)) lhs
        -- TrPushSymAx
@@ -854,29 +924,29 @@ opt_trans_rule is co1 co2
   -- Note [Push transitivity inside newtype axioms only]
   -- TrPushSymAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , True <- sym
+  , isSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is (map mkSymCo cos2) cos1)
   = fireTransRule "TrPushSymAxR" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , False <- sym
+  , notSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxR" co1 co2 newAxInst
 
   -- TrPushSymAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , True <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , isSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos2 (map mkSymCo cos1))
   = fireTransRule "TrPushSymAxL" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , False <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , notSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxL" co1 co2 newAxInst
 
@@ -926,7 +996,7 @@ opt_trans_rule_app is orig_co1 orig_co2 co1a co1bs co2a co2bs
 
         co2a'   = mkCoherenceLeftCo rt2a lt2a kcoa co2a
         co2bs'  = zipWith3 mkGReflLeftCo rt2bs lt2bs kcobs
-        co2bs'' = zipWith mkTransCo co2bs' co2bs
+        co2bs'' = zipWith mk_trans_co co2bs' co2bs
     in
     mkAppCos (opt_trans is co1a co2a')
              (zipWith (opt_trans is) co1bs co2bs'')
@@ -1108,13 +1178,13 @@ The problem described here was first found in dependent/should_compile/dynamic-p
 -}
 
 -----------
-swapSym :: SymFlag -> (a,a) -> (a,a)
-swapSym sym (x,y) | sym       = (y,x)
-                  | otherwise = (x,y)
+swapSym :: SwapFlag -> (a,a) -> (a,a)
+swapSym IsSwapped  (x,y) = (y,x)
+swapSym NotSwapped (x,y) = (x,y)
 
-wrapSym :: SymFlag -> Coercion -> Coercion
-wrapSym sym co | sym       = mkSymCo co
-               | otherwise = co
+wrapSym :: SwapFlag -> Coercion -> Coercion
+wrapSym IsSwapped  co = mkSymCo co
+wrapSym NotSwapped co = co
 
 -- | Conditionally set a role to be representational
 wrapRole :: ReprFlag
@@ -1132,15 +1202,15 @@ chooseRole True _ = Representational
 chooseRole _    r = r
 
 -----------
-isAxiomCo_maybe :: Coercion -> Maybe (SymFlag, CoAxiomRule, [Coercion])
+isAxiomCo_maybe :: Coercion -> Maybe (SwapFlag, CoAxiomRule, [Coercion])
 -- We don't expect to see nested SymCo; and that lets us write a simple,
 -- non-recursive function. (If we see a nested SymCo we'll just fail,
 -- which is ok.)
-isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (True, ax, cos)
-isAxiomCo_maybe (AxiomCo ax cos)         = Just (False, ax, cos)
+isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (IsSwapped,  ax, cos)
+isAxiomCo_maybe (AxiomCo ax cos)         = Just (NotSwapped, ax, cos)
 isAxiomCo_maybe _                        = Nothing
 
-matchNewtypeBranch :: Bool -- True = match LHS, False = match RHS
+matchNewtypeBranch :: SwapFlag -- IsSwapped = match LHS, NotSwapped = match RHS
                    -> CoAxiomRule
                    -> Coercion -> Maybe [Coercion]
 matchNewtypeBranch sym axr co
@@ -1151,7 +1221,7 @@ matchNewtypeBranch sym axr co
                , cab_lhs = lhs
                , cab_rhs = rhs } <- branch
   , Just subst <- liftCoMatch (mkVarSet qtvs)
-                              (if sym then (mkTyConApp tc lhs) else rhs)
+                              (pickSwap sym rhs (mkTyConApp tc lhs))
                               co
   , all (`isMappedByLC` subst) qtvs
   = zipWithM (liftCoSubstTyVar subst) roles qtvs
@@ -1228,7 +1298,7 @@ etaForAllCo_ty_maybe co
   , (role /= Nominal) || (vis1 `eqForAllVis` vis2)
   , let kind_co = mkSelCo SelForAll co
   = Just ( tv1, vis1, vis2, kind_co
-         , mkInstCo co (mkGReflRightCo Nominal (TyVarTy tv1) kind_co))
+         , mkInstCo co (mk_grefl_right_co Nominal (TyVarTy tv1) kind_co))
 
   | otherwise
   = Nothing
@@ -1251,8 +1321,8 @@ etaForAllCo_co_maybe co
         l_co     = mkCoVarCo cv1
         kind_co' = downgradeRole r Nominal kind_co
         r_co     = mkSymCo (mkSelCo (SelTyCon 2 r) kind_co')
-                   `mkTransCo` l_co
-                   `mkTransCo` mkSelCo (SelTyCon 3 r) kind_co'
+                   `mk_trans_co` l_co
+                   `mk_trans_co` mkSelCo (SelTyCon 3 r) kind_co'
     in Just ( cv1, vis1, vis2, kind_co
             , mkInstCo co (mkProofIrrelCo Nominal kind_co l_co r_co))
 
@@ -1329,7 +1399,55 @@ and these two imply
 
 -}
 
-optForAllCoBndr :: LiftingContext -> Bool
+optForAllCoBndr :: LiftingContext -> SwapFlag
                 -> TyCoVar -> Coercion -> (LiftingContext, TyCoVar, Coercion)
 optForAllCoBndr env sym
-  = substForAllCoBndrUsingLC sym (opt_co4_wrap env sym False Nominal) env
+  = substForAllCoBndrUsingLC sym (opt_co4 env sym False Nominal) env
+
+
+{- **********************************************************************
+%*                                                                      *
+       Assertion-checking versions of functions in Coercion.hs
+%*                                                                      *
+%********************************************************************* -}
+
+-- We can't check the assertions in the "main" functions of these
+-- functions, because the assertions don't hold during zonking.
+-- But they are fantastically helpful in finding bugs in the coercion
+-- optimiser itself, so I have copied them here with assertions.
+
+mk_trans_co :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+-- Do assertion checking in mk_trans_co
+mk_trans_co co1 co2
+  = assertPpr (coercionRKind co1 `eqType` coercionLKind co2)
+              (vcat [ text "co1" <+> ppr co1
+                    , text "co2" <+> ppr co2
+                    , text "co1 kind" <+> ppr (coercionKind co1)
+                    , text "co2 kind" <+> ppr (coercionKind co2)
+                    , callStackDoc ]) $
+    mkTransCo co1 co2
+
+mk_coherence_right_co :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
+mk_coherence_right_co r ty co co2
+  = assertGRefl ty co $
+    mkCoherenceRightCo r ty co co2
+
+assertGRefl :: HasDebugCallStack => Type -> Coercion -> r -> r
+assertGRefl ty co res
+  = assertPpr (typeKind ty `eqType` coercionLKind co)
+              (vcat [ pp_ty "ty" ty
+                    , pp_co "co" co
+                    , callStackDoc ]) $
+    res
+
+mk_grefl_right_co :: Role -> Type -> CoercionN -> Coercion
+mk_grefl_right_co r ty co
+  = assertGRefl ty co $
+    mkGReflRightCo r ty co
+
+pp_co :: String -> Coercion -> SDoc
+pp_co s co = text s <+> hang (ppr co) 2 (dcolon <+> ppr (coercionKind co))
+
+pp_ty :: String -> Type -> SDoc
+pp_ty s ty = text s <+> hang (ppr ty) 2 (dcolon <+> ppr (typeKind ty))
+


=====================================
compiler/GHC/Core/TyCo/Subst.hs
=====================================
@@ -68,6 +68,7 @@ import {-# SOURCE #-} GHC.Core ( CoreExpr )
 import GHC.Core.TyCo.Rep
 import GHC.Core.TyCo.FVs
 
+import GHC.Types.Basic( SwapFlag(..), isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -916,7 +917,7 @@ substDCoVarSet subst cvs = coVarsOfCosDSet $ map (substCoVar subst) $
 substForAllCoBndr :: Subst -> TyCoVar -> KindCoercion
                   -> (Subst, TyCoVar, Coercion)
 substForAllCoBndr subst
-  = substForAllCoBndrUsing False (substCo subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCo subst) subst
 
 -- | Like 'substForAllCoBndr', but disables sanity checks.
 -- The problems that the sanity checks in substCo catch are described in
@@ -926,10 +927,10 @@ substForAllCoBndr subst
 substForAllCoBndrUnchecked :: Subst -> TyCoVar -> KindCoercion
                            -> (Subst, TyCoVar, Coercion)
 substForAllCoBndrUnchecked subst
-  = substForAllCoBndrUsing False (substCoUnchecked subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCoUnchecked subst) subst
 
 -- See Note [Sym and ForAllCo]
-substForAllCoBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoBndrUsing :: SwapFlag  -- Apply sym to binder?
                        -> (Coercion -> Coercion)  -- transformation to kind co
                        -> Subst -> TyCoVar -> KindCoercion
                        -> (Subst, TyCoVar, KindCoercion)
@@ -937,7 +938,7 @@ substForAllCoBndrUsing sym sco subst old_var
   | isTyVar old_var = substForAllCoTyVarBndrUsing sym sco subst old_var
   | otherwise       = substForAllCoCoVarBndrUsing sym sco subst old_var
 
-substForAllCoTyVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoTyVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> TyVar -> KindCoercion
                             -> (Subst, TyVar, KindCoercion)
@@ -946,10 +947,13 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
     ( Subst (in_scope `extendInScopeSet` new_var) idenv new_env cenv
     , new_var, new_kind_co )
   where
-    new_env | no_change && not sym = delVarEnv tenv old_var
-            | sym       = extendVarEnv tenv old_var $
-                          TyVarTy new_var `CastTy` new_kind_co
-            | otherwise = extendVarEnv tenv old_var (TyVarTy new_var)
+    new_env | no_change, notSwapped sym
+            = delVarEnv tenv old_var
+            | isSwapped sym
+            = extendVarEnv tenv old_var $
+              TyVarTy new_var `CastTy` new_kind_co
+            | otherwise
+            = extendVarEnv tenv old_var (TyVarTy new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -965,7 +969,7 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
 
     new_var  = uniqAway in_scope (setTyVarKind old_var new_ki1)
 
-substForAllCoCoVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoCoVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> CoVar -> KindCoercion
                             -> (Subst, CoVar, KindCoercion)
@@ -975,8 +979,10 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     ( Subst (in_scope `extendInScopeSet` new_var) idenv tenv new_cenv
     , new_var, new_kind_co )
   where
-    new_cenv | no_change && not sym = delVarEnv cenv old_var
-             | otherwise = extendVarEnv cenv old_var (mkCoVarCo new_var)
+    new_cenv | no_change, notSwapped sym
+             = delVarEnv cenv old_var
+             | otherwise
+             = extendVarEnv cenv old_var (mkCoVarCo new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -987,8 +993,7 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     Pair h1 h2 = coercionKind new_kind_co
 
     new_var       = uniqAway in_scope $ mkCoVar (varName old_var) new_var_type
-    new_var_type  | sym       = h2
-                  | otherwise = h1
+    new_var_type  = pickSwap sym h1 h2
 
 substCoVar :: Subst -> CoVar -> Coercion
 substCoVar (Subst _ _ _ cenv) cv


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -579,7 +579,7 @@ expandTypeSynonyms ty
       -- substForAllCoBndrUsing, which is general enough to
       -- handle coercion optimization (which sometimes swaps the
       -- order of a coercion)
-    go_cobndr subst = substForAllCoBndrUsing False (go_co subst) subst
+    go_cobndr subst = substForAllCoBndrUsing NotSwapped (go_co subst) subst
 
 {- Notes on type synonyms
 ~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/HsToCore.hs
=====================================
@@ -783,7 +783,7 @@ mkUnsafeCoercePrimPair _old_id old_expr
              alpha_co = mkTyConAppCo Nominal tYPETyCon [mkCoVarCo rr_cv]
 
              -- x_co :: alpha ~R# beta
-             x_co = mkGReflCo Representational openAlphaTy (MCo alpha_co) `mkTransCo`
+             x_co = mkGReflMCo Representational openAlphaTy alpha_co `mkTransCo`
                     mkSubCo (mkCoVarCo ab_cv)
 
 


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -80,7 +80,7 @@ module GHC.Types.Basic (
         EP(..),
 
         DefMethSpec(..),
-        SwapFlag(..), flipSwap, unSwap, isSwapped,
+        SwapFlag(..), flipSwap, unSwap, notSwapped, isSwapped, pickSwap,
 
         CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
 
@@ -456,6 +456,7 @@ instance Outputable OneShotInfo where
 data SwapFlag
   = NotSwapped  -- Args are: actual,   expected
   | IsSwapped   -- Args are: expected, actual
+  deriving( Eq )
 
 instance Outputable SwapFlag where
   ppr IsSwapped  = text "Is-swapped"
@@ -469,6 +470,14 @@ isSwapped :: SwapFlag -> Bool
 isSwapped IsSwapped  = True
 isSwapped NotSwapped = False
 
+notSwapped :: SwapFlag -> Bool
+notSwapped NotSwapped = True
+notSwapped IsSwapped  = False
+
+pickSwap :: SwapFlag -> a -> a -> a
+pickSwap NotSwapped a _ = a
+pickSwap IsSwapped  _ b = b
+
 unSwap :: SwapFlag -> (a->a->b) -> a -> a -> b
 unSwap NotSwapped f a b = f a b
 unSwap IsSwapped  f a b = f b a


=====================================
testsuite/tests/dependent/should_compile/T25387.hs
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE GHC2024 #-}
+{-# LANGUAGE TypeFamilies #-}
+module Bug (f) where
+
+import Data.Kind (Type)
+import Data.Type.Equality (type (~~))
+
+type Promote :: Type -> Type
+type family Promote k
+
+type PromoteX :: k -> Promote k
+type family PromoteX a
+
+type Demote :: Type -> Type
+type family Demote (k :: Type) :: Type
+
+type DemoteX :: k -> Demote k
+type family DemoteX a
+
+type HEq :: j -> k -> Type
+data HEq a b where
+  HRefl :: forall j (a :: j). HEq a a
+
+type SHEq :: forall j k (a :: j) (b :: k). HEq a b -> Type
+data SHEq heq where
+  SHRefl :: forall j (a :: j). SHEq (HRefl @j @a)
+
+type SomeSHEq :: j -> k -> Type
+data SomeSHEq a b where
+  SomeSHEq :: forall j k (a :: j) (b :: k) (heq :: HEq a b). SHEq heq -> SomeSHEq a b
+
+f :: forall j k (a :: j) (b :: k).
+     (PromoteX (DemoteX a) ~~ a, PromoteX (DemoteX b) ~~ b) =>
+     HEq (DemoteX a) (DemoteX b) ->
+     SomeSHEq a b
+f HRefl = SomeSHEq SHRefl


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -63,3 +63,4 @@ test('T16347', normal, compile, [''])
 test('T18660', normal, compile, [''])
 test('T12174', normal, compile, [''])
 test('LopezJuan', normal, compile, [''])
+test('T25387', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0740c45fe628ffe19eadfe598084fcd5039bf0d8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 17:21:11 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Fri, 25 Oct 2024 13:21:11 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-7] 5 commits: CorePrep:
 Attach evaldUnfolding to floats to detect more values
Message-ID: <671bd387403c6_1cd39b40d468812b0@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-7 at Glasgow Haskell Compiler / GHC


Commits:
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Stg/InferTags.hs → compiler/GHC/Stg/EnforceEpt.hs
- compiler/GHC/Stg/InferTags/Rewrite.hs → compiler/GHC/Stg/EnforceEpt/Rewrite.hs
- compiler/GHC/Stg/InferTags/TagSig.hs → compiler/GHC/Stg/EnforceEpt/TagSig.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2814fb1e6c5b8c2ae92df12b966936ed130a907d...dbc77ce804c0f410f3f2894a158d0ee899ce64f5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2814fb1e6c5b8c2ae92df12b966936ed130a907d...dbc77ce804c0f410f3f2894a158d0ee899ce64f5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 20:32:01 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Fri, 25 Oct 2024 16:32:01 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/romes/9557
Message-ID: <671c004195cdf_1ddfac17f94445952@gitlab.mail>



Rodrigo Mesquita pushed new branch wip/romes/9557 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/9557
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Fri Oct 25 22:33:49 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Fri, 25 Oct 2024 18:33:49 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/docs-for-monadfix
Message-ID: <671c1ccd608b8_359a7d1b7bc845140@gitlab.mail>



Bodigrim pushed new branch wip/docs-for-monadfix at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/docs-for-monadfix
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 00:25:47 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Fri, 25 Oct 2024 20:25:47 -0400
Subject: [Git][ghc/ghc][wip/docs-for-monadfix] documentation: add motivating
 section to Control.Monad.Fix
Message-ID: <671c370b687a_359a7d700288578de@gitlab.mail>



Bodigrim pushed to branch wip/docs-for-monadfix at Glasgow Haskell Compiler / GHC


Commits:
b1d07bf8 by Andrew Lelechenko at 2024-10-26T01:25:38+01:00
documentation: add motivating section to Control.Monad.Fix

- - - - -


1 changed file:

- libraries/base/src/Control/Monad/Fix.hs


Changes:

=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,107 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Condider the generalized version of so called @repmin@ problem:
+-- traverse a container accumulating its elements into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above traverses the container twice. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future value of accumulator,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkok, , Oregon Graduate Institute, 2002.
+-- * Levent Erkok, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 08:58:06 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Sat, 26 Oct 2024 04:58:06 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 2 commits: Improve performance of
 deriving Show
Message-ID: <671caf1e32c34_10a35a199718578d4@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
45a72fb9 by Rodrigo Mesquita at 2024-10-26T09:57:33+01:00
Improve performance of deriving Show

Significantly improves performance of deriving Show instances by
avoiding using the very polymorphic `.` operator in favour of inlining
its definition. We were generating tons of applications of it, each
which had 3 type arguments!

With the example module linked in #9557, this change makes deriving Show,
on my machine, go from taking:

* 5.5s to 3.5s with -O1
* 2.9s to 2.0s with -O0

Improves on #9557

- - - - -
d7bbd3c2 by Rodrigo Mesquita at 2024-10-26T09:57:38+01:00
deriving Ord compare and <= only

Since the implementation of CLC proposal #24, the default
implementations of Ord's `<`, `>`, and `>=` are given in terms of `<=`.

This means we no longer need to generate implementations for these
methods when stock deriving `Ord`. Rather, just derive the
implementation of `compare` and `<=`, and rely on the default
implementations for the others.

Progress towards #9557

Using the same sample module from #9557, this commit takes compilation
on my machine from being:
* 4.3s to 3.3s with -O0
* 6.9s to 5.2s with -O1

- - - - -


2 changed files:

- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -56,7 +56,7 @@ module GHC.Hs.Utils(
   nlHsTyApp, nlHsTyApps, nlHsVar, nlHsDataCon,
   nlHsLit, nlHsApp, nlHsApps, nlHsSyntaxApps,
   nlHsIntLit, nlHsVarApps,
-  nlHsDo, nlHsOpApp, nlHsPar, nlHsIf, nlHsCase, nlList,
+  nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList,
   mkLHsTupleExpr, mkLHsVarTuple, missingTupArg,
   mkLocatedList, nlAscribe,
 
@@ -598,11 +598,15 @@ nlHsDo ctxt stmts = noLocA (mkHsDo ctxt (noLocA stmts))
 nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
 nlHsOpApp e1 op e2 = noLocA (mkHsOpApp e1 op e2)
 
+nlHsLam  :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
 nlHsPar  :: IsPass p => LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
 nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)]
          -> LHsExpr GhcPs
 nlList   :: [LHsExpr GhcPs] -> LHsExpr GhcPs
 
+nlHsLam match = noLocA $ HsLam noAnn LamSingle
+                  $ mkMatchGroup (Generated OtherExpansion SkipPmc) (noLocA [match])
+
 nlHsPar e     = noLocA (gHsPar e)
 
 -- nlHsIf should generate if-expressions which are NOT subject to


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -339,7 +339,7 @@ Several special cases:
   See function unliftedOrdOp
 
 Note [Game plan for deriving Ord]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 It's a bad idea to define only 'compare', and build the other binary
 comparisons on top of it; see #2130, #4019.  Reason: we don't
 want to laboriously make a three-way comparison, only to extract a
@@ -350,16 +350,22 @@ binary result, something like this:
                                        True  -> False
                                        False -> True
 
-This being said, we can get away with generating full code only for
-'compare' and '<' thus saving us generation of other three operators.
-Other operators can be cheaply expressed through '<':
-a <= b = not $ b < a
-a > b = b < a
-a >= b = not $ a < b
-
 So for sufficiently small types (few constructors, or all nullary)
 we generate all methods; for large ones we just use 'compare'.
 
+This being said, we can get away with generating full code only for
+'compare' and '<=' thus saving us generation of other three operators.
+Other operators can be cheaply expressed through '<=' -- indeed, that's what
+the default implementations of >, <, and >= do.
+
+Historically, derived instances defined '<' and the remaining operators as
+cheap expressions in function of it:
+  a <= b = not $ b < a
+  a > b = b < a
+  a >= b = not $ a < b
+but since the CLC proposal #24 (see 8f174e06185143674d6cbfee75c30e68805d85b8),
+it suffices to derive '<=' and rely on the
+default implementation for the others.
 -}
 
 data OrdOp = OrdCompare | OrdLT | OrdLE | OrdGE | OrdGT
@@ -417,19 +423,10 @@ gen_Ord_binds loc dit@(DerivInstTys{ dit_rep_tc = tycon
     other_ops
       | (last_tag - first_tag) <= 2     -- 1-3 constructors
         || null non_nullary_cons        -- Or it's an enumeration
-      = [mkOrdOp OrdLT, lE, gT, gE]
+      = [mkOrdOp OrdGE]
       | otherwise
       = []
 
-    negate_expr = nlHsApp (nlHsVar not_RDR)
-    pats = noLocA [a_Pat, b_Pat]
-    lE = mkSimpleGeneratedFunBind loc le_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr)
-    gT = mkSimpleGeneratedFunBind loc gt_RDR pats $
-        nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr
-    gE = mkSimpleGeneratedFunBind loc ge_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) a_Expr) b_Expr)
-
     get_tag con = dataConTag con - fIRST_TAG
         -- We want *zero-based* tags, because that's what
         -- con2Tag returns (generated by untag_Expr)!
@@ -2528,11 +2525,14 @@ showParen_Expr
 showParen_Expr e1 e2 = nlHsApp (nlHsApp (nlHsVar showParen_RDR) e1) e2
 
 nested_compose_Expr :: [LHsExpr GhcPs] -> LHsExpr GhcPs
-
-nested_compose_Expr []  = panic "nested_compose_expr"   -- Arg is always non-empty
-nested_compose_Expr [e] = parenify e
-nested_compose_Expr (e:es)
-  = nlHsApp (nlHsApp (nlHsVar compose_RDR) (parenify e)) (nested_compose_Expr es)
+nested_compose_Expr =
+  nlHsLam . mkSimpleMatch (LamAlt LamSingle) (noLocA [z_Pat]) . go
+  where
+    -- Inlined nested applications of (`.`) to speed up deriving!
+    go []  = panic "nested_compose_expr"   -- Arg is always non-empty
+    go [e] = nlHsApp (parenify e) z_Expr
+    go (e:es)
+      = nlHsApp (parenify e) (go es)
 
 -- impossible_Expr is used in case RHSs that should never happen.
 -- We generate these to keep the desugarer from complaining that they *might* happen!



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46e2a9b2eaf2f047db7769ef3759b38f2158ec10...d7bbd3c233af14eb69c9c931916bf6d4098b4f45

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46e2a9b2eaf2f047db7769ef3759b38f2158ec10...d7bbd3c233af14eb69c9c931916bf6d4098b4f45
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 09:05:37 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Sat, 26 Oct 2024 05:05:37 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] deriving Ord compare and <= only
Message-ID: <671cb0e1700ce_10a35a2c08e45817b@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
4ed10080 by Rodrigo Mesquita at 2024-10-26T10:05:27+01:00
deriving Ord compare and <= only

Since the implementation of CLC proposal #24, the default
implementations of Ord's `<`, `>`, and `>=` are given in terms of `<=`.

This means we no longer need to generate implementations for these
methods when stock deriving `Ord`. Rather, just derive the
implementation of `compare` and `<=`, and rely on the default
implementations for the others.

Progress towards #9557

Using the same sample module from #9557, this commit takes compilation
on my machine from being:
* 4.3s to 3.3s with -O0
* 6.9s to 5.2s with -O1

- - - - -


1 changed file:

- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -339,7 +339,7 @@ Several special cases:
   See function unliftedOrdOp
 
 Note [Game plan for deriving Ord]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 It's a bad idea to define only 'compare', and build the other binary
 comparisons on top of it; see #2130, #4019.  Reason: we don't
 want to laboriously make a three-way comparison, only to extract a
@@ -350,16 +350,22 @@ binary result, something like this:
                                        True  -> False
                                        False -> True
 
-This being said, we can get away with generating full code only for
-'compare' and '<' thus saving us generation of other three operators.
-Other operators can be cheaply expressed through '<':
-a <= b = not $ b < a
-a > b = b < a
-a >= b = not $ a < b
-
 So for sufficiently small types (few constructors, or all nullary)
 we generate all methods; for large ones we just use 'compare'.
 
+This being said, we can get away with generating full code only for
+'compare' and '<=' thus saving us generation of other three operators.
+Other operators can be cheaply expressed through '<=' -- indeed, that's what
+the default implementations of >, <, and >= do.
+
+Historically, derived instances defined '<' and the remaining operators as
+cheap expressions in function of it:
+  a <= b = not $ b < a
+  a > b = b < a
+  a >= b = not $ a < b
+but since the CLC proposal #24 (see 8f174e06185143674d6cbfee75c30e68805d85b8),
+it suffices to derive '<=' and rely on the
+default implementation for the others.
 -}
 
 data OrdOp = OrdCompare | OrdLT | OrdLE | OrdGE | OrdGT
@@ -417,19 +423,10 @@ gen_Ord_binds loc dit@(DerivInstTys{ dit_rep_tc = tycon
     other_ops
       | (last_tag - first_tag) <= 2     -- 1-3 constructors
         || null non_nullary_cons        -- Or it's an enumeration
-      = [mkOrdOp OrdLT, lE, gT, gE]
+      = [mkOrdOp OrdLE]
       | otherwise
       = []
 
-    negate_expr = nlHsApp (nlHsVar not_RDR)
-    pats = noLocA [a_Pat, b_Pat]
-    lE = mkSimpleGeneratedFunBind loc le_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr)
-    gT = mkSimpleGeneratedFunBind loc gt_RDR pats $
-        nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr
-    gE = mkSimpleGeneratedFunBind loc ge_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) a_Expr) b_Expr)
-
     get_tag con = dataConTag con - fIRST_TAG
         -- We want *zero-based* tags, because that's what
         -- con2Tag returns (generated by untag_Expr)!



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ed1008080b97ce69c26ac873ba8e8f99f63881b

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 09:30:46 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 26 Oct 2024 05:30:46 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-addepann-8
Message-ID: <671cb6c64caa_10a35a3c8ca0634db@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-addepann-8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 10:04:07 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Sat, 26 Oct 2024 06:04:07 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 3 commits: Improve performance of
 deriving Show
Message-ID: <671cbe976e0f_10a35a5707b0656e4@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
759ce039 by Rodrigo Mesquita at 2024-10-26T11:02:54+01:00
Improve performance of deriving Show

Significantly improves performance of deriving Show instances by
avoiding using the very polymorphic `.` operator in favour of inlining
its definition. We were generating tons of applications of it, each
which had 3 type arguments!

With the example module linked in #9557, this change makes deriving Show,
on my machine, go from taking:

* 5.5s to 3.5s with -O1
* 2.9s to 2.0s with -O0

Improves on #9557

- - - - -
6ba79887 by Rodrigo Mesquita at 2024-10-26T11:03:02+01:00
Deriving Ord: compare and <= only

Since the implementation of CLC proposal #24, the default
implementations of Ord's `<`, `>`, and `>=` are given in terms of `<=`.

This means we no longer need to generate implementations for these
methods when stock deriving `Ord`. Rather, just derive the
implementation of `compare` and `<=`, and rely on the default
implementations for the others.

Progress towards #9557

Using the same sample module from #9557 with deriving Eq, Ord, this
commit takes compilation on my machine from being:
* 4.3s to 3.2s with -O0
* 6.9s to 4.9s with -O1

- - - - -
0f7f0e60 by Rodrigo Mesquita at 2024-10-26T11:03:21+01:00
Dont' eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

On my machine, this brings the module from #9557 with deriving Data from:
* 8s to 6.2s with -O0
* 13s to 9.7s with -O1

- - - - -


2 changed files:

- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -56,7 +56,7 @@ module GHC.Hs.Utils(
   nlHsTyApp, nlHsTyApps, nlHsVar, nlHsDataCon,
   nlHsLit, nlHsApp, nlHsApps, nlHsSyntaxApps,
   nlHsIntLit, nlHsVarApps,
-  nlHsDo, nlHsOpApp, nlHsPar, nlHsIf, nlHsCase, nlList,
+  nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList,
   mkLHsTupleExpr, mkLHsVarTuple, missingTupArg,
   mkLocatedList, nlAscribe,
 
@@ -598,11 +598,15 @@ nlHsDo ctxt stmts = noLocA (mkHsDo ctxt (noLocA stmts))
 nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
 nlHsOpApp e1 op e2 = noLocA (mkHsOpApp e1 op e2)
 
+nlHsLam  :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
 nlHsPar  :: IsPass p => LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
 nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)]
          -> LHsExpr GhcPs
 nlList   :: [LHsExpr GhcPs] -> LHsExpr GhcPs
 
+nlHsLam match = noLocA $ HsLam noAnn LamSingle
+                  $ mkMatchGroup (Generated OtherExpansion SkipPmc) (noLocA [match])
+
 nlHsPar e     = noLocA (gHsPar e)
 
 -- nlHsIf should generate if-expressions which are NOT subject to


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -339,7 +339,7 @@ Several special cases:
   See function unliftedOrdOp
 
 Note [Game plan for deriving Ord]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 It's a bad idea to define only 'compare', and build the other binary
 comparisons on top of it; see #2130, #4019.  Reason: we don't
 want to laboriously make a three-way comparison, only to extract a
@@ -350,16 +350,22 @@ binary result, something like this:
                                        True  -> False
                                        False -> True
 
-This being said, we can get away with generating full code only for
-'compare' and '<' thus saving us generation of other three operators.
-Other operators can be cheaply expressed through '<':
-a <= b = not $ b < a
-a > b = b < a
-a >= b = not $ a < b
-
 So for sufficiently small types (few constructors, or all nullary)
 we generate all methods; for large ones we just use 'compare'.
 
+This being said, we can get away with generating full code only for
+'compare' and '<=' thus saving us generation of other three operators.
+Other operators can be cheaply expressed through '<=' -- indeed, that's what
+the default implementations of >, <, and >= do.
+
+Historically, derived instances defined '<' and the remaining operators as
+cheap expressions in function of it:
+  a <= b = not $ b < a
+  a > b = b < a
+  a >= b = not $ a < b
+but since the CLC proposal #24 (see 8f174e06185143674d6cbfee75c30e68805d85b8),
+it suffices to derive '<=' and rely on the
+default implementation for the others.
 -}
 
 data OrdOp = OrdCompare | OrdLT | OrdLE | OrdGE | OrdGT
@@ -417,19 +423,10 @@ gen_Ord_binds loc dit@(DerivInstTys{ dit_rep_tc = tycon
     other_ops
       | (last_tag - first_tag) <= 2     -- 1-3 constructors
         || null non_nullary_cons        -- Or it's an enumeration
-      = [mkOrdOp OrdLT, lE, gT, gE]
+      = [mkOrdOp OrdLE]
       | otherwise
       = []
 
-    negate_expr = nlHsApp (nlHsVar not_RDR)
-    pats = noLocA [a_Pat, b_Pat]
-    lE = mkSimpleGeneratedFunBind loc le_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr)
-    gT = mkSimpleGeneratedFunBind loc gt_RDR pats $
-        nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr
-    gE = mkSimpleGeneratedFunBind loc ge_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) a_Expr) b_Expr)
-
     get_tag con = dataConTag con - fIRST_TAG
         -- We want *zero-based* tags, because that's what
         -- con2Tag returns (generated by untag_Expr)!
@@ -1407,7 +1404,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1427,16 +1424,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid
@@ -2528,11 +2526,14 @@ showParen_Expr
 showParen_Expr e1 e2 = nlHsApp (nlHsApp (nlHsVar showParen_RDR) e1) e2
 
 nested_compose_Expr :: [LHsExpr GhcPs] -> LHsExpr GhcPs
-
-nested_compose_Expr []  = panic "nested_compose_expr"   -- Arg is always non-empty
-nested_compose_Expr [e] = parenify e
-nested_compose_Expr (e:es)
-  = nlHsApp (nlHsApp (nlHsVar compose_RDR) (parenify e)) (nested_compose_Expr es)
+nested_compose_Expr =
+  nlHsLam . mkSimpleMatch (LamAlt LamSingle) (noLocA [z_Pat]) . go
+  where
+    -- Inlined nested applications of (`.`) to speed up deriving!
+    go []  = panic "nested_compose_expr"   -- Arg is always non-empty
+    go [e] = nlHsApp (parenify e) z_Expr
+    go (e:es)
+      = nlHsApp (parenify e) (go es)
 
 -- impossible_Expr is used in case RHSs that should never happen.
 -- We generate these to keep the desugarer from complaining that they *might* happen!
@@ -2573,7 +2574,7 @@ cs_RDRs         = [ mkVarUnqual (mkFastString ("c"++show i)) | i <- [(1::Int) ..
 a_Expr, b_Expr, c_Expr, z_Expr, ltTag_Expr, eqTag_Expr, gtTag_Expr, false_Expr,
     true_Expr, pure_Expr, unsafeCodeCoerce_Expr :: LHsExpr GhcPs
 a_Expr                = nlHsVar a_RDR
-b_Expr                = nlHsVar b_RDR
+-- b_Expr                = nlHsVar b_RDR
 c_Expr                = nlHsVar c_RDR
 z_Expr                = nlHsVar z_RDR
 ltTag_Expr            = nlHsVar ltTag_RDR



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ed1008080b97ce69c26ac873ba8e8f99f63881b...0f7f0e6042f6287937cf6aec2cfd0bada87f03a4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ed1008080b97ce69c26ac873ba8e8f99f63881b...0f7f0e6042f6287937cf6aec2cfd0bada87f03a4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 10:05:21 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Sat, 26 Oct 2024 06:05:21 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] Dont' eta expand cons when deriving
 Data
Message-ID: <671cbee0f31de_10a35a66b0986598f@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
aa1bf18e by Rodrigo Mesquita at 2024-10-26T11:05:12+01:00
Dont' eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

On my machine, this brings the module from #9557 with deriving Data from:
* 8s to 6.2s with -O0
* 13s to 9.7s with -O1

- - - - -


1 changed file:

- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1404,7 +1404,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1424,16 +1424,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid
@@ -2570,10 +2571,10 @@ as_RDRs         = [ mkVarUnqual (mkFastString ("a"++show i)) | i <- [(1::Int) ..
 bs_RDRs         = [ mkVarUnqual (mkFastString ("b"++show i)) | i <- [(1::Int) .. ] ]
 cs_RDRs         = [ mkVarUnqual (mkFastString ("c"++show i)) | i <- [(1::Int) .. ] ]
 
-a_Expr, b_Expr, c_Expr, z_Expr, ltTag_Expr, eqTag_Expr, gtTag_Expr, false_Expr,
+a_Expr, {- b_Expr, -} c_Expr, z_Expr, ltTag_Expr, eqTag_Expr, gtTag_Expr, false_Expr,
     true_Expr, pure_Expr, unsafeCodeCoerce_Expr :: LHsExpr GhcPs
 a_Expr                = nlHsVar a_RDR
-b_Expr                = nlHsVar b_RDR
+-- b_Expr                = nlHsVar b_RDR
 c_Expr                = nlHsVar c_RDR
 z_Expr                = nlHsVar z_RDR
 ltTag_Expr            = nlHsVar ltTag_RDR



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 10:50:56 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Sat, 26 Oct 2024 06:50:56 -0400
Subject: [Git][ghc/ghc][wip/docs-for-monadfix] documentation: add motivating
 section to Control.Monad.Fix
Message-ID: <671cc98ff2855_10a35a89a0d078470@gitlab.mail>



Bodigrim pushed to branch wip/docs-for-monadfix at Glasgow Haskell Compiler / GHC


Commits:
2174a660 by Andrew Lelechenko at 2024-10-26T11:50:48+01:00
documentation: add motivating section to Control.Monad.Fix

- - - - -


1 changed file:

- libraries/base/src/Control/Monad/Fix.hs


Changes:

=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,108 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Consider the generalized version of so-called @repmin@
+-- (/replace with minimum/) problem:
+-- accumulate elements of a container into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Functor t, Foldable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above makes two traversals. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkök, , Oregon Graduate Institute, 2002.
+-- * Levent Erkök, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2174a660f88d7163aef42de3d0923c5741a93009

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 11:22:48 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 26 Oct 2024 07:22:48 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-8] 17 commits: Improve heap
 overflow exception message (#25198)
Message-ID: <671cd1083f31b_10a35abe4b8c921ec@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
0dd3dd6f by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

- - - - -
1905e004 by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

- - - - -
9b77f34e by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

- - - - -
eb82fcfa by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

- - - - -
2686f890 by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove AddEpAnn from HsRuleAnn

- - - - -
fc969d40 by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
7c7f8c62 by Alan Zimmerman at 2024-10-26T10:34:09+01:00
EPA: Remove AddEpAnn from AnnList

- - - - -
4e4d652d by Alan Zimmerman at 2024-10-26T12:22:08+01:00
EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Doc.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/996503fb908d98b8021fd7d57aced092efd21d15...4e4d652d849b2b58b4c804983a7c3fbd3e688ce2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/996503fb908d98b8021fd7d57aced092efd21d15...4e4d652d849b2b58b4c804983a7c3fbd3e688ce2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 12:13:56 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 26 Oct 2024 08:13:56 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: CorePrep:
 Attach evaldUnfolding to floats to detect more values
Message-ID: <671cdd0499a9b_10a35af20080105682@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
b07d660f by Simon Peyton Jones at 2024-10-26T08:13:51-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -


30 changed files:

- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/16a5f47eb265075cedd86888a5e5da6f167fcb21...b07d660fa52af029eb1291b305fa9fac53f409b8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/16a5f47eb265075cedd86888a5e5da6f167fcb21...b07d660fa52af029eb1291b305fa9fac53f409b8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 16:44:32 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 26 Oct 2024 12:44:32 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove AddEpann commit 7
Message-ID: <671d1c707877c_289b863034281213a6@gitlab.mail>



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


Commits:
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -


8 changed files:

- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -1326,12 +1326,8 @@ type instance XXRuleDecl    (GhcPass _) = DataConCantHappen
 
 data HsRuleAnn
   = HsRuleAnn
-       { ra_tyanns :: Maybe (AddEpAnn, AddEpAnn)
-                 -- ^ The locations of 'forall' and '.' for forall'd type vars
-                 -- Using AddEpAnn to capture possible unicode variants
-       , ra_tmanns :: Maybe (AddEpAnn, AddEpAnn)
-                 -- ^ The locations of 'forall' and '.' for forall'd term vars
-                 -- Using AddEpAnn to capture possible unicode variants
+       { ra_tyanns :: Maybe (TokForall, EpToken ".")
+       , ra_tmanns :: Maybe (TokForall, EpToken ".")
        , ra_equal  :: EpToken "="
        , ra_rest :: ActivationAnn
        } deriving (Data, Eq)


=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -59,7 +59,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
     showAstData' =
       generic
               `ext1Q` list
-              `extQ` list_addEpAnn
               `extQ` list_epaLocation
               `extQ` list_epTokenOpenP
               `extQ` list_epTokenCloseP
@@ -116,12 +115,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
             bytestring :: B.ByteString -> SDoc
             bytestring = text . normalize_newlines . show
 
-            list_addEpAnn :: [AddEpAnn] -> SDoc
-            list_addEpAnn ls = case ba of
-              BlankEpAnnotations -> parens
-                                       $ text "blanked:" <+> text "[AddEpAnn]"
-              NoBlankEpAnnotations -> list ls
-
             list_epaLocation :: [EpaLocation] -> SDoc
             list_epaLocation ls = case ba of
               BlankEpAnnotations -> parens


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -1330,7 +1330,7 @@ names 'getField' and 'setField' are whatever in-scope names they are.
 ************************************************************************
 -}
 
-type instance XCmdArrApp  GhcPs = AddEpAnn
+type instance XCmdArrApp  GhcPs = (IsUnicodeSyntax, EpaLocation)
 type instance XCmdArrApp  GhcRn = NoExtField
 type instance XCmdArrApp  GhcTc = Type
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -838,14 +838,10 @@ litpkgname_segment :: { Located FastString }
 
 -- Parse a minus sign regardless of whether -XLexicalNegation is turned on or off.
 -- See Note [Minus tokens] in GHC.Parser.Lexer
-HYPHEN :: { [AddEpAnn] }
-      : '-'          { [mj AnnMinus $1 ] }
-      | PREFIX_MINUS { [mj AnnMinus $1 ] }
-      | VARSYM  {% if (getVARSYM $1 == fsLit "-")
-                   then return [mj AnnMinus $1]
-                   else do { addError $ mkPlainErrorMsgEnvelope (getLoc $1) $ PsErrExpectedHyphen
-                           ; return [] } }
-
+HYPHEN :: { () }
+      : '-'          { () }
+      | PREFIX_MINUS { () }
+      | VARSYM       { () }
 
 litpkgname :: { Located FastString }
         : litpkgname_segment { $1 }
@@ -1974,11 +1970,11 @@ rule_foralls :: { (EpToken "=" -> ActivationAnn -> HsRuleAnn, Maybe [LHsTyVarBnd
                                                               in hintExplicitForall $1
                                                               >> checkRuleTyVarBndrNames (mkRuleTyVarBndrs $2)
                                                               >> return (\an_eq an_act -> HsRuleAnn
-                                                                          (Just (mu AnnForall $1,mj AnnDot $3))
-                                                                          (Just (mu AnnForall $4,mj AnnDot $6))
+                                                                          (Just (epUniTok $1,epTok $3))
+                                                                          (Just (epUniTok $4,epTok $6))
                                                                           an_eq an_act,
                                                                          Just (mkRuleTyVarBndrs $2), mkRuleBndrs $5) }
-        | 'forall' rule_vars '.'                           { (\an_eq an_act -> HsRuleAnn Nothing (Just (mu AnnForall $1,mj AnnDot $3)) an_eq an_act,
+        | 'forall' rule_vars '.'                           { (\an_eq an_act -> HsRuleAnn Nothing (Just (epUniTok $1,epTok $3)) an_eq an_act,
                                                               Nothing, mkRuleBndrs $2) }
         -- See Note [%shift: rule_foralls -> {- empty -}]
         | {- empty -}            %shift                    { (\an_eq an_act -> HsRuleAnn Nothing Nothing an_eq an_act, Nothing, []) }
@@ -2824,25 +2820,25 @@ exp_gen(IEXP) :: { ECP }
                                 {% runPV (unECP $1) >>= \ $1 ->
                                    runPV (unECP $3) >>= \ $3 ->
                                    fmap ecpFromCmd $
-                                   amsA' (sLL $1 $> $ HsCmdArrApp (mu Annlarrowtail $2) $1 $3
+                                   amsA' (sLL $1 $> $ HsCmdArrApp (isUnicodeSyntax $2, glR $2) $1 $3
                                                         HsFirstOrderApp True) }
         | IEXP '>-' exp_gen(IEXP)
                                 {% runPV (unECP $1) >>= \ $1 ->
                                    runPV (unECP $3) >>= \ $3 ->
                                    fmap ecpFromCmd $
-                                   amsA' (sLL $1 $> $ HsCmdArrApp (mu Annrarrowtail $2) $3 $1
+                                   amsA' (sLL $1 $> $ HsCmdArrApp (isUnicodeSyntax $2, glR $2) $3 $1
                                                       HsFirstOrderApp False) }
         | IEXP '-<<' exp_gen(IEXP)
                                 {% runPV (unECP $1) >>= \ $1 ->
                                    runPV (unECP $3) >>= \ $3 ->
                                    fmap ecpFromCmd $
-                                   amsA' (sLL $1 $> $ HsCmdArrApp (mu AnnLarrowtail $2) $1 $3
+                                   amsA' (sLL $1 $> $ HsCmdArrApp (isUnicodeSyntax $2, glR $2) $1 $3
                                                       HsHigherOrderApp True) }
         | IEXP '>>-' exp_gen(IEXP)
                                 {% runPV (unECP $1) >>= \ $1 ->
                                    runPV (unECP $3) >>= \ $3 ->
                                    fmap ecpFromCmd $
-                                   amsA' (sLL $1 $> $ HsCmdArrApp (mu AnnRarrowtail $2) $3 $1
+                                   amsA' (sLL $1 $> $ HsCmdArrApp (isUnicodeSyntax $2, glR $2) $3 $1
                                                       HsHigherOrderApp False) }
         -- See Note [%shift: exp -> infixexp]
         | IEXP %shift              { $1 }
@@ -4726,7 +4722,7 @@ addTrailingCommaN (L anns a) span = do
 
 addTrailingCommaS :: Located StringLiteral -> EpaLocation -> Located StringLiteral
 addTrailingCommaS (L l sl) span
-    = L (widenSpan l [AddEpAnn AnnComma span]) (sl { sl_tc = Just (epaToNoCommentsLocation span) })
+    = L (widenSpanL l [span]) (sl { sl_tc = Just (epaToNoCommentsLocation span) })
 
 -- -------------------------------------
 
@@ -4738,6 +4734,9 @@ addTrailingDarrowC (L (EpAnn lr (AnnContext _ o c) csc) a) lt cs =
 
 -- -------------------------------------
 
+isUnicodeSyntax :: Located Token -> IsUnicodeSyntax
+isUnicodeSyntax lt = if isUnicode lt then UnicodeSyntax else NormalSyntax
+
 -- We need a location for the where binds, when computing the SrcSpan
 -- for the AST element using them.  Where there is a span, we return
 -- it, else noLoc, which is ignored in the comb2 call.


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -69,13 +69,12 @@ module GHC.Parser.Annotation (
 
   -- ** Building up annotations
   reAnnL, reAnnC,
-  addAnns, addAnnsA, widenSpan, widenSpanL, widenSpanT, widenAnchor, widenAnchorT, widenAnchorS,
-  widenLocatedAn, widenLocatedAnL,
+  addAnnsA, widenSpanL, widenSpanT, widenAnchorT, widenAnchorS,
+  widenLocatedAnL,
   listLocation,
 
   -- ** Querying annotations
   getLocAnn,
-  annParen2AddEpAnn,
   epAnnComments,
 
   -- ** Working with locations of annotations
@@ -1116,25 +1115,11 @@ reAnnL anns cs (L l a) = L (EpAnn (spanAsAnchor l) anns cs) a
 getLocAnn :: Located a  -> SrcSpanAnnA
 getLocAnn (L l _) = noAnnSrcSpan l
 
-addAnns :: EpAnn [AddEpAnn] -> [AddEpAnn] -> EpAnnComments -> EpAnn [AddEpAnn]
-addAnns (EpAnn l as1 cs) as2 cs2
-  = EpAnn (widenAnchor l (as1 ++ as2)) (as1 ++ as2) (cs <> cs2)
-
 -- AZ:TODO use widenSpan here too
 addAnnsA :: SrcSpanAnnA -> [TrailingAnn] -> EpAnnComments -> SrcSpanAnnA
 addAnnsA (EpAnn l as1 cs) as2 cs2
   = EpAnn l (AnnListItem (lann_trailing as1 ++ as2)) (cs <> cs2)
 
--- | The annotations need to all come after the anchor.  Make sure
--- this is the case.
-widenSpan :: SrcSpan -> [AddEpAnn] -> SrcSpan
-widenSpan s as = foldl combineSrcSpans s (go as)
-  where
-    go [] = []
-    go (AddEpAnn _ (EpaSpan (RealSrcSpan s mb)):rest) = RealSrcSpan s mb : go rest
-    go (AddEpAnn _ (EpaSpan _):rest) = go rest
-    go (AddEpAnn _ (EpaDelta _ _ _):rest) = go rest
-
 -- | The annotations need to all come after the anchor.  Make sure
 -- this is the case.
 widenSpanL :: SrcSpan -> [EpaLocation] -> SrcSpan
@@ -1149,35 +1134,6 @@ widenSpanT :: SrcSpan -> EpToken tok -> SrcSpan
 widenSpanT l (EpTok loc) = widenSpanL l [loc]
 widenSpanT l NoEpTok = l
 
--- | The annotations need to all come after the anchor.  Make sure
--- this is the case.
-widenRealSpan :: RealSrcSpan -> [AddEpAnn] -> RealSrcSpan
-widenRealSpan s as = foldl combineRealSrcSpans s (go as)
-  where
-    go [] = []
-    go (AddEpAnn _ (EpaSpan (RealSrcSpan s _)):rest) = s : go rest
-    go (AddEpAnn _ _:rest) = go rest
-
-realSpanFromAnns :: [AddEpAnn] -> Strict.Maybe RealSrcSpan
-realSpanFromAnns as = go Strict.Nothing as
-  where
-    combine Strict.Nothing r  = Strict.Just r
-    combine (Strict.Just l) r = Strict.Just $ combineRealSrcSpans l r
-
-    go acc [] = acc
-    go acc (AddEpAnn _ (EpaSpan (RealSrcSpan s _b)):rest) = go (combine acc s) rest
-    go acc (AddEpAnn _ _             :rest) = go acc rest
-
-bufSpanFromAnns :: [AddEpAnn] -> Strict.Maybe BufSpan
-bufSpanFromAnns as =  go Strict.Nothing as
-  where
-    combine Strict.Nothing r  = Strict.Just r
-    combine (Strict.Just l) r = Strict.Just $ combineBufSpans l r
-
-    go acc [] = acc
-    go acc (AddEpAnn _ (EpaSpan (RealSrcSpan _ (Strict.Just mb))):rest) = go (combine acc mb) rest
-    go acc (AddEpAnn _ _:rest) = go acc rest
-
 listLocation :: [LocatedAn an a] -> EpaLocation
 listLocation as = EpaSpan (go noSrcSpan as)
   where
@@ -1187,14 +1143,6 @@ listLocation as = EpaSpan (go noSrcSpan as)
     go acc (L (EpAnn (EpaSpan s) _ _) _:rest) = go (combine acc s) rest
     go acc (_:rest) = go acc rest
 
-widenAnchor :: EpaLocation -> [AddEpAnn] -> EpaLocation
-widenAnchor (EpaSpan (RealSrcSpan s mb)) as
-  = EpaSpan (RealSrcSpan (widenRealSpan s as) (liftA2 combineBufSpans mb  (bufSpanFromAnns as)))
-widenAnchor (EpaSpan us) _ = EpaSpan us
-widenAnchor a at EpaDelta{} as = case (realSpanFromAnns as) of
-                                    Strict.Nothing -> a
-                                    Strict.Just r -> EpaSpan (RealSrcSpan r Strict.Nothing)
-
 widenAnchorT :: EpaLocation -> EpToken tok -> EpaLocation
 widenAnchorT (EpaSpan ss) (EpTok l) = widenAnchorS l ss
 widenAnchorT ss _ = ss
@@ -1206,24 +1154,12 @@ widenAnchorS (EpaSpan us) _ = EpaSpan us
 widenAnchorS EpaDelta{} (RealSrcSpan r mb) = EpaSpan (RealSrcSpan r mb)
 widenAnchorS anc _ = anc
 
-widenLocatedAn :: EpAnn an -> [AddEpAnn] -> EpAnn an
-widenLocatedAn (EpAnn (EpaSpan l) a cs) as = EpAnn (spanAsAnchor l') a cs
-  where
-    l' = widenSpan l as
-widenLocatedAn (EpAnn anc a cs) _as = EpAnn anc a cs
-
 widenLocatedAnL :: EpAnn an -> [EpaLocation] -> EpAnn an
 widenLocatedAnL (EpAnn (EpaSpan l) a cs) as = EpAnn (spanAsAnchor l') a cs
   where
     l' = widenSpanL l as
 widenLocatedAnL (EpAnn anc a cs) _as = EpAnn anc a cs
 
-annParen2AddEpAnn :: AnnParen -> [AddEpAnn]
-annParen2AddEpAnn (AnnParen pt o c)
-  = [AddEpAnn ai o, AddEpAnn ac c]
-  where
-    (ai,ac) = parenTypeKws pt
-
 epAnnComments :: EpAnn an -> EpAnnComments
 epAnnComments (EpAnn _ _ cs) = cs
 


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -984,7 +984,7 @@ checkTyVars pp_what equals_or_where tc tparms
       = Just (noAnn, HsBndrWildCard noExtField)
     match_bndr_var _ = Nothing
 
-    -- Return an AddEpAnn for use in widenLocatedAn. The AnnKeywordId is not used.
+    -- Return an AddEpAnn for use in widenLocatedAnL. The AnnKeywordId is not used.
     for_widening :: HsBndrVis GhcPs -> EpaLocation
     for_widening (HsBndrInvisible (EpTok loc)) = loc
     for_widening  _                            = noAnn
@@ -1524,9 +1524,7 @@ isFunLhs e = go e [] [] []
    go (L l (PatBuilderAppType (L lp pat) tok ty_pat@(HsTP _ (L (EpAnn anc ann cs) _)))) es ops cps
              = go (L lp' pat) (L (EpAnn anc' ann cs) (ArgPatBuilderArgPat invis_pat) : es) ops cps
              where invis_pat = InvisPat (tok, SpecifiedSpec) ty_pat
-                   anc' = case tok of
-                     NoEpTok -> anc
-                     EpTok l -> widenAnchor anc [AddEpAnn AnnAnyclass l]
+                   anc' = widenAnchorT anc tok
                    (_l, lp') = transferCommentsOnlyA l lp
    go _ _ _ _ = return Nothing
 


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -268,10 +268,6 @@ instance HasTrailing AddEpAnn where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing [AddEpAnn] where
-  trailing _ = []
-  setTrailing a _ = a
-
 instance HasTrailing (AddEpAnn, AddEpAnn) where
   trailing _ = []
   setTrailing a _ = a
@@ -1025,10 +1021,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lidl :: Lens [AddEpAnn] [AddEpAnn]
-lidl k parent = fmap (\new -> new)
-                     (k parent)
-
 lid :: Lens a a
 lid k parent = fmap (\new -> new)
                     (k parent)
@@ -1156,17 +1148,13 @@ lhsCaseAnnOf k parent = fmap (\new -> parent { hsCaseAnnOf = new })
 
 -- data HsRuleAnn
 --   = HsRuleAnn
---        { ra_tyanns :: Maybe (AddEpAnn, AddEpAnn)
---                  -- ^ The locations of 'forall' and '.' for forall'd type vars
---                  -- Using AddEpAnn to capture possible unicode variants
---        , ra_tmanns :: Maybe (AddEpAnn, AddEpAnn)
---                  -- ^ The locations of 'forall' and '.' for forall'd term vars
---                  -- Using AddEpAnn to capture possible unicode variants
+--        { ra_tyanns :: Maybe (TokForall, EpToken ".")
+--        , ra_tmanns :: Maybe (TokForall, EpToken ".")
 --        , ra_equal  :: EpToken "="
 --        , ra_rest :: ActivationAnn
 --        } deriving (Data, Eq)
 
-lra_tyanns :: Lens HsRuleAnn (Maybe (AddEpAnn, AddEpAnn))
+lra_tyanns :: Lens HsRuleAnn (Maybe (TokForall, EpToken "."))
 lra_tyanns k parent = fmap (\new -> parent { ra_tyanns = new })
                                (k (ra_tyanns parent))
 
@@ -1185,20 +1173,20 @@ lff k parent = fmap (\new -> gg new)
                     (k (ff parent))
 
 -- (.) :: Lens' a b -> Lens' b c -> Lens' a c
-lra_tyanns_fst :: Lens HsRuleAnn (Maybe AddEpAnn)
+lra_tyanns_fst :: Lens HsRuleAnn (Maybe TokForall)
 lra_tyanns_fst = lra_tyanns . lff . lfst
 
-lra_tyanns_snd :: Lens HsRuleAnn (Maybe AddEpAnn)
+lra_tyanns_snd :: Lens HsRuleAnn (Maybe (EpToken "."))
 lra_tyanns_snd = lra_tyanns . lff . lsnd
 
-lra_tmanns :: Lens HsRuleAnn (Maybe (AddEpAnn, AddEpAnn))
+lra_tmanns :: Lens HsRuleAnn (Maybe (TokForall, EpToken "."))
 lra_tmanns k parent = fmap (\new -> parent { ra_tmanns = new })
                                (k (ra_tmanns parent))
 
-lra_tmanns_fst :: Lens HsRuleAnn (Maybe AddEpAnn)
+lra_tmanns_fst :: Lens HsRuleAnn (Maybe TokForall)
 lra_tmanns_fst = lra_tmanns . lff . lfst
 
-lra_tmanns_snd :: Lens HsRuleAnn (Maybe AddEpAnn)
+lra_tmanns_snd :: Lens HsRuleAnn (Maybe (EpToken "."))
 lra_tmanns_snd = lra_tmanns . lff . lsnd
 
 lra_equal :: Lens HsRuleAnn (EpToken "=")
@@ -1304,22 +1292,8 @@ markLensTok (EpAnn anc a cs) l = do
   new <- markEpToken (view l a)
   return (EpAnn anc (set l new a) cs)
 
-markLensTok' :: (Monad m, Monoid w, KnownSymbol sym)
-  => a -> Lens a (EpToken sym) -> EP w m a
-markLensTok' a l = do
-  new <- markEpToken (view l a)
-  return (set l new a)
-
 -- ---------------------------------------------------------------------
 
-markEpAnnL :: (Monad m, Monoid w)
-  => ann -> Lens ann [AddEpAnn] -> AnnKeywordId -> EP w m ann
-markEpAnnL a l kw = do
-  anns <- mark (view l a) kw
-  return (set l anns a)
-
--- -------------------------------------
-
 markLensFun' :: (Monad m, Monoid w)
   => EpAnn ann -> Lens ann t -> (t -> EP w m t) -> EP w m (EpAnn ann)
 markLensFun' epann l f = markLensFun epann (lepa . l) f
@@ -1895,46 +1869,36 @@ instance ExactPrint (InstDecl GhcPs) where
     cid' <- markAnnotated cid
     return (ClsInstD     a  cid')
   exact (DataFamInstD a decl) = do
-    d' <- markAnnotated (DataFamInstDeclWithContext noAnn TopLevel decl)
-    return (DataFamInstD a (dc_d d'))
+    decl' <- markAnnotated decl
+    return (DataFamInstD a decl')
   exact (TyFamInstD a eqn) = do
     eqn' <- markAnnotated eqn
     return (TyFamInstD a eqn')
 
 -- ---------------------------------------------------------------------
 
-data DataFamInstDeclWithContext
-  = DataFamInstDeclWithContext
-    { _dc_a :: [AddEpAnn]
-    , _dc_f :: TopLevelFlag
-    , dc_d :: DataFamInstDecl GhcPs
-    }
-
-instance ExactPrint DataFamInstDeclWithContext where
+instance ExactPrint (DataFamInstDecl GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
-  exact (DataFamInstDeclWithContext an c d) = do
-    debugM $ "starting DataFamInstDeclWithContext:an=" ++ showAst an
-    (an', d') <- exactDataFamInstDecl an c d
-    return (DataFamInstDeclWithContext an' c d')
+  exact d = do
+    d' <- exactDataFamInstDecl d
+    return d'
 
 -- ---------------------------------------------------------------------
 
 exactDataFamInstDecl :: (Monad m, Monoid w)
-                     => [AddEpAnn] -> TopLevelFlag -> DataFamInstDecl GhcPs
-                     -> EP w m ([AddEpAnn], DataFamInstDecl GhcPs)
-exactDataFamInstDecl an top_lvl
+                     => DataFamInstDecl GhcPs
+                     -> EP w m (DataFamInstDecl GhcPs)
+exactDataFamInstDecl
   (DataFamInstDecl (FamEqn { feqn_ext    = (ops, cps, eq)
                            , feqn_tycon  = tycon
                            , feqn_bndrs  = bndrs
                            , feqn_pats   = pats
                            , feqn_fixity = fixity
                            , feqn_rhs    = defn })) = do
-    ((ops', cps', an'), tycon', bndrs', pats', defn') <- exactDataDefn pp_hdr defn
-                                          -- See Note [an and an2 in exactDataFamInstDecl]
+    ((ops', cps'), tycon', bndrs', pats', defn') <- exactDataDefn pp_hdr defn
     return
-      (an',
-       DataFamInstDecl ( FamEqn { feqn_ext    = (ops', cps', eq)
+      (DataFamInstDecl ( FamEqn { feqn_ext    = (ops', cps', eq)
                                 , feqn_tycon  = tycon'
                                 , feqn_bndrs  = bndrs'
                                 , feqn_pats   = pats'
@@ -1944,28 +1908,12 @@ exactDataFamInstDecl an top_lvl
   where
     pp_hdr :: (Monad m, Monoid w)
            => Maybe (LHsContext GhcPs)
-           -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
+           -> EP w m ( ([EpToken "("], [EpToken ")"] )
                      , LocatedN RdrName
                      , HsOuterTyVarBndrs () GhcPs
                      , HsFamEqnPats GhcPs
                      , Maybe (LHsContext GhcPs))
-    pp_hdr mctxt = do
-      an0 <- case top_lvl of
-               TopLevel -> markEpAnnL an lidl AnnInstance -- TODO: maybe in toplevel
-               NotTopLevel -> return an
-      exactHsFamInstLHS ops cps an0 tycon bndrs pats fixity mctxt
-
-{-
-Note [an and an2 in exactDataFamInstDecl]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The exactDataFamInstDecl function is called to render a
-DataFamInstDecl within its surrounding context. This context is
-rendered via the 'pp_hdr' function, which uses the exact print
-annotations from that context, named 'an'.  The EPAs used for
-rendering the DataDefn are contained in the FamEqn, and are called
-'an2'.
-
--}
+    pp_hdr mctxt = exactHsFamInstLHS ops cps tycon bndrs pats fixity mctxt
 
 -- ---------------------------------------------------------------------
 
@@ -2152,17 +2100,17 @@ instance ExactPrint (RuleDecl GhcPs) where
       case mtybndrs of
         Nothing -> return (an0, Nothing)
         Just bndrs -> do
-          an1 <-  markLensMAA' an0 lra_tyanns_fst  -- AnnForall
+          an1 <-  markLensFun an0 lra_tyanns_fst (\mt -> mapM markEpUniToken mt)  -- AnnForall
           bndrs' <- mapM markAnnotated bndrs
-          an2 <- markLensMAA' an1 lra_tyanns_snd  -- AnnDot
+          an2 <- markLensFun an1 lra_tyanns_snd (\mt -> mapM markEpToken mt)  -- AnnDot
           return (an2, Just bndrs')
 
-    an2 <- markLensMAA' an1 lra_tmanns_fst  -- AnnForall
+    an2 <- markLensFun an1 lra_tmanns_fst (\mt -> mapM markEpUniToken mt) -- AnnForall
     termbndrs' <- mapM markAnnotated termbndrs
-    an3 <- markLensMAA' an2 lra_tmanns_snd  -- AnnDot
+    an3 <- markLensFun an2 lra_tmanns_snd (\mt -> mapM markEpToken mt)  -- AnnDot
 
     lhs' <- markAnnotated lhs
-    an4 <- markLensTok' an3 lra_equal
+    an4 <- markLensFun an3 lra_equal markEpToken
     rhs' <- markAnnotated rhs
     return (HsRule (an4,nsrc) (L ln' n) act mtybndrs' termbndrs' lhs' rhs')
 
@@ -2268,10 +2216,10 @@ instance (ExactPrint body) => ExactPrint (FamEqn GhcPs body) where
                 , feqn_pats   = pats
                 , feqn_fixity = fixity
                 , feqn_rhs    = rhs }) = do
-    (_an0, tycon', bndrs', pats', _) <- exactHsFamInstLHS ops cps [] tycon bndrs pats fixity Nothing
+    ((ops', cps'), tycon', bndrs', pats',_) <- exactHsFamInstLHS ops cps tycon bndrs pats fixity Nothing
     eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
-    return (FamEqn { feqn_ext    = ([], [], eq')
+    return (FamEqn { feqn_ext    = (ops', cps', eq')
                    , feqn_tycon  = tycon'
                    , feqn_bndrs  = bndrs'
                    , feqn_pats   = pats'
@@ -2284,24 +2232,23 @@ exactHsFamInstLHS ::
       (Monad m, Monoid w)
    => [EpToken "("]
    -> [EpToken ")"]
-   -> [AddEpAnn]
    -> LocatedN RdrName
    -> HsOuterTyVarBndrs () GhcPs
    -> HsFamEqnPats GhcPs
    -> LexicalFixity
    -> Maybe (LHsContext GhcPs)
-   -> EP w m ( ([EpToken "("], [EpToken ")"], [AddEpAnn])
+   -> EP w m ( ([EpToken "("], [EpToken ")"])
              , LocatedN RdrName
              , HsOuterTyVarBndrs () GhcPs
              , HsFamEqnPats GhcPs, Maybe (LHsContext GhcPs))
-exactHsFamInstLHS ops cps an thing bndrs typats fixity mb_ctxt = do
+exactHsFamInstLHS ops cps thing bndrs typats fixity mb_ctxt = do
   -- TODO:AZ: do these ans exist? They are in the binders now
-  an0 <- markEpAnnL an lidl AnnForall
+  -- an0 <- markEpAnnL an lidl AnnForall
   bndrs' <- markAnnotated bndrs
-  an1 <- markEpAnnL an0 lidl AnnDot
+  -- an1 <- markEpAnnL an0 lidl AnnDot
   mb_ctxt' <- mapM markAnnotated mb_ctxt
   (ops', cps', thing', typats') <- exact_pats ops cps typats
-  return ((ops', cps', an1), thing', bndrs', typats', mb_ctxt')
+  return ((ops', cps'), thing', bndrs', typats', mb_ctxt')
   where
     exact_pats :: (Monad m, Monoid w)
       => [EpToken "("] -> [EpToken ")"] -> HsFamEqnPats GhcPs
@@ -2730,8 +2677,8 @@ prepareListAnnotationF :: (Monad m, Monoid w) =>
 prepareListAnnotationF ls = map (\b -> (realSrcSpan $ getLocA b, go b)) ls
   where
     go (L l a) = do
-      (L l' d') <- markAnnotated (L l (DataFamInstDeclWithContext noAnn NotTopLevel a))
-      return (toDyn (L l' (dc_d d')))
+      (L l' d') <- markAnnotated (L l a)
+      return (toDyn (L l' d'))
 
 prepareListAnnotationA :: (Monad m, Monoid w, ExactPrint (LocatedAn an a))
   => [LocatedAn an a] -> [(RealSrcSpan,EP w m Dynamic)]
@@ -3498,18 +3445,34 @@ instance ExactPrint (HsCmd GhcPs) where
   getAnnotationEntry _ = NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
-  exact (HsCmdArrApp an arr arg o isRightToLeft) = do
-    if isRightToLeft
-      then do
-        arr' <- markAnnotated arr
-        an0 <- markKw an
-        arg' <- markAnnotated arg
-        return (HsCmdArrApp an0 arr' arg' o isRightToLeft)
-      else do
-        arg' <- markAnnotated arg
-        an0 <- markKw an
-        arr' <- markAnnotated arr
-        return (HsCmdArrApp an0 arr' arg' o isRightToLeft)
+  exact (HsCmdArrApp (isU, l) arr arg HsFirstOrderApp True) = do
+    arr' <- markAnnotated arr
+    l' <- case isU of
+      UnicodeSyntax -> printStringAtAA l  "⤙"
+      NormalSyntax -> printStringAtAA l  "-<"
+    arg' <- markAnnotated arg
+    return (HsCmdArrApp (isU, l') arr' arg' HsFirstOrderApp True)
+  exact (HsCmdArrApp (isU, l) arr arg HsFirstOrderApp False) = do
+    arg' <- markAnnotated arg
+    l' <- case isU of
+      UnicodeSyntax -> printStringAtAA l  "⤚"
+      NormalSyntax -> printStringAtAA l  ">-"
+    arr' <- markAnnotated arr
+    return (HsCmdArrApp (isU, l') arr' arg' HsFirstOrderApp False)
+  exact (HsCmdArrApp (isU, l) arr arg HsHigherOrderApp True) = do
+    arr' <- markAnnotated arr
+    l' <- case isU of
+      UnicodeSyntax -> printStringAtAA l  "⤛"
+      NormalSyntax -> printStringAtAA l  "-<<"
+    arg' <- markAnnotated arg
+    return (HsCmdArrApp (isU, l') arr' arg' HsHigherOrderApp True)
+  exact (HsCmdArrApp (isU, l) arr arg HsHigherOrderApp False) = do
+    arg' <- markAnnotated arg
+    l' <- case isU of
+      UnicodeSyntax -> printStringAtAA l  "⤜"
+      NormalSyntax -> printStringAtAA l  ">>-"
+    arr' <- markAnnotated arr
+    return (HsCmdArrApp (isU, l') arr' arg' HsHigherOrderApp False)
 
   exact (HsCmdArrForm an e fixity cs) = do
     an0 <- markLensMAA' an lal_open
@@ -3891,7 +3854,7 @@ exactDataDefn exactHdr
       nt' <- markEpToken nt
       return (t, nt', d)
 
-  i' <- markEpToken i -- optional
+  i' <- markEpToken i -- optional 'instance'
   mb_ct' <- mapM markAnnotated mb_ct
   (anx, ln', tvs', b, mctxt') <- exactHdr context
   (dc', mb_sig') <- case mb_sig of


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -842,28 +842,28 @@ type instance XLinearArrow _ DocNameI = NoExtField
 type instance XExplicitMult _ DocNameI = NoExtField
 type instance XXArrow _ DocNameI = DataConCantHappen
 
-type instance XForAllTy DocNameI = EpAnn [AddEpAnn]
-type instance XQualTy DocNameI = EpAnn [AddEpAnn]
-type instance XTyVar DocNameI = EpAnn [AddEpAnn]
-type instance XStarTy DocNameI = EpAnn [AddEpAnn]
-type instance XAppTy DocNameI = EpAnn [AddEpAnn]
-type instance XAppKindTy DocNameI = EpAnn [AddEpAnn]
-type instance XFunTy DocNameI = EpAnn [AddEpAnn]
+type instance XForAllTy DocNameI = EpAnn NoEpAnns
+type instance XQualTy DocNameI = EpAnn NoEpAnns
+type instance XTyVar DocNameI = EpAnn NoEpAnns
+type instance XStarTy DocNameI = EpAnn NoEpAnns
+type instance XAppTy DocNameI = EpAnn NoEpAnns
+type instance XAppKindTy DocNameI = EpAnn NoEpAnns
+type instance XFunTy DocNameI = EpAnn NoEpAnns
 type instance XListTy DocNameI = EpAnn AnnParen
 type instance XTupleTy DocNameI = EpAnn AnnParen
 type instance XSumTy DocNameI = EpAnn AnnParen
-type instance XOpTy DocNameI = EpAnn [AddEpAnn]
+type instance XOpTy DocNameI = EpAnn NoEpAnns
 type instance XParTy DocNameI = (EpToken "(", EpToken ")")
-type instance XIParamTy DocNameI = EpAnn [AddEpAnn]
-type instance XKindSig DocNameI = EpAnn [AddEpAnn]
+type instance XIParamTy DocNameI = EpAnn NoEpAnns
+type instance XKindSig DocNameI = EpAnn NoEpAnns
 type instance XSpliceTy DocNameI = DataConCantHappen
-type instance XDocTy DocNameI = EpAnn [AddEpAnn]
-type instance XBangTy DocNameI = EpAnn [AddEpAnn]
-type instance XRecTy DocNameI = EpAnn [AddEpAnn]
-type instance XExplicitListTy DocNameI = EpAnn [AddEpAnn]
-type instance XExplicitTupleTy DocNameI = EpAnn [AddEpAnn]
-type instance XTyLit DocNameI = EpAnn [AddEpAnn]
-type instance XWildCardTy DocNameI = EpAnn [AddEpAnn]
+type instance XDocTy DocNameI = EpAnn NoEpAnns
+type instance XBangTy DocNameI = EpAnn NoEpAnns
+type instance XRecTy DocNameI = EpAnn NoEpAnns
+type instance XExplicitListTy DocNameI = EpAnn NoEpAnns
+type instance XExplicitTupleTy DocNameI = EpAnn NoEpAnns
+type instance XTyLit DocNameI = EpAnn NoEpAnns
+type instance XWildCardTy DocNameI = EpAnn NoEpAnns
 type instance XXType DocNameI = HsCoreTy
 
 type instance XNumTy DocNameI = NoExtField



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 16:45:11 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 26 Oct 2024 12:45:11 -0400
Subject: [Git][ghc/ghc][master] Fix optimisation of InstCo
Message-ID: <671d1c971d51f_289b863021f41242aa@gitlab.mail>



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


Commits:
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -


9 changed files:

- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/Types/Basic.hs
- + testsuite/tests/dependent/should_compile/T25387.hs
- testsuite/tests/dependent/should_compile/all.T


Changes:

=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -30,7 +30,7 @@ module GHC.Core.Coercion (
         coercionRole, coercionKindRole,
 
         -- ** Constructing coercions
-        mkGReflCo, mkReflCo, mkRepReflCo, mkNomReflCo,
+        mkGReflCo, mkGReflMCo, mkReflCo, mkRepReflCo, mkNomReflCo,
         mkCoVarCo, mkCoVarCos,
         mkAxInstCo, mkUnbranchedAxInstCo,
         mkAxInstRHS, mkUnbranchedAxInstRHS,
@@ -332,8 +332,23 @@ isGReflMCo _ = False
 mkGReflCo :: Role -> Type -> MCoercionN -> Coercion
 mkGReflCo r ty mco
   | isGReflMCo mco = if r == Nominal then Refl ty
-                     else GRefl r ty MRefl
-  | otherwise    = GRefl r ty mco
+                                     else GRefl r ty MRefl
+  | otherwise
+  = -- I'd like to have this assert, but sadly it's not true during type
+    -- inference because the types are not fully zonked
+    -- assertPpr (case mco of
+    --              MCo co -> typeKind ty `eqType` coercionLKind co
+    --              MRefl  -> True)
+    --          (vcat [ text "ty" <+> ppr ty <+> dcolon <+> ppr (typeKind ty)
+    --                , case mco of
+    --                     MCo co -> text "co" <+> ppr co
+    --                                  <+> dcolon <+> ppr (coercionKind co)
+    --                     MRefl  -> text "MRefl"
+    --                , callStackDoc ]) $
+    GRefl r ty mco
+
+mkGReflMCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion
+mkGReflMCo r ty co = mkGReflCo r ty (MCo co)
 
 -- | Compose two MCoercions via transitivity
 mkTransMCo :: MCoercion -> MCoercion -> MCoercion
@@ -1127,14 +1142,19 @@ mkSymCo co@(ForAllCo { fco_kind = kco, fco_body = body_co })
   | isReflCo kco           = co { fco_body = mkSymCo body_co }
 mkSymCo co                 = SymCo co
 
--- | Create a new 'Coercion' by composing the two given 'Coercion's transitively.
---   (co1 ; co2)
-mkTransCo :: Coercion -> Coercion -> Coercion
-mkTransCo co1 co2 | isReflCo co1 = co2
-                  | isReflCo co2 = co1
-mkTransCo (GRefl r t1 (MCo co1)) (GRefl _ _ (MCo co2))
-  = GRefl r t1 (MCo $ mkTransCo co1 co2)
-mkTransCo co1 co2                = TransCo co1 co2
+-- | mkTransCo creates a new 'Coercion' by composing the two
+--   given 'Coercion's transitively: (co1 ; co2)
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+mkTransCo co1 co2
+   | isReflCo co1 = co2
+   | isReflCo co2 = co1
+
+   | GRefl r t1 (MCo kco1) <- co1
+   , GRefl _ _  (MCo kco2) <- co2
+   = GRefl r t1 (MCo $ mkTransCo kco1 kco2)
+
+   | otherwise
+   = TransCo co1 co2
 
 --------------------
 {- Note [mkSelCo precondition]
@@ -1294,7 +1314,7 @@ mkGReflRightCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise = GRefl r ty (MCo co)
+  | otherwise = mkGReflMCo r ty co
 
 -- | Given @r@, @ty :: k1@, and @co :: k1 ~N k2@,
 -- produces @co' :: (ty |> co) ~r ty@
@@ -1303,7 +1323,7 @@ mkGReflLeftCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise    = mkSymCo $ GRefl r ty (MCo co)
+  | otherwise    = mkSymCo $ mkGReflMCo r ty co
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty ~r ty'@,
 -- produces @co' :: (ty |> co) ~r ty'
@@ -1312,16 +1332,16 @@ mkGReflLeftCo r ty co
 mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceLeftCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = (mkSymCo $ GRefl r ty (MCo co)) `mkTransCo` co2
+  | otherwise    = (mkSymCo $ mkGReflMCo r ty co) `mkTransCo` co2
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty' ~r ty@,
 -- produces @co' :: ty' ~r (ty |> co)
 -- It is not only a utility function, but it saves allocation when co
 -- is a GRefl coercion.
-mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
+mkCoherenceRightCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceRightCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = co2 `mkTransCo` GRefl r ty (MCo co)
+  | otherwise    = co2 `mkTransCo` mkGReflMCo r ty co
 
 -- | Given @co :: (a :: k) ~ (b :: k')@ produce @co' :: k ~ k'@.
 mkKindCo :: Coercion -> Coercion
@@ -1680,8 +1700,8 @@ castCoercionKind1 g r t1 t2 h
                  mkNomReflCo (mkCastTy t2 h)
       GRefl _ _ mco -> case mco of
            MRefl       -> mkReflCo r (mkCastTy t2 h)
-           MCo kind_co -> GRefl r (mkCastTy t1 h) $
-                          MCo (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
+           MCo kind_co -> mkGReflMCo r (mkCastTy t1 h)
+                               (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
       _ -> castCoercionKind2 g r t1 t2 h h
 
 -- | Creates a new coercion with both of its types casted by different casts
@@ -2108,10 +2128,10 @@ zapLiftingContext :: LiftingContext -> LiftingContext
 zapLiftingContext (LC subst _) = LC (zapSubst subst) emptyVarEnv
 
 -- | Like 'substForAllCoBndr', but works on a lifting context
-substForAllCoBndrUsingLC :: Bool
-                            -> (Coercion -> Coercion)
-                            -> LiftingContext -> TyCoVar -> Coercion
-                            -> (LiftingContext, TyCoVar, Coercion)
+substForAllCoBndrUsingLC :: SwapFlag
+                         -> (Coercion -> Coercion)
+                         -> LiftingContext -> TyCoVar -> Coercion
+                         -> (LiftingContext, TyCoVar, Coercion)
 substForAllCoBndrUsingLC sym sco (LC subst lc_env) tv co
   = (LC subst' lc_env, tv', co')
   where
@@ -2658,7 +2678,7 @@ mkCoercionType Phantom          = \ty1 ty2 ->
 -- transitivity over coercion applications, where splitting two
 -- AppCos might yield different kinds. See Note [EtaAppCo] in
 -- "GHC.Core.Coercion.Opt".
-buildCoercion :: Type -> Type -> CoercionN
+buildCoercion :: HasDebugCallStack => Type -> Type -> CoercionN
 buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
   where
     go ty1 ty2 | Just ty1' <- coreView ty1 = go ty1' ty2
@@ -2686,7 +2706,10 @@ buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
         mkFunCo Nominal af1 (go w1 w2) (go arg1 arg2) (go res1 res2)
 
     go (TyConApp tc1 args1) (TyConApp tc2 args2)
-      = assert (tc1 == tc2) $
+      = assertPpr (tc1 == tc2) (vcat [ ppr tc1 <+> ppr tc2
+                                     , text "orig_ty1:" <+> ppr orig_ty1
+                                     , text "orig_ty2:" <+> ppr orig_ty2
+                                     ]) $
         mkTyConAppCo Nominal tc1 (zipWith go args1 args2)
 
     go (AppTy ty1a ty1b) ty2


=====================================
compiler/GHC/Core/Coercion.hs-boot
=====================================
@@ -24,7 +24,7 @@ mkCoVarCo :: CoVar -> Coercion
 mkPhantomCo :: Coercion -> Type -> Type -> Coercion
 mkUnivCo :: UnivCoProvenance -> [Coercion] -> Role -> Type -> Type -> Coercion
 mkSymCo :: Coercion -> Coercion
-mkTransCo :: Coercion -> Coercion -> Coercion
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
 mkSelCo :: HasDebugCallStack => CoSel -> Coercion -> Coercion
 mkLRCo :: LeftOrRight -> Coercion -> Coercion
 mkInstCo :: Coercion -> Coercion -> Coercion


=====================================
compiler/GHC/Core/Coercion/Opt.hs
=====================================
@@ -21,6 +21,7 @@ import GHC.Core.TyCon
 import GHC.Core.Coercion.Axiom
 import GHC.Core.Unify
 
+import GHC.Types.Basic( SwapFlag(..), flipSwap, isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -66,32 +67,55 @@ opt_co2.
 
 Note [Optimising InstCo]
 ~~~~~~~~~~~~~~~~~~~~~~~~
-(1) tv is a type variable
-When we have (InstCo (ForAllCo tv h g) g2), we want to optimise.
+Optimising InstCo is pretty subtle: #15725, #25387.
 
-Let's look at the typing rules.
+(1) tv is a type variable. We want to optimise
 
-h : k1 ~ k2
-tv:k1 |- g : t1 ~ t2
------------------------------
-ForAllCo tv h g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym h])
+  InstCo (ForAllCo tv kco g) g2  -->   S(g)
 
-g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
-g2 : s1 ~ s2
---------------------
-InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+where S is some substitution. Let's look at the typing rules.
 
-We thus want some coercion proving this:
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    -----------------------------
+    ForAllCo tv kco g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym kco])
+
+    g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+
+Putting these two together
 
-  (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym h])
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo (ForAllCo tv kco g) g2 : t1[tv |-> s1] ~ t2[tv |-> s2 |> sym kco]
 
-If we substitute the *type* tv for the *coercion*
-(g2 ; t2 ~ t2 |> sym h) in g, we'll get this result exactly.
-This is bizarre,
-though, because we're substituting a type variable with a coercion. However,
-this operation already exists: it's called *lifting*, and defined in GHC.Core.Coercion.
-We just need to enhance the lifting operation to be able to deal with
-an ambient substitution, which is why a LiftingContext stores a TCvSubst.
+We thus want S(g) to have kind
+
+  S(g) :: (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym kco])
+
+All we need do is to substitute the coercion tv_co for tv:
+  S = [tv :-> tv_co]
+where
+  tv_co : s1 ~ (s2 |> sym kco)
+This looks bizarre, because we're substituting a /type variable/ with a
+/coercion/. However, this operation already exists: it's called *lifting*, and
+defined in GHC.Core.Coercion.  We just need to enhance the lifting operation to
+be able to deal with an ambient substitution, which is why a LiftingContext
+stores a TCvSubst.
+
+In general if
+  S = [tv :-> tv_co]
+  tv_co : r1 ~ r2
+  g     : t1 ~ t2
+then
+  S(g) : t1[tv :-> r1] ~ t2[tv :-> r2]
+
+The substitution S is embodied in the LiftingContext argument of `opt_co4`;
+See Note [The LiftingContext in optCoercion]
 
 (2) cv is a coercion variable
 Now consider we have (InstCo (ForAllCo cv h g) g2), we want to optimise.
@@ -117,6 +141,27 @@ We thus want some coercion proving this:
 
 So we substitute the coercion variable c for the coercion
 (h1 ~N (n1; h2; sym n2)) in g.
+
+Note [The LiftingContext in optCoercion]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+To suppport Note [Optimising InstCo] the coercion optimiser carries a
+GHC.Core.Coercion.LiftingContext, which comprises
+  * An ordinary Subst
+  * The `lc_env`: a mapping from /type variables/ to /coercions/
+
+We don't actually have a separate function
+   liftCoSubstCo :: LiftingContext -> Coercion -> Coercion
+The substitution of a type variable by a coercion is done by the calls to
+`liftCoSubst` (on a type) in the Refl and GRefl cases of `opt_co4`.
+
+We use the following invariants:
+ (LC1) The coercions in the range of `lc_env` have already had all substitutions
+       applied; they are "OutCoercions".  If you re-optimise these coercions, you
+       must zap the LiftingContext first.
+
+ (LC2) However they have /not/ had the "ambient sym" (the second argument of
+       `opt_co4`) applied.  The ambient sym applies to the entire coercion not
+       to the little bits being substituted.
 -}
 
 -- | Coercion optimisation options
@@ -147,7 +192,7 @@ optCoercion opts env co
 optCoercion' :: Subst -> Coercion -> NormalCo
 optCoercion' env co
   | debugIsOn
-  = let out_co = opt_co1 lc False co
+  = let out_co = opt_co1 lc NotSwapped co
         (Pair in_ty1  in_ty2,  in_role)  = coercionKindRole co
         (Pair out_ty1 out_ty2, out_role) = coercionKindRole out_co
 
@@ -170,7 +215,7 @@ optCoercion' env co
     out_co
 
   | otherwise
-  = opt_co1 lc False co
+  = opt_co1 lc NotSwapped co
   where
     lc = mkSubstLiftingContext env
 --    ppr_one cv = ppr cv <+> dcolon <+> ppr (coVarKind cv)
@@ -184,41 +229,38 @@ type NormalCo    = Coercion
 
 type NormalNonIdCo = NormalCo  -- Extra invariant: not the identity
 
--- | Do we apply a @sym@ to the result?
-type SymFlag = Bool
-
 -- | Do we force the result to be representational?
 type ReprFlag = Bool
 
 -- | Optimize a coercion, making no assumptions. All coercions in
 -- the lifting context are already optimized (and sym'd if nec'y)
 opt_co1 :: LiftingContext
-        -> SymFlag
+        -> SwapFlag   -- IsSwapped => apply Sym to the result
         -> Coercion -> NormalCo
 opt_co1 env sym co = opt_co2 env sym (coercionRole co) co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's role. No other assumptions.
 opt_co2 :: LiftingContext
-        -> SymFlag
-        -> Role   -- ^ The role of the input coercion
+        -> SwapFlag   -- ^IsSwapped => apply Sym to the result
+        -> Role       -- ^ The role of the input coercion
         -> Coercion -> NormalCo
 opt_co2 env sym Phantom co = opt_phantom env sym co
-opt_co2 env sym r       co = opt_co4_wrap env sym False r co
+opt_co2 env sym r       co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's non-Phantom role,
 --   and with an optional downgrade
-opt_co3 :: LiftingContext -> SymFlag -> Maybe Role -> Role -> Coercion -> NormalCo
+opt_co3 :: LiftingContext -> SwapFlag -> Maybe Role -> Role -> Coercion -> NormalCo
 opt_co3 env sym (Just Phantom)          _ co = opt_phantom env sym co
-opt_co3 env sym (Just Representational) r co = opt_co4_wrap env sym True  r co
+opt_co3 env sym (Just Representational) r co = opt_co4 env sym True  r co
   -- if mrole is Just Nominal, that can't be a downgrade, so we can ignore
-opt_co3 env sym _                       r co = opt_co4_wrap env sym False r co
+opt_co3 env sym _                       r co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a non-phantom coercion.
-opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
-                      -> Role -> Coercion -> NormalCo
+opt_co4, opt_co4' :: LiftingContext -> SwapFlag -> ReprFlag
+                  -> Role -> Coercion -> NormalCo
 -- Precondition:  In every call (opt_co4 lc sym rep role co)
 --                we should have role = coercionRole co
 -- Precondition:  role is not Phantom
@@ -227,20 +269,20 @@ opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
 --                 where wrapsym is SymCo if sym=True
 --                       wrapsub is SubCo if rep=True
 
--- opt_co4_wrap is there just to support tracing, when debugging
--- Usually it just goes straight to opt_co4
-opt_co4_wrap = opt_co4
+-- opt_co4 is there just to support tracing, when debugging
+-- Usually it just goes straight to opt_co4'
+opt_co4 = opt_co4'
 
 {-
-opt_co4_wrap env sym rep r co
-  = pprTrace "opt_co4_wrap {"
+opt_co4 env sym rep r co
+  = pprTrace "opt_co4 {"
    ( vcat [ text "Sym:" <+> ppr sym
           , text "Rep:" <+> ppr rep
           , text "Role:" <+> ppr r
           , text "Co:" <+> ppr co ]) $
    assert (r == coercionRole co )    $
-   let result = opt_co4 env sym rep r co in
-   pprTrace "opt_co4_wrap }" (ppr co $$ text "---" $$ ppr result) $
+   let result = opt_co4' env sym rep r co in
+   pprTrace "opt_co4 }" (ppr co $$ text "---" $$ ppr result) $
    assertPpr (res_role == coercionRole result)
              (vcat [ text "Role:" <+> ppr r
                    , text "Result: " <+>  ppr result
@@ -252,40 +294,45 @@ opt_co4_wrap env sym rep r co
              | otherwise = r
 -}
 
-opt_co4 env _   rep r (Refl ty)
+opt_co4' env sym rep r (Refl ty)
   = assertPpr (r == Nominal)
               (text "Expected role:" <+> ppr r    $$
                text "Found role:" <+> ppr Nominal $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env _   rep r (GRefl _r ty MRefl)
+opt_co4' env sym rep r (GRefl _r ty MRefl)
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env sym  rep r (GRefl _r ty (MCo co))
+opt_co4' env sym  rep r (GRefl _r ty (MCo kco))
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    if isGReflCo co || isGReflCo co'
-    then liftCoSubst r' env ty
-    else wrapSym sym $ mkCoherenceRightCo r' ty' co' (liftCoSubst r' env ty)
+    if isGReflCo kco || isGReflCo kco'
+    then wrapSym sym ty_co
+    else wrapSym sym $ mk_coherence_right_co r' (coercionRKind ty_co) kco' ty_co
+            -- ty :: k1
+            -- kco :: k1 ~ k2
+            -- Desired result coercion:   ty ~ ty |> co
   where
-    r'  = chooseRole rep r
-    ty' = substTy (lcSubstLeft env) ty
-    co' = opt_co4 env False False Nominal co
+    r'    = chooseRole rep r
+    ty_co = liftCoSubst r' env ty
+    kco'  = opt_co4 env NotSwapped False Nominal kco
 
-opt_co4 env sym rep r (SymCo co)  = opt_co4_wrap env (not sym) rep r co
+opt_co4' env sym rep r (SymCo co)  = opt_co4 env (flipSwap sym) rep r co
   -- surprisingly, we don't have to do anything to the env here. This is
   -- because any "lifting" substitutions in the env are tied to ForAllCos,
   -- which treat their left and right sides differently. We don't want to
   -- exchange them.
 
-opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
+opt_co4' env sym rep r g@(TyConAppCo _r tc cos)
   = assert (r == _r) $
     case (rep, r) of
       (True, Nominal) ->
@@ -295,7 +342,7 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                (repeat Nominal)
                                cos)
       (False, Nominal) ->
-        mkTyConAppCo Nominal tc (map (opt_co4_wrap env sym False Nominal) cos)
+        mkTyConAppCo Nominal tc (map (opt_co4 env sym False Nominal) cos)
       (_, Representational) ->
                       -- must use opt_co2 here, because some roles may be P
                       -- See Note [Optimising coercion optimisation]
@@ -304,34 +351,35 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                    cos)
       (_, Phantom) -> pprPanic "opt_co4 sees a phantom!" (ppr g)
 
-opt_co4 env sym rep r (AppCo co1 co2)
-  = mkAppCo (opt_co4_wrap env sym rep r co1)
-            (opt_co4_wrap env sym False Nominal co2)
+opt_co4' env sym rep r (AppCo co1 co2)
+  = mkAppCo (opt_co4 env sym rep r co1)
+            (opt_co4 env sym False Nominal co2)
 
-opt_co4 env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
+opt_co4' env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
                                 , fco_kind = k_co, fco_body = co })
   = case optForAllCoBndr env sym tv k_co of
       (env', tv', k_co') -> mkForAllCo tv' visL' visR' k_co' $
-                            opt_co4_wrap env' sym rep r co
+                            opt_co4 env' sym rep r co
      -- Use the "mk" functions to check for nested Refls
   where
     !(visL', visR') = swapSym sym (visL, visR)
 
-opt_co4 env sym rep r (FunCo _r afl afr cow co1 co2)
+opt_co4' env sym rep r (FunCo _r afl afr cow co1 co2)
   = assert (r == _r) $
     mkFunCo2 r' afl' afr' cow' co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     cow' = opt_co1 env sym cow
     !r' | rep       = Representational
         | otherwise = r
     !(afl', afr') = swapSym sym (afl, afr)
 
-opt_co4 env sym rep r (CoVarCo cv)
+opt_co4' env sym rep r (CoVarCo cv)
   | Just co <- lcLookupCoVar env cv   -- see Note [Forall over coercion] for why
                                       -- this is the right thing here
-  = opt_co4_wrap (zapLiftingContext env) sym rep r co
+  = -- pprTrace "CoVarCo" (ppr cv $$ ppr co) $
+    opt_co4 (zapLiftingContext env) sym rep r co
 
   | ty1 `eqType` ty2   -- See Note [Optimise CoVarCo to Refl]
   = mkReflCo (chooseRole rep r) ty1
@@ -352,10 +400,10 @@ opt_co4 env sym rep r (CoVarCo cv)
                           cv
           -- cv1 might have a substituted kind!
 
-opt_co4 _ _ _ _ (HoleCo h)
+opt_co4' _ _ _ _ (HoleCo h)
   = pprPanic "opt_univ fell into a hole" (ppr h)
 
-opt_co4 env sym rep r (AxiomCo con cos)
+opt_co4' env sym rep r (AxiomCo con cos)
     -- Do *not* push sym inside top-level axioms
     -- e.g. if g is a top-level axiom
     --   g a : f a ~ a
@@ -365,25 +413,25 @@ opt_co4 env sym rep r (AxiomCo con cos)
     wrapSym sym $
                        -- some sub-cos might be P: use opt_co2
                        -- See Note [Optimising coercion optimisation]
-    AxiomCo con (zipWith (opt_co2 env False)
+    AxiomCo con (zipWith (opt_co2 env NotSwapped)
                          (coAxiomRuleArgRoles con)
                          cos)
       -- Note that the_co does *not* have sym pushed into it
 
-opt_co4 env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
+opt_co4' env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
                               , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps (chooseRole rep r) t1 t2
 
-opt_co4 env sym rep r (TransCo co1 co2)
-                      -- sym (g `o` h) = sym h `o` sym g
-  | sym       = opt_trans in_scope co2' co1'
-  | otherwise = opt_trans in_scope co1' co2'
+opt_co4' env sym rep r (TransCo co1 co2)
+  -- sym (g `o` h) = sym h `o` sym g
+  | isSwapped sym = opt_trans in_scope co2' co1'
+  | otherwise     = opt_trans in_scope co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     in_scope = lcInScopeSet env
 
-opt_co4 env sym rep r (SelCo cs co)
+opt_co4' env sym rep r (SelCo cs co)
   -- Historical note 1: we used to check `co` for Refl, TyConAppCo etc
   -- before optimising `co`; but actually the SelCo will have been built
   -- with mkSelCo, so these tests always fail.
@@ -393,19 +441,19 @@ opt_co4 env sym rep r (SelCo cs co)
   -- and (b) wrapRole uses mkSubCo which does much the same job
   = wrapRole rep r $ mkSelCo cs $ opt_co1 env sym co
 
-opt_co4 env sym rep r (LRCo lr co)
+opt_co4' env sym rep r (LRCo lr co)
   | Just pr_co <- splitAppCo_maybe co
   = assert (r == Nominal )
-    opt_co4_wrap env sym rep Nominal (pick_lr lr pr_co)
+    opt_co4 env sym rep Nominal (pick_lr lr pr_co)
   | Just pr_co <- splitAppCo_maybe co'
   = assert (r == Nominal) $
     if rep
-    then opt_co4_wrap (zapLiftingContext env) False True Nominal (pick_lr lr pr_co)
+    then opt_co4 (zapLiftingContext env) NotSwapped True Nominal (pick_lr lr pr_co)
     else pick_lr lr pr_co
   | otherwise
   = wrapRole rep Nominal $ LRCo lr co'
   where
-    co' = opt_co4_wrap env sym False Nominal co
+    co' = opt_co4 env sym False Nominal co
 
     pick_lr CLeft  (l, _) = l
     pick_lr CRight (_, r) = r
@@ -445,66 +493,68 @@ So we extend the environment binding cv to arg's left-hand type.
 -}
 
 -- See Note [Optimising InstCo]
-opt_co4 env sym rep r (InstCo co1 arg)
+opt_co4' env sym rep r (InstCo fun_co arg_co)
     -- forall over type...
-  | Just (tv, _visL, _visR, kind_co, co_body) <- splitForAllCo_ty_maybe co1
-  = opt_co4_wrap (extendLiftingContext env tv
-                    (mkCoherenceRightCo Nominal t2 (mkSymCo kind_co) sym_arg))
-                   -- mkSymCo kind_co :: k1 ~ k2
-                   -- sym_arg :: (t1 :: k1) ~ (t2 :: k2)
-                   -- tv |-> (t1 :: k1) ~ (((t2 :: k2) |> (sym kind_co)) :: k1)
-                 sym rep r co_body
+  | Just (tv, _visL, _visR, k_co, body_co) <- splitForAllCo_ty_maybe fun_co
+    -- tv      :: k1
+    -- k_co    :: k1 ~ k2
+    -- body_co :: t1 ~ t2
+    -- arg_co  :: (s1:k1) ~ (s2:k2)
+  , let arg_co'  = opt_co4 env NotSwapped False Nominal arg_co
+                  -- Do /not/ push Sym into the arg_co, hence sym=False
+                  -- see (LC2) of Note [The LiftingContext in optCoercion]
+        k_co' = opt_co4 env NotSwapped False Nominal k_co
+        s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+                   -- mkSymCo kind_co :: k2 ~ k1
+                   -- tv_co   :: (s1 :: k1) ~ (((s2 :: k2) |> (sym kind_co)) :: k1)
+  = opt_co4 (extendLiftingContext env tv tv_co) sym rep r body_co
 
     -- See Note [Forall over coercion]
-  | Just (cv, _visL, _visR, _kind_co, co_body) <- splitForAllCo_co_maybe co1
-  , CoercionTy h1 <- t1
-  = opt_co4_wrap (extendLiftingContextCvSubst env cv h1) sym rep r co_body
+  | Just (cv, _visL, _visR, _kind_co, body_co) <- splitForAllCo_co_maybe fun_co
+  , CoercionTy h1 <- coercionLKind arg_co
+  , let h1' = opt_co4 env NotSwapped False Nominal h1
+  = opt_co4 (extendLiftingContextCvSubst env cv h1') sym rep r body_co
 
-    -- See if it is a forall after optimization
-    -- If so, do an inefficient one-variable substitution, then re-optimize
+  -- OK so those cases didn't work.  See if it is a forall /after/ optimization
+  -- If so, do an inefficient one-variable substitution, then re-optimize
 
     -- forall over type...
-  | Just (tv', _visL, _visR, kind_co', co_body') <- splitForAllCo_ty_maybe co1'
-  = opt_co4_wrap (extendLiftingContext (zapLiftingContext env) tv'
-                    (mkCoherenceRightCo Nominal t2' (mkSymCo kind_co') arg'))
-            False False r' co_body'
+  | Just (tv', _visL, _visR, k_co', body_co') <- splitForAllCo_ty_maybe fun_co'
+  , let s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+        env'  = extendLiftingContext (zapLiftingContext env) tv' tv_co
+  = opt_co4 env' NotSwapped False r' body_co'
 
     -- See Note [Forall over coercion]
-  | Just (cv', _visL, _visR, _kind_co', co_body') <- splitForAllCo_co_maybe co1'
-  , CoercionTy h1' <- t1'
-  = opt_co4_wrap (extendLiftingContextCvSubst (zapLiftingContext env) cv' h1')
-                    False False r' co_body'
+  | Just (cv', _visL, _visR, _kind_co', body_co') <- splitForAllCo_co_maybe fun_co'
+  , CoercionTy h1' <- coercionLKind arg_co'
+  , let env' = extendLiftingContextCvSubst (zapLiftingContext env) cv' h1'
+  = opt_co4 env' NotSwapped False r' body_co'
+
+  -- Those cases didn't work either, so rebuild the InstCo
+  -- Push Sym into /both/ function /and/ arg_coument
+  | otherwise = InstCo fun_co' arg_co'
 
-  | otherwise = InstCo co1' arg'
   where
-    co1'    = opt_co4_wrap env sym rep r co1
-    r'      = chooseRole rep r
-    arg'    = opt_co4_wrap env sym False Nominal arg
-    sym_arg = wrapSym sym arg'
-
-    -- Performance note: don't be alarmed by the two calls to coercionKind
-    -- here, as only one call to coercionKind is actually demanded per guard.
-    -- t1/t2 are used when checking if co1 is a forall, and t1'/t2' are used
-    -- when checking if co1' (i.e., co1 post-optimization) is a forall.
-    --
-    -- t1/t2 must come from sym_arg, not arg', since it's possible that arg'
-    -- might have an extra Sym at the front (after being optimized) that co1
-    -- lacks, so we need to use sym_arg to balance the number of Syms. (#15725)
-    Pair t1  t2  = coercionKind sym_arg
-    Pair t1' t2' = coercionKind arg'
-
-opt_co4 env sym _rep r (KindCo co)
+    -- fun_co' arg_co' are both optimised, /and/ we have pushed `sym` into both
+    -- So no more sym'ing on th results of fun_co' arg_co'
+    fun_co' = opt_co4 env sym rep r fun_co
+    arg_co' = opt_co4 env sym False Nominal arg_co
+    r'   = chooseRole rep r
+
+opt_co4' env sym _rep r (KindCo co)
   = assert (r == Nominal) $
     let kco' = promoteCoercion co in
     case kco' of
       KindCo co' -> promoteCoercion (opt_co1 env sym co')
-      _          -> opt_co4_wrap env sym False Nominal kco'
+      _          -> opt_co4 env sym False Nominal kco'
   -- This might be able to be optimized more to do the promotion
   -- and substitution/optimization at the same time
 
-opt_co4 env sym _ r (SubCo co)
+opt_co4' env sym _ r (SubCo co)
   = assert (r == Representational) $
-    opt_co4_wrap env sym True Nominal co
+    opt_co4 env sym True Nominal co
 
 {- Note [Optimise CoVarCo to Refl]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -518,7 +568,7 @@ in GHC.Core.Coercion.
 -------------
 -- | Optimize a phantom coercion. The input coercion may not necessarily
 -- be a phantom, but the output sure will be.
-opt_phantom :: LiftingContext -> SymFlag -> Coercion -> NormalCo
+opt_phantom :: LiftingContext -> SwapFlag -> Coercion -> NormalCo
 opt_phantom env sym (UnivCo { uco_prov = prov, uco_lty = t1
                             , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps Phantom t1 t2
@@ -559,7 +609,7 @@ See #19509.
 
  -}
 
-opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance
+opt_univ :: LiftingContext -> SwapFlag -> UnivCoProvenance
          -> [Coercion]
          -> Role -> Type -> Type -> Coercion
 opt_univ env sym prov deps role ty1 ty2
@@ -640,11 +690,19 @@ opt_transList :: HasDebugCallStack => InScopeSet -> [NormalCo] -> [NormalCo] ->
 opt_transList is = zipWithEqual "opt_transList" (opt_trans is)
   -- The input lists must have identical length.
 
-opt_trans, opt_trans' :: InScopeSet -> NormalCo -> NormalCo -> NormalCo
+opt_trans :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 
 -- opt_trans just allows us to add some debug tracing
 -- Usually it just goes to opt_trans'
-opt_trans is co1 co2 = opt_trans' is co1 co2
+opt_trans is co1 co2
+  = -- (if coercionRKind co1 `eqType` coercionLKind co2
+    --  then (\x -> x) else
+    --  pprTrace "opt_trans" (vcat [ text "co1" <+> ppr co1
+    --                             , text "co2" <+> ppr co2
+    --                             , text "co1 kind" <+> ppr (coercionKind co1)
+    --                             , text "co2 kind" <+> ppr (coercionKind co2)
+    --                             , callStackDoc ])) $
+    opt_trans' is co1 co2
 
 {-
 opt_trans is co1 co2
@@ -658,19 +716,20 @@ opt_trans is co1 co2
     r2 = coercionRole co1
 -}
 
+opt_trans' :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 opt_trans' is co1 co2
   | isReflCo co1 = co2
     -- optimize when co1 is a Refl Co
   | otherwise    = opt_trans1 is co1 co2
 
-opt_trans1 :: InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
+opt_trans1 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
 -- First arg is not the identity
 opt_trans1 is co1 co2
   | isReflCo co2 = co1
     -- optimize when co2 is a Refl Co
   | otherwise    = opt_trans2 is co1 co2
 
-opt_trans2 :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
+opt_trans2 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
 -- Neither arg is the identity
 opt_trans2 is (TransCo co1a co1b) co2
     -- Don't know whether the sub-coercions are the identity
@@ -687,16 +746,27 @@ opt_trans2 is co1 (TransCo co2a co2b)
     else opt_trans1 is co1_2a co2b
 
 opt_trans2 _ co1 co2
-  = mkTransCo co1 co2
+  = mk_trans_co co1 co2
+
 
 ------
 -- Optimize coercions with a top-level use of transitivity.
-opt_trans_rule :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
-
-opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _ (MCo co2))
+opt_trans_rule :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
+
+opt_trans_rule _ in_co1 in_co2
+  | assertPpr (coercionRKind in_co1 `eqType` coercionLKind in_co2)
+              (vcat [ text "in_co1" <+> ppr in_co1
+                   , text "in_co2" <+> ppr in_co2
+                   , text "in_co1 kind" <+> ppr (coercionKind in_co1)
+                   , text "in_co2 kind" <+> ppr (coercionKind in_co2)
+                   , callStackDoc ]) $
+    False
+  = panic "opt_trans_rule"  -- This entire equation is purely assertion checking
+
+opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _t2 (MCo co2))
   = assert (r1 == r2) $
     fireTransRule "GRefl" in_co1 in_co2 $
-    mkGReflRightCo r1 t1 (opt_trans is co1 co2)
+    mk_grefl_right_co r1 t1 (opt_trans is co1 co2)
 
 -- Push transitivity through matching destructors
 opt_trans_rule is in_co1@(SelCo d1 co1) in_co2@(SelCo d2 co2)
@@ -818,8 +888,8 @@ opt_trans_rule is co1 co2
       eta1' = downgradeRole role Nominal eta1
       n1   = mkSelCo (SelTyCon 2 role) eta1'
       n2   = mkSelCo (SelTyCon 3 role) eta1'
-      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mkTransCo`
-                                        (mkCoVarCo cv1) `mkTransCo` n2])
+      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mk_trans_co`
+                                        (mkCoVarCo cv1) `mk_trans_co` n2])
                     r2
 
 -- Push transitivity inside axioms
@@ -836,15 +906,15 @@ opt_trans_rule is co1 co2
   | Just (sym1, axr1, cos1) <- isAxiomCo_maybe co1
   , Just (sym2, axr2, cos2) <- isAxiomCo_maybe co2
   , axr1 == axr2
-  , sym1 == not sym2
+  , sym1 == flipSwap sym2
   , Just (tc, role, branch) <- coAxiomRuleBranch_maybe axr1
   , let qtvs   = coAxBranchTyVars branch ++ coAxBranchCoVars branch
         lhs    = mkTyConApp tc (coAxBranchLHS branch)
         rhs    = coAxBranchRHS branch
-        pivot_tvs = exactTyCoVarsOfType (if sym2 then rhs else lhs)
+        pivot_tvs = exactTyCoVarsOfType (pickSwap sym2 lhs rhs)
   , all (`elemVarSet` pivot_tvs) qtvs
   = fireTransRule "TrPushAxSym" co1 co2 $
-    if sym2
+    if isSwapped sym2
        -- TrPushAxSym
     then liftCoSubstWith role qtvs (opt_transList is cos1 (map mkSymCo cos2)) lhs
        -- TrPushSymAx
@@ -854,29 +924,29 @@ opt_trans_rule is co1 co2
   -- Note [Push transitivity inside newtype axioms only]
   -- TrPushSymAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , True <- sym
+  , isSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is (map mkSymCo cos2) cos1)
   = fireTransRule "TrPushSymAxR" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , False <- sym
+  , notSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxR" co1 co2 newAxInst
 
   -- TrPushSymAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , True <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , isSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos2 (map mkSymCo cos1))
   = fireTransRule "TrPushSymAxL" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , False <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , notSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxL" co1 co2 newAxInst
 
@@ -926,7 +996,7 @@ opt_trans_rule_app is orig_co1 orig_co2 co1a co1bs co2a co2bs
 
         co2a'   = mkCoherenceLeftCo rt2a lt2a kcoa co2a
         co2bs'  = zipWith3 mkGReflLeftCo rt2bs lt2bs kcobs
-        co2bs'' = zipWith mkTransCo co2bs' co2bs
+        co2bs'' = zipWith mk_trans_co co2bs' co2bs
     in
     mkAppCos (opt_trans is co1a co2a')
              (zipWith (opt_trans is) co1bs co2bs'')
@@ -1108,13 +1178,13 @@ The problem described here was first found in dependent/should_compile/dynamic-p
 -}
 
 -----------
-swapSym :: SymFlag -> (a,a) -> (a,a)
-swapSym sym (x,y) | sym       = (y,x)
-                  | otherwise = (x,y)
+swapSym :: SwapFlag -> (a,a) -> (a,a)
+swapSym IsSwapped  (x,y) = (y,x)
+swapSym NotSwapped (x,y) = (x,y)
 
-wrapSym :: SymFlag -> Coercion -> Coercion
-wrapSym sym co | sym       = mkSymCo co
-               | otherwise = co
+wrapSym :: SwapFlag -> Coercion -> Coercion
+wrapSym IsSwapped  co = mkSymCo co
+wrapSym NotSwapped co = co
 
 -- | Conditionally set a role to be representational
 wrapRole :: ReprFlag
@@ -1132,15 +1202,15 @@ chooseRole True _ = Representational
 chooseRole _    r = r
 
 -----------
-isAxiomCo_maybe :: Coercion -> Maybe (SymFlag, CoAxiomRule, [Coercion])
+isAxiomCo_maybe :: Coercion -> Maybe (SwapFlag, CoAxiomRule, [Coercion])
 -- We don't expect to see nested SymCo; and that lets us write a simple,
 -- non-recursive function. (If we see a nested SymCo we'll just fail,
 -- which is ok.)
-isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (True, ax, cos)
-isAxiomCo_maybe (AxiomCo ax cos)         = Just (False, ax, cos)
+isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (IsSwapped,  ax, cos)
+isAxiomCo_maybe (AxiomCo ax cos)         = Just (NotSwapped, ax, cos)
 isAxiomCo_maybe _                        = Nothing
 
-matchNewtypeBranch :: Bool -- True = match LHS, False = match RHS
+matchNewtypeBranch :: SwapFlag -- IsSwapped = match LHS, NotSwapped = match RHS
                    -> CoAxiomRule
                    -> Coercion -> Maybe [Coercion]
 matchNewtypeBranch sym axr co
@@ -1151,7 +1221,7 @@ matchNewtypeBranch sym axr co
                , cab_lhs = lhs
                , cab_rhs = rhs } <- branch
   , Just subst <- liftCoMatch (mkVarSet qtvs)
-                              (if sym then (mkTyConApp tc lhs) else rhs)
+                              (pickSwap sym rhs (mkTyConApp tc lhs))
                               co
   , all (`isMappedByLC` subst) qtvs
   = zipWithM (liftCoSubstTyVar subst) roles qtvs
@@ -1228,7 +1298,7 @@ etaForAllCo_ty_maybe co
   , (role /= Nominal) || (vis1 `eqForAllVis` vis2)
   , let kind_co = mkSelCo SelForAll co
   = Just ( tv1, vis1, vis2, kind_co
-         , mkInstCo co (mkGReflRightCo Nominal (TyVarTy tv1) kind_co))
+         , mkInstCo co (mk_grefl_right_co Nominal (TyVarTy tv1) kind_co))
 
   | otherwise
   = Nothing
@@ -1251,8 +1321,8 @@ etaForAllCo_co_maybe co
         l_co     = mkCoVarCo cv1
         kind_co' = downgradeRole r Nominal kind_co
         r_co     = mkSymCo (mkSelCo (SelTyCon 2 r) kind_co')
-                   `mkTransCo` l_co
-                   `mkTransCo` mkSelCo (SelTyCon 3 r) kind_co'
+                   `mk_trans_co` l_co
+                   `mk_trans_co` mkSelCo (SelTyCon 3 r) kind_co'
     in Just ( cv1, vis1, vis2, kind_co
             , mkInstCo co (mkProofIrrelCo Nominal kind_co l_co r_co))
 
@@ -1329,7 +1399,55 @@ and these two imply
 
 -}
 
-optForAllCoBndr :: LiftingContext -> Bool
+optForAllCoBndr :: LiftingContext -> SwapFlag
                 -> TyCoVar -> Coercion -> (LiftingContext, TyCoVar, Coercion)
 optForAllCoBndr env sym
-  = substForAllCoBndrUsingLC sym (opt_co4_wrap env sym False Nominal) env
+  = substForAllCoBndrUsingLC sym (opt_co4 env sym False Nominal) env
+
+
+{- **********************************************************************
+%*                                                                      *
+       Assertion-checking versions of functions in Coercion.hs
+%*                                                                      *
+%********************************************************************* -}
+
+-- We can't check the assertions in the "main" functions of these
+-- functions, because the assertions don't hold during zonking.
+-- But they are fantastically helpful in finding bugs in the coercion
+-- optimiser itself, so I have copied them here with assertions.
+
+mk_trans_co :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+-- Do assertion checking in mk_trans_co
+mk_trans_co co1 co2
+  = assertPpr (coercionRKind co1 `eqType` coercionLKind co2)
+              (vcat [ text "co1" <+> ppr co1
+                    , text "co2" <+> ppr co2
+                    , text "co1 kind" <+> ppr (coercionKind co1)
+                    , text "co2 kind" <+> ppr (coercionKind co2)
+                    , callStackDoc ]) $
+    mkTransCo co1 co2
+
+mk_coherence_right_co :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
+mk_coherence_right_co r ty co co2
+  = assertGRefl ty co $
+    mkCoherenceRightCo r ty co co2
+
+assertGRefl :: HasDebugCallStack => Type -> Coercion -> r -> r
+assertGRefl ty co res
+  = assertPpr (typeKind ty `eqType` coercionLKind co)
+              (vcat [ pp_ty "ty" ty
+                    , pp_co "co" co
+                    , callStackDoc ]) $
+    res
+
+mk_grefl_right_co :: Role -> Type -> CoercionN -> Coercion
+mk_grefl_right_co r ty co
+  = assertGRefl ty co $
+    mkGReflRightCo r ty co
+
+pp_co :: String -> Coercion -> SDoc
+pp_co s co = text s <+> hang (ppr co) 2 (dcolon <+> ppr (coercionKind co))
+
+pp_ty :: String -> Type -> SDoc
+pp_ty s ty = text s <+> hang (ppr ty) 2 (dcolon <+> ppr (typeKind ty))
+


=====================================
compiler/GHC/Core/TyCo/Subst.hs
=====================================
@@ -68,6 +68,7 @@ import {-# SOURCE #-} GHC.Core ( CoreExpr )
 import GHC.Core.TyCo.Rep
 import GHC.Core.TyCo.FVs
 
+import GHC.Types.Basic( SwapFlag(..), isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -916,7 +917,7 @@ substDCoVarSet subst cvs = coVarsOfCosDSet $ map (substCoVar subst) $
 substForAllCoBndr :: Subst -> TyCoVar -> KindCoercion
                   -> (Subst, TyCoVar, Coercion)
 substForAllCoBndr subst
-  = substForAllCoBndrUsing False (substCo subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCo subst) subst
 
 -- | Like 'substForAllCoBndr', but disables sanity checks.
 -- The problems that the sanity checks in substCo catch are described in
@@ -926,10 +927,10 @@ substForAllCoBndr subst
 substForAllCoBndrUnchecked :: Subst -> TyCoVar -> KindCoercion
                            -> (Subst, TyCoVar, Coercion)
 substForAllCoBndrUnchecked subst
-  = substForAllCoBndrUsing False (substCoUnchecked subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCoUnchecked subst) subst
 
 -- See Note [Sym and ForAllCo]
-substForAllCoBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoBndrUsing :: SwapFlag  -- Apply sym to binder?
                        -> (Coercion -> Coercion)  -- transformation to kind co
                        -> Subst -> TyCoVar -> KindCoercion
                        -> (Subst, TyCoVar, KindCoercion)
@@ -937,7 +938,7 @@ substForAllCoBndrUsing sym sco subst old_var
   | isTyVar old_var = substForAllCoTyVarBndrUsing sym sco subst old_var
   | otherwise       = substForAllCoCoVarBndrUsing sym sco subst old_var
 
-substForAllCoTyVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoTyVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> TyVar -> KindCoercion
                             -> (Subst, TyVar, KindCoercion)
@@ -946,10 +947,13 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
     ( Subst (in_scope `extendInScopeSet` new_var) idenv new_env cenv
     , new_var, new_kind_co )
   where
-    new_env | no_change && not sym = delVarEnv tenv old_var
-            | sym       = extendVarEnv tenv old_var $
-                          TyVarTy new_var `CastTy` new_kind_co
-            | otherwise = extendVarEnv tenv old_var (TyVarTy new_var)
+    new_env | no_change, notSwapped sym
+            = delVarEnv tenv old_var
+            | isSwapped sym
+            = extendVarEnv tenv old_var $
+              TyVarTy new_var `CastTy` new_kind_co
+            | otherwise
+            = extendVarEnv tenv old_var (TyVarTy new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -965,7 +969,7 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
 
     new_var  = uniqAway in_scope (setTyVarKind old_var new_ki1)
 
-substForAllCoCoVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoCoVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> CoVar -> KindCoercion
                             -> (Subst, CoVar, KindCoercion)
@@ -975,8 +979,10 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     ( Subst (in_scope `extendInScopeSet` new_var) idenv tenv new_cenv
     , new_var, new_kind_co )
   where
-    new_cenv | no_change && not sym = delVarEnv cenv old_var
-             | otherwise = extendVarEnv cenv old_var (mkCoVarCo new_var)
+    new_cenv | no_change, notSwapped sym
+             = delVarEnv cenv old_var
+             | otherwise
+             = extendVarEnv cenv old_var (mkCoVarCo new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -987,8 +993,7 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     Pair h1 h2 = coercionKind new_kind_co
 
     new_var       = uniqAway in_scope $ mkCoVar (varName old_var) new_var_type
-    new_var_type  | sym       = h2
-                  | otherwise = h1
+    new_var_type  = pickSwap sym h1 h2
 
 substCoVar :: Subst -> CoVar -> Coercion
 substCoVar (Subst _ _ _ cenv) cv


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -580,7 +580,7 @@ expandTypeSynonyms ty
       -- substForAllCoBndrUsing, which is general enough to
       -- handle coercion optimization (which sometimes swaps the
       -- order of a coercion)
-    go_cobndr subst = substForAllCoBndrUsing False (go_co subst) subst
+    go_cobndr subst = substForAllCoBndrUsing NotSwapped (go_co subst) subst
 
 {- Notes on type synonyms
 ~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/HsToCore.hs
=====================================
@@ -784,7 +784,7 @@ mkUnsafeCoercePrimPair _old_id old_expr
              alpha_co = mkTyConAppCo Nominal tYPETyCon [mkCoVarCo rr_cv]
 
              -- x_co :: alpha ~R# beta
-             x_co = mkGReflCo Representational openAlphaTy (MCo alpha_co) `mkTransCo`
+             x_co = mkGReflMCo Representational openAlphaTy alpha_co `mkTransCo`
                     mkSubCo (mkCoVarCo ab_cv)
 
 


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -80,7 +80,7 @@ module GHC.Types.Basic (
         EP(..),
 
         DefMethSpec(..),
-        SwapFlag(..), flipSwap, unSwap, isSwapped,
+        SwapFlag(..), flipSwap, unSwap, notSwapped, isSwapped, pickSwap,
 
         CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
 
@@ -456,6 +456,7 @@ instance Outputable OneShotInfo where
 data SwapFlag
   = NotSwapped  -- Args are: actual,   expected
   | IsSwapped   -- Args are: expected, actual
+  deriving( Eq )
 
 instance Outputable SwapFlag where
   ppr IsSwapped  = text "Is-swapped"
@@ -469,6 +470,14 @@ isSwapped :: SwapFlag -> Bool
 isSwapped IsSwapped  = True
 isSwapped NotSwapped = False
 
+notSwapped :: SwapFlag -> Bool
+notSwapped NotSwapped = True
+notSwapped IsSwapped  = False
+
+pickSwap :: SwapFlag -> a -> a -> a
+pickSwap NotSwapped a _ = a
+pickSwap IsSwapped  _ b = b
+
 unSwap :: SwapFlag -> (a->a->b) -> a -> a -> b
 unSwap NotSwapped f a b = f a b
 unSwap IsSwapped  f a b = f b a


=====================================
testsuite/tests/dependent/should_compile/T25387.hs
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE GHC2024 #-}
+{-# LANGUAGE TypeFamilies #-}
+module Bug (f) where
+
+import Data.Kind (Type)
+import Data.Type.Equality (type (~~))
+
+type Promote :: Type -> Type
+type family Promote k
+
+type PromoteX :: k -> Promote k
+type family PromoteX a
+
+type Demote :: Type -> Type
+type family Demote (k :: Type) :: Type
+
+type DemoteX :: k -> Demote k
+type family DemoteX a
+
+type HEq :: j -> k -> Type
+data HEq a b where
+  HRefl :: forall j (a :: j). HEq a a
+
+type SHEq :: forall j k (a :: j) (b :: k). HEq a b -> Type
+data SHEq heq where
+  SHRefl :: forall j (a :: j). SHEq (HRefl @j @a)
+
+type SomeSHEq :: j -> k -> Type
+data SomeSHEq a b where
+  SomeSHEq :: forall j k (a :: j) (b :: k) (heq :: HEq a b). SHEq heq -> SomeSHEq a b
+
+f :: forall j k (a :: j) (b :: k).
+     (PromoteX (DemoteX a) ~~ a, PromoteX (DemoteX b) ~~ b) =>
+     HEq (DemoteX a) (DemoteX b) ->
+     SomeSHEq a b
+f HRefl = SomeSHEq SHRefl


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -63,3 +63,4 @@ test('T16347', normal, compile, [''])
 test('T18660', normal, compile, [''])
 test('T12174', normal, compile, [''])
 test('LopezJuan', normal, compile, [''])
+test('T25387', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23ddcc0102b3b0c31829a8f67003f4f00fb52f9a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 16:55:31 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sat, 26 Oct 2024 12:55:31 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-8] EPA: Remove
 NameAdornment from NameAnn
Message-ID: <671d1f0320f81_289b8673260c128974@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC


Commits:
1a41de9c by Alan Zimmerman at 2024-10-26T17:53:22+01:00
EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

- - - - -


17 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_compile/T20846.stderr
- testsuite/tests/parser/should_compile/T23315/T23315.stderr
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -216,11 +216,13 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
              BlankSrcSpanFile -> braces $ char ' ' <> (pprUserRealSpan False ss) <> char ' '
 
             annParen :: AnnParen -> SDoc
-            annParen (AnnParen a o c) = case ba of
+            annParen ap = case ba of
              BlankEpAnnotations -> parens $ text "blanked:" <+> text "AnnParen"
-             NoBlankEpAnnotations ->
-              parens $ text "AnnParen"
-                        $$ vcat [ppr a, epaLocation o, epaLocation c]
+             NoBlankEpAnnotations -> parens (case ap of
+                                      (AnnParens       o c) -> text "AnnParens"       $$ vcat [showAstData' o, showAstData' c]
+                                      (AnnParensHash   o c) -> text "AnnParensHash"   $$ vcat [showAstData' o, showAstData' c]
+                                      (AnnParensSquare o c) -> text "AnnParensSquare" $$ vcat [showAstData' o, showAstData' c]
+                                      )
 
             annClassDecl :: AnnClassDecl -> SDoc
             annClassDecl (AnnClassDecl c ops cps v w oc cc s) = case ba of


=====================================
compiler/GHC/Parser.y
=====================================
@@ -791,7 +791,7 @@ identifier :: { LocatedN RdrName }
         | qvarop                        { $1 }
         | qconop                        { $1 }
     | '->'              {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
-                                (NameAnnRArrow (isUnicode $1) Nothing (glR $1) Nothing []) }
+                                (NameAnnRArrow  Nothing (epUniTok $1) Nothing []) }
 
 -----------------------------------------------------------------------------
 -- Backpack stuff
@@ -2330,16 +2330,16 @@ atype :: { LHsType GhcPs }
                                                         -- Constructor sigs only
 
         -- List and tuple syntax whose interpretation depends on the extension ListTuplePuns.
-        | '(' ')'                        {% amsA' . sLL $1 $> =<< (mkTupleSyntaxTy (glR $1) [] (glR $>)) }
+        | '(' ')'                        {% amsA' . sLL $1 $> =<< (mkTupleSyntaxTy (epTok $1) [] (epTok $>)) }
         | '(' ktype ',' comma_types1 ')' {% do { h <- addTrailingCommaA $2 (gl $3)
-                                               ; amsA' . sLL $1 $> =<< (mkTupleSyntaxTy (glR $1) (h : $4) (glR $>)) }}
+                                               ; amsA' . sLL $1 $> =<< (mkTupleSyntaxTy (epTok $1) (h : $4) (epTok $>)) }}
         | '(#' '#)'                   {% do { requireLTPuns PEP_TupleSyntaxType $1 $>
-                                            ; amsA' (sLL $1 $> $ HsTupleTy (AnnParen AnnParensHash (glR $1) (glR $2)) HsUnboxedTuple []) } }
+                                            ; amsA' (sLL $1 $> $ HsTupleTy (AnnParensHash (epTok $1) (epTok $2)) HsUnboxedTuple []) } }
         | '(#' comma_types1 '#)'      {% do { requireLTPuns PEP_TupleSyntaxType $1 $>
-                                            ; amsA' (sLL $1 $> $ HsTupleTy (AnnParen AnnParensHash (glR $1) (glR $3)) HsUnboxedTuple $2) } }
+                                            ; amsA' (sLL $1 $> $ HsTupleTy (AnnParensHash (epTok $1) (epTok $3)) HsUnboxedTuple $2) } }
         | '(#' bar_types2 '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
-                                      ; amsA' (sLL $1 $> $ HsSumTy (AnnParen AnnParensHash (glR $1) (glR $3)) $2) } }
-        | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (glR $1) $2 (glR $3)) }
+                                      ; amsA' (sLL $1 $> $ HsSumTy (AnnParensHash (epTok $1) (epTok $3)) $2) } }
+        | '[' ktype ']'               {% amsA' . sLL $1 $> =<< (mkListSyntaxTy1 (epTok $1) $2 (epTok $3)) }
         | '(' ktype ')'               {% amsA' (sLL $1 $> $ HsParTy (epTok $1, epTok $3) $2) }
                                       -- see Note [Promotion] for the followings
         | SIMPLEQUOTE '(' ')'         {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
@@ -2351,7 +2351,7 @@ atype :: { LHsType GhcPs }
                              {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                    ; h <- addTrailingCommaA $3 (gl $4)
                                    ; amsA' (sLL $1 $> $ HsExplicitTupleTy (epTok $1,epTok $2,epTok $6) (h : $5)) }}
-        | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (glR $1) (glR $2)) }
+        | '[' ']'               {% withCombinedComments $1 $> (mkListSyntaxTy0 (epTok $1) (epTok $2)) }
         | SIMPLEQUOTE  '[' comma_types0 ']'     {% do { requireLTPuns PEP_QuoteDisambiguation $1 $>
                                                       ; amsA' (sLL $1 $> $ HsExplicitListTy (epTok $1, epTok $2, epTok $4) IsPromoted $3) }}
         | SIMPLEQUOTE var                       {% amsA' (sLL $1 $> $ HsTyVar (epTok $1) IsPromoted $2) }
@@ -2630,9 +2630,9 @@ deriv_clause_types :: { LDerivClauseTys GhcPs }
                                            sL1a $1 $ HsTyVar noAnn NotPromoted $1 } in
                                 sL1a $1 (DctSingle noExtField tc) }
         | '(' ')'             {% amsr (sLL $1 $> (DctMulti noExtField []))
-                                      (AnnContext Nothing [glR $1] [glR $2]) }
+                                      (AnnContext Nothing [epTok $1] [epTok $2]) }
         | '(' deriv_types ')' {% amsr (sLL $1 $> (DctMulti noExtField $2))
-                                      (AnnContext Nothing [glR $1] [glR $3])}
+                                      (AnnContext Nothing [epTok $1] [epTok $3])}
 
 -----------------------------------------------------------------------------
 -- Value definitions
@@ -3759,12 +3759,12 @@ qcon :: { LocatedN RdrName }
 gen_qcon :: { LocatedN RdrName }
   : qconid                { $1 }
   | '(' qconsym ')'       {% amsr (sLL $1 $> (unLoc $2))
-                                  (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                  (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 
 con     :: { LocatedN RdrName }
         : conid                 { $1 }
         | '(' consym ')'        {% amsr (sLL $1 $> (unLoc $2))
-                                        (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                        (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
         | syscon                { $1 }
 
 con_list :: { Located (NonEmpty (LocatedN RdrName)) }
@@ -3779,31 +3779,31 @@ qcon_list : qcon                  { [$1] }
 -- See Note [ExplicitTuple] in GHC.Hs.Expr
 sysdcon_nolist :: { LocatedN DataCon }  -- Wired in data constructors
         : '(' commas ')'        {% amsr (sLL $1 $> $ tupleDataCon Boxed (snd $2 + 1))
-                                       (NameAnnCommas NameParens (glR $1) (map srcSpan2e (fst $2)) (glR $3) []) }
-        | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly NameParensHash (glR $1) (glR $2) []) }
+                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+        | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '(#' commas '#)'      {% amsr (sLL $1 $> $ tupleDataCon Unboxed (snd $2 + 1))
-                                       (NameAnnCommas NameParensHash (glR $1) (map srcSpan2e (fst $2)) (glR $3) []) }
+                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
 
 syscon :: { LocatedN RdrName }
         : sysdcon               {  L (getLoc $1) $ nameRdrName (dataConName (unLoc $1)) }
         | '(' '->' ')'          {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
-                                        (NameAnnRArrow (isUnicode $2) (Just $ glR $1) (glR $2) (Just $ glR $3) []) }
+                                        (NameAnnRArrow  (Just $ epTok $1) (epUniTok $2) (Just $ epTok $3) []) }
 
 -- See Note [Empty lists] in GHC.Hs.Expr
 sysdcon :: { LocatedN DataCon }
         : sysdcon_nolist                 { $1 }
-        | '(' ')'               {% amsr (sLL $1 $> unitDataCon) (NameAnnOnly NameParens (glR $1) (glR $2) []) }
-        | '[' ']'               {% amsr (sLL $1 $> nilDataCon)  (NameAnnOnly NameSquare (glR $1) (glR $2) []) }
+        | '(' ')'               {% amsr (sLL $1 $> unitDataCon) (NameAnnOnly (NameParens (epTok $1) (epTok $2)) []) }
+        | '[' ']'               {% amsr (sLL $1 $> nilDataCon)  (NameAnnOnly (NameSquare (epTok $1) (epTok $2)) []) }
 
 conop :: { LocatedN RdrName }
         : consym                { $1 }
         | '`' conid '`'         {% amsr (sLL $1 $> (unLoc $2))
-                                          (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                          (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 qconop :: { LocatedN RdrName }
         : qconsym               { $1 }
         | '`' qconid '`'        {% amsr (sLL $1 $> (unLoc $2))
-                                          (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                          (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 ----------------------------------------------------------------------------
 -- Type constructors
@@ -3814,29 +3814,29 @@ qconop :: { LocatedN RdrName }
 gtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, including unit tuples
         : ntgtycon                     { $1 }
         | '(' ')'                      {% amsr (sLL $1 $> $ getRdrName unitTyCon)
-                                                (NameAnnOnly NameParens (glR $1) (glR $2) []) }
+                                                (NameAnnOnly (NameParens (epTok $1) (epTok $2)) []) }
         | '(#' '#)'                    {% amsr (sLL $1 $> $ getRdrName unboxedUnitTyCon)
-                                                (NameAnnOnly NameParensHash (glR $1) (glR $2) []) }
+                                                (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '[' ']'               {% amsr (sLL $1 $> $ listTyCon_RDR)
-                                      (NameAnnOnly NameSquare (glR $1) (glR $2) []) }
+                                      (NameAnnOnly (NameSquare (epTok $1) (epTok $2)) []) }
 
 ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit tuples
         : oqtycon               { $1 }
         | '(' commas ')'        {% do { n <- mkTupleSyntaxTycon Boxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas NameParens (glR $1) (map srcSpan2e (fst $2)) (glR $3) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
         | '(#' commas '#)'      {% do { n <- mkTupleSyntaxTycon Unboxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas NameParensHash (glR $1) (map srcSpan2e (fst $2)) (glR $3) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
-                                       (NameAnnBars NameParensHash (glR $1) (map srcSpan2e (fst $2)) (glR $3) []) } }
+                                       (NameAnnBars (epTok $1, epTok $3) (map srcSpan2e (fst $2)) []) } }
         | '(' '->' ')'          {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
-                                       (NameAnnRArrow (isUnicode $2) (Just $ glR $1) (glR $2) (Just $ glR $3) []) }
+                                       (NameAnnRArrow  (Just $ epTok $1) (epUniTok $2) (Just $ epTok $3) []) }
 
 oqtycon :: { LocatedN RdrName }  -- An "ordinary" qualified tycon;
                                 -- These can appear in export lists
         : qtycon                        { $1 }
         | '(' qtyconsym ')'             {% amsr (sLL $1 $> (unLoc $2))
-                                                  (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                                  (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 
 oqtycon_no_varcon :: { LocatedN RdrName }  -- Type constructor which cannot be mistaken
                                           -- for variable constructor in export lists
@@ -3844,13 +3844,13 @@ oqtycon_no_varcon :: { LocatedN RdrName }  -- Type constructor which cannot be m
         :  qtycon            { $1 }
         | '(' QCONSYM ')'    {% let { name :: Located RdrName
                                     ; name = sL1 $2 $! mkQual tcClsName (getQCONSYM $2) }
-                                in amsr (sLL $1 $> (unLoc name)) (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                in amsr (sLL $1 $> (unLoc name)) (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
         | '(' CONSYM ')'     {% let { name :: Located RdrName
                                     ; name = sL1 $2 $! mkUnqual tcClsName (getCONSYM $2) }
-                                in amsr (sLL $1 $> (unLoc name)) (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                in amsr (sLL $1 $> (unLoc name)) (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
         | '(' ':' ')'        {% let { name :: Located RdrName
                                     ; name = sL1 $2 $! consDataCon_RDR }
-                                in amsr (sLL $1 $> (unLoc name)) (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                in amsr (sLL $1 $> (unLoc name)) (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 
 {- Note [Type constructors in export list]
 ~~~~~~~~~~~~~~~~~~~~~
@@ -3876,7 +3876,7 @@ qtyconop :: { LocatedN RdrName } -- Qualified or unqualified
         -- See Note [%shift: qtyconop -> qtyconsym]
         : qtyconsym %shift              { $1 }
         | '`' qtycon '`'                {% amsr (sLL $1 $> (unLoc $2))
-                                                (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                                (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 qtycon :: { LocatedN RdrName }   -- Qualified or unqualified
         : QCONID            { sL1n $1 $! mkQual tcClsName (getQCONID $1) }
@@ -3902,7 +3902,7 @@ tyconsym :: { LocatedN RdrName }
 otycon :: { LocatedN RdrName }
         : tycon                 { $1 }
         | '(' tyconsym ')'      {% amsr (sLL $1 $> (unLoc $2))
-                                        (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                        (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 
 -----------------------------------------------------------------------------
 -- Operators
@@ -3911,12 +3911,12 @@ op      :: { LocatedN RdrName }   -- used in infix decls
         : varop                 { $1 }
         | conop                 { $1 }
         | '->'                  {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
-                                     (NameAnnRArrow (isUnicode $1) Nothing (glR $1) Nothing []) }
+                                     (NameAnnRArrow  Nothing (epUniTok $1) Nothing []) }
 
 varop   :: { LocatedN RdrName }
         : varsym                { $1 }
         | '`' varid '`'         {% amsr (sLL $1 $> (unLoc $2))
-                                           (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                           (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 qop     :: { forall b. DisambInfixOp b => PV (LocatedN b) }   -- used in sections
         : qvarop                { mkHsVarOpPV $1 }
@@ -3934,12 +3934,12 @@ hole_op : '`' '_' '`'           { sLLa $1 $> (hsHoleExpr (Just $ EpAnnUnboundVar
 qvarop :: { LocatedN RdrName }
         : qvarsym               { $1 }
         | '`' qvarid '`'        {% amsr (sLL $1 $> (unLoc $2))
-                                           (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                           (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 qvaropm :: { LocatedN RdrName }
         : qvarsym_no_minus      { $1 }
         | '`' qvarid '`'        {% amsr (sLL $1 $> (unLoc $2))
-                                           (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                           (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 -----------------------------------------------------------------------------
 -- Type variables
@@ -3949,7 +3949,7 @@ tyvar   : tyvarid               { $1 }
 
 tyvarop :: { LocatedN RdrName }
 tyvarop : '`' tyvarid '`'       {% amsr (sLL $1 $> (unLoc $2))
-                                           (NameAnn NameBackquotes (glR $1) (glR $2) (glR $3) []) }
+                                           (NameAnn (NameBackquotes (epTok $1) (epTok $3)) (glR $2) []) }
 
 tyvarid :: { LocatedN RdrName }
         : VARID            { sL1n $1 $! mkUnqual tvName (getVARID $1) }
@@ -3967,14 +3967,14 @@ tyvarid :: { LocatedN RdrName }
 var     :: { LocatedN RdrName }
         : varid                 { $1 }
         | '(' varsym ')'        {% amsr (sLL $1 $> (unLoc $2))
-                                   (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                   (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 
 qvar    :: { LocatedN RdrName }
         : qvarid                { $1 }
         | '(' varsym ')'        {% amsr (sLL $1 $> (unLoc $2))
-                                   (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                   (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
         | '(' qvarsym1 ')'      {% amsr (sLL $1 $> (unLoc $2))
-                                   (NameAnn NameParens (glR $1) (glR $2) (glR $3) []) }
+                                   (NameAnn (NameParens (epTok $1) (epTok $3)) (glR $2) []) }
 -- We've inlined qvarsym here so that the decision about
 -- whether it's a qvar or a var can be postponed until
 -- *after* we see the close paren.
@@ -4730,7 +4730,7 @@ addTrailingDarrowC :: LocatedC a -> Located Token -> EpAnnComments -> LocatedC a
 addTrailingDarrowC (L (EpAnn lr (AnnContext _ o c) csc) a) lt cs =
   let
     u = if (isUnicode lt) then UnicodeSyntax else NormalSyntax
-  in L (EpAnn lr (AnnContext (Just (u,glR lt)) o c) (cs Semi.<> csc)) a
+  in L (EpAnn lr (AnnContext (Just (epUniTok lt)) o c) (cs Semi.<> csc)) a
 
 -- -------------------------------------
 


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -48,7 +48,7 @@ module GHC.Parser.Annotation (
   -- ** Annotation data types used in 'GenLocated'
 
   AnnListItem(..), AnnList(..), AnnListBrackets(..),
-  AnnParen(..), ParenType(..), parenTypeKws,
+  AnnParen(..),
   AnnPragma(..),
   AnnContext(..),
   NameAnn(..), NameAdornment(..),
@@ -726,35 +726,20 @@ data AnnListBrackets
 -- | exact print annotation for an item having surrounding "brackets", such as
 -- tuples or lists
 data AnnParen
-  = AnnParen {
-      ap_adornment :: ParenType,
-      ap_open      :: EpaLocation,
-      ap_close     :: EpaLocation
-      } deriving (Data)
-
--- | Detail of the "brackets" used in an 'AnnParen' exact print annotation.
-data ParenType
-  = AnnParens       -- ^ '(', ')'
-  | AnnParensHash   -- ^ '(#', '#)'
-  | AnnParensSquare -- ^ '[', ']'
-  deriving (Eq, Ord, Data, Show)
-
--- | Maps the 'ParenType' to the related opening and closing
--- AnnKeywordId. Used when actually printing the item.
-parenTypeKws :: ParenType -> (AnnKeywordId, AnnKeywordId)
-parenTypeKws AnnParens       = (AnnOpenP, AnnCloseP)
-parenTypeKws AnnParensHash   = (AnnOpenPH, AnnClosePH)
-parenTypeKws AnnParensSquare = (AnnOpenS, AnnCloseS)
+  = AnnParens       (EpToken "(")  (EpToken ")")  -- ^ '(', ')'
+  | AnnParensHash   (EpToken "(#") (EpToken "#)") -- ^ '(#', '#)'
+  | AnnParensSquare (EpToken "[")  (EpToken "]")  -- ^ '[', ']'
+  deriving Data
 
 -- ---------------------------------------------------------------------
 
 -- | Exact print annotation for the 'Context' data type.
 data AnnContext
   = AnnContext {
-      ac_darrow    :: Maybe (IsUnicodeSyntax, EpaLocation),
-                      -- ^ location and encoding of the '=>', if present.
-      ac_open      :: [EpaLocation], -- ^ zero or more opening parentheses.
-      ac_close     :: [EpaLocation]  -- ^ zero or more closing parentheses.
+      ac_darrow    :: Maybe TokDarrow,
+                      -- ^ location of the '=>', if present.
+      ac_open      :: [EpToken "("], -- ^ zero or more opening parentheses.
+      ac_close     :: [EpToken ")"]  -- ^ zero or more closing parentheses.
       } deriving (Data)
 
 
@@ -769,40 +754,31 @@ data NameAnn
   -- | Used for a name with an adornment, so '`foo`', '(bar)'
   = NameAnn {
       nann_adornment :: NameAdornment,
-      nann_open      :: EpaLocation,
       nann_name      :: EpaLocation,
-      nann_close     :: EpaLocation,
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(,,,)@, or @(#,,,#)@
   | NameAnnCommas {
       nann_adornment :: NameAdornment,
-      nann_open      :: EpaLocation,
       nann_commas    :: [EpaLocation],
-      nann_close     :: EpaLocation,
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(# | | #)@
   | NameAnnBars {
-      nann_adornment :: NameAdornment,
-      nann_open      :: EpaLocation,
+      nann_parensh   :: (EpToken "(#", EpToken "#)"),
       nann_bars      :: [EpaLocation],
-      nann_close     :: EpaLocation,
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @()@, @(##)@, @[]@
   | NameAnnOnly {
       nann_adornment :: NameAdornment,
-      nann_open      :: EpaLocation,
-      nann_close     :: EpaLocation,
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @->@, as an identifier
   | NameAnnRArrow {
-      nann_unicode   :: Bool,
-      nann_mopen     :: Maybe EpaLocation,
-      nann_name      :: EpaLocation,
-      nann_mclose    :: Maybe EpaLocation,
+      nann_mopen     :: Maybe (EpToken "("),
+      nann_arrow     :: TokRarrow,
+      nann_mclose    :: Maybe (EpToken ")"),
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for an item with a leading @'@. The annotation for
@@ -823,11 +799,13 @@ data NameAnn
 -- such as parens or backquotes. This data type identifies what
 -- particular pair are being used.
 data NameAdornment
-  = NameParens -- ^ '(' ')'
-  | NameParensHash -- ^ '(#' '#)'
-  | NameBackquotes -- ^ '`'
-  | NameSquare -- ^ '[' ']'
-  deriving (Eq, Ord, Data)
+  = NameParens     (EpToken "(")  (EpToken ")") -- ^ '(' ')'
+  | NameParensHash (EpToken "(#") (EpToken "#)")-- ^ '(#' '#)'
+  | NameBackquotes (EpToken "`")  (EpToken "`")-- ^ '`'
+  | NameSquare     (EpToken "[")  (EpToken "]")-- ^ '[' ']'
+  | NameNoAdornment
+  deriving (Eq, Data)
+
 
 -- ---------------------------------------------------------------------
 
@@ -1374,7 +1352,7 @@ instance NoAnn AnnPragma where
   noAnn = AnnPragma noAnn noAnn noAnn noAnn noAnn noAnn noAnn
 
 instance NoAnn AnnParen where
-  noAnn = AnnParen AnnParens noAnn noAnn
+  noAnn = AnnParens noAnn noAnn
 
 instance NoAnn (EpToken s) where
   noAnn = NoEpTok
@@ -1432,29 +1410,32 @@ instance (Outputable e)
      => Outputable (GenLocated EpaLocation e) where
   ppr = pprLocated
 
-instance Outputable ParenType where
-  ppr t = text (show t)
+instance Outputable AnnParen where
+  ppr (AnnParens       o c) = text "AnnParens" <+> ppr o <+> ppr c
+  ppr (AnnParensHash   o c) = text "AnnParensHash" <+> ppr o <+> ppr c
+  ppr (AnnParensSquare o c) = text "AnnParensSquare" <+> ppr o <+> ppr c
 
 instance Outputable AnnListItem where
   ppr (AnnListItem ts) = text "AnnListItem" <+> ppr ts
 
 instance Outputable NameAdornment where
-  ppr NameParens     = text "NameParens"
-  ppr NameParensHash = text "NameParensHash"
-  ppr NameBackquotes = text "NameBackquotes"
-  ppr NameSquare     = text "NameSquare"
+  ppr (NameParens     o c) = text "NameParens" <+> ppr o <+> ppr c
+  ppr (NameParensHash o c) = text "NameParensHash" <+> ppr o <+> ppr c
+  ppr (NameBackquotes o c) = text "NameBackquotes" <+> ppr o <+> ppr c
+  ppr (NameSquare     o c) = text "NameSquare" <+> ppr o <+> ppr c
+  ppr NameNoAdornment      = text "NameNoAdornment"
 
 instance Outputable NameAnn where
-  ppr (NameAnn a o n c t)
-    = text "NameAnn" <+> ppr a <+> ppr o <+> ppr n <+> ppr c <+> ppr t
-  ppr (NameAnnCommas a o n c t)
-    = text "NameAnnCommas" <+> ppr a <+> ppr o <+> ppr n <+> ppr c <+> ppr t
-  ppr (NameAnnBars a o n b t)
-    = text "NameAnnBars" <+> ppr a <+> ppr o <+> ppr n <+> ppr b <+> ppr t
-  ppr (NameAnnOnly a o c t)
-    = text "NameAnnOnly" <+> ppr a <+> ppr o <+> ppr c <+> ppr t
-  ppr (NameAnnRArrow u o n c t)
-    = text "NameAnnRArrow" <+> ppr u <+> ppr o <+> ppr n <+> ppr c <+> ppr t
+  ppr (NameAnn a n t)
+    = text "NameAnn" <+> ppr a <+> ppr n <+> ppr t
+  ppr (NameAnnCommas a n t)
+    = text "NameAnnCommas" <+> ppr a <+> ppr n <+> ppr t
+  ppr (NameAnnBars a n t)
+    = text "NameAnnBars" <+> ppr a <+> ppr n <+> ppr t
+  ppr (NameAnnOnly a t)
+    = text "NameAnnOnly" <+> ppr a <+> ppr t
+  ppr (NameAnnRArrow o n c t)
+    = text "NameAnnRArrow" <+> ppr o <+> ppr n <+> ppr c <+> ppr t
   ppr (NameAnnQuote q n t)
     = text "NameAnnQuote" <+> ppr q <+> ppr n <+> ppr t
   ppr (NameAnnTrailing t)


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1102,7 +1102,7 @@ checkTyClHdr is_cls ty
       let
         lr = combineSrcSpans (locA l1) (locA l)
       in
-        EpAnn (EpaSpan lr) (NameAnn NameParens (getEpTokenLoc o) ap (getEpTokenLoc c) ta) (csp0 Semi.<> csp)
+        EpAnn (EpaSpan lr) (NameAnn (NameParens o c) ap ta) (csp0 Semi.<> csp)
 
 -- | Yield a parse error if we have a function applied directly to a do block
 -- etc. and BlockArguments is not enabled.
@@ -1148,13 +1148,13 @@ checkContext :: LHsType GhcPs -> P (LHsContext GhcPs)
 checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
   check ([],[],cs) orig_t
  where
-  check :: ([EpaLocation],[EpaLocation],EpAnnComments)
+  check :: ([EpToken "("],[EpToken ")"],EpAnnComments)
         -> LHsType GhcPs -> P (LHsContext GhcPs)
-  check (oparens,cparens,cs) (L _l (HsTupleTy ann' HsBoxedOrConstraintTuple ts))
+  check (oparens,cparens,cs) (L _l (HsTupleTy (AnnParens o c) HsBoxedOrConstraintTuple ts))
     -- (Eq a, Ord b) shows up as a tuple type. Only boxed tuples can
     -- be used as context constraints.
     -- Ditto ()
-    = mkCTuple (oparens ++ [ap_open ann'], ap_close ann' : cparens, cs) ts
+    = mkCTuple (oparens ++ [o], c : cparens, cs) ts
 
   -- With NoListTuplePuns, contexts are parsed as data constructors, which causes failure
   -- downstream.
@@ -1164,15 +1164,13 @@ checkContext orig_t@(L (EpAnn l _ cs) _orig_t) =
       True -> unprocessed
       False -> do
         let
-          ol = (getEpTokenLoc o)
-          cl = (getEpTokenLoc c)
           (op, cp) = case q of
-            EpTok ql -> ([ql], [cl])
-            _        -> ([ol], [cl])
+            EpTok ql -> ([EpTok ql], [c])
+            _        -> ([o], [c])
         mkCTuple (oparens ++ op, cp ++ cparens, cs) ts
   check (opi,cpi,csi) (L _lp1 (HsParTy (o,c) ty))
                                              -- to be sure HsParTy doesn't get into the way
-    = check (getEpTokenLoc o:opi, getEpTokenLoc c:cpi, csi) ty
+    = check (o:opi, c:cpi, csi) ty
 
   -- No need for anns, returning original
   check (_opi,_cpi,_csi) _t = unprocessed
@@ -1200,16 +1198,16 @@ checkContextExpr :: LHsExpr GhcPs -> PV (LocatedC [LHsExpr GhcPs])
 checkContextExpr orig_expr@(L (EpAnn l _ cs) _) =
   check ([],[], cs) orig_expr
   where
-    check :: ([EpaLocation],[EpaLocation],EpAnnComments)
+    check :: ([EpToken "("],[EpToken ")"],EpAnnComments)
         -> LHsExpr GhcPs -> PV (LocatedC [LHsExpr GhcPs])
     check (oparens,cparens,cs) (L _ (ExplicitTuple (ap_open, ap_close) tup_args boxity))
              -- Neither unboxed tuples (#e1,e2#) nor tuple sections (e1,,e2,) can be a context
       | isBoxed boxity
       , Just es <- tupArgsPresent_maybe tup_args
-      = mkCTuple (oparens ++ [ap_open], ap_close : cparens, cs) es
-    check (opi, cpi, csi) (L _ (HsPar (EpTok open_tok, EpTok close_tok) expr))
+      = mkCTuple (oparens ++ [EpTok ap_open], EpTok ap_close : cparens, cs) es
+    check (opi, cpi, csi) (L _ (HsPar (open_tok, close_tok) expr))
       = check (opi ++ [open_tok], close_tok : cpi, csi) expr
-    check (oparens,cparens,cs) (L _ (HsVar _ (L (EpAnn _ (NameAnnOnly NameParens open closed []) _) name)))
+    check (oparens,cparens,cs) (L _ (HsVar _ (L (EpAnn _ (NameAnnOnly (NameParens open closed) []) _) name)))
       | name == nameRdrName (dataConName unitDataCon)
       = mkCTuple (oparens ++ [open], closed : cparens, cs) []
     check _ _ = unprocessed
@@ -3613,9 +3611,9 @@ withCombinedComments start end use = do
 -- type or data constructor, based on the extension @ListTuplePuns at .
 -- The case with an explicit promotion quote, @'(Int, Double)@, is handled
 -- by 'mkExplicitTupleTy'.
-mkTupleSyntaxTy :: EpaLocation
+mkTupleSyntaxTy :: EpToken "("
                 -> [LocatedA (HsType GhcPs)]
-                -> EpaLocation
+                -> EpToken ")"
                 -> P (HsType GhcPs)
 mkTupleSyntaxTy parOpen args parClose =
   punsIfElse enabled disabled
@@ -3625,8 +3623,8 @@ mkTupleSyntaxTy parOpen args parClose =
     disabled =
       HsExplicitTupleTy annsKeyword args
 
-    annParen = AnnParen AnnParens parOpen parClose
-    annsKeyword = (NoEpTok, EpTok parOpen, EpTok parClose)
+    annParen = AnnParens parOpen parClose
+    annsKeyword = (NoEpTok, parOpen, parClose)
 
 -- | Decide whether to parse tuple con syntax @(,)@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
@@ -3642,8 +3640,8 @@ mkTupleSyntaxTycon boxity n =
 -- constructor, based on the extension @ListTuplePuns at .
 -- The case with an explicit promotion quote, @'[]@, is handled by
 -- 'mkExplicitListTy'.
-mkListSyntaxTy0 :: EpaLocation
-                -> EpaLocation
+mkListSyntaxTy0 :: EpToken "["
+                -> EpToken "]"
                 -> SrcSpan
                 -> P (HsType GhcPs)
 mkListSyntaxTy0 brkOpen brkClose span =
@@ -3657,17 +3655,17 @@ mkListSyntaxTy0 brkOpen brkClose span =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted []
 
-    rdrNameAnn = NameAnnOnly NameSquare brkOpen brkClose []
-    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
+    rdrNameAnn = NameAnnOnly (NameSquare brkOpen brkClose) []
+    annsKeyword = (NoEpTok, brkOpen, brkClose)
     fullLoc = EpaSpan span
 
 -- | Decide whether to parse list type syntax @[Int]@ in a type as a
 -- type or data constructor, based on the extension @ListTuplePuns at .
 -- The case with an explicit promotion quote, @'[Int]@, is handled
 -- by 'mkExplicitListTy'.
-mkListSyntaxTy1 :: EpaLocation
+mkListSyntaxTy1 :: EpToken "["
                 -> LocatedA (HsType GhcPs)
-                -> EpaLocation
+                -> EpToken "]"
                 -> P (HsType GhcPs)
 mkListSyntaxTy1 brkOpen t brkClose =
   punsIfElse enabled disabled
@@ -3677,5 +3675,5 @@ mkListSyntaxTy1 brkOpen t brkClose =
     disabled =
       HsExplicitListTy annsKeyword NotPromoted [t]
 
-    annsKeyword = (NoEpTok, EpTok brkOpen, EpTok brkClose)
-    annParen = AnnParen AnnParensSquare brkOpen brkClose
+    annsKeyword = (NoEpTok, brkOpen, brkClose)
+    annParen = AnnParensSquare brkOpen brkClose


=====================================
testsuite/tests/ghc-api/exactprint/Test20239.stderr
=====================================
@@ -366,10 +366,11 @@
                             (EpaComments
                              []))
                            (HsTupleTy
-                            (AnnParen
-                             AnnParens
-                             (EpaSpan { Test20239.hs:7:83 })
-                             (EpaSpan { Test20239.hs:7:84 }))
+                            (AnnParens
+                             (EpTok
+                              (EpaSpan { Test20239.hs:7:83 }))
+                             (EpTok
+                              (EpaSpan { Test20239.hs:7:84 })))
                             (HsBoxedOrConstraintTuple)
                             [])))))))))))))])
              (Nothing)))])


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -257,10 +257,11 @@
                (EpaComments
                 []))
               (HsTupleTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { T17544_kw.hs:19:18 })
-                (EpaSpan { T17544_kw.hs:19:19 }))
+               (AnnParens
+                (EpTok
+                 (EpaSpan { T17544_kw.hs:19:18 }))
+                (EpTok
+                 (EpaSpan { T17544_kw.hs:19:19 })))
                (HsBoxedOrConstraintTuple)
                [])))])
           (L


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -254,10 +254,11 @@
             (EpaComments
              []))
            (HsListTy
-            (AnnParen
-             AnnParensSquare
-             (EpaSpan { DumpParsedAst.hs:9:16 })
-             (EpaSpan { DumpParsedAst.hs:9:18 }))
+            (AnnParensSquare
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:9:16 }))
+             (EpTok
+              (EpaSpan { DumpParsedAst.hs:9:18 })))
             (L
              (EpAnn
               (EpaSpan { DumpParsedAst.hs:9:17 })
@@ -626,10 +627,11 @@
               (EpaComments
                []))
              (HsListTy
-              (AnnParen
-               AnnParensSquare
-               (EpaSpan { DumpParsedAst.hs:10:27 })
-               (EpaSpan { DumpParsedAst.hs:10:29 }))
+              (AnnParensSquare
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:10:27 }))
+               (EpTok
+                (EpaSpan { DumpParsedAst.hs:10:29 })))
               (L
                (EpAnn
                 (EpaSpan { DumpParsedAst.hs:10:28 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -548,10 +548,11 @@
                 (EpaComments
                  []))
                (HsListTy
-                (AnnParen
-                 AnnParensSquare
-                 (EpaSpan { DumpRenamedAst.hs:12:27 })
-                 (EpaSpan { DumpRenamedAst.hs:12:29 }))
+                (AnnParensSquare
+                 (EpTok
+                  (EpaSpan { DumpRenamedAst.hs:12:27 }))
+                 (EpTok
+                  (EpaSpan { DumpRenamedAst.hs:12:29 })))
                 (L
                  (EpAnn
                   (EpaSpan { DumpRenamedAst.hs:12:28 })
@@ -646,10 +647,11 @@
               (EpaComments
                []))
              (HsListTy
-              (AnnParen
-               AnnParensSquare
-               (EpaSpan { DumpRenamedAst.hs:11:16 })
-               (EpaSpan { DumpRenamedAst.hs:11:18 }))
+              (AnnParensSquare
+               (EpTok
+                (EpaSpan { DumpRenamedAst.hs:11:16 }))
+               (EpTok
+                (EpaSpan { DumpRenamedAst.hs:11:18 })))
               (L
                (EpAnn
                 (EpaSpan { DumpRenamedAst.hs:11:17 })
@@ -2231,10 +2233,11 @@
                (EpaComments
                 []))
               (HsListTy
-               (AnnParen
-                AnnParensSquare
-                (EpaSpan { DumpRenamedAst.hs:31:12 })
-                (EpaSpan { DumpRenamedAst.hs:31:14 }))
+               (AnnParensSquare
+                (EpTok
+                 (EpaSpan { DumpRenamedAst.hs:31:12 }))
+                (EpTok
+                 (EpaSpan { DumpRenamedAst.hs:31:14 })))
                (L
                 (EpAnn
                  (EpaSpan { DumpRenamedAst.hs:31:13 })
@@ -2292,10 +2295,11 @@
                  (EpaComments
                   []))
                 (HsListTy
-                 (AnnParen
-                  AnnParensSquare
-                  (EpaSpan { DumpRenamedAst.hs:32:10 })
-                  (EpaSpan { DumpRenamedAst.hs:32:12 }))
+                 (AnnParensSquare
+                  (EpTok
+                   (EpaSpan { DumpRenamedAst.hs:32:10 }))
+                  (EpTok
+                   (EpaSpan { DumpRenamedAst.hs:32:12 })))
                  (L
                   (EpAnn
                    (EpaSpan { DumpRenamedAst.hs:32:11 })


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -223,10 +223,11 @@
              (EpaComments
               []))
             (HsTupleTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { DumpSemis.hs:9:11 })
-              (EpaSpan { DumpSemis.hs:9:12 }))
+             (AnnParens
+              (EpTok
+               (EpaSpan { DumpSemis.hs:9:11 }))
+              (EpTok
+               (EpaSpan { DumpSemis.hs:9:12 })))
              (HsBoxedOrConstraintTuple)
              []))))))))))
   ,(L
@@ -527,10 +528,11 @@
              (EpaComments
               []))
             (HsTupleTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { DumpSemis.hs:14:11 })
-              (EpaSpan { DumpSemis.hs:14:12 }))
+             (AnnParens
+              (EpTok
+               (EpaSpan { DumpSemis.hs:14:11 }))
+              (EpTok
+               (EpaSpan { DumpSemis.hs:14:12 })))
              (HsBoxedOrConstraintTuple)
              []))))))))))
   ,(L
@@ -792,10 +794,11 @@
              (EpaComments
               []))
             (HsTupleTy
-             (AnnParen
-              AnnParens
-              (EpaSpan { DumpSemis.hs:21:11 })
-              (EpaSpan { DumpSemis.hs:21:12 }))
+             (AnnParens
+              (EpTok
+               (EpaSpan { DumpSemis.hs:21:11 }))
+              (EpTok
+               (EpaSpan { DumpSemis.hs:21:12 })))
              (HsBoxedOrConstraintTuple)
              []))))))))))
   ,(L
@@ -1547,13 +1550,17 @@
              (EpaSpan { DumpSemis.hs:31:6-20 })
              (AnnContext
               (Just
-               ((,)
-                (NormalSyntax)
-                (EpaSpan { DumpSemis.hs:31:22-23 })))
-              [(EpaSpan { DumpSemis.hs:31:6 })
-              ,(EpaSpan { DumpSemis.hs:31:7 })]
-              [(EpaSpan { DumpSemis.hs:31:19 })
-              ,(EpaSpan { DumpSemis.hs:31:20 })])
+               (EpUniTok
+                (EpaSpan { DumpSemis.hs:31:22-23 })
+                (NormalSyntax)))
+              [(EpTok
+                (EpaSpan { DumpSemis.hs:31:6 }))
+              ,(EpTok
+                (EpaSpan { DumpSemis.hs:31:7 }))]
+              [(EpTok
+                (EpaSpan { DumpSemis.hs:31:19 }))
+              ,(EpTok
+                (EpaSpan { DumpSemis.hs:31:20 }))])
              (EpaComments
               []))
             [(L


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -312,10 +312,11 @@
         (EpaComments
          []))
        (HsTupleTy
-        (AnnParen
-         AnnParens
-         (EpaSpan { KindSigs.hs:15:14 })
-         (EpaSpan { KindSigs.hs:15:51 }))
+        (AnnParens
+         (EpTok
+          (EpaSpan { KindSigs.hs:15:14 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:15:51 })))
         (HsBoxedOrConstraintTuple)
         [(L
           (EpAnn
@@ -529,10 +530,11 @@
         (EpaComments
          []))
        (HsTupleTy
-        (AnnParen
-         AnnParensHash
-         (EpaSpan { KindSigs.hs:16:15-16 })
-         (EpaSpan { KindSigs.hs:16:53-54 }))
+        (AnnParensHash
+         (EpTok
+          (EpaSpan { KindSigs.hs:16:15-16 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:16:53-54 })))
         (HsUnboxedTuple)
         [(L
           (EpAnn
@@ -719,10 +721,11 @@
         (EpaComments
          []))
        (HsListTy
-        (AnnParen
-         AnnParensSquare
-         (EpaSpan { KindSigs.hs:19:12 })
-         (EpaSpan { KindSigs.hs:19:26 }))
+        (AnnParensSquare
+         (EpTok
+          (EpaSpan { KindSigs.hs:19:12 }))
+         (EpTok
+          (EpaSpan { KindSigs.hs:19:26 })))
         (L
          (EpAnn
           (EpaSpan { KindSigs.hs:19:14-24 })
@@ -949,10 +952,11 @@
                    (EpaComments
                     []))
                   (HsTupleTy
-                   (AnnParen
-                    AnnParens
-                    (EpaSpan { KindSigs.hs:22:34 })
-                    (EpaSpan { KindSigs.hs:22:35 }))
+                   (AnnParens
+                    (EpTok
+                     (EpaSpan { KindSigs.hs:22:34 }))
+                    (EpTok
+                     (EpaSpan { KindSigs.hs:22:35 })))
                    (HsBoxedOrConstraintTuple)
                    []))
                  (L
@@ -1085,9 +1089,11 @@
                   (EpAnn
                    (EpaSpan { KindSigs.hs:23:11-12 })
                    (NameAnnOnly
-                    (NameParens)
-                    (EpaSpan { KindSigs.hs:23:11 })
-                    (EpaSpan { KindSigs.hs:23:12 })
+                    (NameParens
+                     (EpTok
+                      (EpaSpan { KindSigs.hs:23:11 }))
+                     (EpTok
+                      (EpaSpan { KindSigs.hs:23:12 })))
                     [])
                    (EpaComments
                     []))
@@ -1480,10 +1486,11 @@
              (EpaComments
               []))
             (HsListTy
-             (AnnParen
-              AnnParensSquare
-              (EpaSpan { KindSigs.hs:28:34 })
-              (EpaSpan { KindSigs.hs:28:39 }))
+             (AnnParensSquare
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:34 }))
+              (EpTok
+               (EpaSpan { KindSigs.hs:28:39 })))
              (L
               (EpAnn
                (EpaSpan { KindSigs.hs:28:35-38 })


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -182,9 +182,9 @@
               (EpaSpan { T15323.hs:6:31-36 })
               (AnnContext
                (Just
-                ((,)
-                 (NormalSyntax)
-                 (EpaSpan { T15323.hs:6:38-39 })))
+                (EpUniTok
+                 (EpaSpan { T15323.hs:6:38-39 })
+                 (NormalSyntax)))
                []
                [])
               (EpaComments


=====================================
testsuite/tests/parser/should_compile/T20452.stderr
=====================================
@@ -455,10 +455,11 @@
              (EpaComments
               []))
             (HsListTy
-             (AnnParen
-              AnnParensSquare
-              (EpaSpan { T20452.hs:8:57 })
-              (EpaSpan { T20452.hs:8:74 }))
+             (AnnParensSquare
+              (EpTok
+               (EpaSpan { T20452.hs:8:57 }))
+              (EpTok
+               (EpaSpan { T20452.hs:8:74 })))
              (L
               (EpAnn
                (EpaSpan { T20452.hs:8:58-73 })
@@ -467,10 +468,11 @@
                (EpaComments
                 []))
               (HsTupleTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { T20452.hs:8:58 })
-                (EpaSpan { T20452.hs:8:73 }))
+               (AnnParens
+                (EpTok
+                 (EpaSpan { T20452.hs:8:58 }))
+                (EpTok
+                 (EpaSpan { T20452.hs:8:73 })))
                (HsBoxedOrConstraintTuple)
                [(L
                  (EpAnn
@@ -698,10 +700,11 @@
              (EpaComments
               []))
             (HsListTy
-             (AnnParen
-              AnnParensSquare
-              (EpaSpan { T20452.hs:9:57 })
-              (EpaSpan { T20452.hs:9:74 }))
+             (AnnParensSquare
+              (EpTok
+               (EpaSpan { T20452.hs:9:57 }))
+              (EpTok
+               (EpaSpan { T20452.hs:9:74 })))
              (L
               (EpAnn
                (EpaSpan { T20452.hs:9:58-73 })
@@ -710,10 +713,11 @@
                (EpaComments
                 []))
               (HsTupleTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { T20452.hs:9:58 })
-                (EpaSpan { T20452.hs:9:73 }))
+               (AnnParens
+                (EpTok
+                 (EpaSpan { T20452.hs:9:58 }))
+                (EpTok
+                 (EpaSpan { T20452.hs:9:73 })))
                (HsBoxedOrConstraintTuple)
                [(L
                  (EpAnn


=====================================
testsuite/tests/parser/should_compile/T20846.stderr
=====================================
@@ -113,10 +113,12 @@
              (EpAnn
               (EpaSpan { T20846.hs:4:1-6 })
               (NameAnn
-               (NameParens)
-               (EpaSpan { T20846.hs:4:1 })
+               (NameParens
+                (EpTok
+                 (EpaSpan { T20846.hs:4:1 }))
+                (EpTok
+                 (EpaSpan { T20846.hs:4:6 })))
                (EpaSpan { T20846.hs:4:2-5 })
-               (EpaSpan { T20846.hs:4:6 })
                [])
               (EpaComments
                []))


=====================================
testsuite/tests/parser/should_compile/T23315/T23315.stderr
=====================================
@@ -101,10 +101,11 @@
            (EpaComments
             []))
           (HsTupleTy
-           (AnnParen
-            AnnParens
-            (EpaSpan { T23315.hsig:3:6 })
-            (EpaSpan { T23315.hsig:3:7 }))
+           (AnnParens
+            (EpTok
+             (EpaSpan { T23315.hsig:3:6 }))
+            (EpTok
+             (EpaSpan { T23315.hsig:3:7 })))
            (HsBoxedOrConstraintTuple)
            []))))))))
   ,(L


=====================================
testsuite/tests/printer/Test24533.stdout
=====================================
@@ -89,11 +89,13 @@
              (EpaSpan { Test24533.hs:(5,3)-(7,3) })
              (AnnContext
               (Just
-               ((,)
-                (NormalSyntax)
-                (EpaSpan { Test24533.hs:7:5-6 })))
-              [(EpaSpan { Test24533.hs:5:3 })]
-              [(EpaSpan { Test24533.hs:7:3 })])
+               (EpUniTok
+                (EpaSpan { Test24533.hs:7:5-6 })
+                (NormalSyntax)))
+              [(EpTok
+                (EpaSpan { Test24533.hs:5:3 }))]
+              [(EpTok
+                (EpaSpan { Test24533.hs:7:3 }))])
              (EpaComments
               [(L
                 (EpaSpan
@@ -233,10 +235,11 @@
                (EpaComments
                 []))
               (HsTupleTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { Test24533.hs:8:8 })
-                (EpaSpan { Test24533.hs:8:13 }))
+               (AnnParens
+                (EpTok
+                 (EpaSpan { Test24533.hs:8:8 }))
+                (EpTok
+                 (EpaSpan { Test24533.hs:8:13 })))
                (HsBoxedOrConstraintTuple)
                [(L
                  (EpAnn
@@ -761,11 +764,13 @@
              (EpaSpan { Test24533.ppr.hs:3:10-25 })
              (AnnContext
               (Just
-               ((,)
-                (NormalSyntax)
-                (EpaSpan { Test24533.ppr.hs:3:27-28 })))
-              [(EpaSpan { Test24533.ppr.hs:3:10 })]
-              [(EpaSpan { Test24533.ppr.hs:3:25 })])
+               (EpUniTok
+                (EpaSpan { Test24533.ppr.hs:3:27-28 })
+                (NormalSyntax)))
+              [(EpTok
+                (EpaSpan { Test24533.ppr.hs:3:10 }))]
+              [(EpTok
+                (EpaSpan { Test24533.ppr.hs:3:25 }))])
              (EpaComments
               []))
             [(L
@@ -899,10 +904,11 @@
                (EpaComments
                 []))
               (HsTupleTy
-               (AnnParen
-                AnnParens
-                (EpaSpan { Test24533.ppr.hs:3:35 })
-                (EpaSpan { Test24533.ppr.hs:3:40 }))
+               (AnnParens
+                (EpTok
+                 (EpaSpan { Test24533.ppr.hs:3:35 }))
+                (EpTok
+                 (EpaSpan { Test24533.ppr.hs:3:40 })))
                (HsBoxedOrConstraintTuple)
                [(L
                  (EpAnn


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -291,12 +291,12 @@ instance HasTrailing AnnPragma where
 instance HasTrailing AnnContext where
   trailing (AnnContext ma _opens _closes)
     = case ma of
-      Just (UnicodeSyntax, r) -> [AddDarrowUAnn r]
-      Just (NormalSyntax,  r) -> [AddDarrowAnn r]
-      Nothing -> []
+      Just (EpUniTok r UnicodeSyntax) -> [AddDarrowUAnn r]
+      Just (EpUniTok r NormalSyntax)  -> [AddDarrowAnn r]
+      _ -> []
 
-  setTrailing a [AddDarrowUAnn r] = a {ac_darrow = Just (UnicodeSyntax, r)}
-  setTrailing a [AddDarrowAnn r] = a{ac_darrow = Just (NormalSyntax, r)}
+  setTrailing a [AddDarrowUAnn r] = a {ac_darrow = Just (EpUniTok r UnicodeSyntax)}
+  setTrailing a [AddDarrowAnn r] = a{ac_darrow = Just (EpUniTok r NormalSyntax)}
   setTrailing a [] = a{ac_darrow = Nothing}
   setTrailing a ts = error $ "Cannot setTrailing " ++ showAst ts ++ " for " ++ showAst a
 
@@ -882,27 +882,32 @@ markAnnOpen'' el NoSourceText txt   = printStringAtAA el txt
 markAnnOpen'' el (SourceText txt) _ = printStringAtAA el $ unpackFS txt
 
 -- ---------------------------------------------------------------------
-{-
-data AnnParen
-  = AnnParen {
-      ap_adornment :: ParenType,
-      ap_open      :: EpaLocation,
-      ap_close     :: EpaLocation
-      } deriving (Data)
--}
+
 markOpeningParen, markClosingParen :: (Monad m, Monoid w) => AnnParen -> EP w m AnnParen
-markOpeningParen an = markParen an lfst
-markClosingParen an = markParen an lsnd
-
-markParen :: (Monad m, Monoid w) => AnnParen -> (forall a. Lens (a,a) a) -> EP w m AnnParen
-markParen (AnnParen pt o c) l = do
-  loc' <- markKwA (view l $ kw pt) (view l (o, c))
-  let (o',c') = set l loc' (o,c)
-  return (AnnParen pt o' c')
-  where
-    kw AnnParens       = (AnnOpenP,  AnnCloseP)
-    kw AnnParensHash   = (AnnOpenPH, AnnClosePH)
-    kw AnnParensSquare = (AnnOpenS, AnnCloseS)
+markOpeningParen an = markParenO an
+markClosingParen an = markParenC an
+
+markParenO :: (Monad m, Monoid w) => AnnParen -> EP w m AnnParen
+markParenO (AnnParens o c) = do
+  o' <- markEpToken o
+  return (AnnParens o' c)
+markParenO (AnnParensHash o c) = do
+  o' <- markEpToken o
+  return (AnnParensHash o' c)
+markParenO (AnnParensSquare o c) = do
+  o' <- markEpToken o
+  return (AnnParensSquare o' c)
+
+markParenC :: (Monad m, Monoid w) => AnnParen -> EP w m AnnParen
+markParenC (AnnParens o c) = do
+  c' <- markEpToken c
+  return (AnnParens o c')
+markParenC (AnnParensHash o c) = do
+  c' <- markEpToken c
+  return (AnnParensHash o c')
+markParenC (AnnParensSquare o c) = do
+  c' <- markEpToken c
+  return (AnnParensSquare o c')
 
 -- ---------------------------------------------------------------------
 -- Bare bones Optics
@@ -1028,10 +1033,6 @@ lal_rest :: Lens (AnnList l) l
 lal_rest k parent = fmap (\new -> parent { al_rest = new })
                            (k (al_rest parent))
 
--- lal_trailing :: Lens AnnList [TrailingAnn]
--- lal_trailing k parent = fmap (\new -> parent { al_trailing = new })
---                            (k (al_trailing parent))
-
 -- -------------------------------------
 
 lid :: Lens a a
@@ -4175,9 +4176,9 @@ instance (ExactPrint a) => ExactPrint (LocatedC a) where
   setAnnotationAnchor = setAnchorAn
 
   exact (L (EpAnn anc (AnnContext ma opens closes) cs) a) = do
-    opens' <- mapM (markKwA AnnOpenP) opens
+    opens' <- mapM markEpToken opens
     a' <- markAnnotated a
-    closes' <- mapM (markKwA AnnCloseP) closes
+    closes' <- mapM markEpToken closes
     return (L (EpAnn anc (AnnContext ma opens' closes') cs) a')
 
 -- ---------------------------------------------------------------------
@@ -4213,43 +4214,30 @@ instance ExactPrint (LocatedN RdrName) where
   exact (L (EpAnn anc ann cs) n) = do
     ann' <-
       case ann of
-        NameAnn a o l c t -> do
-          mn <- markName a o (Just (l,n)) c
+        NameAnn a l t -> do
+          mn <- markName a (Just (l,n))
           case mn of
-            (o', (Just (l',_n)), c') -> do
-              return (NameAnn a o' l' c' t)
+            (a', (Just (l',_n))) -> do
+              return (NameAnn a' l' t)
             _ -> error "ExactPrint (LocatedN RdrName)"
-        NameAnnCommas a o commas c t -> do
-          let (kwo,kwc) = adornments a
-          (AddEpAnn _ o') <- markKwC NoCaptureComments (AddEpAnn kwo o)
+        NameAnnCommas a commas t -> do
+          a0 <- markNameAdornmentO a
           commas' <- forM commas (\loc -> locFromAdd <$> markKwC NoCaptureComments (AddEpAnn AnnComma loc))
-          (AddEpAnn _ c') <- markKwC NoCaptureComments (AddEpAnn kwc c)
-          return (NameAnnCommas a o' commas' c' t)
-        NameAnnBars a o bars c t -> do
-          let (kwo,kwc) = adornments a
-          (AddEpAnn _ o') <- markKwC NoCaptureComments (AddEpAnn kwo o)
+          a1 <- markNameAdornmentC a0
+          return (NameAnnCommas a1 commas' t)
+        NameAnnBars (o,c) bars t -> do
+          o' <- markEpToken o
           bars' <- forM bars (\loc -> locFromAdd <$> markKwC NoCaptureComments (AddEpAnn AnnVbar loc))
-          (AddEpAnn _ c') <- markKwC NoCaptureComments (AddEpAnn kwc c)
-          return (NameAnnBars a o' bars' c' t)
-        NameAnnOnly a o c t -> do
-          (o',_,c') <- markName a o Nothing c
-          return (NameAnnOnly a o' c' t)
-        NameAnnRArrow unicode o nl c t -> do
-          o' <- case o of
-            Just o0 -> do
-              (AddEpAnn _ o') <- markKwC NoCaptureComments (AddEpAnn AnnOpenP o0)
-              return (Just o')
-            Nothing -> return Nothing
-          (AddEpAnn _ nl') <-
-            if unicode
-              then markKwC NoCaptureComments (AddEpAnn AnnRarrowU nl)
-              else markKwC NoCaptureComments (AddEpAnn AnnRarrow nl)
-          c' <- case c of
-            Just c0 -> do
-              (AddEpAnn _ c') <- markKwC NoCaptureComments (AddEpAnn AnnCloseP c0)
-              return (Just c')
-            Nothing -> return Nothing
-          return (NameAnnRArrow unicode o' nl' c' t)
+          c' <- markEpToken c
+          return (NameAnnBars (o',c') bars' t)
+        NameAnnOnly a t -> do
+          (a',_) <- markName a Nothing
+          return (NameAnnOnly a' t)
+        NameAnnRArrow o nl c t -> do
+          o' <- mapM markEpToken o
+          nl' <- markEpUniToken nl
+          c' <- mapM markEpToken c
+          return (NameAnnRArrow o' nl' c' t)
         NameAnnQuote q name t -> do
           debugM $ "NameAnnQuote"
           (AddEpAnn _ q') <- markKwC NoCaptureComments (AddEpAnn AnnSimpleQuote q)
@@ -4260,6 +4248,37 @@ instance ExactPrint (LocatedN RdrName) where
           return (NameAnnTrailing t)
     return (L (EpAnn anc ann' cs) n)
 
+
+markNameAdornmentO :: (Monad m, Monoid w) => NameAdornment -> EP w m NameAdornment
+markNameAdornmentO (NameParens o c) = do
+  o' <- markEpToken o
+  return (NameParens o' c)
+markNameAdornmentO (NameParensHash o c) = do
+  o' <- markEpToken o
+  return (NameParensHash o' c)
+markNameAdornmentO (NameBackquotes o c) = do
+  o' <- markEpToken o
+  return (NameBackquotes o' c)
+markNameAdornmentO (NameSquare o c) = do
+  o' <- markEpToken o
+  return (NameSquare o' c)
+markNameAdornmentO NameNoAdornment      = return NameNoAdornment
+
+markNameAdornmentC :: (Monad m, Monoid w) => NameAdornment -> EP w m NameAdornment
+markNameAdornmentC (NameParens o c) = do
+  c' <- markEpToken c
+  return (NameParens o c')
+markNameAdornmentC (NameParensHash o c) = do
+  c' <- markEpToken c
+  return (NameParensHash o c')
+markNameAdornmentC (NameBackquotes o c) = do
+  c' <- markEpToken c
+  return (NameBackquotes o c')
+markNameAdornmentC (NameSquare o c) = do
+  c' <- markEpToken c
+  return (NameSquare o c')
+markNameAdornmentC NameNoAdornment      = return NameNoAdornment
+
 locFromAdd :: AddEpAnn -> EpaLocation
 locFromAdd (AddEpAnn _ loc) = loc
 
@@ -4277,25 +4296,18 @@ printUnicode anc n = do
 
 
 markName :: (Monad m, Monoid w)
-  => NameAdornment -> EpaLocation -> Maybe (EpaLocation,RdrName) -> EpaLocation
-  -> EP w m (EpaLocation, Maybe (EpaLocation,RdrName), EpaLocation)
-markName adorn open mname close = do
-  let (kwo,kwc) = adornments adorn
-  (AddEpAnn _ open') <- markKwC CaptureComments (AddEpAnn kwo open)
+  => NameAdornment -> Maybe (EpaLocation,RdrName)
+  -> EP w m (NameAdornment, Maybe (EpaLocation,RdrName))
+markName adorn mname = do
+  adorn0 <- markNameAdornmentO adorn
   mname' <-
     case mname of
       Nothing -> return Nothing
       Just (name, a) -> do
         name' <- printStringAtAAC CaptureComments name (showPprUnsafe a)
         return (Just (name',a))
-  (AddEpAnn _ close') <- markKwC CaptureComments (AddEpAnn kwc close)
-  return (open', mname', close')
-
-adornments :: NameAdornment -> (AnnKeywordId, AnnKeywordId)
-adornments NameParens     = (AnnOpenP, AnnCloseP)
-adornments NameParensHash = (AnnOpenPH, AnnClosePH)
-adornments NameBackquotes = (AnnBackquote, AnnBackquote)
-adornments NameSquare     = (AnnOpenS, AnnCloseS)
+  adorn1 <- markNameAdornmentC adorn0
+  return (adorn1, mname')
 
 markTrailing :: (Monad m, Monoid w) => [TrailingAnn] -> EP w m [TrailingAnn]
 markTrailing ts = do


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -998,40 +998,31 @@ instance NFData (EpAnn NameAnn) where
   rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` ()
 
 instance NFData NameAnn where
-  rnf (NameAnn a b c d e) =
+  rnf (NameAnn a b c) =
     a `deepseq`
       b `deepseq`
         c `deepseq`
-          d `deepseq`
-            e `deepseq`
-              ()
-  rnf (NameAnnCommas a b c d e) =
+           ()
+  rnf (NameAnnCommas a b c) =
     a `deepseq`
       b `deepseq`
         c `deepseq`
-          d `deepseq`
-            e `deepseq`
-              ()
-  rnf (NameAnnBars a b c d e) =
+          ()
+  rnf (NameAnnBars a b c) =
     a `deepseq`
       b `deepseq`
         c `deepseq`
-          d `deepseq`
-            e `deepseq`
-              ()
-  rnf (NameAnnOnly a b c d) =
+          ()
+  rnf (NameAnnOnly a b) =
     a `deepseq`
       b `deepseq`
-        c `deepseq`
-          d `deepseq`
-            ()
-  rnf (NameAnnRArrow a b c d e) =
+        ()
+  rnf (NameAnnRArrow a b c d) =
     a `deepseq`
       b `deepseq`
         c `deepseq`
           d `deepseq`
-            e `deepseq`
-              ()
+            ()
   rnf (NameAnnQuote a b c) =
     a `deepseq`
       b `deepseq`
@@ -1047,10 +1038,11 @@ instance NFData TrailingAnn where
   rnf (AddDarrowUAnn epaL) = rnf epaL
 
 instance NFData NameAdornment where
-  rnf NameParens = ()
-  rnf NameParensHash = ()
-  rnf NameBackquotes = ()
-  rnf NameSquare = ()
+  rnf (NameParens  o c) =  o `deepseq` c `seq` ()
+  rnf (NameParensHash o c) =  o `deepseq` c `seq` ()
+  rnf (NameBackquotes o c) =  o `deepseq` c `seq` ()
+  rnf (NameSquare o c) =  o `deepseq` c `seq` ()
+  rnf NameNoAdornment = ()
 
 instance NFData NoComments where
   rnf NoComments = ()
@@ -1085,3 +1077,15 @@ instance NFData BufPos where
 instance NFData DeltaPos where
   rnf (SameLine n) = rnf n
   rnf (DifferentLine n m) = n `deepseq` m `deepseq` ()
+
+instance NFData (EpToken tok) where
+  rnf (EpTok l) = rnf l
+  rnf NoEpTok = ()
+
+instance NFData (EpUniToken tok toku) where
+  rnf (EpUniTok l s) = l `deepseq` s `deepseq` ()
+  rnf NoEpUniTok = ()
+
+instance NFData IsUnicodeSyntax where
+  rnf NormalSyntax = ()
+  rnf UnicodeSyntax = ()



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a41de9cd511b8d971c92fc8fcd9b973b6609c72

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 17:15:51 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 26 Oct 2024 13:15:51 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Fix
 optimisation of InstCo
Message-ID: <671d23c791196_289b8685f8f41339e2@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
7e240b23 by Simon Peyton Jones at 2024-10-26T13:15:29-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
aa9ddd4c by Andrew Lelechenko at 2024-10-26T13:15:30-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -


11 changed files:

- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/Types/Basic.hs
- libraries/base/src/Control/Monad/Fix.hs
- + testsuite/tests/dependent/should_compile/T25387.hs
- testsuite/tests/dependent/should_compile/all.T


Changes:

=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -30,7 +30,7 @@ module GHC.Core.Coercion (
         coercionRole, coercionKindRole,
 
         -- ** Constructing coercions
-        mkGReflCo, mkReflCo, mkRepReflCo, mkNomReflCo,
+        mkGReflCo, mkGReflMCo, mkReflCo, mkRepReflCo, mkNomReflCo,
         mkCoVarCo, mkCoVarCos,
         mkAxInstCo, mkUnbranchedAxInstCo,
         mkAxInstRHS, mkUnbranchedAxInstRHS,
@@ -332,8 +332,23 @@ isGReflMCo _ = False
 mkGReflCo :: Role -> Type -> MCoercionN -> Coercion
 mkGReflCo r ty mco
   | isGReflMCo mco = if r == Nominal then Refl ty
-                     else GRefl r ty MRefl
-  | otherwise    = GRefl r ty mco
+                                     else GRefl r ty MRefl
+  | otherwise
+  = -- I'd like to have this assert, but sadly it's not true during type
+    -- inference because the types are not fully zonked
+    -- assertPpr (case mco of
+    --              MCo co -> typeKind ty `eqType` coercionLKind co
+    --              MRefl  -> True)
+    --          (vcat [ text "ty" <+> ppr ty <+> dcolon <+> ppr (typeKind ty)
+    --                , case mco of
+    --                     MCo co -> text "co" <+> ppr co
+    --                                  <+> dcolon <+> ppr (coercionKind co)
+    --                     MRefl  -> text "MRefl"
+    --                , callStackDoc ]) $
+    GRefl r ty mco
+
+mkGReflMCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion
+mkGReflMCo r ty co = mkGReflCo r ty (MCo co)
 
 -- | Compose two MCoercions via transitivity
 mkTransMCo :: MCoercion -> MCoercion -> MCoercion
@@ -1127,14 +1142,19 @@ mkSymCo co@(ForAllCo { fco_kind = kco, fco_body = body_co })
   | isReflCo kco           = co { fco_body = mkSymCo body_co }
 mkSymCo co                 = SymCo co
 
--- | Create a new 'Coercion' by composing the two given 'Coercion's transitively.
---   (co1 ; co2)
-mkTransCo :: Coercion -> Coercion -> Coercion
-mkTransCo co1 co2 | isReflCo co1 = co2
-                  | isReflCo co2 = co1
-mkTransCo (GRefl r t1 (MCo co1)) (GRefl _ _ (MCo co2))
-  = GRefl r t1 (MCo $ mkTransCo co1 co2)
-mkTransCo co1 co2                = TransCo co1 co2
+-- | mkTransCo creates a new 'Coercion' by composing the two
+--   given 'Coercion's transitively: (co1 ; co2)
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+mkTransCo co1 co2
+   | isReflCo co1 = co2
+   | isReflCo co2 = co1
+
+   | GRefl r t1 (MCo kco1) <- co1
+   , GRefl _ _  (MCo kco2) <- co2
+   = GRefl r t1 (MCo $ mkTransCo kco1 kco2)
+
+   | otherwise
+   = TransCo co1 co2
 
 --------------------
 {- Note [mkSelCo precondition]
@@ -1294,7 +1314,7 @@ mkGReflRightCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise = GRefl r ty (MCo co)
+  | otherwise = mkGReflMCo r ty co
 
 -- | Given @r@, @ty :: k1@, and @co :: k1 ~N k2@,
 -- produces @co' :: (ty |> co) ~r ty@
@@ -1303,7 +1323,7 @@ mkGReflLeftCo r ty co
   | isGReflCo co = mkReflCo r ty
     -- the kinds of @k1@ and @k2@ are the same, thus @isGReflCo@
     -- instead of @isReflCo@
-  | otherwise    = mkSymCo $ GRefl r ty (MCo co)
+  | otherwise    = mkSymCo $ mkGReflMCo r ty co
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty ~r ty'@,
 -- produces @co' :: (ty |> co) ~r ty'
@@ -1312,16 +1332,16 @@ mkGReflLeftCo r ty co
 mkCoherenceLeftCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceLeftCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = (mkSymCo $ GRefl r ty (MCo co)) `mkTransCo` co2
+  | otherwise    = (mkSymCo $ mkGReflMCo r ty co) `mkTransCo` co2
 
 -- | Given @ty :: k1@, @co :: k1 ~ k2@, @co2:: ty' ~r ty@,
 -- produces @co' :: ty' ~r (ty |> co)
 -- It is not only a utility function, but it saves allocation when co
 -- is a GRefl coercion.
-mkCoherenceRightCo :: Role -> Type -> CoercionN -> Coercion -> Coercion
+mkCoherenceRightCo :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
 mkCoherenceRightCo r ty co co2
   | isGReflCo co = co2
-  | otherwise    = co2 `mkTransCo` GRefl r ty (MCo co)
+  | otherwise    = co2 `mkTransCo` mkGReflMCo r ty co
 
 -- | Given @co :: (a :: k) ~ (b :: k')@ produce @co' :: k ~ k'@.
 mkKindCo :: Coercion -> Coercion
@@ -1680,8 +1700,8 @@ castCoercionKind1 g r t1 t2 h
                  mkNomReflCo (mkCastTy t2 h)
       GRefl _ _ mco -> case mco of
            MRefl       -> mkReflCo r (mkCastTy t2 h)
-           MCo kind_co -> GRefl r (mkCastTy t1 h) $
-                          MCo (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
+           MCo kind_co -> mkGReflMCo r (mkCastTy t1 h)
+                               (mkSymCo h `mkTransCo` kind_co `mkTransCo` h)
       _ -> castCoercionKind2 g r t1 t2 h h
 
 -- | Creates a new coercion with both of its types casted by different casts
@@ -2108,10 +2128,10 @@ zapLiftingContext :: LiftingContext -> LiftingContext
 zapLiftingContext (LC subst _) = LC (zapSubst subst) emptyVarEnv
 
 -- | Like 'substForAllCoBndr', but works on a lifting context
-substForAllCoBndrUsingLC :: Bool
-                            -> (Coercion -> Coercion)
-                            -> LiftingContext -> TyCoVar -> Coercion
-                            -> (LiftingContext, TyCoVar, Coercion)
+substForAllCoBndrUsingLC :: SwapFlag
+                         -> (Coercion -> Coercion)
+                         -> LiftingContext -> TyCoVar -> Coercion
+                         -> (LiftingContext, TyCoVar, Coercion)
 substForAllCoBndrUsingLC sym sco (LC subst lc_env) tv co
   = (LC subst' lc_env, tv', co')
   where
@@ -2658,7 +2678,7 @@ mkCoercionType Phantom          = \ty1 ty2 ->
 -- transitivity over coercion applications, where splitting two
 -- AppCos might yield different kinds. See Note [EtaAppCo] in
 -- "GHC.Core.Coercion.Opt".
-buildCoercion :: Type -> Type -> CoercionN
+buildCoercion :: HasDebugCallStack => Type -> Type -> CoercionN
 buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
   where
     go ty1 ty2 | Just ty1' <- coreView ty1 = go ty1' ty2
@@ -2686,7 +2706,10 @@ buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
         mkFunCo Nominal af1 (go w1 w2) (go arg1 arg2) (go res1 res2)
 
     go (TyConApp tc1 args1) (TyConApp tc2 args2)
-      = assert (tc1 == tc2) $
+      = assertPpr (tc1 == tc2) (vcat [ ppr tc1 <+> ppr tc2
+                                     , text "orig_ty1:" <+> ppr orig_ty1
+                                     , text "orig_ty2:" <+> ppr orig_ty2
+                                     ]) $
         mkTyConAppCo Nominal tc1 (zipWith go args1 args2)
 
     go (AppTy ty1a ty1b) ty2


=====================================
compiler/GHC/Core/Coercion.hs-boot
=====================================
@@ -24,7 +24,7 @@ mkCoVarCo :: CoVar -> Coercion
 mkPhantomCo :: Coercion -> Type -> Type -> Coercion
 mkUnivCo :: UnivCoProvenance -> [Coercion] -> Role -> Type -> Type -> Coercion
 mkSymCo :: Coercion -> Coercion
-mkTransCo :: Coercion -> Coercion -> Coercion
+mkTransCo :: HasDebugCallStack => Coercion -> Coercion -> Coercion
 mkSelCo :: HasDebugCallStack => CoSel -> Coercion -> Coercion
 mkLRCo :: LeftOrRight -> Coercion -> Coercion
 mkInstCo :: Coercion -> Coercion -> Coercion


=====================================
compiler/GHC/Core/Coercion/Opt.hs
=====================================
@@ -21,6 +21,7 @@ import GHC.Core.TyCon
 import GHC.Core.Coercion.Axiom
 import GHC.Core.Unify
 
+import GHC.Types.Basic( SwapFlag(..), flipSwap, isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -66,32 +67,55 @@ opt_co2.
 
 Note [Optimising InstCo]
 ~~~~~~~~~~~~~~~~~~~~~~~~
-(1) tv is a type variable
-When we have (InstCo (ForAllCo tv h g) g2), we want to optimise.
+Optimising InstCo is pretty subtle: #15725, #25387.
 
-Let's look at the typing rules.
+(1) tv is a type variable. We want to optimise
 
-h : k1 ~ k2
-tv:k1 |- g : t1 ~ t2
------------------------------
-ForAllCo tv h g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym h])
+  InstCo (ForAllCo tv kco g) g2  -->   S(g)
 
-g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
-g2 : s1 ~ s2
---------------------
-InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+where S is some substitution. Let's look at the typing rules.
 
-We thus want some coercion proving this:
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    -----------------------------
+    ForAllCo tv kco g : (all tv:k1.t1) ~ (all tv:k2.t2[tv |-> tv |> sym kco])
+
+    g1 : (all tv:k1.t1') ~ (all tv:k2.t2')
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo g1 g2 : t1'[tv |-> s1] ~ t2'[tv |-> s2]
+
+Putting these two together
 
-  (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym h])
+    kco : k1 ~ k2
+    tv:k1 |- g : t1 ~ t2
+    g2 : (s1:k1) ~ (s2:k2)
+    --------------------
+    InstCo (ForAllCo tv kco g) g2 : t1[tv |-> s1] ~ t2[tv |-> s2 |> sym kco]
 
-If we substitute the *type* tv for the *coercion*
-(g2 ; t2 ~ t2 |> sym h) in g, we'll get this result exactly.
-This is bizarre,
-though, because we're substituting a type variable with a coercion. However,
-this operation already exists: it's called *lifting*, and defined in GHC.Core.Coercion.
-We just need to enhance the lifting operation to be able to deal with
-an ambient substitution, which is why a LiftingContext stores a TCvSubst.
+We thus want S(g) to have kind
+
+  S(g) :: (t1[tv |-> s1]) ~ (t2[tv |-> s2 |> sym kco])
+
+All we need do is to substitute the coercion tv_co for tv:
+  S = [tv :-> tv_co]
+where
+  tv_co : s1 ~ (s2 |> sym kco)
+This looks bizarre, because we're substituting a /type variable/ with a
+/coercion/. However, this operation already exists: it's called *lifting*, and
+defined in GHC.Core.Coercion.  We just need to enhance the lifting operation to
+be able to deal with an ambient substitution, which is why a LiftingContext
+stores a TCvSubst.
+
+In general if
+  S = [tv :-> tv_co]
+  tv_co : r1 ~ r2
+  g     : t1 ~ t2
+then
+  S(g) : t1[tv :-> r1] ~ t2[tv :-> r2]
+
+The substitution S is embodied in the LiftingContext argument of `opt_co4`;
+See Note [The LiftingContext in optCoercion]
 
 (2) cv is a coercion variable
 Now consider we have (InstCo (ForAllCo cv h g) g2), we want to optimise.
@@ -117,6 +141,27 @@ We thus want some coercion proving this:
 
 So we substitute the coercion variable c for the coercion
 (h1 ~N (n1; h2; sym n2)) in g.
+
+Note [The LiftingContext in optCoercion]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+To suppport Note [Optimising InstCo] the coercion optimiser carries a
+GHC.Core.Coercion.LiftingContext, which comprises
+  * An ordinary Subst
+  * The `lc_env`: a mapping from /type variables/ to /coercions/
+
+We don't actually have a separate function
+   liftCoSubstCo :: LiftingContext -> Coercion -> Coercion
+The substitution of a type variable by a coercion is done by the calls to
+`liftCoSubst` (on a type) in the Refl and GRefl cases of `opt_co4`.
+
+We use the following invariants:
+ (LC1) The coercions in the range of `lc_env` have already had all substitutions
+       applied; they are "OutCoercions".  If you re-optimise these coercions, you
+       must zap the LiftingContext first.
+
+ (LC2) However they have /not/ had the "ambient sym" (the second argument of
+       `opt_co4`) applied.  The ambient sym applies to the entire coercion not
+       to the little bits being substituted.
 -}
 
 -- | Coercion optimisation options
@@ -147,7 +192,7 @@ optCoercion opts env co
 optCoercion' :: Subst -> Coercion -> NormalCo
 optCoercion' env co
   | debugIsOn
-  = let out_co = opt_co1 lc False co
+  = let out_co = opt_co1 lc NotSwapped co
         (Pair in_ty1  in_ty2,  in_role)  = coercionKindRole co
         (Pair out_ty1 out_ty2, out_role) = coercionKindRole out_co
 
@@ -170,7 +215,7 @@ optCoercion' env co
     out_co
 
   | otherwise
-  = opt_co1 lc False co
+  = opt_co1 lc NotSwapped co
   where
     lc = mkSubstLiftingContext env
 --    ppr_one cv = ppr cv <+> dcolon <+> ppr (coVarKind cv)
@@ -184,41 +229,38 @@ type NormalCo    = Coercion
 
 type NormalNonIdCo = NormalCo  -- Extra invariant: not the identity
 
--- | Do we apply a @sym@ to the result?
-type SymFlag = Bool
-
 -- | Do we force the result to be representational?
 type ReprFlag = Bool
 
 -- | Optimize a coercion, making no assumptions. All coercions in
 -- the lifting context are already optimized (and sym'd if nec'y)
 opt_co1 :: LiftingContext
-        -> SymFlag
+        -> SwapFlag   -- IsSwapped => apply Sym to the result
         -> Coercion -> NormalCo
 opt_co1 env sym co = opt_co2 env sym (coercionRole co) co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's role. No other assumptions.
 opt_co2 :: LiftingContext
-        -> SymFlag
-        -> Role   -- ^ The role of the input coercion
+        -> SwapFlag   -- ^IsSwapped => apply Sym to the result
+        -> Role       -- ^ The role of the input coercion
         -> Coercion -> NormalCo
 opt_co2 env sym Phantom co = opt_phantom env sym co
-opt_co2 env sym r       co = opt_co4_wrap env sym False r co
+opt_co2 env sym r       co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a coercion, knowing the coercion's non-Phantom role,
 --   and with an optional downgrade
-opt_co3 :: LiftingContext -> SymFlag -> Maybe Role -> Role -> Coercion -> NormalCo
+opt_co3 :: LiftingContext -> SwapFlag -> Maybe Role -> Role -> Coercion -> NormalCo
 opt_co3 env sym (Just Phantom)          _ co = opt_phantom env sym co
-opt_co3 env sym (Just Representational) r co = opt_co4_wrap env sym True  r co
+opt_co3 env sym (Just Representational) r co = opt_co4 env sym True  r co
   -- if mrole is Just Nominal, that can't be a downgrade, so we can ignore
-opt_co3 env sym _                       r co = opt_co4_wrap env sym False r co
+opt_co3 env sym _                       r co = opt_co4 env sym False r co
 
 -- See Note [Optimising coercion optimisation]
 -- | Optimize a non-phantom coercion.
-opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
-                      -> Role -> Coercion -> NormalCo
+opt_co4, opt_co4' :: LiftingContext -> SwapFlag -> ReprFlag
+                  -> Role -> Coercion -> NormalCo
 -- Precondition:  In every call (opt_co4 lc sym rep role co)
 --                we should have role = coercionRole co
 -- Precondition:  role is not Phantom
@@ -227,20 +269,20 @@ opt_co4, opt_co4_wrap :: LiftingContext -> SymFlag -> ReprFlag
 --                 where wrapsym is SymCo if sym=True
 --                       wrapsub is SubCo if rep=True
 
--- opt_co4_wrap is there just to support tracing, when debugging
--- Usually it just goes straight to opt_co4
-opt_co4_wrap = opt_co4
+-- opt_co4 is there just to support tracing, when debugging
+-- Usually it just goes straight to opt_co4'
+opt_co4 = opt_co4'
 
 {-
-opt_co4_wrap env sym rep r co
-  = pprTrace "opt_co4_wrap {"
+opt_co4 env sym rep r co
+  = pprTrace "opt_co4 {"
    ( vcat [ text "Sym:" <+> ppr sym
           , text "Rep:" <+> ppr rep
           , text "Role:" <+> ppr r
           , text "Co:" <+> ppr co ]) $
    assert (r == coercionRole co )    $
-   let result = opt_co4 env sym rep r co in
-   pprTrace "opt_co4_wrap }" (ppr co $$ text "---" $$ ppr result) $
+   let result = opt_co4' env sym rep r co in
+   pprTrace "opt_co4 }" (ppr co $$ text "---" $$ ppr result) $
    assertPpr (res_role == coercionRole result)
              (vcat [ text "Role:" <+> ppr r
                    , text "Result: " <+>  ppr result
@@ -252,40 +294,45 @@ opt_co4_wrap env sym rep r co
              | otherwise = r
 -}
 
-opt_co4 env _   rep r (Refl ty)
+opt_co4' env sym rep r (Refl ty)
   = assertPpr (r == Nominal)
               (text "Expected role:" <+> ppr r    $$
                text "Found role:" <+> ppr Nominal $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env _   rep r (GRefl _r ty MRefl)
+opt_co4' env sym rep r (GRefl _r ty MRefl)
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    liftCoSubst (chooseRole rep r) env ty
+    wrapSym sym $ liftCoSubst (chooseRole rep r) env ty
+        -- wrapSym: see (LC2) of Note [The LiftingContext in optCoercion]
 
-opt_co4 env sym  rep r (GRefl _r ty (MCo co))
+opt_co4' env sym  rep r (GRefl _r ty (MCo kco))
   = assertPpr (r == _r)
               (text "Expected role:" <+> ppr r $$
                text "Found role:" <+> ppr _r   $$
                text "Type:" <+> ppr ty) $
-    if isGReflCo co || isGReflCo co'
-    then liftCoSubst r' env ty
-    else wrapSym sym $ mkCoherenceRightCo r' ty' co' (liftCoSubst r' env ty)
+    if isGReflCo kco || isGReflCo kco'
+    then wrapSym sym ty_co
+    else wrapSym sym $ mk_coherence_right_co r' (coercionRKind ty_co) kco' ty_co
+            -- ty :: k1
+            -- kco :: k1 ~ k2
+            -- Desired result coercion:   ty ~ ty |> co
   where
-    r'  = chooseRole rep r
-    ty' = substTy (lcSubstLeft env) ty
-    co' = opt_co4 env False False Nominal co
+    r'    = chooseRole rep r
+    ty_co = liftCoSubst r' env ty
+    kco'  = opt_co4 env NotSwapped False Nominal kco
 
-opt_co4 env sym rep r (SymCo co)  = opt_co4_wrap env (not sym) rep r co
+opt_co4' env sym rep r (SymCo co)  = opt_co4 env (flipSwap sym) rep r co
   -- surprisingly, we don't have to do anything to the env here. This is
   -- because any "lifting" substitutions in the env are tied to ForAllCos,
   -- which treat their left and right sides differently. We don't want to
   -- exchange them.
 
-opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
+opt_co4' env sym rep r g@(TyConAppCo _r tc cos)
   = assert (r == _r) $
     case (rep, r) of
       (True, Nominal) ->
@@ -295,7 +342,7 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                (repeat Nominal)
                                cos)
       (False, Nominal) ->
-        mkTyConAppCo Nominal tc (map (opt_co4_wrap env sym False Nominal) cos)
+        mkTyConAppCo Nominal tc (map (opt_co4 env sym False Nominal) cos)
       (_, Representational) ->
                       -- must use opt_co2 here, because some roles may be P
                       -- See Note [Optimising coercion optimisation]
@@ -304,34 +351,35 @@ opt_co4 env sym rep r g@(TyConAppCo _r tc cos)
                                    cos)
       (_, Phantom) -> pprPanic "opt_co4 sees a phantom!" (ppr g)
 
-opt_co4 env sym rep r (AppCo co1 co2)
-  = mkAppCo (opt_co4_wrap env sym rep r co1)
-            (opt_co4_wrap env sym False Nominal co2)
+opt_co4' env sym rep r (AppCo co1 co2)
+  = mkAppCo (opt_co4 env sym rep r co1)
+            (opt_co4 env sym False Nominal co2)
 
-opt_co4 env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
+opt_co4' env sym rep r (ForAllCo { fco_tcv = tv, fco_visL = visL, fco_visR = visR
                                 , fco_kind = k_co, fco_body = co })
   = case optForAllCoBndr env sym tv k_co of
       (env', tv', k_co') -> mkForAllCo tv' visL' visR' k_co' $
-                            opt_co4_wrap env' sym rep r co
+                            opt_co4 env' sym rep r co
      -- Use the "mk" functions to check for nested Refls
   where
     !(visL', visR') = swapSym sym (visL, visR)
 
-opt_co4 env sym rep r (FunCo _r afl afr cow co1 co2)
+opt_co4' env sym rep r (FunCo _r afl afr cow co1 co2)
   = assert (r == _r) $
     mkFunCo2 r' afl' afr' cow' co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     cow' = opt_co1 env sym cow
     !r' | rep       = Representational
         | otherwise = r
     !(afl', afr') = swapSym sym (afl, afr)
 
-opt_co4 env sym rep r (CoVarCo cv)
+opt_co4' env sym rep r (CoVarCo cv)
   | Just co <- lcLookupCoVar env cv   -- see Note [Forall over coercion] for why
                                       -- this is the right thing here
-  = opt_co4_wrap (zapLiftingContext env) sym rep r co
+  = -- pprTrace "CoVarCo" (ppr cv $$ ppr co) $
+    opt_co4 (zapLiftingContext env) sym rep r co
 
   | ty1 `eqType` ty2   -- See Note [Optimise CoVarCo to Refl]
   = mkReflCo (chooseRole rep r) ty1
@@ -352,10 +400,10 @@ opt_co4 env sym rep r (CoVarCo cv)
                           cv
           -- cv1 might have a substituted kind!
 
-opt_co4 _ _ _ _ (HoleCo h)
+opt_co4' _ _ _ _ (HoleCo h)
   = pprPanic "opt_univ fell into a hole" (ppr h)
 
-opt_co4 env sym rep r (AxiomCo con cos)
+opt_co4' env sym rep r (AxiomCo con cos)
     -- Do *not* push sym inside top-level axioms
     -- e.g. if g is a top-level axiom
     --   g a : f a ~ a
@@ -365,25 +413,25 @@ opt_co4 env sym rep r (AxiomCo con cos)
     wrapSym sym $
                        -- some sub-cos might be P: use opt_co2
                        -- See Note [Optimising coercion optimisation]
-    AxiomCo con (zipWith (opt_co2 env False)
+    AxiomCo con (zipWith (opt_co2 env NotSwapped)
                          (coAxiomRuleArgRoles con)
                          cos)
       -- Note that the_co does *not* have sym pushed into it
 
-opt_co4 env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
+opt_co4' env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1
                               , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps (chooseRole rep r) t1 t2
 
-opt_co4 env sym rep r (TransCo co1 co2)
-                      -- sym (g `o` h) = sym h `o` sym g
-  | sym       = opt_trans in_scope co2' co1'
-  | otherwise = opt_trans in_scope co1' co2'
+opt_co4' env sym rep r (TransCo co1 co2)
+  -- sym (g `o` h) = sym h `o` sym g
+  | isSwapped sym = opt_trans in_scope co2' co1'
+  | otherwise     = opt_trans in_scope co1' co2'
   where
-    co1' = opt_co4_wrap env sym rep r co1
-    co2' = opt_co4_wrap env sym rep r co2
+    co1' = opt_co4 env sym rep r co1
+    co2' = opt_co4 env sym rep r co2
     in_scope = lcInScopeSet env
 
-opt_co4 env sym rep r (SelCo cs co)
+opt_co4' env sym rep r (SelCo cs co)
   -- Historical note 1: we used to check `co` for Refl, TyConAppCo etc
   -- before optimising `co`; but actually the SelCo will have been built
   -- with mkSelCo, so these tests always fail.
@@ -393,19 +441,19 @@ opt_co4 env sym rep r (SelCo cs co)
   -- and (b) wrapRole uses mkSubCo which does much the same job
   = wrapRole rep r $ mkSelCo cs $ opt_co1 env sym co
 
-opt_co4 env sym rep r (LRCo lr co)
+opt_co4' env sym rep r (LRCo lr co)
   | Just pr_co <- splitAppCo_maybe co
   = assert (r == Nominal )
-    opt_co4_wrap env sym rep Nominal (pick_lr lr pr_co)
+    opt_co4 env sym rep Nominal (pick_lr lr pr_co)
   | Just pr_co <- splitAppCo_maybe co'
   = assert (r == Nominal) $
     if rep
-    then opt_co4_wrap (zapLiftingContext env) False True Nominal (pick_lr lr pr_co)
+    then opt_co4 (zapLiftingContext env) NotSwapped True Nominal (pick_lr lr pr_co)
     else pick_lr lr pr_co
   | otherwise
   = wrapRole rep Nominal $ LRCo lr co'
   where
-    co' = opt_co4_wrap env sym False Nominal co
+    co' = opt_co4 env sym False Nominal co
 
     pick_lr CLeft  (l, _) = l
     pick_lr CRight (_, r) = r
@@ -445,66 +493,68 @@ So we extend the environment binding cv to arg's left-hand type.
 -}
 
 -- See Note [Optimising InstCo]
-opt_co4 env sym rep r (InstCo co1 arg)
+opt_co4' env sym rep r (InstCo fun_co arg_co)
     -- forall over type...
-  | Just (tv, _visL, _visR, kind_co, co_body) <- splitForAllCo_ty_maybe co1
-  = opt_co4_wrap (extendLiftingContext env tv
-                    (mkCoherenceRightCo Nominal t2 (mkSymCo kind_co) sym_arg))
-                   -- mkSymCo kind_co :: k1 ~ k2
-                   -- sym_arg :: (t1 :: k1) ~ (t2 :: k2)
-                   -- tv |-> (t1 :: k1) ~ (((t2 :: k2) |> (sym kind_co)) :: k1)
-                 sym rep r co_body
+  | Just (tv, _visL, _visR, k_co, body_co) <- splitForAllCo_ty_maybe fun_co
+    -- tv      :: k1
+    -- k_co    :: k1 ~ k2
+    -- body_co :: t1 ~ t2
+    -- arg_co  :: (s1:k1) ~ (s2:k2)
+  , let arg_co'  = opt_co4 env NotSwapped False Nominal arg_co
+                  -- Do /not/ push Sym into the arg_co, hence sym=False
+                  -- see (LC2) of Note [The LiftingContext in optCoercion]
+        k_co' = opt_co4 env NotSwapped False Nominal k_co
+        s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+                   -- mkSymCo kind_co :: k2 ~ k1
+                   -- tv_co   :: (s1 :: k1) ~ (((s2 :: k2) |> (sym kind_co)) :: k1)
+  = opt_co4 (extendLiftingContext env tv tv_co) sym rep r body_co
 
     -- See Note [Forall over coercion]
-  | Just (cv, _visL, _visR, _kind_co, co_body) <- splitForAllCo_co_maybe co1
-  , CoercionTy h1 <- t1
-  = opt_co4_wrap (extendLiftingContextCvSubst env cv h1) sym rep r co_body
+  | Just (cv, _visL, _visR, _kind_co, body_co) <- splitForAllCo_co_maybe fun_co
+  , CoercionTy h1 <- coercionLKind arg_co
+  , let h1' = opt_co4 env NotSwapped False Nominal h1
+  = opt_co4 (extendLiftingContextCvSubst env cv h1') sym rep r body_co
 
-    -- See if it is a forall after optimization
-    -- If so, do an inefficient one-variable substitution, then re-optimize
+  -- OK so those cases didn't work.  See if it is a forall /after/ optimization
+  -- If so, do an inefficient one-variable substitution, then re-optimize
 
     -- forall over type...
-  | Just (tv', _visL, _visR, kind_co', co_body') <- splitForAllCo_ty_maybe co1'
-  = opt_co4_wrap (extendLiftingContext (zapLiftingContext env) tv'
-                    (mkCoherenceRightCo Nominal t2' (mkSymCo kind_co') arg'))
-            False False r' co_body'
+  | Just (tv', _visL, _visR, k_co', body_co') <- splitForAllCo_ty_maybe fun_co'
+  , let s2'   = coercionRKind arg_co'
+        tv_co = mk_coherence_right_co Nominal s2' (mkSymCo k_co') arg_co'
+        env'  = extendLiftingContext (zapLiftingContext env) tv' tv_co
+  = opt_co4 env' NotSwapped False r' body_co'
 
     -- See Note [Forall over coercion]
-  | Just (cv', _visL, _visR, _kind_co', co_body') <- splitForAllCo_co_maybe co1'
-  , CoercionTy h1' <- t1'
-  = opt_co4_wrap (extendLiftingContextCvSubst (zapLiftingContext env) cv' h1')
-                    False False r' co_body'
+  | Just (cv', _visL, _visR, _kind_co', body_co') <- splitForAllCo_co_maybe fun_co'
+  , CoercionTy h1' <- coercionLKind arg_co'
+  , let env' = extendLiftingContextCvSubst (zapLiftingContext env) cv' h1'
+  = opt_co4 env' NotSwapped False r' body_co'
+
+  -- Those cases didn't work either, so rebuild the InstCo
+  -- Push Sym into /both/ function /and/ arg_coument
+  | otherwise = InstCo fun_co' arg_co'
 
-  | otherwise = InstCo co1' arg'
   where
-    co1'    = opt_co4_wrap env sym rep r co1
-    r'      = chooseRole rep r
-    arg'    = opt_co4_wrap env sym False Nominal arg
-    sym_arg = wrapSym sym arg'
-
-    -- Performance note: don't be alarmed by the two calls to coercionKind
-    -- here, as only one call to coercionKind is actually demanded per guard.
-    -- t1/t2 are used when checking if co1 is a forall, and t1'/t2' are used
-    -- when checking if co1' (i.e., co1 post-optimization) is a forall.
-    --
-    -- t1/t2 must come from sym_arg, not arg', since it's possible that arg'
-    -- might have an extra Sym at the front (after being optimized) that co1
-    -- lacks, so we need to use sym_arg to balance the number of Syms. (#15725)
-    Pair t1  t2  = coercionKind sym_arg
-    Pair t1' t2' = coercionKind arg'
-
-opt_co4 env sym _rep r (KindCo co)
+    -- fun_co' arg_co' are both optimised, /and/ we have pushed `sym` into both
+    -- So no more sym'ing on th results of fun_co' arg_co'
+    fun_co' = opt_co4 env sym rep r fun_co
+    arg_co' = opt_co4 env sym False Nominal arg_co
+    r'   = chooseRole rep r
+
+opt_co4' env sym _rep r (KindCo co)
   = assert (r == Nominal) $
     let kco' = promoteCoercion co in
     case kco' of
       KindCo co' -> promoteCoercion (opt_co1 env sym co')
-      _          -> opt_co4_wrap env sym False Nominal kco'
+      _          -> opt_co4 env sym False Nominal kco'
   -- This might be able to be optimized more to do the promotion
   -- and substitution/optimization at the same time
 
-opt_co4 env sym _ r (SubCo co)
+opt_co4' env sym _ r (SubCo co)
   = assert (r == Representational) $
-    opt_co4_wrap env sym True Nominal co
+    opt_co4 env sym True Nominal co
 
 {- Note [Optimise CoVarCo to Refl]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -518,7 +568,7 @@ in GHC.Core.Coercion.
 -------------
 -- | Optimize a phantom coercion. The input coercion may not necessarily
 -- be a phantom, but the output sure will be.
-opt_phantom :: LiftingContext -> SymFlag -> Coercion -> NormalCo
+opt_phantom :: LiftingContext -> SwapFlag -> Coercion -> NormalCo
 opt_phantom env sym (UnivCo { uco_prov = prov, uco_lty = t1
                             , uco_rty = t2, uco_deps = deps })
   = opt_univ env sym prov deps Phantom t1 t2
@@ -559,7 +609,7 @@ See #19509.
 
  -}
 
-opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance
+opt_univ :: LiftingContext -> SwapFlag -> UnivCoProvenance
          -> [Coercion]
          -> Role -> Type -> Type -> Coercion
 opt_univ env sym prov deps role ty1 ty2
@@ -640,11 +690,19 @@ opt_transList :: HasDebugCallStack => InScopeSet -> [NormalCo] -> [NormalCo] ->
 opt_transList is = zipWithEqual "opt_transList" (opt_trans is)
   -- The input lists must have identical length.
 
-opt_trans, opt_trans' :: InScopeSet -> NormalCo -> NormalCo -> NormalCo
+opt_trans :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 
 -- opt_trans just allows us to add some debug tracing
 -- Usually it just goes to opt_trans'
-opt_trans is co1 co2 = opt_trans' is co1 co2
+opt_trans is co1 co2
+  = -- (if coercionRKind co1 `eqType` coercionLKind co2
+    --  then (\x -> x) else
+    --  pprTrace "opt_trans" (vcat [ text "co1" <+> ppr co1
+    --                             , text "co2" <+> ppr co2
+    --                             , text "co1 kind" <+> ppr (coercionKind co1)
+    --                             , text "co2 kind" <+> ppr (coercionKind co2)
+    --                             , callStackDoc ])) $
+    opt_trans' is co1 co2
 
 {-
 opt_trans is co1 co2
@@ -658,19 +716,20 @@ opt_trans is co1 co2
     r2 = coercionRole co1
 -}
 
+opt_trans' :: HasDebugCallStack => InScopeSet -> NormalCo -> NormalCo -> NormalCo
 opt_trans' is co1 co2
   | isReflCo co1 = co2
     -- optimize when co1 is a Refl Co
   | otherwise    = opt_trans1 is co1 co2
 
-opt_trans1 :: InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
+opt_trans1 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalCo -> NormalCo
 -- First arg is not the identity
 opt_trans1 is co1 co2
   | isReflCo co2 = co1
     -- optimize when co2 is a Refl Co
   | otherwise    = opt_trans2 is co1 co2
 
-opt_trans2 :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
+opt_trans2 :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> NormalCo
 -- Neither arg is the identity
 opt_trans2 is (TransCo co1a co1b) co2
     -- Don't know whether the sub-coercions are the identity
@@ -687,16 +746,27 @@ opt_trans2 is co1 (TransCo co2a co2b)
     else opt_trans1 is co1_2a co2b
 
 opt_trans2 _ co1 co2
-  = mkTransCo co1 co2
+  = mk_trans_co co1 co2
+
 
 ------
 -- Optimize coercions with a top-level use of transitivity.
-opt_trans_rule :: InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
-
-opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _ (MCo co2))
+opt_trans_rule :: HasDebugCallStack => InScopeSet -> NormalNonIdCo -> NormalNonIdCo -> Maybe NormalCo
+
+opt_trans_rule _ in_co1 in_co2
+  | assertPpr (coercionRKind in_co1 `eqType` coercionLKind in_co2)
+              (vcat [ text "in_co1" <+> ppr in_co1
+                   , text "in_co2" <+> ppr in_co2
+                   , text "in_co1 kind" <+> ppr (coercionKind in_co1)
+                   , text "in_co2 kind" <+> ppr (coercionKind in_co2)
+                   , callStackDoc ]) $
+    False
+  = panic "opt_trans_rule"  -- This entire equation is purely assertion checking
+
+opt_trans_rule is in_co1@(GRefl r1 t1 (MCo co1)) in_co2@(GRefl r2 _t2 (MCo co2))
   = assert (r1 == r2) $
     fireTransRule "GRefl" in_co1 in_co2 $
-    mkGReflRightCo r1 t1 (opt_trans is co1 co2)
+    mk_grefl_right_co r1 t1 (opt_trans is co1 co2)
 
 -- Push transitivity through matching destructors
 opt_trans_rule is in_co1@(SelCo d1 co1) in_co2@(SelCo d2 co2)
@@ -818,8 +888,8 @@ opt_trans_rule is co1 co2
       eta1' = downgradeRole role Nominal eta1
       n1   = mkSelCo (SelTyCon 2 role) eta1'
       n2   = mkSelCo (SelTyCon 3 role) eta1'
-      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mkTransCo`
-                                        (mkCoVarCo cv1) `mkTransCo` n2])
+      r2'  = substCo (zipCvSubst [cv2] [(mkSymCo n1) `mk_trans_co`
+                                        (mkCoVarCo cv1) `mk_trans_co` n2])
                     r2
 
 -- Push transitivity inside axioms
@@ -836,15 +906,15 @@ opt_trans_rule is co1 co2
   | Just (sym1, axr1, cos1) <- isAxiomCo_maybe co1
   , Just (sym2, axr2, cos2) <- isAxiomCo_maybe co2
   , axr1 == axr2
-  , sym1 == not sym2
+  , sym1 == flipSwap sym2
   , Just (tc, role, branch) <- coAxiomRuleBranch_maybe axr1
   , let qtvs   = coAxBranchTyVars branch ++ coAxBranchCoVars branch
         lhs    = mkTyConApp tc (coAxBranchLHS branch)
         rhs    = coAxBranchRHS branch
-        pivot_tvs = exactTyCoVarsOfType (if sym2 then rhs else lhs)
+        pivot_tvs = exactTyCoVarsOfType (pickSwap sym2 lhs rhs)
   , all (`elemVarSet` pivot_tvs) qtvs
   = fireTransRule "TrPushAxSym" co1 co2 $
-    if sym2
+    if isSwapped sym2
        -- TrPushAxSym
     then liftCoSubstWith role qtvs (opt_transList is cos1 (map mkSymCo cos2)) lhs
        -- TrPushSymAx
@@ -854,29 +924,29 @@ opt_trans_rule is co1 co2
   -- Note [Push transitivity inside newtype axioms only]
   -- TrPushSymAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , True <- sym
+  , isSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is (map mkSymCo cos2) cos1)
   = fireTransRule "TrPushSymAxR" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxR
   | Just (sym, axr, cos1) <- isAxiomCo_maybe co1
-  , False <- sym
+  , notSwapped sym
   , Just cos2 <- matchNewtypeBranch sym axr co2
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxR" co1 co2 newAxInst
 
   -- TrPushSymAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , True <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , isSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos2 (map mkSymCo cos1))
   = fireTransRule "TrPushSymAxL" co1 co2 $ SymCo newAxInst
 
   -- TrPushAxL
   | Just (sym, axr, cos2) <- isAxiomCo_maybe co2
-  , False <- sym
-  , Just cos1 <- matchNewtypeBranch (not sym) axr co1
+  , notSwapped sym
+  , Just cos1 <- matchNewtypeBranch (flipSwap sym) axr co1
   , let newAxInst = AxiomCo axr (opt_transList is cos1 cos2)
   = fireTransRule "TrPushAxL" co1 co2 newAxInst
 
@@ -926,7 +996,7 @@ opt_trans_rule_app is orig_co1 orig_co2 co1a co1bs co2a co2bs
 
         co2a'   = mkCoherenceLeftCo rt2a lt2a kcoa co2a
         co2bs'  = zipWith3 mkGReflLeftCo rt2bs lt2bs kcobs
-        co2bs'' = zipWith mkTransCo co2bs' co2bs
+        co2bs'' = zipWith mk_trans_co co2bs' co2bs
     in
     mkAppCos (opt_trans is co1a co2a')
              (zipWith (opt_trans is) co1bs co2bs'')
@@ -1108,13 +1178,13 @@ The problem described here was first found in dependent/should_compile/dynamic-p
 -}
 
 -----------
-swapSym :: SymFlag -> (a,a) -> (a,a)
-swapSym sym (x,y) | sym       = (y,x)
-                  | otherwise = (x,y)
+swapSym :: SwapFlag -> (a,a) -> (a,a)
+swapSym IsSwapped  (x,y) = (y,x)
+swapSym NotSwapped (x,y) = (x,y)
 
-wrapSym :: SymFlag -> Coercion -> Coercion
-wrapSym sym co | sym       = mkSymCo co
-               | otherwise = co
+wrapSym :: SwapFlag -> Coercion -> Coercion
+wrapSym IsSwapped  co = mkSymCo co
+wrapSym NotSwapped co = co
 
 -- | Conditionally set a role to be representational
 wrapRole :: ReprFlag
@@ -1132,15 +1202,15 @@ chooseRole True _ = Representational
 chooseRole _    r = r
 
 -----------
-isAxiomCo_maybe :: Coercion -> Maybe (SymFlag, CoAxiomRule, [Coercion])
+isAxiomCo_maybe :: Coercion -> Maybe (SwapFlag, CoAxiomRule, [Coercion])
 -- We don't expect to see nested SymCo; and that lets us write a simple,
 -- non-recursive function. (If we see a nested SymCo we'll just fail,
 -- which is ok.)
-isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (True, ax, cos)
-isAxiomCo_maybe (AxiomCo ax cos)         = Just (False, ax, cos)
+isAxiomCo_maybe (SymCo (AxiomCo ax cos)) = Just (IsSwapped,  ax, cos)
+isAxiomCo_maybe (AxiomCo ax cos)         = Just (NotSwapped, ax, cos)
 isAxiomCo_maybe _                        = Nothing
 
-matchNewtypeBranch :: Bool -- True = match LHS, False = match RHS
+matchNewtypeBranch :: SwapFlag -- IsSwapped = match LHS, NotSwapped = match RHS
                    -> CoAxiomRule
                    -> Coercion -> Maybe [Coercion]
 matchNewtypeBranch sym axr co
@@ -1151,7 +1221,7 @@ matchNewtypeBranch sym axr co
                , cab_lhs = lhs
                , cab_rhs = rhs } <- branch
   , Just subst <- liftCoMatch (mkVarSet qtvs)
-                              (if sym then (mkTyConApp tc lhs) else rhs)
+                              (pickSwap sym rhs (mkTyConApp tc lhs))
                               co
   , all (`isMappedByLC` subst) qtvs
   = zipWithM (liftCoSubstTyVar subst) roles qtvs
@@ -1228,7 +1298,7 @@ etaForAllCo_ty_maybe co
   , (role /= Nominal) || (vis1 `eqForAllVis` vis2)
   , let kind_co = mkSelCo SelForAll co
   = Just ( tv1, vis1, vis2, kind_co
-         , mkInstCo co (mkGReflRightCo Nominal (TyVarTy tv1) kind_co))
+         , mkInstCo co (mk_grefl_right_co Nominal (TyVarTy tv1) kind_co))
 
   | otherwise
   = Nothing
@@ -1251,8 +1321,8 @@ etaForAllCo_co_maybe co
         l_co     = mkCoVarCo cv1
         kind_co' = downgradeRole r Nominal kind_co
         r_co     = mkSymCo (mkSelCo (SelTyCon 2 r) kind_co')
-                   `mkTransCo` l_co
-                   `mkTransCo` mkSelCo (SelTyCon 3 r) kind_co'
+                   `mk_trans_co` l_co
+                   `mk_trans_co` mkSelCo (SelTyCon 3 r) kind_co'
     in Just ( cv1, vis1, vis2, kind_co
             , mkInstCo co (mkProofIrrelCo Nominal kind_co l_co r_co))
 
@@ -1329,7 +1399,55 @@ and these two imply
 
 -}
 
-optForAllCoBndr :: LiftingContext -> Bool
+optForAllCoBndr :: LiftingContext -> SwapFlag
                 -> TyCoVar -> Coercion -> (LiftingContext, TyCoVar, Coercion)
 optForAllCoBndr env sym
-  = substForAllCoBndrUsingLC sym (opt_co4_wrap env sym False Nominal) env
+  = substForAllCoBndrUsingLC sym (opt_co4 env sym False Nominal) env
+
+
+{- **********************************************************************
+%*                                                                      *
+       Assertion-checking versions of functions in Coercion.hs
+%*                                                                      *
+%********************************************************************* -}
+
+-- We can't check the assertions in the "main" functions of these
+-- functions, because the assertions don't hold during zonking.
+-- But they are fantastically helpful in finding bugs in the coercion
+-- optimiser itself, so I have copied them here with assertions.
+
+mk_trans_co :: HasDebugCallStack => Coercion -> Coercion -> Coercion
+-- Do assertion checking in mk_trans_co
+mk_trans_co co1 co2
+  = assertPpr (coercionRKind co1 `eqType` coercionLKind co2)
+              (vcat [ text "co1" <+> ppr co1
+                    , text "co2" <+> ppr co2
+                    , text "co1 kind" <+> ppr (coercionKind co1)
+                    , text "co2 kind" <+> ppr (coercionKind co2)
+                    , callStackDoc ]) $
+    mkTransCo co1 co2
+
+mk_coherence_right_co :: HasDebugCallStack => Role -> Type -> CoercionN -> Coercion -> Coercion
+mk_coherence_right_co r ty co co2
+  = assertGRefl ty co $
+    mkCoherenceRightCo r ty co co2
+
+assertGRefl :: HasDebugCallStack => Type -> Coercion -> r -> r
+assertGRefl ty co res
+  = assertPpr (typeKind ty `eqType` coercionLKind co)
+              (vcat [ pp_ty "ty" ty
+                    , pp_co "co" co
+                    , callStackDoc ]) $
+    res
+
+mk_grefl_right_co :: Role -> Type -> CoercionN -> Coercion
+mk_grefl_right_co r ty co
+  = assertGRefl ty co $
+    mkGReflRightCo r ty co
+
+pp_co :: String -> Coercion -> SDoc
+pp_co s co = text s <+> hang (ppr co) 2 (dcolon <+> ppr (coercionKind co))
+
+pp_ty :: String -> Type -> SDoc
+pp_ty s ty = text s <+> hang (ppr ty) 2 (dcolon <+> ppr (typeKind ty))
+


=====================================
compiler/GHC/Core/TyCo/Subst.hs
=====================================
@@ -68,6 +68,7 @@ import {-# SOURCE #-} GHC.Core ( CoreExpr )
 import GHC.Core.TyCo.Rep
 import GHC.Core.TyCo.FVs
 
+import GHC.Types.Basic( SwapFlag(..), isSwapped, pickSwap, notSwapped )
 import GHC.Types.Var
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
@@ -916,7 +917,7 @@ substDCoVarSet subst cvs = coVarsOfCosDSet $ map (substCoVar subst) $
 substForAllCoBndr :: Subst -> TyCoVar -> KindCoercion
                   -> (Subst, TyCoVar, Coercion)
 substForAllCoBndr subst
-  = substForAllCoBndrUsing False (substCo subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCo subst) subst
 
 -- | Like 'substForAllCoBndr', but disables sanity checks.
 -- The problems that the sanity checks in substCo catch are described in
@@ -926,10 +927,10 @@ substForAllCoBndr subst
 substForAllCoBndrUnchecked :: Subst -> TyCoVar -> KindCoercion
                            -> (Subst, TyCoVar, Coercion)
 substForAllCoBndrUnchecked subst
-  = substForAllCoBndrUsing False (substCoUnchecked subst) subst
+  = substForAllCoBndrUsing NotSwapped (substCoUnchecked subst) subst
 
 -- See Note [Sym and ForAllCo]
-substForAllCoBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoBndrUsing :: SwapFlag  -- Apply sym to binder?
                        -> (Coercion -> Coercion)  -- transformation to kind co
                        -> Subst -> TyCoVar -> KindCoercion
                        -> (Subst, TyCoVar, KindCoercion)
@@ -937,7 +938,7 @@ substForAllCoBndrUsing sym sco subst old_var
   | isTyVar old_var = substForAllCoTyVarBndrUsing sym sco subst old_var
   | otherwise       = substForAllCoCoVarBndrUsing sym sco subst old_var
 
-substForAllCoTyVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoTyVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> TyVar -> KindCoercion
                             -> (Subst, TyVar, KindCoercion)
@@ -946,10 +947,13 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
     ( Subst (in_scope `extendInScopeSet` new_var) idenv new_env cenv
     , new_var, new_kind_co )
   where
-    new_env | no_change && not sym = delVarEnv tenv old_var
-            | sym       = extendVarEnv tenv old_var $
-                          TyVarTy new_var `CastTy` new_kind_co
-            | otherwise = extendVarEnv tenv old_var (TyVarTy new_var)
+    new_env | no_change, notSwapped sym
+            = delVarEnv tenv old_var
+            | isSwapped sym
+            = extendVarEnv tenv old_var $
+              TyVarTy new_var `CastTy` new_kind_co
+            | otherwise
+            = extendVarEnv tenv old_var (TyVarTy new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -965,7 +969,7 @@ substForAllCoTyVarBndrUsing sym sco (Subst in_scope idenv tenv cenv) old_var old
 
     new_var  = uniqAway in_scope (setTyVarKind old_var new_ki1)
 
-substForAllCoCoVarBndrUsing :: Bool  -- apply sym to binder?
+substForAllCoCoVarBndrUsing :: SwapFlag  -- Apply sym to binder?
                             -> (Coercion -> Coercion)  -- transformation to kind co
                             -> Subst -> CoVar -> KindCoercion
                             -> (Subst, CoVar, KindCoercion)
@@ -975,8 +979,10 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     ( Subst (in_scope `extendInScopeSet` new_var) idenv tenv new_cenv
     , new_var, new_kind_co )
   where
-    new_cenv | no_change && not sym = delVarEnv cenv old_var
-             | otherwise = extendVarEnv cenv old_var (mkCoVarCo new_var)
+    new_cenv | no_change, notSwapped sym
+             = delVarEnv cenv old_var
+             | otherwise
+             = extendVarEnv cenv old_var (mkCoVarCo new_var)
 
     no_kind_change = noFreeVarsOfCo old_kind_co
     no_change = no_kind_change && (new_var == old_var)
@@ -987,8 +993,7 @@ substForAllCoCoVarBndrUsing sym sco (Subst in_scope idenv tenv cenv)
     Pair h1 h2 = coercionKind new_kind_co
 
     new_var       = uniqAway in_scope $ mkCoVar (varName old_var) new_var_type
-    new_var_type  | sym       = h2
-                  | otherwise = h1
+    new_var_type  = pickSwap sym h1 h2
 
 substCoVar :: Subst -> CoVar -> Coercion
 substCoVar (Subst _ _ _ cenv) cv


=====================================
compiler/GHC/Core/TyCo/Tidy.hs
=====================================
@@ -336,16 +336,18 @@ tidyCo env co
     go (AppCo co1 co2)       = (AppCo $! go co1) $! go co2
     go (ForAllCo tv visL visR h co)
       = ((((ForAllCo $! tvp) $! visL) $! visR) $! (go h)) $! (tidyCo envp co)
-                               where (envp, tvp) = tidyVarBndr env tv
+      where (envp, tvp) = tidyVarBndr env tv
             -- the case above duplicates a bit of work in tidying h and the kind
             -- of tv. But the alternative is to use coercionKind, which seems worse.
     go (FunCo r afl afr w co1 co2) = ((FunCo r afl afr $! go w) $! go co1) $! go co2
     go (CoVarCo cv)          = CoVarCo $! go_cv cv
     go (HoleCo h)            = HoleCo $! go_hole h
     go (AxiomCo ax cos)      = AxiomCo ax $ strictMap go cos
-    go co@(UnivCo { uco_lty  = t1, uco_rty = t2 })
-                             = co { uco_lty = tidyType env t1, uco_rty = tidyType env t2 }
-                               -- Don't bother to tidy the uco_deps field
+    go (UnivCo prov role t1 t2 cos)
+                             = ((UnivCo prov role
+                                $! tidyType env t1)
+                                $! tidyType env t2)
+                                $! strictMap go cos
     go (SymCo co)            = SymCo $! go co
     go (TransCo co1 co2)     = (TransCo $! go co1) $! go co2
     go (SelCo d co)          = SelCo d $! go co


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -580,7 +580,7 @@ expandTypeSynonyms ty
       -- substForAllCoBndrUsing, which is general enough to
       -- handle coercion optimization (which sometimes swaps the
       -- order of a coercion)
-    go_cobndr subst = substForAllCoBndrUsing False (go_co subst) subst
+    go_cobndr subst = substForAllCoBndrUsing NotSwapped (go_co subst) subst
 
 {- Notes on type synonyms
 ~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/HsToCore.hs
=====================================
@@ -784,7 +784,7 @@ mkUnsafeCoercePrimPair _old_id old_expr
              alpha_co = mkTyConAppCo Nominal tYPETyCon [mkCoVarCo rr_cv]
 
              -- x_co :: alpha ~R# beta
-             x_co = mkGReflCo Representational openAlphaTy (MCo alpha_co) `mkTransCo`
+             x_co = mkGReflMCo Representational openAlphaTy alpha_co `mkTransCo`
                     mkSubCo (mkCoVarCo ab_cv)
 
 


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -80,7 +80,7 @@ module GHC.Types.Basic (
         EP(..),
 
         DefMethSpec(..),
-        SwapFlag(..), flipSwap, unSwap, isSwapped,
+        SwapFlag(..), flipSwap, unSwap, notSwapped, isSwapped, pickSwap,
 
         CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
 
@@ -456,6 +456,7 @@ instance Outputable OneShotInfo where
 data SwapFlag
   = NotSwapped  -- Args are: actual,   expected
   | IsSwapped   -- Args are: expected, actual
+  deriving( Eq )
 
 instance Outputable SwapFlag where
   ppr IsSwapped  = text "Is-swapped"
@@ -469,6 +470,14 @@ isSwapped :: SwapFlag -> Bool
 isSwapped IsSwapped  = True
 isSwapped NotSwapped = False
 
+notSwapped :: SwapFlag -> Bool
+notSwapped NotSwapped = True
+notSwapped IsSwapped  = False
+
+pickSwap :: SwapFlag -> a -> a -> a
+pickSwap NotSwapped a _ = a
+pickSwap IsSwapped  _ b = b
+
 unSwap :: SwapFlag -> (a->a->b) -> a -> a -> b
 unSwap NotSwapped f a b = f a b
 unSwap IsSwapped  f a b = f b a


=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,108 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Consider the generalized version of so-called @repmin@
+-- (/replace with minimum/) problem:
+-- accumulate elements of a container into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Functor t, Foldable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above makes two traversals. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkök, , Oregon Graduate Institute, 2002.
+-- * Levent Erkök, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),


=====================================
testsuite/tests/dependent/should_compile/T25387.hs
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE GHC2024 #-}
+{-# LANGUAGE TypeFamilies #-}
+module Bug (f) where
+
+import Data.Kind (Type)
+import Data.Type.Equality (type (~~))
+
+type Promote :: Type -> Type
+type family Promote k
+
+type PromoteX :: k -> Promote k
+type family PromoteX a
+
+type Demote :: Type -> Type
+type family Demote (k :: Type) :: Type
+
+type DemoteX :: k -> Demote k
+type family DemoteX a
+
+type HEq :: j -> k -> Type
+data HEq a b where
+  HRefl :: forall j (a :: j). HEq a a
+
+type SHEq :: forall j k (a :: j) (b :: k). HEq a b -> Type
+data SHEq heq where
+  SHRefl :: forall j (a :: j). SHEq (HRefl @j @a)
+
+type SomeSHEq :: j -> k -> Type
+data SomeSHEq a b where
+  SomeSHEq :: forall j k (a :: j) (b :: k) (heq :: HEq a b). SHEq heq -> SomeSHEq a b
+
+f :: forall j k (a :: j) (b :: k).
+     (PromoteX (DemoteX a) ~~ a, PromoteX (DemoteX b) ~~ b) =>
+     HEq (DemoteX a) (DemoteX b) ->
+     SomeSHEq a b
+f HRefl = SomeSHEq SHRefl


=====================================
testsuite/tests/dependent/should_compile/all.T
=====================================
@@ -63,3 +63,4 @@ test('T16347', normal, compile, [''])
 test('T18660', normal, compile, [''])
 test('T12174', normal, compile, [''])
 test('LopezJuan', normal, compile, [''])
+test('T25387', normal, compile, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b07d660fa52af029eb1291b305fa9fac53f409b8...aa9ddd4c2961eeed323e09c68436e8c7dfdbcc9b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b07d660fa52af029eb1291b305fa9fac53f409b8...aa9ddd4c2961eeed323e09c68436e8c7dfdbcc9b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 18:43:50 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Sat, 26 Oct 2024 14:43:50 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-safari-wasm-warning
Message-ID: <671d386665aba_3b48112ff800105068@gitlab.mail>



Cheng Shao pushed new branch wip/fix-safari-wasm-warning at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-safari-wasm-warning
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 19:40:35 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Sat, 26 Oct 2024 15:40:35 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/text-2.1.2
Message-ID: <671d45b35877a_3b48115e0da8111284@gitlab.mail>



Bodigrim pushed new branch wip/text-2.1.2 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/text-2.1.2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sat Oct 26 22:26:12 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Sat, 26 Oct 2024 18:26:12 -0400
Subject: [Git][ghc/ghc][wip/text-2.1.2] hadrian: allow -Wunused-imports for
 text package
Message-ID: <671d6c84bbcad_3b4811b85f241238c@gitlab.mail>



Bodigrim pushed to branch wip/text-2.1.2 at Glasgow Haskell Compiler / GHC


Commits:
d3ad95e6 by Andrew Lelechenko at 2024-10-26T23:26:06+01:00
hadrian: allow -Wunused-imports for text package

- - - - -


1 changed file:

- hadrian/src/Settings/Warnings.hs


Changes:

=====================================
hadrian/src/Settings/Warnings.hs
=====================================
@@ -66,7 +66,9 @@ ghcWarningsArgs = do
         , package primitive    ? pure [ "-Wno-unused-imports"
                                       , "-Wno-deprecations" ]
         , package rts          ? pure [ "-Wcpp-undef" ]
-        , package text         ? pure [ "-Wno-deprecations", "-Wno-deriving-typeable" ]
+        , package text         ? pure [ "-Wno-deprecations"
+                                      , "-Wno-deriving-typeable"
+                                      , "-Wno-unused-imports" ]
         , package terminfo     ? pure [ "-Wno-unused-imports", "-Wno-deriving-typeable" ]
         , package stm          ? pure [ "-Wno-deriving-typeable" ]
         , package osString     ? pure [ "-Wno-deriving-typeable" ]



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 01:17:23 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sat, 26 Oct 2024 21:17:23 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: ghcid: use
 multi repl for ghcid
Message-ID: <671d94a3e387c_19b7a5bc91c772ec@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
10df22da by Cheng Shao at 2024-10-26T21:16:25-04:00
ghcid: use multi repl for ghcid

- - - - -
9cc8c99f by Andrew Lelechenko at 2024-10-26T21:16:25-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
7ea6165a by Cheng Shao at 2024-10-26T21:16:25-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -


3 changed files:

- .ghcid
- libraries/base/src/Control/Monad/Fix.hs
- utils/jsffi/prelude.mjs


Changes:

=====================================
.ghcid
=====================================
@@ -1,5 +1,5 @@
---command sh -c "HADRIAN_ARGS=-j ./hadrian/ghci -j"
+--command sh -c "HADRIAN_ARGS=-j exec ./hadrian/ghci-multi -j"
 --reload compiler
 --reload ghc
 --reload includes
---restart hadrian/ghci
+--restart hadrian/ghci-multi


=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,108 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Consider the generalized version of so-called @repmin@
+-- (/replace with minimum/) problem:
+-- accumulate elements of a container into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Functor t, Foldable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above makes two traversals. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkök, , Oregon Graduate Institute, 2002.
+-- * Levent Erkök, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),


=====================================
utils/jsffi/prelude.mjs
=====================================
@@ -58,9 +58,9 @@ const setImmediate = await (async () => {
   }
 
   // deno
-  try {
+  if (globalThis.Deno) {
     return (await import("node:timers")).setImmediate;
-  } catch {}
+  }
 
   // https://developer.mozilla.org/en-US/docs/Web/API/Scheduler/postTask
   if (globalThis.scheduler) {



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa9ddd4c2961eeed323e09c68436e8c7dfdbcc9b...7ea6165aadff1d9954b9d351461b1b9c7b48bb45

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa9ddd4c2961eeed323e09c68436e8c7dfdbcc9b...7ea6165aadff1d9954b9d351461b1b9c7b48bb45
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 09:37:12 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 05:37:12 -0400
Subject: [Git][ghc/ghc][master] ghcid: use multi repl for ghcid
Message-ID: <671e09c86f2f6_2f05a9116ad4708b5@gitlab.mail>



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


Commits:
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -


1 changed file:

- .ghcid


Changes:

=====================================
.ghcid
=====================================
@@ -1,5 +1,5 @@
---command sh -c "HADRIAN_ARGS=-j ./hadrian/ghci -j"
+--command sh -c "HADRIAN_ARGS=-j exec ./hadrian/ghci-multi -j"
 --reload compiler
 --reload ghc
 --reload includes
---restart hadrian/ghci
+--restart hadrian/ghci-multi



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/589fea7f1035970f515d422e6956d7d09d363f8f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 09:37:43 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 05:37:43 -0400
Subject: [Git][ghc/ghc][master] documentation: add motivating section to
 Control.Monad.Fix
Message-ID: <671e09e78bc37_2f05a92a11d873959@gitlab.mail>



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


Commits:
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -


1 changed file:

- libraries/base/src/Control/Monad/Fix.hs


Changes:

=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,108 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Consider the generalized version of so-called @repmin@
+-- (/replace with minimum/) problem:
+-- accumulate elements of a container into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Functor t, Foldable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above makes two traversals. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkök, , Oregon Graduate Institute, 2002.
+-- * Levent Erkök, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 09:38:28 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 05:38:28 -0400
Subject: [Git][ghc/ghc][master] wasm: fix safari console error message related
 to import("node:timers")
Message-ID: <671e0a14668ce_2f05a9116c3c768ce@gitlab.mail>



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


Commits:
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -


1 changed file:

- utils/jsffi/prelude.mjs


Changes:

=====================================
utils/jsffi/prelude.mjs
=====================================
@@ -58,9 +58,9 @@ const setImmediate = await (async () => {
   }
 
   // deno
-  try {
+  if (globalThis.Deno) {
     return (await import("node:timers")).setImmediate;
-  } catch {}
+  }
 
   // https://developer.mozilla.org/en-US/docs/Web/API/Scheduler/postTask
   if (globalThis.scheduler) {



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/301c3b541de825b76cff59c739a8797b64321d1a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 10:31:16 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Sun, 27 Oct 2024 06:31:16 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Concentrate boot extension logic in
 Finder
Message-ID: <671e16748fea2_200dd81c4d149006f@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
21154a5d by Sjoerd Visscher at 2024-10-27T11:31:04+01:00
Concentrate boot extension logic in Finder

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Location.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -854,16 +854,14 @@ hsModuleToModSummary home_keys pn hsc_src modname
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation fopts modname
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
-                              (case hsc_src of
+                             (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
+                             hsc_src
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2123,31 +2123,16 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = unsafeEncodeUtf src_fn
+            (basename, extension) = splitExtension src_fn
 
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
+            hsc_src
+              | isHaskellSigSuffix (drop 1 extension) = HsigFile
+              | isHaskellBootSuffix (drop 1 extension) = HsBootFile
+              | otherwise = HsSrcFile
 
             -- Make a ModLocation for this file, adding the @-boot@ suffix to
             -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf extension) hsc_src
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
@@ -2239,7 +2224,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2242,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2252,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env imp is_boot pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Phases.hs
=====================================
@@ -23,6 +23,7 @@ module GHC.Driver.Phases (
    isDynLibSuffix,
    isHaskellUserSrcSuffix,
    isHaskellSigSuffix,
+   isHaskellBootSuffix,
    isSourceSuffix,
 
    isHaskellishTarget,
@@ -247,7 +248,8 @@ js_suffixes                  = [ "js" ]
 
 -- Will not be deleted as temp files:
 haskellish_user_src_suffixes =
-  haskellish_sig_suffixes ++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+  haskellish_sig_suffixes ++ haskellish_boot_suffixes ++ [ "hs", "lhs" ]
+haskellish_boot_suffixes     = [ "hs-boot", "lhs-boot" ]
 haskellish_sig_suffixes      = [ "hsig", "lhsig" ]
 backpackish_suffixes         = [ "bkp" ]
 
@@ -270,6 +272,7 @@ isHaskellishSuffix, isBackpackishSuffix, isHaskellSrcSuffix, isCishSuffix,
 isHaskellishSuffix     s = s `elem` haskellish_suffixes
 isBackpackishSuffix    s = s `elem` backpackish_suffixes
 isHaskellSigSuffix     s = s `elem` haskellish_sig_suffixes
+isHaskellBootSuffix    s = s `elem` haskellish_boot_suffixes
 isHaskellSrcSuffix     s = s `elem` haskellish_src_suffixes
 isCishSuffix           s = s `elem` cish_suffixes
 isJsSuffix             s = s `elem` js_suffixes


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,18 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+    let location1 = mkHomeModLocation fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) src_flavour
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -807,11 +801,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
         location5 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
     return location5
     where
       fopts = initFinderOpts dflags


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -896,9 +896,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,6 +15,7 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
@@ -157,6 +158,13 @@ findImportedModule hsc_env mod pkg_qual =
   in do
     findImportedModuleNoHsc fc fopts (hsc_unit_env hsc_env) mhome_unit mod pkg_qual
 
+findImportedModuleWithIsBoot :: HscEnv -> ModuleName -> IsBootInterface -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod is_boot pkg_qual = do
+  res <- findImportedModule hsc_env mod pkg_qual
+  case (res, is_boot) of
+    (Found loc mod, IsBoot) -> return (Found (addBootSuffixLocn loc) mod)
+    _ -> return res
+
 findImportedModuleNoHsc
   :: FinderCache
   -> FinderOpts
@@ -229,15 +237,19 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
-  case mhome_unit of
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
+  res <- case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
         -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
         -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
     _ -> findPackageModule fc unit_state fopts mod
+  case (res, is_boot) of
+    (InstalledFound loc, IsBoot) -> return (InstalledFound (addBootSuffixLocn loc))
+    _ -> return res
+
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -592,10 +604,12 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
-mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
-   in mkHomeModLocation2 dflags mod basename extension
+mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> FileExt -> HscSource -> ModLocation
+mkHomeModLocation dflags mod src_basename ext hsc_src =
+   let loc = mkHomeModLocation2 dflags mod src_basename ext
+   in case hsc_src of
+     HsBootFile -> addBootSuffixLocnOut loc
+     _ -> loc
 
 mkHomeModLocation2 :: FinderOpts
                    -> ModuleName


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,8 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
    , addBootSuffixLocn
    , addBootSuffixLocnOut
    , removeBootSuffix
@@ -25,7 +23,6 @@ where
 import GHC.Prelude
 
 import GHC.Data.OsPath
-import GHC.Unit.Types
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Data.FastString (mkFastString)
@@ -99,26 +96,10 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
 -- | Add the @-boot@ suffix to all file paths associated with the module
 addBootSuffixLocn :: ModLocation -> ModLocation
 addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
+  = addBootSuffixLocnOut locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) }
 
 -- | Add the @-boot@ suffix to all output file paths associated with the
 -- module, not including the input file itself



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/21154a5d93f25af7a2848b4a73c8392c839b787f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 11:21:55 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 27 Oct 2024 07:21:55 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-8] EPA: Remove AddEpAnn. 
 Final removal
Message-ID: <671e2253ac5e8_200dd84286009263a@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC


Commits:
9c81da55 by Alan Zimmerman at 2024-10-27T11:20:22+00:00
EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -


6 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- testsuite/tests/parser/should_compile/T15279.stderr
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Utils.hs


Changes:

=====================================
compiler/GHC/Hs/Dump.hs
=====================================
@@ -73,7 +73,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
               `extQ` annotationNoEpAnns
               `extQ` annotationExprBracket
               `extQ` annotationTypedBracket
-              `extQ` addEpAnn
               `extQ` epTokenOC
               `extQ` epTokenCC
               `extQ` epTokenInstance
@@ -270,13 +269,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
                                  showAstData' d, showAstData' e]
 
 
-            addEpAnn :: AddEpAnn -> SDoc
-            addEpAnn (AddEpAnn a s) = case ba of
-             BlankEpAnnotations -> parens
-                                      $ text "blanked:" <+> text "AddEpAnn"
-             NoBlankEpAnnotations ->
-              parens $ text "AddEpAnn" <+> ppr a <+> epaLocation s
-
             annotationExprBracket :: BracketAnn (EpUniToken "[|" "⟦") (EpToken "[e|") -> SDoc
             annotationExprBracket = annotationBracket
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -2268,7 +2268,6 @@ type :: { LHsType GhcPs }
 
         | btype '->.' ctype            {% hintLinear (getLoc $2) >>
                                           amsA' (sLL $1 $> $ HsFunTy noExtField (HsLinearArrow (EpLolly (epTok $2))) $1 $3) }
-                                              -- [mu AnnLollyU $2] }
 
 mult :: { Located (EpUniToken "->" "\8594" -> HsArrow GhcPs) }
         : PREFIX_PERCENT atype          { sLL $1 $> (mkMultTy (epTok $1) $2) }
@@ -2307,10 +2306,10 @@ tyop :: { (LocatedN RdrName, PromotionFlag) }
         : qtyconop                      { ($1, NotPromoted) }
         | tyvarop                       { ($1, NotPromoted) }
         | SIMPLEQUOTE qconop            {% do { op <- amsr (sLL $1 $> (unLoc $2))
-                                                           (NameAnnQuote (glR $1) (gl $2) [])
+                                                           (NameAnnQuote (epTok $1) (gl $2) [])
                                               ; return (op, IsPromoted) } }
         | SIMPLEQUOTE varop             {% do { op <- amsr (sLL $1 $> (unLoc $2))
-                                                           (NameAnnQuote (glR $1) (gl $2) [])
+                                                           (NameAnnQuote (epTok $1) (gl $2) [])
                                               ; return (op, IsPromoted) } }
 
 atype :: { LHsType GhcPs }
@@ -4476,14 +4475,6 @@ in GHC.Parser.Annotation
 
 -}
 
--- |Construct an AddEpAnn from the annotation keyword and the location
--- of the keyword itself
-mj :: AnnKeywordId -> Located e -> AddEpAnn
-mj !a !l = AddEpAnn a (srcSpan2e $ gl l)
-
-mjN :: AnnKeywordId -> LocatedN e -> AddEpAnn
-mjN !a !l = AddEpAnn a (srcSpan2e $ glA l)
-
 msemi :: Located e -> [TrailingAnn]
 msemi !l = if isZeroWidthSpan (gl l) then [] else [AddSemiAnn (srcSpan2e $ gl l)]
 
@@ -4493,12 +4484,6 @@ msemiA !l = if isZeroWidthSpan (gl l) then [] else [EpTok (srcSpan2e $ gl l)]
 msemim :: Located e -> Maybe EpaLocation
 msemim !l = if isZeroWidthSpan (gl l) then Nothing else Just (srcSpan2e $ gl l)
 
--- |Construct an AddEpAnn from the annotation keyword and the Located Token. If
--- the token has a unicode equivalent and this has been used, provide the
--- unicode variant of the annotation.
-mu :: AnnKeywordId -> Located Token -> AddEpAnn
-mu !a lt@(L l t) = AddEpAnn (toUnicodeAnn a lt) (srcSpan2e l)
-
 -- | If the 'Token' is using its unicode variant return the unicode variant of
 --   the annotation
 toUnicodeAnn :: AnnKeywordId -> Located Token -> AnnKeywordId
@@ -4579,27 +4564,6 @@ amsr (L l a) an = do
   !cs <- getCommentsFor l
   return (L (EpAnn (spanAsAnchor l) an cs) a)
 
--- |Synonyms for AddEpAnn versions of AnnOpen and AnnClose
-mo,mc :: Located Token -> AddEpAnn
-mo !ll = mj AnnOpen ll
-mc !ll = mj AnnClose ll
-
-moc,mcc :: Located Token -> AddEpAnn
-moc !ll = mj AnnOpenC ll
-mcc !ll = mj AnnCloseC ll
-
-mop,mcp :: Located Token -> AddEpAnn
-mop !ll = mj AnnOpenP ll
-mcp !ll = mj AnnCloseP ll
-
-moh,mch :: Located Token -> AddEpAnn
-moh !ll = mj AnnOpenPH ll
-mch !ll = mj AnnClosePH ll
-
-mos,mcs :: Located Token -> AddEpAnn
-mos !ll = mj AnnOpenS ll
-mcs !ll = mj AnnCloseS ll
-
 -- | Parse a Haskell module with Haddock comments. This is done in two steps:
 --
 -- * 'parseModuleNoHaddock' to build the AST
@@ -4643,10 +4607,6 @@ hsDoAnn :: EpToken "rec" -> LocatedAn t b -> AnnList (EpToken "rec")
 hsDoAnn tok (L ll _)
   = AnnList (Just $ spanAsAnchor (locA ll)) ListNone [] tok []
 
-listAsAnchor :: [LocatedAn t a] -> Located b -> EpaLocation
-listAsAnchor [] (L l _) = spanAsAnchor l
-listAsAnchor (h:_) s = spanAsAnchor (comb2 h s)
-
 listAsAnchorM :: [LocatedAn t a] -> Maybe EpaLocation
 listAsAnchorM [] = Nothing
 listAsAnchorM (L l _:_) =


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -20,7 +20,6 @@ module GHC.Parser.Annotation (
   HasE(..),
 
   -- * In-tree Exact Print Annotations
-  AddEpAnn(..),
   EpaLocation, EpaLocation'(..), epaLocationRealSrcSpan,
   TokenLocation(..),
   DeltaPos(..), deltaPos, getDeltaLine,
@@ -477,17 +476,6 @@ instance Outputable EpaComment where
 
 -- ---------------------------------------------------------------------
 
--- | Captures an annotation, storing the @'AnnKeywordId'@ and its
--- location.  The parser only ever inserts @'EpaLocation'@ fields with a
--- RealSrcSpan being the original location of the annotation in the
--- source file.
--- The @'EpaLocation'@ can also store a delta position if the AST has been
--- modified and needs to be pretty printed again.
--- The usual way an 'AddEpAnn' is created is using the 'mj' ("make
--- jump") function, and then it can be inserted into the appropriate
--- annotation.
-data AddEpAnn = AddEpAnn AnnKeywordId EpaLocation deriving (Data,Eq)
-
 type EpaLocation = EpaLocation' [LEpaComment]
 
 epaToNoCommentsLocation :: EpaLocation -> NoCommentsLocation
@@ -514,9 +502,6 @@ epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
 epaLocationRealSrcSpan (EpaSpan (RealSrcSpan r _)) = r
 epaLocationRealSrcSpan _ = panic "epaLocationRealSrcSpan"
 
-instance Outputable AddEpAnn where
-  ppr (AddEpAnn kw ss) = text "AddEpAnn" <+> ppr kw <+> ppr ss
-
 -- ---------------------------------------------------------------------
 
 -- | The exact print annotations (EPAs) are kept in the HsSyn AST for
@@ -784,7 +769,7 @@ data NameAnn
   -- | Used for an item with a leading @'@. The annotation for
   -- unquoted item is stored in 'nann_quoted'.
   | NameAnnQuote {
-      nann_quote     :: EpaLocation,
+      nann_quote     :: EpToken "'",
       nann_quoted    :: SrcSpanAnnN,
       nann_trailing  :: [TrailingAnn]
       }
@@ -1303,9 +1288,6 @@ instance NoAnn EpaLocation where
 instance NoAnn AnnKeywordId where
   noAnn = Annlarrowtail  {- gotta pick one -}
 
-instance NoAnn AddEpAnn where
-  noAnn = AddEpAnn noAnn noAnn
-
 instance NoAnn [a] where
   noAnn = []
 


=====================================
testsuite/tests/parser/should_compile/T15279.stderr
=====================================
@@ -8,8 +8,12 @@
    (EpAnn
     (EpaSpan { T15279.hs:1:1 })
     (AnnsModule
-     [(AddEpAnn AnnModule (EpaSpan { T15279.hs:3:1-6 }))
-     ,(AddEpAnn AnnWhere (EpaSpan { T15279.hs:3:15-19 }))]
+     (NoEpTok)
+     (EpTok
+      (EpaSpan { T15279.hs:3:1-6 }))
+     (EpTok
+      (EpaSpan { T15279.hs:3:15-19 }))
+     []
      []
      (Just
       ((,)
@@ -18,374 +22,354 @@
     (EpaCommentsBalanced
      []
      []))
-   (VirtualBraces
+   (EpVirtualBraces
     (1))
    (Nothing)
    (Nothing))
   (Just
    (L
-    (SrcSpanAnn (EpAnn
-                 (EpaSpan { T15279.hs:3:8-13 })
-                 (AnnListItem
-                  [])
-                 (EpaComments
-                  [])) { T15279.hs:3:8-13 })
+    (EpAnn
+     (EpaSpan { T15279.hs:3:8-13 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
     {ModuleName: T15279}))
   (Nothing)
   []
   [(L
-    (SrcSpanAnn (EpAnn
-                 (EpaSpan { T15279.hs:5:1-19 })
-                 (AnnListItem
-                  [])
-                 (EpaComments
-                  [])) { T15279.hs:5:1-19 })
+    (EpAnn
+     (EpaSpan { T15279.hs:5:1-19 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
     (SigD
      (NoExtField)
      (TypeSig
-      (EpAnn
-       (EpaSpan { T15279.hs:5:1-19 })
-       (AnnSig
-        (AddEpAnn AnnDcolon (EpaSpan { T15279.hs:5:5-6 }))
-        [])
-       (EpaComments
-        []))
+      (AnnSig
+       (EpUniTok
+        (EpaSpan { T15279.hs:5:5-6 })
+        (NormalSyntax))
+       (Nothing)
+       (Nothing))
       [(L
-        (SrcSpanAnn (EpAnn
-                     (EpaSpan { T15279.hs:5:1-3 })
-                     (NameAnnTrailing
-                      [])
-                     (EpaComments
-                      [])) { T15279.hs:5:1-3 })
+        (EpAnn
+         (EpaSpan { T15279.hs:5:1-3 })
+         (NameAnnTrailing
+          [])
+         (EpaComments
+          []))
         (Unqual
          {OccName: foo}))]
       (HsWC
        (NoExtField)
        (L
-        (SrcSpanAnn (EpAnn
-                     (EpaSpan { T15279.hs:5:8-19 })
-                     (AnnListItem
-                      [])
-                     (EpaComments
-                      [])) { T15279.hs:5:8-19 })
+        (EpAnn
+         (EpaSpan { T15279.hs:5:8-19 })
+         (AnnListItem
+          [])
+         (EpaComments
+          []))
         (HsSig
          (NoExtField)
          (HsOuterImplicit
           (NoExtField))
          (L
-          (SrcSpanAnn (EpAnn
-                       (EpaSpan { T15279.hs:5:8-19 })
-                       (AnnListItem
-                        [])
-                       (EpaComments
-                        [])) { T15279.hs:5:8-19 })
+          (EpAnn
+           (EpaSpan { T15279.hs:5:8-19 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
           (HsFunTy
-           (EpAnn
-            (EpaSpan { T15279.hs:5:8-19 })
-            (NoEpAnns)
-            (EpaComments
-             []))
+           (NoExtField)
            (HsUnrestrictedArrow
-            (L
-             (TokenLoc
-              (EpaSpan { T15279.hs:5:13-14 }))
-             (HsNormalTok)))
+            (EpUniTok
+             (EpaSpan { T15279.hs:5:13-14 })
+             (NormalSyntax)))
            (L
-            (SrcSpanAnn (EpAnn
-                         (EpaSpan { T15279.hs:5:8-11 })
-                         (AnnListItem
-                          [])
-                         (EpaComments
-                          [])) { T15279.hs:5:8-11 })
+            (EpAnn
+             (EpaSpan { T15279.hs:5:8-11 })
+             (AnnListItem
+              [])
+             (EpaComments
+              []))
             (HsTyVar
-             (EpAnn
-              (EpaSpan { T15279.hs:5:8-11 })
-              []
-              (EpaComments
-               []))
+             (NoEpTok)
              (NotPromoted)
              (L
-              (SrcSpanAnn (EpAnn
-                           (EpaSpan { T15279.hs:5:8-11 })
-                           (NameAnnTrailing
-                            [])
-                           (EpaComments
-                            [])) { T15279.hs:5:8-11 })
+              (EpAnn
+               (EpaSpan { T15279.hs:5:8-11 })
+               (NameAnnTrailing
+                [])
+               (EpaComments
+                []))
               (Unqual
                {OccName: Char}))))
            (L
-            (SrcSpanAnn (EpAnn
-                         (EpaSpan { T15279.hs:5:16-19 })
-                         (AnnListItem
-                          [])
-                         (EpaComments
-                          [])) { T15279.hs:5:16-19 })
+            (EpAnn
+             (EpaSpan { T15279.hs:5:16-19 })
+             (AnnListItem
+              [])
+             (EpaComments
+              []))
             (HsTyVar
-             (EpAnn
-              (EpaSpan { T15279.hs:5:16-19 })
-              []
-              (EpaComments
-               []))
+             (NoEpTok)
              (NotPromoted)
              (L
-              (SrcSpanAnn (EpAnn
-                           (EpaSpan { T15279.hs:5:16-19 })
-                           (NameAnnTrailing
-                            [])
-                           (EpaComments
-                            [])) { T15279.hs:5:16-19 })
+              (EpAnn
+               (EpaSpan { T15279.hs:5:16-19 })
+               (NameAnnTrailing
+                [])
+               (EpaComments
+                []))
               (Unqual
                {OccName: Char}))))))))))))
   ,(L
-    (SrcSpanAnn (EpAnn
-                 (EpaSpan { foo:-1:-1 })
-                 (AnnListItem
-                  [])
-                 (EpaComments
-                  [])) {  })
+    (EpAnn
+     (EpaSpan {  })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
     (ValD
      (NoExtField)
      (FunBind
       (NoExtField)
       (L
-       (SrcSpanAnn (EpAnn
-                    (EpaSpan { T15279.hs-incl:1:1-3 })
-                    (NameAnnTrailing
-                     [])
-                    (EpaComments
-                     [])) { T15279.hs-incl:1:1-3 })
+       (EpAnn
+        (EpaSpan { T15279.hs-incl:1:1-3 })
+        (NameAnnTrailing
+         [])
+        (EpaComments
+         []))
        (Unqual
         {OccName: foo}))
       (MG
        (FromSource)
        (L
-        (SrcSpanAnn (EpAnn
-                     (EpaSpan {  })
-                     (AnnList
-                      (Nothing)
-                      (Nothing)
-                      (Nothing)
-                      []
-                      [])
-                     (EpaComments
-                      [])) {  })
+        (EpAnn
+         (EpaSpan {  })
+         (AnnList
+          (Nothing)
+          (ListNone)
+          []
+          (NoEpTok)
+          [])
+         (EpaComments
+          []))
         [(L
-          (SrcSpanAnn (EpAnn
-                       (EpaSpan { T15279.hs-incl:1:1-13 })
-                       (AnnListItem
-                        [])
-                       (EpaComments
-                        [])) { T15279.hs-incl:1:1-13 })
+          (EpAnn
+           (EpaSpan { T15279.hs-incl:1:1-13 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
           (Match
-           (EpAnn
-            (EpaSpan { T15279.hs-incl:1:1-13 })
-            []
-            (EpaComments
-             []))
+           (NoExtField)
            (FunRhs
             (L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs-incl:1:1-3 })
-                          (NameAnnTrailing
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs-incl:1:1-3 })
+             (EpAnn
+              (EpaSpan { T15279.hs-incl:1:1-3 })
+              (NameAnnTrailing
+               [])
+              (EpaComments
+               []))
              (Unqual
               {OccName: foo}))
             (Prefix)
-            (NoSrcStrict))
-           [(L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs-incl:1:5-7 })
-                          (AnnListItem
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs-incl:1:5-7 })
-             (LitPat
-              (NoExtField)
-              (HsChar
-               (SourceText 'a')
-               ('a'))))]
+            (NoSrcStrict)
+            (AnnFunRhs
+             (NoEpTok)
+             []
+             []))
+           (L
+            (EpaSpan { T15279.hs-incl:1:5-7 })
+            [(L
+              (EpAnn
+               (EpaSpan { T15279.hs-incl:1:5-7 })
+               (AnnListItem
+                [])
+               (EpaComments
+                []))
+              (LitPat
+               (NoExtField)
+               (HsChar
+                (SourceText 'a')
+                ('a'))))])
            (GRHSs
             (EpaComments
              [])
             [(L
-              (SrcSpanAnn
-               (EpAnn
-                (EpaSpan { T15279.hs-incl:1:9-13 })
-                (NoEpAnns)
-                (EpaComments
-                 []))
-               { T15279.hs-incl:1:9-13 })
+              (EpAnn
+               (EpaSpan { T15279.hs-incl:1:9-13 })
+               (NoEpAnns)
+               (EpaComments
+                []))
               (GRHS
                (EpAnn
                 (EpaSpan { T15279.hs-incl:1:9-13 })
                 (GrhsAnn
                  (Nothing)
-                 (AddEpAnn AnnEqual (EpaSpan { T15279.hs-incl:1:9 })))
+                 (Left
+                  (EpTok
+                   (EpaSpan { T15279.hs-incl:1:9 }))))
                 (EpaComments
                  []))
                []
                (L
-                (SrcSpanAnn (EpAnn
-                             (EpaSpan { T15279.hs-incl:1:11-13 })
-                             (AnnListItem
-                              [])
-                             (EpaComments
-                              [])) { T15279.hs-incl:1:11-13 })
+                (EpAnn
+                 (EpaSpan { T15279.hs-incl:1:11-13 })
+                 (AnnListItem
+                  [])
+                 (EpaComments
+                  []))
                 (HsLit
-                 (EpAnn
-                  (EpaSpan { T15279.hs-incl:1:11-13 })
-                  (NoEpAnns)
-                  (EpaComments
-                   []))
+                 (NoExtField)
                  (HsChar
                   (SourceText 'b')
                   ('b'))))))]
             (EmptyLocalBinds
              (NoExtField)))))
         ,(L
-          (SrcSpanAnn (EpAnn
-                       (EpaSpan { T15279.hs-incl:2:1-13 })
-                       (AnnListItem
-                        [])
-                       (EpaComments
-                        [])) { T15279.hs-incl:2:1-13 })
+          (EpAnn
+           (EpaSpan { T15279.hs-incl:2:1-13 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
           (Match
-           (EpAnn
-            (EpaSpan { T15279.hs-incl:2:1-13 })
-            []
-            (EpaComments
-             []))
+           (NoExtField)
            (FunRhs
             (L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs-incl:2:1-3 })
-                          (NameAnnTrailing
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs-incl:2:1-3 })
+             (EpAnn
+              (EpaSpan { T15279.hs-incl:2:1-3 })
+              (NameAnnTrailing
+               [])
+              (EpaComments
+               []))
              (Unqual
               {OccName: foo}))
             (Prefix)
-            (NoSrcStrict))
-           [(L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs-incl:2:5-7 })
-                          (AnnListItem
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs-incl:2:5-7 })
-             (LitPat
-              (NoExtField)
-              (HsChar
-               (SourceText 'b')
-               ('b'))))]
+            (NoSrcStrict)
+            (AnnFunRhs
+             (NoEpTok)
+             []
+             []))
+           (L
+            (EpaSpan { T15279.hs-incl:2:5-7 })
+            [(L
+              (EpAnn
+               (EpaSpan { T15279.hs-incl:2:5-7 })
+               (AnnListItem
+                [])
+               (EpaComments
+                []))
+              (LitPat
+               (NoExtField)
+               (HsChar
+                (SourceText 'b')
+                ('b'))))])
            (GRHSs
             (EpaComments
              [])
             [(L
-              (SrcSpanAnn
-               (EpAnn
-                (EpaSpan { T15279.hs-incl:2:9-13 })
-                (NoEpAnns)
-                (EpaComments
-                 []))
-               { T15279.hs-incl:2:9-13 })
+              (EpAnn
+               (EpaSpan { T15279.hs-incl:2:9-13 })
+               (NoEpAnns)
+               (EpaComments
+                []))
               (GRHS
                (EpAnn
                 (EpaSpan { T15279.hs-incl:2:9-13 })
                 (GrhsAnn
                  (Nothing)
-                 (AddEpAnn AnnEqual (EpaSpan { T15279.hs-incl:2:9 })))
+                 (Left
+                  (EpTok
+                   (EpaSpan { T15279.hs-incl:2:9 }))))
                 (EpaComments
                  []))
                []
                (L
-                (SrcSpanAnn (EpAnn
-                             (EpaSpan { T15279.hs-incl:2:11-13 })
-                             (AnnListItem
-                              [])
-                             (EpaComments
-                              [])) { T15279.hs-incl:2:11-13 })
+                (EpAnn
+                 (EpaSpan { T15279.hs-incl:2:11-13 })
+                 (AnnListItem
+                  [])
+                 (EpaComments
+                  []))
                 (HsLit
-                 (EpAnn
-                  (EpaSpan { T15279.hs-incl:2:11-13 })
-                  (NoEpAnns)
-                  (EpaComments
-                   []))
+                 (NoExtField)
                  (HsChar
                   (SourceText 'c')
                   ('c'))))))]
             (EmptyLocalBinds
              (NoExtField)))))
         ,(L
-          (SrcSpanAnn (EpAnn
-                       (EpaSpan { T15279.hs:7:1-11 })
-                       (AnnListItem
-                        [])
-                       (EpaComments
-                        [])) { T15279.hs:7:1-11 })
+          (EpAnn
+           (EpaSpan { T15279.hs:7:1-11 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
           (Match
-           (EpAnn
-            (EpaSpan { T15279.hs:7:1-11 })
-            []
-            (EpaComments
-             []))
+           (NoExtField)
            (FunRhs
             (L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs:7:1-3 })
-                          (NameAnnTrailing
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs:7:1-3 })
+             (EpAnn
+              (EpaSpan { T15279.hs:7:1-3 })
+              (NameAnnTrailing
+               [])
+              (EpaComments
+               []))
              (Unqual
               {OccName: foo}))
             (Prefix)
-            (NoSrcStrict))
-           [(L
-             (SrcSpanAnn (EpAnn
-                          (EpaSpan { T15279.hs:7:5 })
-                          (AnnListItem
-                           [])
-                          (EpaComments
-                           [])) { T15279.hs:7:5 })
-             (WildPat
-              (NoExtField)))]
+            (NoSrcStrict)
+            (AnnFunRhs
+             (NoEpTok)
+             []
+             []))
+           (L
+            (EpaSpan { T15279.hs:7:5 })
+            [(L
+              (EpAnn
+               (EpaSpan { T15279.hs:7:5 })
+               (AnnListItem
+                [])
+               (EpaComments
+                []))
+              (WildPat
+               (NoExtField)))])
            (GRHSs
             (EpaComments
              [])
             [(L
-              (SrcSpanAnn
-               (EpAnn
-                (EpaSpan { T15279.hs:7:7-11 })
-                (NoEpAnns)
-                (EpaComments
-                 []))
-               { T15279.hs:7:7-11 })
+              (EpAnn
+               (EpaSpan { T15279.hs:7:7-11 })
+               (NoEpAnns)
+               (EpaComments
+                []))
               (GRHS
                (EpAnn
                 (EpaSpan { T15279.hs:7:7-11 })
                 (GrhsAnn
                  (Nothing)
-                 (AddEpAnn AnnEqual (EpaSpan { T15279.hs:7:7 })))
+                 (Left
+                  (EpTok
+                   (EpaSpan { T15279.hs:7:7 }))))
                 (EpaComments
                  []))
                []
                (L
-                (SrcSpanAnn (EpAnn
-                             (EpaSpan { T15279.hs:7:9-11 })
-                             (AnnListItem
-                              [])
-                             (EpaComments
-                              [])) { T15279.hs:7:9-11 })
+                (EpAnn
+                 (EpaSpan { T15279.hs:7:9-11 })
+                 (AnnListItem
+                  [])
+                 (EpaComments
+                  []))
                 (HsLit
-                 (EpAnn
-                  (EpaSpan { T15279.hs:7:9-11 })
-                  (NoEpAnns)
-                  (EpaComments
-                   []))
+                 (NoExtField)
                  (HsChar
                   (SourceText 'a')
                   ('a'))))))]


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -264,14 +264,6 @@ instance HasTrailing EpaLocation where
   trailing _ = []
   setTrailing a _ = a
 
-instance HasTrailing AddEpAnn where
-  trailing _ = []
-  setTrailing a _ = a
-
-instance HasTrailing (AddEpAnn, AddEpAnn) where
-  trailing _ = []
-  setTrailing a _ = a
-
 instance HasTrailing EpAnnSumPat where
   trailing _ = []
   setTrailing a _ = a
@@ -1336,11 +1328,6 @@ markEpaLocationAll :: (Monad m, Monoid w)
   => [EpaLocation] -> String -> EP w m [EpaLocation]
 markEpaLocationAll locs str = mapM (\l -> printStringAtAA l str) locs
 
-markKwC :: (Monad m, Monoid w) => CaptureComments -> AddEpAnn -> EP w m AddEpAnn
-markKwC capture (AddEpAnn kw ss) = do
-  ss' <- markKwAC capture kw ss
-  return (AddEpAnn kw ss')
-
 -- | This should be the main driver of the process, managing printing keywords.
 -- It returns the 'EpaDelta' variant of the passed in 'EpaLocation'
 markKwA :: (Monad m, Monoid w) => AnnKeywordId -> EpaLocation -> EP w m EpaLocation
@@ -3638,7 +3625,7 @@ instance ExactPrint (TyClDecl GhcPs) where
     epTokensToComments AnnCloseP cps
     t' <- markEpToken t
 
-    (_anx, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
+    (_,ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
     eq' <- markEpToken eq
     rhs' <- markAnnotated rhs
     return (SynDecl { tcdSExt = AnnSynDecl [] [] t' eq'
@@ -3647,7 +3634,7 @@ instance ExactPrint (TyClDecl GhcPs) where
 
   exact (DataDecl { tcdDExt = x, tcdLName = ltycon, tcdTyVars = tyvars
                   , tcdFixity = fixity, tcdDataDefn = defn }) = do
-    (_, ltycon', tyvars', _, defn') <-
+    (_,ltycon', tyvars', _, defn') <-
       exactDataDefn (exactVanillaDeclHead ltycon tyvars fixity) defn
     return (DataDecl { tcdDExt = x, tcdLName = ltycon', tcdTyVars = tyvars'
                      , tcdFixity = fixity, tcdDataDefn = defn' })
@@ -3705,7 +3692,7 @@ instance ExactPrint (TyClDecl GhcPs) where
           epTokensToComments AnnOpenP ops
           epTokensToComments AnnCloseP cps
           c' <- markEpToken c
-          (_, lclas', tyvars',_,context') <-  exactVanillaDeclHead lclas tyvars fixity context
+          (_,lclas', tyvars',_,context') <- exactVanillaDeclHead lclas tyvars fixity context
           (vb', fds') <- if (null fds)
             then return (vb, fds)
             else do
@@ -3747,7 +3734,7 @@ instance ExactPrint (FamilyDecl GhcPs) where
 
     epTokensToComments AnnOpenP ops
     epTokensToComments AnnCloseP cps
-    (_, ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
+    (_,ltycon', tyvars',_,_) <- exactVanillaDeclHead ltycon tyvars fixity Nothing
     (dc', eq', result') <- exact_kind (dc, eq)
     (vb', mb_inj') <-
       case mb_inj of
@@ -3876,7 +3863,7 @@ exactVanillaDeclHead :: (Monad m, Monoid w)
                      -> LHsQTyVars GhcPs
                      -> LexicalFixity
                      -> Maybe (LHsContext GhcPs)
-                     -> EP w m ( [AddEpAnn]
+                     -> EP w m ( () -- TO allow use in exactDataDefn
                                , LocatedN RdrName
                                , LHsQTyVars GhcPs
                                , (), Maybe (LHsContext GhcPs))
@@ -3904,7 +3891,7 @@ exactVanillaDeclHead thing tvs@(HsQTvs { hsq_explicit = tyvars }) fixity context
       return (thing', [])
   context' <- mapM markAnnotated context
   (thing', tyvars') <- exact_tyvars tyvars
-  return (noAnn, thing', tvs { hsq_explicit = tyvars' }, (), context')
+  return ((), thing', tvs { hsq_explicit = tyvars' }, (), context')
 
 -- ---------------------------------------------------------------------
 
@@ -4222,12 +4209,12 @@ instance ExactPrint (LocatedN RdrName) where
             _ -> error "ExactPrint (LocatedN RdrName)"
         NameAnnCommas a commas t -> do
           a0 <- markNameAdornmentO a
-          commas' <- forM commas (\loc -> locFromAdd <$> markKwC NoCaptureComments (AddEpAnn AnnComma loc))
+          commas' <- forM commas (\loc -> printStringAtAAC NoCaptureComments loc ",")
           a1 <- markNameAdornmentC a0
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
           o' <- markEpToken o
-          bars' <- forM bars (\loc -> locFromAdd <$> markKwC NoCaptureComments (AddEpAnn AnnVbar loc))
+          bars' <- forM bars (\loc -> printStringAtAAC NoCaptureComments loc "|")
           c' <- markEpToken c
           return (NameAnnBars (o',c') bars' t)
         NameAnnOnly a t -> do
@@ -4240,7 +4227,7 @@ instance ExactPrint (LocatedN RdrName) where
           return (NameAnnRArrow o' nl' c' t)
         NameAnnQuote q name t -> do
           debugM $ "NameAnnQuote"
-          (AddEpAnn _ q') <- markKwC NoCaptureComments (AddEpAnn AnnSimpleQuote q)
+          q' <- markEpToken q
           (L name' _) <- markAnnotated (L name n)
           return (NameAnnQuote q' name' t)
         NameAnnTrailing t -> do
@@ -4279,9 +4266,6 @@ markNameAdornmentC (NameSquare o c) = do
   return (NameSquare o c')
 markNameAdornmentC NameNoAdornment      = return NameNoAdornment
 
-locFromAdd :: AddEpAnn -> EpaLocation
-locFromAdd (AddEpAnn _ loc) = loc
-
 printUnicode :: (Monad m, Monoid w) => EpaLocation -> RdrName -> EP w m EpaLocation
 printUnicode anc n = do
   let str = case (showPprUnsafe n) of


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -34,7 +34,6 @@ import GHC.Types.Name.Reader
 import GHC.Types.SrcLoc
 import GHC.Driver.Ppr
 import GHC.Data.FastString
-import qualified GHC.Data.Strict as Strict
 import GHC.Base (NonEmpty(..))
 import GHC.Parser.Lexer (allocateComments)
 
@@ -140,13 +139,6 @@ undelta (l,_) (DifferentLine dl dc) (LayoutStartCol co) = (fl,fc)
     fl = l + dl
     fc = co + dc
 
-undeltaSpan :: RealSrcSpan -> AnnKeywordId -> DeltaPos -> AddEpAnn
-undeltaSpan anc kw dp = AddEpAnn kw (EpaSpan (RealSrcSpan sp Strict.Nothing))
-  where
-    (l,c) = undelta (ss2pos anc) dp (LayoutStartCol 0)
-    len = length (keywordToString kw)
-    sp = range2rs ((l,c),(l,c+len))
-
 -- ---------------------------------------------------------------------
 
 adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos
@@ -594,9 +586,6 @@ setTrailingAnnLoc (AddVbarAnn _)    ss = (AddVbarAnn ss)
 setTrailingAnnLoc (AddDarrowAnn _)  ss = (AddDarrowAnn ss)
 setTrailingAnnLoc (AddDarrowUAnn _) ss = (AddDarrowUAnn ss)
 
-addEpAnnLoc :: AddEpAnn -> EpaLocation
-addEpAnnLoc (AddEpAnn _ l) = l
-
 -- ---------------------------------------------------------------------
 
 type DeclsByTag a = Map.Map DeclTag [(RealSrcSpan, a)]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c81da559be4b6f0ccd0f6c8872fbe665b2432da

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 11:27:59 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 27 Oct 2024 07:27:59 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-8] 9 commits: EPA: Remove
 AddEpann commit 7
Message-ID: <671e23bfbe152_200dd84a0efc928c2@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC


Commits:
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
564f567e by Alan Zimmerman at 2024-10-27T11:26:17+00:00
EPA: Remove AddEpAnn from AnnList

- - - - -
fb0c732f by Alan Zimmerman at 2024-10-27T11:26:17+00:00
EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

- - - - -
48c93a17 by Alan Zimmerman at 2024-10-27T11:26:17+00:00
EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

- - - - -
2ed6af73 by Alan Zimmerman at 2024-10-27T11:26:17+00:00
EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -


30 changed files:

- .ghcid
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Types/Basic.hs
- libraries/base/src/Control/Monad/Fix.hs
- + testsuite/tests/dependent/should_compile/T25387.hs
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c81da559be4b6f0ccd0f6c8872fbe665b2432da...2ed6af73cbb251863b1c9823427502da0332b96b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9c81da559be4b6f0ccd0f6c8872fbe665b2432da...2ed6af73cbb251863b1c9823427502da0332b96b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 12:36:33 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 08:36:33 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] 37 commits: Interpreter: Add
 locking for communication with external interpreter
Message-ID: <671e33d175d5a_1ff074c53b434382@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
6b60906e by Hassan Al-Awwadi at 2024-10-27T13:36:11+01:00
Moved TyConFlavour to L.H.S, moved TopLevelFlag to extension field

side note is that I don't think Haddoc makes use of the fdTopLevel field so it doesn't get TopLeveLFlag in its extension field

- - - - -
3bf08128 by Hassan Al-Awwadi at 2024-10-27T13:36:11+01:00
Moved InlinePragma to L.H.S and parameterized it over the pass

Because its no longer "Basic", I figured I would define the GHC specific
stuff in GHC.Hs.InlinePragma, and would add it as an import. Little did I
know that InlinePragma is very prolific and this would cause *so much churn*.

Also the linter claims it can't find some notes, yet I can see them with
my own eyes...

- - - - -
bba8d00d by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
whitespace

- - - - -
641e506e by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
Moved OverlapMode from GHC.Types.Basic to L.H.S.OverlapPragma

Parameterized it over the pass too. The rest is churn.

- - - - -
1ff040be by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
move RuleName to L.H.S.Basic

- - - - -
197862eb by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
cleanup

- - - - -
9b513053 by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
review suggestions

- - - - -
da8bebdf by Hassan Al-Awwadi at 2024-10-27T13:36:12+01:00
unused import

- - - - -


30 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d22b13c530b029cb75b92c67b87e6fba7d141261...da8bebdfe6b86064f5add40010d0cdcaa425d915

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d22b13c530b029cb75b92c67b87e6fba7d141261...da8bebdfe6b86064f5add40010d0cdcaa425d915
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 12:40:06 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 08:40:06 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: ghcid: use
 multi repl for ghcid
Message-ID: <671e34a677cc0_1ff074bc46c34790@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
8ac497bc by Simon Peyton Jones at 2024-10-27T08:39:59-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
6bd383ea by Andrew Lelechenko at 2024-10-27T08:39:59-04:00
Bump text submodule to 2.1.2

- - - - -
311f6a08 by Andrew Lelechenko at 2024-10-27T08:39:59-04:00
hadrian: allow -Wunused-imports for text package

- - - - -


6 changed files:

- .ghcid
- compiler/GHC/Core/TyCo/Tidy.hs
- hadrian/src/Settings/Warnings.hs
- libraries/base/src/Control/Monad/Fix.hs
- libraries/text
- utils/jsffi/prelude.mjs


Changes:

=====================================
.ghcid
=====================================
@@ -1,5 +1,5 @@
---command sh -c "HADRIAN_ARGS=-j ./hadrian/ghci -j"
+--command sh -c "HADRIAN_ARGS=-j exec ./hadrian/ghci-multi -j"
 --reload compiler
 --reload ghc
 --reload includes
---restart hadrian/ghci
+--restart hadrian/ghci-multi


=====================================
compiler/GHC/Core/TyCo/Tidy.hs
=====================================
@@ -336,16 +336,18 @@ tidyCo env co
     go (AppCo co1 co2)       = (AppCo $! go co1) $! go co2
     go (ForAllCo tv visL visR h co)
       = ((((ForAllCo $! tvp) $! visL) $! visR) $! (go h)) $! (tidyCo envp co)
-                               where (envp, tvp) = tidyVarBndr env tv
+      where (envp, tvp) = tidyVarBndr env tv
             -- the case above duplicates a bit of work in tidying h and the kind
             -- of tv. But the alternative is to use coercionKind, which seems worse.
     go (FunCo r afl afr w co1 co2) = ((FunCo r afl afr $! go w) $! go co1) $! go co2
     go (CoVarCo cv)          = CoVarCo $! go_cv cv
     go (HoleCo h)            = HoleCo $! go_hole h
     go (AxiomCo ax cos)      = AxiomCo ax $ strictMap go cos
-    go co@(UnivCo { uco_lty  = t1, uco_rty = t2 })
-                             = co { uco_lty = tidyType env t1, uco_rty = tidyType env t2 }
-                               -- Don't bother to tidy the uco_deps field
+    go (UnivCo prov role t1 t2 cos)
+                             = ((UnivCo prov role
+                                $! tidyType env t1)
+                                $! tidyType env t2)
+                                $! strictMap go cos
     go (SymCo co)            = SymCo $! go co
     go (TransCo co1 co2)     = (TransCo $! go co1) $! go co2
     go (SelCo d co)          = SelCo d $! go co


=====================================
hadrian/src/Settings/Warnings.hs
=====================================
@@ -66,7 +66,9 @@ ghcWarningsArgs = do
         , package primitive    ? pure [ "-Wno-unused-imports"
                                       , "-Wno-deprecations" ]
         , package rts          ? pure [ "-Wcpp-undef" ]
-        , package text         ? pure [ "-Wno-deprecations", "-Wno-deriving-typeable" ]
+        , package text         ? pure [ "-Wno-deprecations"
+                                      , "-Wno-deriving-typeable"
+                                      , "-Wno-unused-imports" ]
         , package terminfo     ? pure [ "-Wno-unused-imports", "-Wno-deriving-typeable" ]
         , package stm          ? pure [ "-Wno-deriving-typeable" ]
         , package osString     ? pure [ "-Wno-deriving-typeable" ]


=====================================
libraries/base/src/Control/Monad/Fix.hs
=====================================
@@ -10,11 +10,108 @@
 -- Stability   :  stable
 -- Portability :  portable
 --
--- Monadic fixpoints.
+-- Monadic fixpoints, used for desugaring of @{-# LANGUAGE RecursiveDo #-}@.
 --
--- For a detailed discussion, see Levent Erkok's thesis,
--- /Value Recursion in Monadic Computations/, Oregon Graduate Institute, 2002.
+-- Consider the generalized version of so-called @repmin@
+-- (/replace with minimum/) problem:
+-- accumulate elements of a container into a 'Monoid'
+-- and modify each element using the final accumulator.
 --
+-- @
+-- repmin
+--   :: (Functor t, Foldable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = fmap (\`g\` foldMap f as) as
+-- @
+--
+-- The naive implementation as above makes two traversals. Can we do better
+-- and achieve the goal in a single pass? It's seemingly impossible, because we would
+-- have to know the future,
+-- but lazy evaluation comes to the rescue:
+--
+-- @
+-- import Data.Traversable (mapAccumR)
+--
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as =
+--   let (b, cs) = mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as in cs
+-- @
+--
+-- How can we check that @repmin@ indeed traverses only once?
+-- Let's run it on an infinite input:
+--
+-- >>> import Data.Monoid (All(..))
+-- >>> take 3 $ repmin All (const id) ([True, True, False] ++ undefined)
+-- [All {getAll = False},All {getAll = False},All {getAll = False}]
+--
+-- So far so good, but can we generalise @g@ to return a monadic value @a -> b -> m c@?
+-- The following does not work, complaining that @b@ is not in scope:
+--
+-- @
+-- import Data.Traversable (mapAccumM)
+--
+-- repminM
+--   :: (Traversable t, Monoid b, Monad m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = do
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- To solve the riddle, let's rewrite @repmin@ via 'fix':
+--
+-- @
+-- repmin
+--   :: (Traversable t, Monoid b)
+--   => (a -> b) -> (a -> b -> c) -> t a -> t c
+-- repmin f g as = snd $ fix $
+--   \\(b, cs) -> mapAccumR (\\acc a -> (f a <> acc, g a b)) mempty as
+-- @
+--
+-- Now we can replace 'fix' with 'mfix' to obtain the solution:
+--
+-- @
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = fmap snd $ mfix $
+--   \\(~(b, cs)) -> mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+-- @
+--
+-- For example,
+--
+-- >>> import Data.Monoid (Sum(..))
+-- >>> repminM Sum (\a b -> print a >> pure (a + getSum b)) [3, 5, 2]
+-- 3
+-- 5
+-- 2
+-- [13,15,12]
+--
+-- Incredibly, GHC is capable to do this transformation automatically,
+-- when {-# LANGUAGE RecursiveDo #-} is enabled. Namely, the following
+-- implementation of @repminM@ works (note @mdo@ instead of @do@):
+--
+-- @
+-- {-# LANGUAGE RecursiveDo #-}
+--
+-- repminM
+--   :: (Traversable t, Monoid b, MonadFix m)
+--   => (a -> b) -> (a -> b -> m c) -> t a -> m (t c)
+-- repminM f g as = mdo
+--   (b, cs) \<- mapAccumM (\\acc a -> (f a <> acc,) <$> g a b) mempty as
+--   pure cs
+-- @
+--
+-- Further reading:
+--
+-- * GHC User’s Guide, The recursive do-notation.
+-- * Haskell Wiki, .
+-- * Levent Erkök, , Oregon Graduate Institute, 2002.
+-- * Levent Erkök, John Launchbury, , Haskell '02, 29-37, 2002.
+-- * Richard S. Bird, , Acta Informatica 21, 239-250, 1984.
+-- * Jasper Van der Jeugt, , 2023.
 
 module Control.Monad.Fix
     (MonadFix(mfix),


=====================================
libraries/text
=====================================
@@ -1 +1 @@
-Subproject commit cdb9e13b39079904eed9d75cd332b66ee0cad0c0
+Subproject commit ee0a8f8b9a4bd3fdad23e9ac0db56e7f08ce35cd


=====================================
utils/jsffi/prelude.mjs
=====================================
@@ -58,9 +58,9 @@ const setImmediate = await (async () => {
   }
 
   // deno
-  try {
+  if (globalThis.Deno) {
     return (await import("node:timers")).setImmediate;
-  } catch {}
+  }
 
   // https://developer.mozilla.org/en-US/docs/Web/API/Scheduler/postTask
   if (globalThis.scheduler) {



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ea6165aadff1d9954b9d351461b1b9c7b48bb45...311f6a08f517f1ec909c744d293aba8b5ebaeb23

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ea6165aadff1d9954b9d351461b1b9c7b48bb45...311f6a08f517f1ec909c744d293aba8b5ebaeb23
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 14:01:25 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 10:01:25 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] properly store locs in
 BooleanFormula nodes again
Message-ID: <671e47b54e1b6_c015c27bb4015728@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
35fe87ee by Hassan Al-Awwadi at 2024-10-27T14:59:45+01:00
properly store locs in BooleanFormula nodes again

- - - - -


15 changed files:

- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Types/Basic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/BooleanFormula.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


Changes:

=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -43,6 +43,7 @@ module GHC.CoreToIface
     , toIfaceVar
       -- * Other stuff
     , toIfaceLFInfo
+    , toIfaceBooleanFormula
       -- * CgBreakInfo
     , dehydrateCgBreakInfo
     ) where
@@ -69,6 +70,7 @@ import GHC.Builtin.Types ( heqTyCon )
 
 import GHC.Iface.Syntax
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula qualified as BF(BooleanFormula(..))
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -82,11 +84,14 @@ import GHC.Types.Var.Set
 import GHC.Types.Tickish
 import GHC.Types.Demand ( isNopSig )
 import GHC.Types.Cpr ( topCprSig )
+import GHC.Types.SrcLoc (unLoc)
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Misc
 
+import GHC.Hs.Extension (GhcRn)
+
 import Data.Maybe ( isNothing, catMaybes )
 
 {- Note [Avoiding space leaks in toIface*]
@@ -537,6 +542,14 @@ toIfGuidance src guidance
   , isStableSource src = IfWhen arity unsat_ok boring_ok
   | otherwise          = IfNoGuidance
 
+toIfaceBooleanFormula :: BF.BooleanFormula GhcRn -> IfaceBooleanFormula
+toIfaceBooleanFormula = go
+  where
+    go (BF.Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
+    go (BF.And bfs  ) = IfAnd    $ map (go . unLoc) bfs
+    go (BF.Or bfs   ) = IfOr     $ map (go . unLoc) bfs
+    go (BF.Parens bf) = IfParens $     (go . unLoc) bf
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -50,9 +50,9 @@ bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
 bfMap f = go
   where
     go (Var    a  ) = Var     $ f a
-    go (And    bfs) = And     $ map go bfs
-    go (Or     bfs) = Or      $ map go bfs
-    go (Parens bf ) = Parens  $     go bf
+    go (And    bfs) = And     $ map (fmap go) bfs
+    go (Or     bfs) = Or      $ map (fmap go) bfs
+    go (Parens bf ) = Parens  $ fmap go bf
 
 bfTraverse  :: Applicative f
             => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
@@ -61,9 +61,9 @@ bfTraverse  :: Applicative f
 bfTraverse f = go
   where
     go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] go bfs
-    go (Or     bfs) = Or     <$> traverse @[] go bfs
-    go (Parens bf ) = Parens <$>              go bf
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
 
 
 
@@ -114,10 +114,10 @@ isTrue (And []) = True
 isTrue _ = False
 
 eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
-eval f (Var x)    = f x
-eval f (And xs)   = all (eval f) xs
-eval f (Or xs)    = any (eval f) xs
-eval f (Parens x) = eval f x
+eval f (Var x)  = f x
+eval f (And xs) = all (eval f . unLoc) xs
+eval f (Or xs)  = any (eval f . unLoc) xs
+eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
@@ -128,9 +128,9 @@ simplify :: forall p. Eq (LIdP (GhcPass p))
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs)   = mkAnd (map (simplify f) xs)
-simplify f (Or xs)    = mkOr  (map (simplify f) xs)
-simplify f (Parens x) = simplify f x
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
+simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
@@ -152,11 +152,11 @@ isUnsatisfied f bf
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
 impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
-Var x  `impliesAtom` y = unLoc x == unLoc y
-And xs `impliesAtom` y = any (`impliesAtom` y) xs
--- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (`impliesAtom` y) xs
-Parens x `impliesAtom` y =  x `impliesAtom` y
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
+           -- we have all of xs, so one of them implying y is enough
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
 implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
@@ -166,16 +166,16 @@ implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
         case hyp of
             Var x | memberClauseAtoms (unLoc x) r -> True
                   | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
-            Parens hyp' -> go l { clauseExprs = hyp':hyps }     r
-            And hyps'  -> go l { clauseExprs =  hyps' ++ hyps } r
-            Or hyps'   -> all (\hyp' -> go l { clauseExprs = hyp':hyps } r) hyps'
+            Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
+            And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
+            Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
             Var x | memberClauseAtoms (unLoc x) l -> True
                   | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
-            Parens con' -> go l r { clauseExprs = con':cons }
-            And cons'   -> all (\con' -> go l r { clauseExprs = con':cons }) cons'
-            Or cons'    -> go l r { clauseExprs = cons' ++ cons }
+            Parens con' -> go l r { clauseExprs = unLoc con':cons }
+            And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
+            Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
@@ -203,10 +203,10 @@ pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
   go p (And []) = cparen (p > 0) empty
-  go p (And xs) = pprAnd p (map (go 3) xs)
+  go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
-  go p (Or  xs) = pprOr p (map (go 2) xs)
-  go p (Parens x) = go p x
+  go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
+  go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
 pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
@@ -234,7 +234,7 @@ pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> S
 pprBooleanFormulaNormal = go
   where
     go (Var x)    = pprPrefixOcc (unLoc x)
-    go (And xs)   = fsep $ punctuate comma (map go xs)
+    go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
-    go (Or xs)    = fsep $ intersperse vbar (map go xs)
-    go (Parens x) = parens (go x)
+    go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)
+    go (Parens x) = parens (go $ unLoc x)
\ No newline at end of file


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,7 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
-import GHC.Data.BooleanFormula ( BooleanFormula, pprBooleanFormulaNormal )
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -968,8 +968,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: OutputableBndrId p  => BooleanFormula (GhcPass p) -> SDoc
-pprMinimalSig = pprBooleanFormulaNormal
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2043,10 +2043,7 @@ instance ToHie PendingTcSplice where
 
 instance (HiePass p, Data (IdGhcP p))
   => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
-    toHie (L span form) =  concatM [makeNode form (locA span), toHie form]
-instance (HiePass p, Data (IdGhcP p))
-  => ToHie (BooleanFormula (GhcPass p)) where
-    toHie formula =  concatM $ case formula of
+    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -37,7 +37,7 @@ module GHC.Iface.Syntax (
         ifaceDeclFingerprints,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
-        toIfaceBooleanFormula, fromIfaceBooleanFormula,
+        fromIfaceBooleanFormula,
         -- Free Names
         freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
         freeNamesIfConDecls,
@@ -216,29 +216,22 @@ data IfaceClassBody
      ifMinDef    :: IfaceBooleanFormula       -- Minimal complete definition
     }
 
+-- See also 'BooleanFormula'
 data IfaceBooleanFormula
   = IfVar IfLclName
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
 
-toIfaceBooleanFormula :: BooleanFormula GhcRn -> IfaceBooleanFormula
-toIfaceBooleanFormula = go
-  where
-    go (Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
-    go (And bfs  ) = IfAnd    $ map go bfs
-    go (Or bfs   ) = IfOr     $ map go bfs
-    go (Parens bf) = IfParens $     go bf
-
 -- | note that this makes unbound names, so if you actually want
 -- proper Names, you'll need to properly Rename it (lookupIfaceTop).
 fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
 fromIfaceBooleanFormula = go
   where
    go (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
-   go (IfAnd bfs  ) = And    $ map go bfs
-   go (IfOr bfs   ) = Or     $ map go bfs
-   go (IfParens bf) = Parens $     go bf
+   go (IfAnd bfs  ) = And    $ map (noLocA . go) bfs
+   go (IfOr bfs   ) = Or     $ map (noLocA . go) bfs
+   go (IfParens bf) = Parens $     (noLocA . go) bf
 
 data IfaceTyConParent
   = IfNoParent


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -139,6 +139,7 @@ import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
+import GHC.CoreToIface(toIfaceBooleanFormula)
 
 import Language.Haskell.Syntax.BooleanFormula (mkOr, BooleanFormula)
 import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
@@ -305,7 +306,7 @@ mergeIfaceDecl d1 d2
 
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . mkOr . map fromIfaceBooleanFormula $ [ bf1, bf2]
+                ifMinDef = toIfaceBooleanFormula . mkOr . map (noLocA . fromIfaceBooleanFormula) $ [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -851,11 +852,12 @@ tc_iface_decl _parent ignore_prags
           return (ATI tc mb_def)
 
    tc_boolean_formula :: IfaceBooleanFormula -> IfL (BooleanFormula GhcRn)
-   tc_boolean_formula (IfVar nm    ) = BF.Var . noLocA <$>
-    (lookupIfaceTop . mkVarOccFS . ifLclNameFS) nm
-   tc_boolean_formula (IfAnd ibfs  ) = BF.And    <$> traverse tc_boolean_formula ibfs
-   tc_boolean_formula (IfOr ibfs   ) = BF.Or     <$> traverse tc_boolean_formula ibfs
-   tc_boolean_formula (IfParens ibf) = BF.Parens <$> tc_boolean_formula ibf
+   tc_boolean_formula (IfAnd ibfs  ) = BF.And    . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfOr ibfs   ) = BF.Or     . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfParens ibf) = BF.Parens .     noLocA <$>          tc_boolean_formula ibf
+   tc_boolean_formula (IfVar nm    ) = BF.Var    .     noLocA <$>          tc_id nm
+    where
+      tc_id = lookupIfaceTop . mkVarOccFS . ifLclNameFS
 
    mk_sc_doc pred = text "Superclass" <+> ppr pred
    mk_at_doc tc = text "Associated type" <+> ppr tc


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3715,26 +3715,30 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { BooleanFormula GhcPs }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
-        | {- empty -}               { mkTrue }
+        | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { BooleanFormula GhcPs }
-        : name_boolformula_and       { $1 }
+name_boolformula :: { LBooleanFormula GhcPs }
+        : name_boolformula_and      { $1 }
         | name_boolformula_and '|' name_boolformula
-                           { (Or [$1, $3]) }
+                           {% do { h <- addTrailingVbarL $1 (gl $2)
+                                 ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { BooleanFormula GhcPs }
-        : name_boolformula_and_list { (And ($1)) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
+        : name_boolformula_and_list
+                  { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [BooleanFormula GhcPs] }
-        : name_boolformula_atom  { [$1] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
+        : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
-                                 {  ($1 : $3) }
+            {% do { h <- addTrailingCommaL $1 (gl $2)
+                  ; return (h : $3) } }
 
-name_boolformula_atom :: { BooleanFormula GhcPs }
-        : '(' name_boolformula ')'  {  (Parens $2) }
-        | name_var                  {  (Var $1) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
+        : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
+                                      (AnnList Nothing (Just (mop $1)) (Just (mcp $3)) [] []) }
+        | name_var                  { sL1a $1 (Var $1) }
 
 namelist :: { Located [LocatedN RdrName] }
 namelist : name_var              { sL1 $1 [$1] }
@@ -4742,4 +4746,4 @@ combineHasLocs a b = combineSrcSpans (getHasLoc a) (getHasLoc b)
 fromTrailingN :: SrcSpanAnnN -> SrcSpanAnnA
 fromTrailingN (EpAnn anc ann cs)
     = EpAnn anc (AnnListItem (nann_trailing ann)) cs
-}
+}
\ No newline at end of file


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -1137,9 +1137,9 @@ renameSig ctxt (FixSig _ fsig)
   = do  { new_fsig <- rnSrcFixityDecl ctxt fsig
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
-renameSig ctxt sig@(MinimalSig (_, s) bf)
+renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
   = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
-       return (MinimalSig (noAnn, s) new_bf, emptyFVs)
+       return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)
   = do  { new_vs <- mapM (lookupSigOccRnN ctxt sig) vs


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ mkVar (noLocA name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,7 +402,7 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ bf)) = Just bf
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
     toMinimalDef _                             = Nothing
 
 {-
@@ -603,4 +603,4 @@ warnMissingAT name
                   $ InvalidAssoc $ InvalidAssocInstance
                   $ AssocInstanceMissing name
        ; diagnosticTc  (warn && hsc_src == HsSrcFile) diag
-                       }
+                       }
\ No newline at end of file


=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -127,19 +127,6 @@ import GHC.Prelude
 import GHC.ForeignSrcLang
 import GHC.Data.FastString
 import GHC.Utils.Outputable
-    ( SDoc,
-      Outputable(..),
-      IsLine((<+>), sep, ftext, fsep, char, text, (<>)),
-      IsOutput(empty),
-      JoinPointHood(..),
-      parens,
-      vbar,
-      brackets,
-      ifPprDebug,
-      doubleQuotes,
-      int,
-      isJoinPoint,
-      OutputableP(..) )
 import GHC.Utils.Panic
 import GHC.Utils.Binary
 import GHC.Types.SourceText


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -26,10 +26,8 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   ( LHsExpr
   , MatchGroup
   , GRHSs )
-import {-# SOURCE #-} Language.Haskell.Syntax.Pat
-  ( LPat )
-import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
-
+import {-# SOURCE #-} Language.Haskell.Syntax.Pat( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
 import Language.Haskell.Syntax.Basic ( Fixity )
@@ -464,7 +462,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (BooleanFormula pass)
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -9,16 +9,16 @@ module Language.Haskell.Syntax.BooleanFormula(
 
 import Prelude hiding ( init, last )
 import Data.List ( nub )
-import Language.Haskell.Syntax.Extension (XRec, LIdP)
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
 
 
 -- types
 type LBooleanFormula p = XRec p (BooleanFormula p)
-data BooleanFormula p = Var (LIdP p) | And [BooleanFormula p] | Or [BooleanFormula p]
-                      | Parens (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
 
 -- instances
-deriving instance Eq (LIdP p) => Eq (BooleanFormula p)
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
 
 -- smart constructors
 -- see note [Simplification of BooleanFormulas]
@@ -35,28 +35,28 @@ mkBool False = mkFalse
 mkBool True  = mkTrue
 
 -- Make a conjunction, and try to simplify
-mkAnd :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
 mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
   where
   -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: BooleanFormula p -> Maybe [BooleanFormula p]
-  fromAnd bf = case bf of
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
     (And xs) -> Just xs
      -- assume that xs are already simplified
      -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
     (Or [])  -> Nothing
      -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
     _        -> Just [bf]
-  mkAnd' [x] = x
+  mkAnd' [x] = unXRec @p x
   mkAnd' xs = And xs
 
-mkOr :: Eq (LIdP p) => [BooleanFormula p] -> BooleanFormula p
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
 mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
   where
   -- See Note [Simplification of BooleanFormulas]
-  fromOr bf = case  bf of
+  fromOr bf = case unXRec @p bf of
     (Or xs)  -> Just xs
     (And []) -> Nothing
     _        -> Just [bf]
-  mkOr' [x] = x
-  mkOr' xs  = Or xs
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
=====================================
@@ -990,10 +990,10 @@ ppClassDecl
           ]
 
       -- Minimal complete definition
-      minimalBit = case [s | MinimalSig _ s <- sigs] of
+      minimalBit = case [s | MinimalSig _ (L _ s) <- sigs] of
         -- Miminal complete definition = every shown method
         And xs : _
-          | sort [getName n | (Var (L _ n)) <- xs]
+          | sort [getName n | L _ (Var (L _ n)) <- xs]
               == sort [getName n | ClassOpSig _ _ ns _ <- sigs, L _ n <- ns] ->
               noHtml
         -- Minimal complete definition = the only shown method
@@ -1007,11 +1007,11 @@ ppClassDecl
         _ -> noHtml
 
       ppMinimal _ (Var (L _ n)) = ppDocName qual Prefix True n
-      ppMinimal _ (And fs) = foldr1 (\a b -> a +++ ", " +++ b) $ map (ppMinimal True) fs
-      ppMinimal p (Or fs) = wrap $ foldr1 (\a b -> a +++ " | " +++ b) $ map (ppMinimal False ) fs
+      ppMinimal _ (And fs) = foldr1 (\a b -> a +++ ", " +++ b) $ map (ppMinimal True . unLoc) fs
+      ppMinimal p (Or fs) = wrap $ foldr1 (\a b -> a +++ " | " +++ b) $ map (ppMinimal False . unLoc) fs
         where
           wrap | p = parens | otherwise = id
-      ppMinimal p (Parens x) = ppMinimal p x
+      ppMinimal p (Parens x) = ppMinimal p (unLoc x)
 
       -- Instances
       instancesBit =


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -177,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -772,9 +772,9 @@ renameSig sig = case sig of
   FixSig _ (FixitySig _ lnames fixity) -> do
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
-  MinimalSig _ s -> do
+  MinimalSig _ (L l s) -> do
     s' <- bfTraverse (traverse lookupRn) s
-    return $ MinimalSig noExtField s'
+    return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
@@ -782,12 +782,12 @@ bfTraverse  :: Applicative f
             => (LIdP (GhcPass p) -> f (LIdP DocNameI))
             -> BooleanFormula (GhcPass p)
             -> f (BooleanFormula DocNameI)
-bfTraverse f = go 
-  where 
+bfTraverse f = go
+  where
     go (Var    a  ) = Var    <$> f a
-    go (And    bfs) = And    <$> traverse @[] go bfs
-    go (Or     bfs) = Or     <$> traverse @[] go bfs
-    go (Parens bf ) = Parens <$>              go bf
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
 
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35fe87ee309a87d7eaf72eca6cba538c0a90c420

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 14:12:57 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 10:12:57 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] Refactored BooleanFormula to
 be in line with TTG (#21592)
Message-ID: <671e4a69a31f6_c015c39159816366@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
3a1114d9 by Hassan Al-Awwadi at 2024-10-27T15:10:02+01:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit.
- We moved the definition of BooleanFormula over to L.H.S.BooleanFormula
- We parameterized the BooleanFormula over the pass

The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula.
Because its parameterized over the pass its no longer a functor or
traversable, but we defined bfMap and bfTraverse for the cases where we
needed fmap and traverse originally. Most other changes are just churn.

There is one slightly harder change which is for IFaceBooleanFormula,
it used to be the case that we went back and forth between IFaceBooleanFormula
and regular BooleanFormula without any worry, since BooleanFormula could
contain an IfLclName without any issue. Since this is no longer the case,
we also need to go back and forth between Name and IfLclName when we do
toIfaceBooleanFormula/fromIfaceBooleanFormula. Not that big of a deal, though.

- - - - -


23 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
+import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -35,7 +36,7 @@ import GHC.Utils.Panic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
 import GHC.Utils.Outputable
-import GHC.Data.BooleanFormula (BooleanFormula, mkTrue)
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula, mkTrue )
 
 import qualified Data.Data as Data
 
@@ -135,7 +136,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula Name -- Required methods
+type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -43,6 +43,7 @@ module GHC.CoreToIface
     , toIfaceVar
       -- * Other stuff
     , toIfaceLFInfo
+    , toIfaceBooleanFormula
       -- * CgBreakInfo
     , dehydrateCgBreakInfo
     ) where
@@ -69,6 +70,7 @@ import GHC.Builtin.Types ( heqTyCon )
 
 import GHC.Iface.Syntax
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula qualified as BF(BooleanFormula(..))
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -82,11 +84,14 @@ import GHC.Types.Var.Set
 import GHC.Types.Tickish
 import GHC.Types.Demand ( isNopSig )
 import GHC.Types.Cpr ( topCprSig )
+import GHC.Types.SrcLoc (unLoc)
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Misc
 
+import GHC.Hs.Extension (GhcRn)
+
 import Data.Maybe ( isNothing, catMaybes )
 
 {- Note [Avoiding space leaks in toIface*]
@@ -537,6 +542,14 @@ toIfGuidance src guidance
   , isStableSource src = IfWhen arity unsat_ok boring_ok
   | otherwise          = IfNoGuidance
 
+toIfaceBooleanFormula :: BF.BooleanFormula GhcRn -> IfaceBooleanFormula
+toIfaceBooleanFormula = go
+  where
+    go (BF.Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
+    go (BF.And bfs  ) = IfAnd    $ map (go . unLoc) bfs
+    go (BF.Or bfs   ) = IfOr     $ map (go . unLoc) bfs
+    go (BF.Parens bf) = IfParens $     (go . unLoc) bf
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,5 +1,6 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable  #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
 -- | Boolean formulas without quantifiers and without negation.
@@ -8,73 +9,62 @@
 -- This module is used to represent minimal complete definitions for classes.
 --
 module GHC.Data.BooleanFormula (
-        BooleanFormula(..), LBooleanFormula,
-        mkFalse, mkTrue, mkAnd, mkOr, mkVar,
+        module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
+        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
-        pprBooleanFormula, pprBooleanFormulaNice
+        pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
   ) where
 
-import GHC.Prelude hiding ( init, last )
-
-import Data.List ( nub, intersperse )
+import Data.List ( intersperse )
 import Data.List.NonEmpty ( NonEmpty (..), init, last )
-import Data.Data
 
-import GHC.Utils.Monad
-import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( LocatedL )
-import GHC.Types.SrcLoc
+import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
+import GHC.Types.SrcLoc (unLoc)
+import GHC.Utils.Outputable
+import GHC.Parser.Annotation ( SrcSpanAnnL )
+import GHC.Hs.Extension (GhcPass (..), OutputableBndrId)
+import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
+import Language.Haskell.Syntax.BooleanFormula
+
 
 ----------------------------------------------------------------------
 -- Boolean formula type and smart constructors
 ----------------------------------------------------------------------
 
-type LBooleanFormula a = LocatedL (BooleanFormula a)
-
-data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a]
-                      | Parens (LBooleanFormula a)
-  deriving (Eq, Data, Functor, Foldable, Traversable)
-
-mkVar :: a -> BooleanFormula a
-mkVar = Var
+type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
-mkFalse, mkTrue :: BooleanFormula a
-mkFalse = Or []
-mkTrue = And []
+-- if we had Functor/Traversable (LbooleanFormula p) we could use that
+-- as a constraint and we wouldn't need to specialize to just GhcPass p,
+-- but becuase LBooleanFormula is a type synonym such a constraint is
+-- impossible.
 
--- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula a
-mkBool False = mkFalse
-mkBool True  = mkTrue
-
--- Make a conjunction, and try to simplify
-mkAnd :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkAnd = maybe mkFalse (mkAnd' . nub) . concatMapM fromAnd
+-- BooleanFormula can't be an instance of functor because it can't lift
+-- arbitrary functions `a -> b`, only functions of type `LIdP a -> LIdP b`
+-- ditto for Traversable.
+bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
+      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
+bfMap f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula a -> Maybe [LBooleanFormula a]
-  fromAnd (L _ (And xs)) = Just xs
-     -- assume that xs are already simplified
-     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
-  fromAnd (L _ (Or [])) = Nothing
-     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
-  fromAnd x = Just [x]
-  mkAnd' [x] = unLoc x
-  mkAnd' xs = And xs
-
-mkOr :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkOr = maybe mkTrue (mkOr' . nub) . concatMapM fromOr
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (fmap go) bfs
+    go (Or     bfs) = Or      $ map (fmap go) bfs
+    go (Parens bf ) = Parens  $ fmap go bf
+
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (GhcPass p'))
+bfTraverse f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromOr (L _ (Or xs)) = Just xs
-  fromOr (L _ (And [])) = Nothing
-  fromOr x = Just [x]
-  mkOr' [x] = unLoc x
-  mkOr' xs = Or xs
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 
 
 {-
@@ -115,15 +105,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula a -> Bool
+isFalse :: BooleanFormula (GhcPass p) -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula a -> Bool
+isTrue :: BooleanFormula (GhcPass p) -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (a -> Bool) -> BooleanFormula a -> Bool
+eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
 eval f (Var x)  = f x
 eval f (And xs) = all (eval f . unLoc) xs
 eval f (Or xs)  = any (eval f . unLoc) xs
@@ -131,18 +121,24 @@ eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: Eq a => (a -> Maybe Bool) -> BooleanFormula a -> BooleanFormula a
+simplify :: forall p. Eq (LIdP (GhcPass p))
+          => (LIdP (GhcPass p) ->  Maybe Bool)
+          -> BooleanFormula (GhcPass p)
+          -> BooleanFormula (GhcPass p)
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (\(L l x) -> L l (simplify f x)) xs)
-simplify f (Or xs) = mkOr (map (\(L l x) -> L l (simplify f x)) xs)
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
 simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq a => (a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
+isUnsatisfied :: Eq (LIdP (GhcPass p))
+              => (LIdP (GhcPass p) -> Bool)
+              -> BooleanFormula (GhcPass p)
+              -> Maybe (BooleanFormula (GhcPass p))
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -155,42 +151,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq a => BooleanFormula a -> a -> Bool
-Var x  `impliesAtom` y = x == y
-And xs `impliesAtom` y = any (\x -> (unLoc x) `impliesAtom` y) xs
+impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
            -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> (unLoc x) `impliesAtom` y) xs
-Parens x `impliesAtom` y = (unLoc x) `impliesAtom` y
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
-implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
+implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable a => Clause a -> Clause a -> Bool
+    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms x r -> True
-                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms (unLoc x) r -> True
+                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
             And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms x l -> True
-                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
+            Var x | memberClauseAtoms (unLoc x) l -> True
+                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = unLoc con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause a = Clause {
-        clauseAtoms :: UniqSet a,
-        clauseExprs :: [BooleanFormula a]
+data Clause p = Clause {
+        clauseAtoms :: UniqSet (IdP p),
+        clauseExprs :: [BooleanFormula p]
     }
-extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
+extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
+memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -199,28 +195,29 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula' :: (Rational -> a -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
-  go p (And []) = cparen (p > 0) $ empty
+  go p (And []) = cparen (p > 0) empty
   go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
   go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
   go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
+pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -230,15 +227,14 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance (OutputableBndr a) => Outputable (BooleanFormula a) where
+instance OutputableBndrId p => Outputable (BooleanFormula (GhcPass p)) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: (OutputableBndr a)
-                        => BooleanFormula a -> SDoc
+pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc x
+    go (Var x)    = pprPrefixOcc (unLoc x)
     go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)
-    go (Parens x) = parens (go $ unLoc x)
+    go (Parens x) = parens (go $ unLoc x)
\ No newline at end of file


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,6 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -47,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Var
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.Name
 
 import GHC.Utils.Outputable
@@ -968,9 +968,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: (OutputableBndr name)
-              => LBooleanFormula (GenLocated l name) -> SDoc
-pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -107,6 +107,7 @@ module GHC.Hs.Decls (
 import GHC.Prelude
 
 import Language.Haskell.Syntax.Decls
+import Language.Haskell.Syntax.Extension
 
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprUntypedSplice )
         -- Because Expr imports Decls via HsBracket
@@ -116,7 +117,7 @@ import GHC.Hs.Type
 import GHC.Hs.Doc
 import GHC.Types.Basic
 import GHC.Core.Coercion
-import Language.Haskell.Syntax.Extension
+
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
 import GHC.Types.Name


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -33,6 +33,8 @@ import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
+import GHC.Data.BooleanFormula (BooleanFormula(..))
+import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -590,3 +592,6 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+
+deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -13,7 +13,6 @@
 module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
-   , toIfaceBooleanFormula
    )
 where
 
@@ -33,21 +32,17 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
 import GHC.Types.TyThing
-import GHC.Types.SrcLoc
 
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
 import GHC.Data.Maybe
-import GHC.Data.BooleanFormula
-
 import Data.List ( findIndex, mapAccumL )
 
 {-
@@ -287,7 +282,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula $ fmap (mkIfLclName . getOccFS) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -335,10 +330,3 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
-
-toIfaceBooleanFormula :: BooleanFormula IfLclName -> IfaceBooleanFormula
-toIfaceBooleanFormula = \case
-    Var nm    -> IfVar    nm
-    And bfs   -> IfAnd    (map (toIfaceBooleanFormula . unLoc) bfs)
-    Or bfs    -> IfOr     (map (toIfaceBooleanFormula . unLoc) bfs)
-    Parens bf -> IfParens (toIfaceBooleanFormula . unLoc $ bf)


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2041,8 +2041,9 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance ToHie (LBooleanFormula (LocatedN Name)) where
-  toHie (L span form) = concatM $ makeNode form (locA span) : case form of
+instance (HiePass p, Data (IdGhcP p))
+  => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -35,10 +35,9 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
-        fromIfaceBooleanFormula,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
-
+        fromIfaceBooleanFormula,
         -- Free Names
         freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
         freeNamesIfConDecls,
@@ -51,7 +50,10 @@ module GHC.Iface.Syntax (
 
 import GHC.Prelude
 
+import GHC.Builtin.Names(mkUnboundName)
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula (pprBooleanFormula, isTrue)
+
 import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey,
                            constraintKindTyConKey )
 import GHC.Types.Unique ( hasKey )
@@ -62,9 +64,9 @@ import GHC.Types.Demand
 import GHC.Types.Cpr
 import GHC.Core.Class
 import GHC.Types.FieldLabel
-import GHC.Types.Name.Set
 import GHC.Core.Coercion.Axiom ( BranchIndex )
 import GHC.Types.Name
+import GHC.Types.Name.Set
 import GHC.Types.Name.Reader
 import GHC.Types.CostCentre
 import GHC.Types.Literal
@@ -75,7 +77,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
@@ -94,6 +95,8 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
                        seqList, zipWithEqual )
 
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
+
 import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
@@ -213,18 +216,22 @@ data IfaceClassBody
      ifMinDef    :: IfaceBooleanFormula       -- Minimal complete definition
     }
 
+-- See also 'BooleanFormula'
 data IfaceBooleanFormula
   = IfVar IfLclName
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
 
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
-fromIfaceBooleanFormula = \case
-    IfVar nm     -> Var    nm
-    IfAnd ibfs   -> And    (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfOr ibfs    -> Or     (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfParens ibf -> Parens (noLocA . fromIfaceBooleanFormula $ ibf)
+-- | note that this makes unbound names, so if you actually want
+-- proper Names, you'll need to properly Rename it (lookupIfaceTop).
+fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
+fromIfaceBooleanFormula = go
+  where
+   go (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
+   go (IfAnd bfs  ) = And    $ map (noLocA . go) bfs
+   go (IfOr bfs   ) = Or     $ map (noLocA . go) bfs
+   go (IfParens bf) = Parens $     (noLocA . go) bf
 
 data IfaceTyConParent
   = IfNoParent
@@ -1039,13 +1046,15 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | showSub ss sg = Just $  pprIfaceClassOp ss sg
         | otherwise     = Nothing
 
-      pprMinDef :: BooleanFormula IfLclName -> SDoc
+      pprMinDef :: BooleanFormula GhcRn -> SDoc
       pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
         pprBooleanFormula
-          (\_ def -> cparen (isLexSym def) (ppr def)) 0 (fmap ifLclNameFS minDef) <+>
+          (\_ def -> let fs = getOccFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+
+
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -32,6 +32,7 @@ module GHC.IfaceToCore (
         hydrateCgBreakInfo
  ) where
 
+
 import GHC.Prelude
 
 import GHC.ByteCode.Types
@@ -43,7 +44,6 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (toIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -123,11 +123,13 @@ import GHC.Types.Tickish
 import GHC.Types.TyThing
 import GHC.Types.Error
 
+import GHC.Parser.Annotation (noLocA)
+
+import GHC.Hs.Extension ( GhcRn )
+
 import GHC.Fingerprint
-import qualified GHC.Data.BooleanFormula as BF
 
 import Control.Monad
-import GHC.Parser.Annotation
 import GHC.Driver.Env.KnotVars
 import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
@@ -137,6 +139,10 @@ import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
+import GHC.CoreToIface(toIfaceBooleanFormula)
+
+import Language.Haskell.Syntax.BooleanFormula (mkOr, BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
 {-
@@ -297,9 +303,10 @@ mergeIfaceDecl d1 d2
                   plusNameEnv_C mergeIfaceClassOp
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
+
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . BF.mkOr . map (noLocA . fromIfaceBooleanFormula) $ [bf1, bf2]
+                ifMinDef = toIfaceBooleanFormula . mkOr . map (noLocA . fromIfaceBooleanFormula) $ [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
@@ -795,8 +802,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef_occ = fromIfaceBooleanFormula if_mindef
-    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) mindef_occ
+    ; mindef <- tc_boolean_formula if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)
@@ -845,6 +851,14 @@ tc_iface_decl _parent ignore_prags
                   -- e.g.   type AT a; type AT b = AT [b]   #8002
           return (ATI tc mb_def)
 
+   tc_boolean_formula :: IfaceBooleanFormula -> IfL (BooleanFormula GhcRn)
+   tc_boolean_formula (IfAnd ibfs  ) = BF.And    . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfOr ibfs   ) = BF.Or     . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfParens ibf) = BF.Parens .     noLocA <$>          tc_boolean_formula ibf
+   tc_boolean_formula (IfVar nm    ) = BF.Var    .     noLocA <$>          tc_id nm
+    where
+      tc_id = lookupIfaceTop . mkVarOccFS . ifLclNameFS
+
    mk_sc_doc pred = text "Superclass" <+> ppr pred
    mk_at_doc tc = text "Associated type" <+> ppr tc
    mk_op_doc op_name op_ty = text "Class op" <+> sep [ppr op_name, ppr op_ty]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -39,9 +39,9 @@ module GHC.Parser
 where
 
 -- base
-import Control.Monad    ( unless, liftM, when, (<=<) )
+import Control.Monad      ( unless, liftM, when, (<=<) )
 import GHC.Exts
-import Data.Maybe       ( maybeToList )
+import Data.Maybe         ( maybeToList )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
@@ -3715,27 +3715,27 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
         | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { LBooleanFormula (LocatedN RdrName) }
-        : name_boolformula_and                      { $1 }
+name_boolformula :: { LBooleanFormula GhcPs }
+        : name_boolformula_and      { $1 }
         | name_boolformula_and '|' name_boolformula
                            {% do { h <- addTrailingVbarL $1 (gl $2)
                                  ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
         : name_boolformula_and_list
                   { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula (LocatedN RdrName)] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
         : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
             {% do { h <- addTrailingCommaL $1 (gl $2)
                   ; return (h : $3) } }
 
-name_boolformula_atom :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
         : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
                                       (AnnList Nothing (Just (mop $1)) (Just (mcp $3)) [] []) }
         | name_var                  { sL1a $1 (Var $1) }
@@ -4746,4 +4746,4 @@ combineHasLocs a b = combineSrcSpans (getHasLoc a) (getHasLoc b)
 fromTrailingN :: SrcSpanAnnN -> SrcSpanAnnA
 fromTrailingN (EpAnn anc ann cs)
     = EpAnn anc (AnnListItem (nann_trailing ann)) cs
-}
+}
\ No newline at end of file


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,6 +80,7 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
+import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1137,7 +1138,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
-  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just (fmap unLoc bf)
-    toMinimalDef _                               = Nothing
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef _                             = Nothing
 
 {-
 Note [Polymorphic methods]
@@ -603,4 +603,4 @@ warnMissingAT name
                   $ InvalidAssoc $ InvalidAssocInstance
                   $ AssocInstanceMissing name
        ; diagnosticTc  (warn && hsc_src == HsSrcFile) diag
-                       }
+                       }
\ No newline at end of file


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -26,15 +26,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   ( LHsExpr
   , MatchGroup
   , GRHSs )
-import {-# SOURCE #-} Language.Haskell.Syntax.Pat
-  ( LPat )
-
+import {-# SOURCE #-} Language.Haskell.Syntax.Pat( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
 import Language.Haskell.Syntax.Basic ( Fixity )
 
 import GHC.Types.Basic (InlinePragma)
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 
 import Data.Void
@@ -464,7 +462,7 @@ data Sig pass
         --      'GHC.Parser.Annotation.AnnClose'
 
         -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -0,0 +1,62 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+
+module Language.Haskell.Syntax.BooleanFormula(
+  BooleanFormula(..), LBooleanFormula,
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr
+  ) where
+
+import Prelude hiding ( init, last )
+import Data.List ( nub )
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+
+
+-- types
+type LBooleanFormula p = XRec p (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
+
+-- instances
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+
+-- smart constructors
+-- see note [Simplification of BooleanFormulas]
+mkVar :: LIdP p -> BooleanFormula p
+mkVar = Var
+
+mkFalse, mkTrue :: BooleanFormula p
+mkFalse = Or []
+mkTrue = And []
+
+-- Convert a Bool to a BooleanFormula
+mkBool :: Bool -> BooleanFormula p
+mkBool False = mkFalse
+mkBool True  = mkTrue
+
+-- Make a conjunction, and try to simplify
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
+    (And xs) -> Just xs
+     -- assume that xs are already simplified
+     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
+    (Or [])  -> Nothing
+     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
+    _        -> Just [bf]
+  mkAnd' [x] = unXRec @p x
+  mkAnd' xs = And xs
+
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromOr bf = case unXRec @p bf of
+    (Or xs)  -> Just xs
+    (And []) -> Nothing
+    _        -> Just [bf]
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
compiler/ghc.cabal.in
=====================================
@@ -990,6 +990,7 @@ Library
         Language.Haskell.Syntax
         Language.Haskell.Syntax.Basic
         Language.Haskell.Syntax.Binds
+        Language.Haskell.Syntax.BooleanFormula
         Language.Haskell.Syntax.Decls
         Language.Haskell.Syntax.Expr
         Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -234,6 +234,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -258,6 +258,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -3010,7 +3010,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4703,7 +4703,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -45,6 +45,7 @@ import GHC.Builtin.Types
   , promotedNilDataCon
   , unitTy
   )
+
 import GHC.Builtin.Types.Prim (alphaTyVars)
 import GHC.Core.Class
 import GHC.Core.Coercion.Axiom
@@ -176,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA . fmap noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -19,6 +19,8 @@
 -- Portability :  portable
 module Haddock.Interface.Rename (renameInterface) where
 
+import Prelude hiding (mapM)
+
 import Control.Applicative ()
 import Control.DeepSeq (force)
 import Control.Monad hiding (mapM)
@@ -28,12 +30,13 @@ import Data.Foldable (traverse_)
 import qualified Data.Map.Strict as Map
 import qualified Data.Set as Set
 import Data.Traversable (mapM)
+
 import GHC hiding (NoLink)
 import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName)
 import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
-import Prelude hiding (mapM)
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -770,11 +773,22 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- traverse (traverse lookupRn) s
+    s' <- bfTraverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP DocNameI))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula DocNameI)
+bfTraverse f = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do
   lname' <- renameNameL lname


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -52,6 +52,7 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 import GHC
 import qualified GHC.Data.Strict as Strict
+import GHC.Data.BooleanFormula (BooleanFormula)
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
@@ -818,6 +819,7 @@ type instance Anno (HsDecl DocNameI) = SrcSpanAnnA
 type instance Anno (FamilyResultSig DocNameI) = EpAnn NoEpAnns
 type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
+type instance Anno (BooleanFormula DocNameI) = SrcSpanAnnL
 
 type XRecCond a =
   ( XParTy a ~ AnnParen



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3a1114d9e56b3b0b6a6698381508cb3264e2f511

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 14:15:44 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 10:15:44 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 30 commits: Interpreter: Add
 locking for communication with external interpreter
Message-ID: <671e4b10847bb_c015c384c58185db@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
b2845ca6 by Hassan Al-Awwadi at 2024-10-27T15:15:21+01:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit.
- We moved the definition of BooleanFormula over to L.H.S.BooleanFormula
- We parameterized the BooleanFormula over the pass

The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula.
Because its parameterized over the pass its no longer a functor or
traversable, but we defined bfMap and bfTraverse for the cases where we
needed fmap and traverse originally. Most other changes are just churn.

There is one slightly harder change which is for IFaceBooleanFormula,
it used to be the case that we went back and forth between IFaceBooleanFormula
and regular BooleanFormula without any worry, since BooleanFormula could
contain an IfLclName without any issue. Since this is no longer the case,
we also need to go back and forth between Name and IfLclName when we do
toIfaceBooleanFormula/fromIfaceBooleanFormula. Not that big of a deal, though.

- - - - -


30 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Bag.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a1114d9e56b3b0b6a6698381508cb3264e2f511...b2845ca6325fdd7242570d7329a97148b527502a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a1114d9e56b3b0b6a6698381508cb3264e2f511...b2845ca6325fdd7242570d7329a97148b527502a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 15:23:51 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 11:23:51 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] Removed a bunch of warnings.
 Hopefully none remain.
Message-ID: <671e5b07e20ef_14b61021d1589839e@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
9eab1e9a by Hassan Al-Awwadi at 2024-10-27T16:23:21+01:00
Removed a bunch of warnings. Hopefully none remain.

- - - - -


23 changed files:

- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs


Changes:

=====================================
compiler/GHC/Core/Opt/WorkWrap.hs
=====================================
@@ -831,8 +831,8 @@ mkWWBindPair ww_opts fn_id fn_info fn_args fn_body work_uniq div
 
     work_rhs = work_fn (mkLams fn_args fn_body)
     work_act = case fn_inline_spec of  -- See Note [Worker activation]
-                   NoInline _  -> inl_act fn_inl_prag
-                   _           -> inl_act wrap_prag
+                   NoInline _  -> inl_act' fn_inl_prag
+                   _           -> inl_act' wrap_prag
 
     work_prag = InlinePragma { inl_ext = InlExt (SourceText $ fsLit "{-# INLINE") Nothing
                              , inl_inline = fn_inline_spec
@@ -893,10 +893,17 @@ mkWWBindPair ww_opts fn_id fn_info fn_args fn_body work_uniq div
                         -- about a loop breaker with an INLINE rule
 
     fn_inl_prag     = inlinePragInfo fn_info
-    fn_inline_spec  = inl_inline fn_inl_prag
+    fn_inline_spec  = inl_inline' fn_inl_prag
     fn_unfolding    = realUnfoldingInfo fn_info
     fn_rules        = ruleInfoRules (ruleInfo fn_info)
 
+    inl_inline' (XCInlinePragma imp) = dataConCantHappen imp
+    inl_inline' (InlinePragma{ inl_inline = inline }) = inline
+
+    inl_act' (XCInlinePragma imp) = dataConCantHappen imp
+    inl_act' (InlinePragma{ inl_act = act }) = act
+
+
 mkStrWrapperInlinePrag :: InlinePragma GhcTc -> [CoreRule] -> InlinePragma GhcTc
 mkStrWrapperInlinePrag (XCInlinePragma impossible) _ = dataConCantHappen impossible
 mkStrWrapperInlinePrag (InlinePragma { inl_inline = fn_inl


=====================================
compiler/GHC/Hs.hs
=====================================
@@ -36,7 +36,6 @@ module GHC.Hs (
         module GHC.Hs.InlinePragma,
         module GHC.Hs.OverlapPragma,
         module GHC.Parser.Annotation,
-        Fixity,
 
         HsModule(..), AnnsModule(..),
         HsParsedModule(..), XModulePs(..)
@@ -64,7 +63,6 @@ import GHC.Hs.Instances () -- For Data instances
 
 -- others:
 import GHC.Utils.Outputable
-import GHC.Types.Fixity         ( Fixity )
 import GHC.Types.SrcLoc
 import GHC.Unit.Module.Warnings
 


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -13,6 +13,8 @@
                                       -- in module Language.Haskell.Syntax.Extension
 
 {-# OPTIONS_GHC -Wno-orphans #-} -- Outputable
+{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
+{-# HLINT ignore "Use camelCase" #-}
 
 {-
 (c) The University of Glasgow 2006
@@ -864,7 +866,8 @@ ppr_sig (SpecSig _ var ty inl@(InlinePragma { inl_inline = spec }))
       pragmaSrc = case spec of
         NoUserInlinePrag _ -> "{-# " ++ extractSpecPragName (inl_src inl)
         _                  -> "{-# " ++ extractSpecPragName (inl_src inl)  ++ "_INLINE"
-ppr_sig (InlineSig _ var inl)
+ppr_sig (InlineSig _ _   (XCInlinePragma imp)) = dataConCantHappen imp
+ppr_sig (InlineSig _ var inl@(InlinePragma{}))
   = ppr_pfx <+> pprInline inl <+> pprPrefixOcc (unLoc var) <+> text "#-}"
     where
       ppr_pfx = case inlinePragmaSource inl of
@@ -904,8 +907,10 @@ hsSigDoc (PatSynSig {})         = text "pattern synonym signature"
 hsSigDoc (ClassOpSig _ is_deflt _ _)
  | is_deflt                     = text "default type signature"
  | otherwise                    = text "class method signature"
-hsSigDoc (SpecSig _ _ _ inl)    = (inlinePragmaName . inl_inline $ inl) <+> text "pragma"
-hsSigDoc (InlineSig _ _ prag)   = (inlinePragmaName . inl_inline $ prag) <+> text "pragma"
+hsSigDoc (SpecSig _ _ _ (InlinePragma{inl_inline = spec}))   = inlinePragmaName spec <+> text "pragma"
+hsSigDoc (SpecSig _ _ _ (XCInlinePragma imp))                = dataConCantHappen imp
+hsSigDoc (InlineSig _ _ (InlinePragma{inl_inline = spec}))   = inlinePragmaName spec <+> text "pragma"
+hsSigDoc (InlineSig _ _ (XCInlinePragma imp))                = dataConCantHappen imp
 -- Using the 'inlinePragmaName' function ensures that the pragma name for any
 -- one of the INLINE/INLINABLE/NOINLINE pragmas are printed after being extracted
 -- from the InlineSpec field of the pragma.


=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -27,7 +27,7 @@ module GHC.Hs.InlinePragma(
         pprInline, pprInlineDebug,
         convertInlinePragma, convertInlineSpec, convertActivation,
 
-        set_pragma_inline, set_pragma_activation, set_pragma_rule, set_pragma_sat
+        set_pragma_rule, set_pragma_sat
 ) where
 
 import GHC.Prelude


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -146,7 +146,6 @@ import GHC.Types.Name.Reader
 import GHC.Types.Var
 import GHC.Types.Basic
 import GHC.Types.SrcLoc
-import GHC.Types.Fixity
 import GHC.Types.SourceText
 
 import GHC.Data.FastString
@@ -165,7 +164,6 @@ import Data.IntMap ( IntMap )
 import qualified Data.IntMap.Strict as IntMap
 import Data.Map ( Map )
 import qualified Data.Map.Strict as Map
-import GHC.Core.TyCon (TyConFlavour)
 
 {-
 ************************************************************************


=====================================
compiler/GHC/HsToCore/Errors/Types.hs
=====================================
@@ -6,14 +6,13 @@ module GHC.HsToCore.Errors.Types where
 
 import GHC.Prelude
 
-import GHC.Core (CoreRule, CoreExpr, RuleName)
+import GHC.Core (CoreRule, CoreExpr)
 import GHC.Core.DataCon
 import GHC.Core.ConLike
 import GHC.Core.Type
 import GHC.Driver.DynFlags (DynFlags, xopt)
 import GHC.Driver.Flags (WarningFlag)
 import GHC.Hs
-import GHC.Hs.InlinePragma (Activation)
 import GHC.HsToCore.Pmc.Solver.Types
 import GHC.Types.Error
 import GHC.Types.ForeignCall


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -74,12 +74,10 @@ import GHC.Data.Maybe
 
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Unique
-import GHC.Types.Basic
 import GHC.Types.ForeignCall
 import GHC.Types.Var
 import GHC.Types.Id
 import GHC.Types.SourceText
-import GHC.Types.Fixity
 import GHC.Types.TyThing
 import GHC.Types.Name hiding( varName, tcName )
 import GHC.Types.Name.Env
@@ -89,8 +87,6 @@ import Data.Kind (Constraint)
 
 import qualified GHC.LanguageExtensions as LangExt
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Data.ByteString ( unpack )
 import Control.Monad
 import Data.List (sort, sortBy)
@@ -1079,13 +1075,13 @@ rep_inline :: LocatedN Name
            -> InlinePragma (GhcPass p)      -- Never defaultInlinePragma
            -> SrcSpan
            -> MetaM [(SrcSpan, Core (M TH.Dec))]
+rep_inline _  (XCInlinePragma imp) _ = dataConCantHappen imp
 rep_inline nm ispec loc
   | Opaque {} <- inl_inline ispec
   = do { nm1    <- lookupLOcc nm
        ; opq <- repPragOpaque nm1
        ; return [(loc, opq)]
        }
-
 rep_inline nm ispec loc
   = do { nm1    <- lookupLOcc nm
        ; inline <- repInline $ inl_inline ispec
@@ -1098,6 +1094,7 @@ rep_inline nm ispec loc
 rep_specialise :: LocatedN Name -> LHsSigType GhcRn -> InlinePragma (GhcPass p)
                -> SrcSpan
                -> MetaM [(SrcSpan, Core (M TH.Dec))]
+rep_specialise _  _ (XCInlinePragma imp) _ = dataConCantHappen imp
 rep_specialise nm ty ispec loc
   = do { nm1 <- lookupLOcc nm
        ; ty1 <- repHsSigType ty
@@ -1144,6 +1141,7 @@ repInline (Opaque            _ )   = panic "repInline: Opaque"
 repInline (Inline            _ )   = dataCon inlineDataConName
 repInline (Inlinable         _ )   = dataCon inlinableDataConName
 repInline (NoUserInlinePrag  _ )   = notHandled ThNoUserInline
+repInline (XInlineSpec     imp )   = dataConCantHappen imp
 
 repRuleMatch :: RuleMatchInfo -> MetaM (Core TH.RuleMatch)
 repRuleMatch ConLike = dataCon conLikeDataConName


=====================================
compiler/GHC/Parser.y
=====================================
@@ -95,8 +95,6 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, sumTyCon,
                            listTyCon_RDR, consDataCon_RDR,
                            unrestrictedFunTyCon )
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import qualified Data.Semigroup as Semi
 }
 


=====================================
compiler/GHC/Parser/Errors/Types.hs
=====================================
@@ -6,7 +6,6 @@ module GHC.Parser.Errors.Types where
 
 import GHC.Prelude
 
-import GHC.Core.TyCon (Role)
 import GHC.Data.FastString
 import GHC.Hs
 import GHC.Parser.Types


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -131,7 +131,7 @@ import GHC.Hs           -- Lots of it
 import GHC.Core.TyCon          ( TyCon, isTupleTyCon, tyConSingleDataCon_maybe )
 import GHC.Core.DataCon        ( DataCon, dataConTyCon, dataConName )
 import GHC.Core.ConLike        ( ConLike(..) )
-import GHC.Core.Coercion.Axiom ( Role, fsFromRole )
+import GHC.Core.Coercion.Axiom ( fsFromRole )
 import GHC.Types.Name.Reader
 import GHC.Types.Name
 import GHC.Types.Basic


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -74,8 +74,6 @@ import GHC.Data.Maybe          ( orElse, mapMaybe )
 import GHC.Data.OrdList
 import qualified GHC.LanguageExtensions as LangExt
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -91,8 +91,6 @@ import GHC.Data.Bag
 import GHC.Data.Maybe ( expectJust )
 import GHC.Unit.Module
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Data.List  ( find, partition, intersperse )
 
 -- | A declarative description of an auxiliary binding that should be


=====================================
compiler/GHC/Tc/Deriv/Generics.hs
=====================================
@@ -45,8 +45,6 @@ import GHC.Iface.Env    ( newGlobalBinder )
 import GHC.Types.Name hiding ( varName )
 import GHC.Types.Name.Reader
 import GHC.Types.SourceText
-import GHC.Types.Fixity
-import GHC.Types.Basic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Env
 import GHC.Types.Var.Set (elemVarSet)
@@ -63,8 +61,6 @@ import GHC.Utils.Misc
 import GHC.Driver.DynFlags
 import GHC.Data.FastString
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Control.Monad (mplus)
 import Data.List (zip4, partition)
 import qualified Data.List as Partial (last)


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -217,7 +217,7 @@ import GHC.Core.FamInstEnv (FamInst)
 import GHC.Core.InstEnv (LookupInstanceErrReason, ClsInst, DFunId)
 import GHC.Core.PatSyn (PatSyn)
 import GHC.Core.Predicate (EqRel, predTypeEqRel)
-import GHC.Core.TyCon (TyCon, Role, FamTyConFlav, AlgTyConRhs)
+import GHC.Core.TyCon (TyCon, FamTyConFlav, AlgTyConRhs)
 import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag)
 import GHC.Driver.Backend (Backend)
 
@@ -229,8 +229,6 @@ import GHC.Data.FastString (FastString)
 import GHC.Data.Pair
 import GHC.Exception.Type (SomeException)
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import qualified Data.List.NonEmpty as NE
 import           Data.Typeable (Typeable)
 import qualified GHC.Internal.TH.Syntax as TH


=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -65,7 +65,6 @@ import GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 
 import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic( isBoxed )
 
 import Control.Monad
 import Data.Function


=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -27,8 +27,6 @@ module GHC.Tc.Gen.Expr
 
 import GHC.Prelude
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import {-# SOURCE #-} GHC.Tc.Gen.Splice
   ( tcTypedSplice, tcTypedBracket, tcUntypedBracket, getUntypedSpliceBody )
 


=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -59,7 +59,6 @@ import GHC.Core.DataCon
 import GHC.Core.PatSyn
 import GHC.Core.ConLike
 import GHC.Builtin.Names
-import GHC.Types.Basic hiding (SuccessFlag(..))
 import GHC.Driver.DynFlags
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
@@ -73,8 +72,6 @@ import GHC.Data.FastString
 import qualified Data.List.NonEmpty as NE
 
 import GHC.Data.List.SetOps ( getNth )
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Data.List( partition )
 import Control.Monad.Trans.Writer.CPS
 import Control.Monad.Trans.Class


=====================================
compiler/GHC/Tc/Gen/Rule.hs
=====================================
@@ -34,7 +34,7 @@ import GHC.Core.Predicate
 import GHC.Types.Id
 import GHC.Types.Var( EvVar, tyVarName )
 import GHC.Types.Var.Set
-import GHC.Types.Basic ( RuleName, NonStandardDefaultingStrategy(..) )
+import GHC.Types.Basic ( NonStandardDefaultingStrategy(..) )
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Utils.Panic


=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -592,6 +592,7 @@ add_inl_arity ar prag@(InlinePragma { inl_inline = inl_spec })
   = set_pragma_sat prag (Just ar)
   | otherwise
   = prag
+add_inl_arity _ (XCInlinePragma imp) = dataConCantHappen imp
 
 lhsBindArity :: LHsBind GhcRn -> NameEnv Arity -> NameEnv Arity
 lhsBindArity (L _ (FunBind { fun_id = id, fun_matches = ms })) env


=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -63,10 +63,11 @@ import GHC.Unit.Module.Warnings
 
 import GHC.Hs.Extension
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
 import GHC.Types.Id.Info
 import GHC.Tc.Errors.Types
 
+import Language.Haskell.Syntax.Basic (FieldLabelString(..))
+
 import Data.Functor
 import Data.Maybe
 


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -102,8 +102,6 @@ import GHC.Utils.Panic
 import GHC.Utils.Constants (debugIsOn)
 import GHC.Utils.Misc
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Control.Monad
 import Data.Foldable ( toList, traverse_ )
 import Data.Functor.Identity


=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -79,8 +79,6 @@ import GHC.Types.Unique.Set
 import GHC.Types.TyThing
 import qualified GHC.LanguageExtensions as LangExt
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import Control.Monad
 
 {-


=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -81,8 +81,6 @@ import GHC.Utils.Misc( HasDebugCallStack )
 import GHC.Types.Unique
 import GHC.Types.Unique.Supply
 
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
 import qualified Data.Kind as Hs
 
 {- *********************************************************************



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9eab1e9af0de7180a04069106d3fd921dd577c8d

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 17:24:11 2024
From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim))
Date: Sun, 27 Oct 2024 13:24:11 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/mention-clc-in-mr-template
Message-ID: <671e773b44bae_1a02c511aef496010@gitlab.mail>



Bodigrim pushed new branch wip/mention-clc-in-mr-template at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/mention-clc-in-mr-template
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 18:44:11 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Sun, 27 Oct 2024 14:44:11 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] Concentrate boot extension logic in
 Finder
Message-ID: <671e89fbcf9e3_1a02c5433924109970@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
ee10a07d by Sjoerd Visscher at 2024-10-27T19:44:01+01:00
Concentrate boot extension logic in Finder

- - - - -


8 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Location.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -854,16 +854,14 @@ hsModuleToModSummary home_keys pn hsc_src modname
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation fopts modname
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
-                              (case hsc_src of
+                             (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
+                             hsc_src
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2123,31 +2123,16 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = unsafeEncodeUtf src_fn
+            (basename, extension) = splitExtension src_fn
 
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
+            hsc_src
+              | isHaskellSigSuffix (drop 1 extension) = HsigFile
+              | isHaskellBootSuffix (drop 1 extension) = HsBootFile
+              | otherwise = HsSrcFile
 
             -- Make a ModLocation for this file, adding the @-boot@ suffix to
             -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf extension) hsc_src
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
@@ -2239,7 +2224,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2257,10 +2242,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2270,7 +2252,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env imp is_boot pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Phases.hs
=====================================
@@ -23,6 +23,7 @@ module GHC.Driver.Phases (
    isDynLibSuffix,
    isHaskellUserSrcSuffix,
    isHaskellSigSuffix,
+   isHaskellBootSuffix,
    isSourceSuffix,
 
    isHaskellishTarget,
@@ -234,7 +235,7 @@ phaseInputExt Js                  = "js"
 phaseInputExt StopLn              = "o"
 
 haskellish_src_suffixes, backpackish_suffixes, haskellish_suffixes, cish_suffixes,
-    js_suffixes, haskellish_user_src_suffixes, haskellish_sig_suffixes
+    js_suffixes, haskellish_user_src_suffixes, haskellish_sig_suffixes, haskellish_boot_suffixes
  :: [String]
 -- When a file with an extension in the haskellish_src_suffixes group is
 -- loaded in --make mode, its imports will be loaded too.
@@ -247,7 +248,8 @@ js_suffixes                  = [ "js" ]
 
 -- Will not be deleted as temp files:
 haskellish_user_src_suffixes =
-  haskellish_sig_suffixes ++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+  haskellish_sig_suffixes ++ haskellish_boot_suffixes ++ [ "hs", "lhs" ]
+haskellish_boot_suffixes     = [ "hs-boot", "lhs-boot" ]
 haskellish_sig_suffixes      = [ "hsig", "lhsig" ]
 backpackish_suffixes         = [ "bkp" ]
 
@@ -265,11 +267,12 @@ dynlib_suffixes platform = case platformOS platform of
   _         -> ["so"]
 
 isHaskellishSuffix, isBackpackishSuffix, isHaskellSrcSuffix, isCishSuffix,
-    isHaskellUserSrcSuffix, isJsSuffix, isHaskellSigSuffix
+    isHaskellUserSrcSuffix, isJsSuffix, isHaskellSigSuffix, isHaskellBootSuffix
  :: String -> Bool
 isHaskellishSuffix     s = s `elem` haskellish_suffixes
 isBackpackishSuffix    s = s `elem` backpackish_suffixes
 isHaskellSigSuffix     s = s `elem` haskellish_sig_suffixes
+isHaskellBootSuffix    s = s `elem` haskellish_boot_suffixes
 isHaskellSrcSuffix     s = s `elem` haskellish_src_suffixes
 isCishSuffix           s = s `elem` cish_suffixes
 isJsSuffix             s = s `elem` js_suffixes


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -777,24 +777,18 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+    let location1 = mkHomeModLocation fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) src_flavour
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -807,11 +801,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
         location5 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
     return location5
     where
       fopts = initFinderOpts dflags


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -896,9 +896,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,6 +15,7 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
@@ -157,6 +158,13 @@ findImportedModule hsc_env mod pkg_qual =
   in do
     findImportedModuleNoHsc fc fopts (hsc_unit_env hsc_env) mhome_unit mod pkg_qual
 
+findImportedModuleWithIsBoot :: HscEnv -> ModuleName -> IsBootInterface -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod is_boot pkg_qual = do
+  res <- findImportedModule hsc_env mod pkg_qual
+  case (res, is_boot) of
+    (Found loc mod, IsBoot) -> return (Found (addBootSuffixLocn loc) mod)
+    _ -> return res
+
 findImportedModuleNoHsc
   :: FinderCache
   -> FinderOpts
@@ -229,15 +237,19 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
-  case mhome_unit of
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
+  res <- case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
         -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
         -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
     _ -> findPackageModule fc unit_state fopts mod
+  case (res, is_boot) of
+    (InstalledFound loc, IsBoot) -> return (InstalledFound (addBootSuffixLocn loc))
+    _ -> return res
+
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -592,10 +604,12 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
-mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
-   in mkHomeModLocation2 dflags mod basename extension
+mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> FileExt -> HscSource -> ModLocation
+mkHomeModLocation dflags mod src_basename ext hsc_src =
+   let loc = mkHomeModLocation2 dflags mod src_basename ext
+   in case hsc_src of
+     HsBootFile -> addBootSuffixLocnOut loc
+     _ -> loc
 
 mkHomeModLocation2 :: FinderOpts
                    -> ModuleName


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,8 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
    , addBootSuffixLocn
    , addBootSuffixLocnOut
    , removeBootSuffix
@@ -25,7 +23,6 @@ where
 import GHC.Prelude
 
 import GHC.Data.OsPath
-import GHC.Unit.Types
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Data.FastString (mkFastString)
@@ -99,26 +96,10 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
 -- | Add the @-boot@ suffix to all file paths associated with the module
 addBootSuffixLocn :: ModLocation -> ModLocation
 addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
+  = addBootSuffixLocnOut locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) }
 
 -- | Add the @-boot@ suffix to all output file paths associated with the
 -- module, not including the input file itself



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 19:10:43 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 15:10:43 -0400
Subject: [Git][ghc/ghc][master] Add a missing tidy in UnivCo
Message-ID: <671e903338203_1a02c55ec3101148c@gitlab.mail>



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


Commits:
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -


1 changed file:

- compiler/GHC/Core/TyCo/Tidy.hs


Changes:

=====================================
compiler/GHC/Core/TyCo/Tidy.hs
=====================================
@@ -336,16 +336,18 @@ tidyCo env co
     go (AppCo co1 co2)       = (AppCo $! go co1) $! go co2
     go (ForAllCo tv visL visR h co)
       = ((((ForAllCo $! tvp) $! visL) $! visR) $! (go h)) $! (tidyCo envp co)
-                               where (envp, tvp) = tidyVarBndr env tv
+      where (envp, tvp) = tidyVarBndr env tv
             -- the case above duplicates a bit of work in tidying h and the kind
             -- of tv. But the alternative is to use coercionKind, which seems worse.
     go (FunCo r afl afr w co1 co2) = ((FunCo r afl afr $! go w) $! go co1) $! go co2
     go (CoVarCo cv)          = CoVarCo $! go_cv cv
     go (HoleCo h)            = HoleCo $! go_hole h
     go (AxiomCo ax cos)      = AxiomCo ax $ strictMap go cos
-    go co@(UnivCo { uco_lty  = t1, uco_rty = t2 })
-                             = co { uco_lty = tidyType env t1, uco_rty = tidyType env t2 }
-                               -- Don't bother to tidy the uco_deps field
+    go (UnivCo prov role t1 t2 cos)
+                             = ((UnivCo prov role
+                                $! tidyType env t1)
+                                $! tidyType env t2)
+                                $! strictMap go cos
     go (SymCo co)            = SymCo $! go co
     go (TransCo co1 co2)     = (TransCo $! go co1) $! go co2
     go (SelCo d co)          = SelCo d $! go co



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f02dfb502dda37fc50c66ce7ebd55cc36350a45

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 19:11:09 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Sun, 27 Oct 2024 15:11:09 -0400
Subject: [Git][ghc/ghc][master] 2 commits: Bump text submodule to 2.1.2
Message-ID: <671e904dd3e8b_1a02c55ec3241177b3@gitlab.mail>



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


Commits:
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -


2 changed files:

- hadrian/src/Settings/Warnings.hs
- libraries/text


Changes:

=====================================
hadrian/src/Settings/Warnings.hs
=====================================
@@ -66,7 +66,9 @@ ghcWarningsArgs = do
         , package primitive    ? pure [ "-Wno-unused-imports"
                                       , "-Wno-deprecations" ]
         , package rts          ? pure [ "-Wcpp-undef" ]
-        , package text         ? pure [ "-Wno-deprecations", "-Wno-deriving-typeable" ]
+        , package text         ? pure [ "-Wno-deprecations"
+                                      , "-Wno-deriving-typeable"
+                                      , "-Wno-unused-imports" ]
         , package terminfo     ? pure [ "-Wno-unused-imports", "-Wno-deriving-typeable" ]
         , package stm          ? pure [ "-Wno-deriving-typeable" ]
         , package osString     ? pure [ "-Wno-deriving-typeable" ]


=====================================
libraries/text
=====================================
@@ -1 +1 @@
-Subproject commit cdb9e13b39079904eed9d75cd332b66ee0cad0c0
+Subproject commit ee0a8f8b9a4bd3fdad23e9ac0db56e7f08ce35cd



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f02dfb502dda37fc50c66ce7ebd55cc36350a45...90746a591919fc51a0ec9dec58d8f1c8397040e3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f02dfb502dda37fc50c66ce7ebd55cc36350a45...90746a591919fc51a0ec9dec58d8f1c8397040e3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 19:46:27 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Sun, 27 Oct 2024 15:46:27 -0400
Subject: [Git][ghc/ghc][wip/az/epa-remove-addepann-8] 4 commits: Add a missing
 tidy in UnivCo
Message-ID: <671e9893dad63_214c2dc1d68186b@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-remove-addepann-8 at Glasgow Haskell Compiler / GHC


Commits:
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -


30 changed files:

- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- hadrian/src/Settings/Warnings.hs
- libraries/text
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15279.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_compile/T20718.stderr
- testsuite/tests/parser/should_compile/T20846.stderr
- testsuite/tests/parser/should_compile/T23315/T23315.stderr
- testsuite/tests/printer/Test20297.stdout
- testsuite/tests/printer/Test24533.stdout


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed6af73cbb251863b1c9823427502da0332b96b...8a6691c3a947a21c7dcc9772d6cc396894c4756f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed6af73cbb251863b1c9823427502da0332b96b...8a6691c3a947a21c7dcc9772d6cc396894c4756f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 19:58:51 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Sun, 27 Oct 2024 15:58:51 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] use total function to please GHC
Message-ID: <671e9b7b1b819_214c2dc1cb454fe@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
35a66414 by Hassan Al-Awwadi at 2024-10-27T20:58:19+01:00
use total function to please GHC

- - - - -


2 changed files:

- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/Tc/Deriv/Generics.hs


Changes:

=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -27,7 +27,7 @@ module GHC.Hs.InlinePragma(
         pprInline, pprInlineDebug,
         convertInlinePragma, convertInlineSpec, convertActivation,
 
-        set_pragma_rule, set_pragma_sat
+        set_pragma_activation, set_pragma_rule, set_pragma_sat
 ) where
 
 import GHC.Prelude


=====================================
compiler/GHC/Tc/Deriv/Generics.hs
=====================================
@@ -377,7 +377,7 @@ mkBindsRep dflags gk loc dit@(DerivInstTys{dit_rep_tc = tycon}) = (binds, sigs)
                max_fields = maximum $ map dataConSourceArity datacons
 
            inline1 f = L loc'' . InlineSig noAnn (L loc' f)
-                     $ alwaysInlinePragma { inl_act = ActiveAfter NoSourceText 1 }
+                     $ set_pragma_activation alwaysInlinePragma (ActiveAfter NoSourceText 1) 
 
         -- The topmost M1 (the datatype metadata) has the exact same type
         -- across all cases of a from/to definition, and can be factored out



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35a66414c3c75a29e9e95c7eea4e1525d8ef1402

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 22:17:42 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Sun, 27 Oct 2024 18:17:42 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/hnf-spec
Message-ID: <671ebc062518e_214c2d6d51001017e@gitlab.mail>



Sebastian Graf pushed new branch wip/hnf-spec at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/hnf-spec
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 23:05:21 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Sun, 27 Oct 2024 19:05:21 -0400
Subject: [Git][ghc/ghc][wip/T20264] Progress
Message-ID: <671ec7318260b_214c2d8bf59c14277@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
063914f5 by Simon Peyton Jones at 2024-10-27T23:05:10+00:00
Progress

- - - - -


30 changed files:

- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/FloatIn.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Ppr.hs-boot
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Pat.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/063914f58f38bed55dfc5c20d27bca0038b9dd66

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Sun Oct 27 23:24:50 2024
From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812))
Date: Sun, 27 Oct 2024 19:24:50 -0400
Subject: [Git][ghc/ghc][wip/hnf-spec] Make exprIsHNF imply exprOkForSpeculation
Message-ID: <671ecbc2ac439_58da9bc6103978e@gitlab.mail>



Sebastian Graf pushed to branch wip/hnf-spec at Glasgow Haskell Compiler / GHC


Commits:
1f37d307 by Sebastian Graf at 2024-10-28T00:23:54+01:00
Make exprIsHNF imply exprOkForSpeculation

Fixes #23256 because SetLevels and CSE no longer do a reverse binder
swap.
Furthermore, we no longer need to check for exprIsHNF when
exprOkForSpeculation fails.

- - - - -


7 changed files:

- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -592,7 +592,7 @@ lintLetBind top_lvl rec_flag binder rhs rhs_ty
                || (isNonRec rec_flag && exprOkForSpeculation rhs)
                || isDataConWorkId binder || isDataConWrapId binder -- until #17521 is fixed
                || exprIsTickedString rhs)
-           (badBndrTyMsg binder (text "unlifted"))
+           (badUnliftedBndrTyMsg binder rhs)
 
         -- Check that if the binder is at the top level and has type Addr#,
         -- that it is a string literal.
@@ -3741,10 +3741,11 @@ mkRhsMsg binder what ty
      hsep [text "Binder's type:", ppr (idType binder)],
      hsep [text "Rhs type:", ppr ty]]
 
-badBndrTyMsg :: Id -> SDoc -> SDoc
-badBndrTyMsg binder what
-  = vcat [ text "The type of this binder is" <+> what <> colon <+> ppr binder
-         , text "Binder's type:" <+> ppr (idType binder) ]
+badUnliftedBndrTyMsg :: Id -> CoreExpr -> SDoc
+badUnliftedBndrTyMsg bndr rhs
+  = vcat [ text "The let binder" <+> ppr bndr <+> text "does not satisfy the let-can-float invariant"
+         , text "Type:" <+> ppr (idType bndr)
+         , text "RHS:" <+> ppr rhs ]
 
 mkNonTopExportedMsg :: Id -> SDoc
 mkNonTopExportedMsg binder


=====================================
compiler/GHC/Core/Opt/CSE.hs
=====================================
@@ -498,7 +498,9 @@ extendCSEnvWithBinding env in_id out_id rhs' cse_done
 
     -- Should we use SUBSTITUTE or EXTEND?
     -- See Note [CSE for bindings]
-    use_subst | Var {} <- rhs' = True
+    use_subst | Var v <- rhs'
+              , isEvaldUnfolding (idUnfolding v) == isEvaldUnfolding (idUnfolding in_id)
+              = True
               | otherwise      = False
 
 -- | Given a binder `let x = e`, this function


=====================================
compiler/GHC/Core/Opt/CprAnal.hs
=====================================
@@ -298,14 +298,8 @@ data TermFlag -- Better than using a Bool
 exprTerminates :: CoreExpr -> TermFlag
 -- ^ A /very/ simple termination analysis.
 exprTerminates e
-  | exprIsHNF e            = Terminates
   | exprOkForSpeculation e = Terminates
   | otherwise              = MightDiverge
-  -- Annoyingly, we have to check both for HNF and ok-for-spec.
-  --   * `I# (x# *# 2#)` is ok-for-spec, but not in HNF. Still worth CPR'ing!
-  --   * `lvl` is an HNF if its unfolding is evaluated
-  --     (perhaps `lvl = I# 0#` at top-level). But, tiresomely, it is never
-  --     ok-for-spec due to Note [exprOkForSpeculation and evaluated variables].
 
 cprAnalApp :: AnalEnv -> CoreExpr -> [(CprType, CoreArg)] -> (CprType, CoreExpr)
 -- Main function that takes care of /nested/ CPR. See Note [Nested CPR]


=====================================
compiler/GHC/Core/Opt/SetLevels.hs
=====================================
@@ -127,6 +127,7 @@ import GHC.Utils.Outputable
 import GHC.Utils.Panic
 
 import Data.Maybe
+import Data.Either
 
 {-
 ************************************************************************
@@ -452,14 +453,14 @@ lvlCase env scrut_fvs scrut' case_bndr ty alts
   =     -- Always float the case if possible
         -- Unlike lets we don't insist that it escapes a value lambda
     do { (env1, (case_bndr' : bs')) <- cloneCaseBndrs env dest_lvl (case_bndr : bs)
-       ; let rhs_env = extendCaseBndrEnv env1 case_bndr scrut'
+       ; let rhs_env = rememberEval env1 case_bndr' scrut'
        ; body' <- lvlMFE rhs_env True body
        ; let alt' = Alt con (map (stayPut dest_lvl) bs') body'
        ; return (Case scrut' (TB case_bndr' (FloatMe dest_lvl)) ty' [alt']) }
 
   | otherwise     -- Stays put
-  = do { let (alts_env1, [case_bndr']) = substAndLvlBndrs NonRecursive env incd_lvl [case_bndr]
-             alts_env = extendCaseBndrEnv alts_env1 case_bndr scrut'
+  = do { let (alts_env1, [case_bndr'@(TB case_bndrr _)]) = substAndLvlBndrs NonRecursive env incd_lvl [case_bndr]
+             alts_env = rememberEval alts_env1 case_bndrr scrut'
        ; alts' <- mapM (lvl_alt alts_env) alts
        ; return (Case scrut' case_bndr' ty' alts') }
   where
@@ -632,7 +633,7 @@ lvlMFE env strict_ctxt ann_expr
   |  float_is_new_lam || exprIsTopLevelBindable expr expr_ty
          -- No wrapping needed if the type is lifted, or is a literal string
          -- or if we are wrapping it in one or more value lambdas
-  = do { expr1 <- lvlFloatRhs abs_vars dest_lvl rhs_env NonRecursive
+  = do { expr1 <- lvlFloatRhs abs_vars eval_vars dest_lvl rhs_env NonRecursive
                               is_bot_lam NotJoinPoint ann_expr
                   -- Treat the expr just like a right-hand side
        ; var <- newLvlVar expr1 NotJoinPoint is_mk_static
@@ -653,6 +654,7 @@ lvlMFE env strict_ctxt ann_expr
   = do { expr1 <- lvlExpr rhs_env ann_expr
        ; let l1r       = incMinorLvlFrom rhs_env
              float_rhs = mkLams abs_vars_w_lvls $
+                         flip (foldr (wrapEval l1r)) eval_vars $
                          Case expr1 (stayPut l1r ubx_bndr) box_ty
                              [Alt DEFAULT [] (App boxing_expr (Var ubx_bndr))]
 
@@ -678,7 +680,8 @@ lvlMFE env strict_ctxt ann_expr
                            -- See Note [Bottoming floats]
                            -- esp Bottoming floats (2)
     expr_ok_for_spec = exprOkForSpeculation expr
-    abs_vars = abstractVars dest_lvl env fvs
+    (abs_vars, eval_vars) = eliminateAbsCaseBndrs dest_lvl env $
+                            abstractVars dest_lvl env fvs
     dest_lvl = destLevel env fvs fvs_ty is_function is_bot_lam
                -- NB: is_bot_lam not is_bot; see (3) in
                --     Note [Bottoming floats]
@@ -1233,7 +1236,7 @@ lvlBind env (AnnNonRec bndr rhs)
   -- Otherwise we are going to float
   | null abs_vars
   = do {  -- No type abstraction; clone existing binder
-         rhs' <- lvlFloatRhs [] dest_lvl env NonRecursive
+         rhs' <- lvlFloatRhs [] [] dest_lvl env NonRecursive
                              is_bot_lam NotJoinPoint rhs
        ; (env', [bndr']) <- cloneLetVars NonRecursive env dest_lvl [bndr]
        ; let bndr2 = annotateBotStr bndr' 0 mb_bot_str
@@ -1241,7 +1244,7 @@ lvlBind env (AnnNonRec bndr rhs)
 
   | otherwise
   = do {  -- Yes, type abstraction; create a new binder, extend substitution, etc
-         rhs' <- lvlFloatRhs abs_vars dest_lvl env NonRecursive
+         rhs' <- lvlFloatRhs abs_vars eval_vars dest_lvl env NonRecursive
                              is_bot_lam NotJoinPoint rhs
        ; (env', [bndr']) <- newPolyBndrs dest_lvl env abs_vars [bndr]
        ; let bndr2 = annotateBotStr bndr' n_extra mb_bot_str
@@ -1252,7 +1255,8 @@ lvlBind env (AnnNonRec bndr rhs)
     ty_fvs     = tyCoVarsOfType bndr_ty
     rhs_fvs    = freeVarsOf rhs
     bind_fvs   = rhs_fvs `unionDVarSet` dIdFreeVars bndr
-    abs_vars   = abstractVars dest_lvl env bind_fvs
+    (abs_vars, eval_vars) = eliminateAbsCaseBndrs dest_lvl env $
+                            abstractVars dest_lvl env bind_fvs
     dest_lvl   = destLevel env bind_fvs ty_fvs (isFunction rhs) is_bot_lam
 
     deann_rhs  = deAnnotate rhs
@@ -1332,9 +1336,8 @@ lvlBind env (AnnRec pairs)
                       -- function in a Rec, and we don't much care what
                       -- happens to it.  False is simple!
 
-    do_rhs env (_,rhs) = lvlFloatRhs abs_vars dest_lvl env Recursive
-                                     is_bot NotJoinPoint
-                                     rhs
+    do_rhs env (_,rhs) = lvlFloatRhs abs_vars eval_vars dest_lvl env Recursive
+                                     is_bot NotJoinPoint rhs
 
         -- Finding the free vars of the binding group is annoying
     bind_fvs = ((unionDVarSets [ freeVarsOf rhs | (_, rhs) <- pairs])
@@ -1346,7 +1349,8 @@ lvlBind env (AnnRec pairs)
 
     ty_fvs   = foldr (unionVarSet . tyCoVarsOfType . idType) emptyVarSet bndrs
     dest_lvl = destLevel env bind_fvs ty_fvs is_fun is_bot
-    abs_vars = abstractVars dest_lvl env bind_fvs
+    (abs_vars, eval_vars) = eliminateAbsCaseBndrs dest_lvl env $
+                            abstractVars dest_lvl env bind_fvs
 
     is_top_bindable = not (any (mightBeUnliftedType . idType) bndrs)
        -- This mightBeUnliftedType stuff is the same test as in the non-rec case
@@ -1396,21 +1400,28 @@ lvlRhs :: LevelEnv
        -> CoreExprWithFVs
        -> LvlM LevelledExpr
 lvlRhs env rec_flag is_bot mb_join_arity expr
-  = lvlFloatRhs [] (le_ctxt_lvl env) env
+  = lvlFloatRhs [] [] (le_ctxt_lvl env) env
                 rec_flag is_bot mb_join_arity expr
 
-lvlFloatRhs :: [OutVar] -> Level -> LevelEnv -> RecFlag
+wrapEval :: Level -> (OutId, OutId) -> Expr LevelledBndr -> Expr LevelledBndr
+-- A bit like GHC.Core.Utils.mkDefaultCase, but `Expr LevelledBndr`
+wrapEval dest_lvl (scrut_v, case_bndr) body
+  = Case (Var scrut_v) (TB case_bndr (StayPut dest_lvl))
+         (exprType $ deTagExpr body) [Alt DEFAULT [] body]
+
+lvlFloatRhs :: [OutVar] -> [(OutId,OutId)] -> Level -> LevelEnv -> RecFlag
             -> Bool   -- Binding is for a bottoming function
             -> JoinPointHood
             -> CoreExprWithFVs
             -> LvlM (Expr LevelledBndr)
 -- Ignores the le_ctxt_lvl in env; treats dest_lvl as the baseline
-lvlFloatRhs abs_vars dest_lvl env rec is_bot mb_join_arity rhs
-  = do { body' <- if not is_bot  -- See Note [Floating from a RHS]
+lvlFloatRhs abs_vars eval_vars dest_lvl env rec is_bot mb_join_arity rhs
+  = do { body1 <- if not is_bot  -- See Note [Floating from a RHS]
                      && any isId bndrs
                   then lvlMFE  body_env True body
                   else lvlExpr body_env      body
-       ; return (mkLams bndrs' body') }
+       ; let body2 = foldr (wrapEval dest_lvl) body1 eval_vars
+       ; return (mkLams bndrs' body2) }
   where
     (bndrs, body)     | JoinPoint join_arity <- mb_join_arity
                       = collectNAnnBndrs join_arity rhs
@@ -1633,14 +1644,20 @@ countFreeIds = nonDetStrictFoldUDFM add 0 . getUniqDSet
 
 data LevelEnv
   = LE { le_switches :: FloatOutSwitches
-       , le_ctxt_lvl :: Level           -- The current level
-       , le_lvl_env  :: VarEnv Level    -- Domain is *post-cloned* TyVars and Ids
+       , le_ctxt_lvl :: Level
+       -- ^ The current level
+       , le_lvl_env  :: VarEnv (Level, Maybe OutId)
+       -- ^ Domain is *post-cloned* TyVars and Ids.
+       -- If `Just scrut`, then the var mapping belongs to a case binder with
+       -- variable scrutinee `scrut`.
+       -- This is to support Note [Duplicate evals into float].
 
        -- See Note [le_subst and le_env]
-       , le_subst    :: Subst           -- Domain is pre-cloned TyVars and Ids
-                                        -- The Id -> CoreExpr in the Subst is ignored
-                                        -- (since we want to substitute a LevelledExpr for
-                                        -- an Id via le_env) but we do use the Co/TyVar substs
+       , le_subst    :: Subst
+       -- ^ Domain is pre-cloned TyVars and Ids.
+       -- The Id -> CoreExpr in the Subst is ignored
+       -- (since we want to substitute a LevelledExpr for
+       -- an Id via le_env) but we do use the Co/TyVar substs
        , le_env      :: IdEnv ([OutVar], LevelledExpr)  -- Domain is pre-cloned Ids
     }
 
@@ -1690,10 +1707,10 @@ initialEnv float_lams binds
       -- to a later one.  So here we put all the top-level binders in scope before
       -- we start, to satisfy the lookupIdSubst invariants (#20200 and #20294)
 
-addLvl :: Level -> VarEnv Level -> OutVar -> VarEnv Level
-addLvl dest_lvl env v' = extendVarEnv env v' dest_lvl
+addLvl :: Level -> VarEnv (Level, Maybe OutId) -> OutVar -> VarEnv (Level, Maybe OutId)
+addLvl dest_lvl env v' = extendVarEnv env v' (dest_lvl, Nothing)
 
-addLvls :: Level -> VarEnv Level -> [OutVar] -> VarEnv Level
+addLvls :: Level -> VarEnv (Level, Maybe OutId) -> [OutVar] -> VarEnv (Level, Maybe OutId)
 addLvls dest_lvl env vs = foldl' (addLvl dest_lvl) env vs
 
 floatLams :: LevelEnv -> Maybe Int
@@ -1711,20 +1728,19 @@ floatTopLvlOnly le = floatToTopLevelOnly (le_switches le)
 incMinorLvlFrom :: LevelEnv -> Level
 incMinorLvlFrom env = incMinorLvl (le_ctxt_lvl env)
 
--- extendCaseBndrEnv adds the mapping case-bndr->scrut-var if it can
+-- rememberEval adds the mapping case-bndr->scrut-var if it can
 -- See Note [Binder-swap during float-out]
-extendCaseBndrEnv :: LevelEnv
-                  -> Id                 -- Pre-cloned case binder
-                  -> Expr LevelledBndr  -- Post-cloned scrutinee
-                  -> LevelEnv
-extendCaseBndrEnv le@(LE { le_subst = subst, le_env = id_env })
+rememberEval :: LevelEnv
+             -> OutId              -- Post-cloned case binder
+             -> Expr LevelledBndr  -- Post-cloned scrutinee
+             -> LevelEnv
+rememberEval le@(LE { le_lvl_env = lvl_env })
                   case_bndr (Var scrut_var)
   -- We could use OccurAnal. scrutOkForBinderSwap here, and perhaps
   -- get a bit more floating.  But we didn't in the past and it's
   -- an unforced change, so I'm leaving it.
-  = le { le_subst   = extendSubstWithVar subst case_bndr scrut_var
-       , le_env     = add_id id_env (case_bndr, scrut_var) }
-extendCaseBndrEnv env _ _ = env
+  = le { le_lvl_env = modifyVarEnv (\(lvl,_) -> (lvl, Just scrut_var)) lvl_env case_bndr }
+rememberEval env _ _ = env
 
 maxFvLevel :: (Var -> Bool) -> LevelEnv -> DVarSet -> Level
 maxFvLevel max_me env var_set
@@ -1745,8 +1761,8 @@ maxIn max_me (LE { le_lvl_env = lvl_env, le_env = id_env }) in_var lvl
   where
     max_out out_var lvl
         | max_me out_var = case lookupVarEnv lvl_env out_var of
-                                Just lvl' -> maxLvl lvl' lvl
-                                Nothing   -> lvl
+                                Just (lvl',_) -> maxLvl lvl' lvl
+                                Nothing       -> lvl
         | otherwise = lvl       -- Ignore some vars depending on max_me
 
 lookupVar :: LevelEnv -> Id -> LevelledExpr
@@ -1765,20 +1781,16 @@ abstractVars :: Level -> LevelEnv -> DVarSet -> [OutVar]
         -- variable computation and deterministic sort.
         -- See Note [Unique Determinism] in GHC.Types.Unique for explanation of why
         -- Uniques are not deterministic.
-abstractVars dest_lvl (LE { le_subst = subst, le_lvl_env = lvl_env }) in_fvs
+abstractVars dest_lvl le@(LE { le_subst = subst }) in_fvs
   =  -- NB: sortQuantVars might not put duplicates next to each other
-    map zap $ sortQuantVars $
-    filter abstract_me      $
-    dVarSetElems            $
-    closeOverKindsDSet      $
+    map zap $ sortQuantVars         $
+    filter (abstractMe dest_lvl le) $
+    dVarSetElems                    $
+    closeOverKindsDSet              $
     substDVarSet subst in_fvs
         -- NB: it's important to call abstract_me only on the OutIds the
         -- come from substDVarSet (not on fv, which is an InId)
   where
-    abstract_me v = case lookupVarEnv lvl_env v of
-                        Just lvl -> dest_lvl `ltLvl` lvl
-                        Nothing  -> False
-
         -- We are going to lambda-abstract, so nuke any IdInfo,
         -- and add the tyvars of the Id (if necessary)
     zap v | isId v = warnPprTrace (isStableUnfolding (idUnfolding v) ||
@@ -1787,6 +1799,23 @@ abstractVars dest_lvl (LE { le_subst = subst, le_lvl_env = lvl_env }) in_fvs
                      setIdInfo v vanillaIdInfo
           | otherwise = v
 
+abstractMe :: Level -> LevelEnv -> Var -> Bool
+abstractMe dest_lvl (LE { le_lvl_env = lvl_env }) v
+  | Just (lvl, _) <- lookupVarEnv lvl_env v
+  = dest_lvl `ltLvl` lvl
+  | otherwise
+  = False
+
+eliminateAbsCaseBndrs :: Level -> LevelEnv -> [OutVar] -> ([OutVar], [(OutId,OutId)])
+eliminateAbsCaseBndrs dest_lvl le@(LE { le_lvl_env = lvl_env })
+  = partitionEithers . map try_elim
+  where
+    try_elim v = case lookupVarEnv lvl_env v of
+      Just (_, Just scrut_id)
+        | not (abstractMe dest_lvl le scrut_id) -- would not abstract scrut_id
+        -> Right (scrut_id, v) -- turn abs_var v into an eval on scrut_id!
+      _ -> Left v              -- retain as an abs_var
+
 type LvlM result = UniqSM result
 
 initLvl :: UniqSupply -> UniqSM a -> a
@@ -1835,9 +1864,12 @@ newLvlVar :: LevelledExpr        -- The RHS of the new binding
           -> LvlM Id
 newLvlVar lvld_rhs join_arity_maybe is_mk_static
   = do { uniq <- getUniqueM
-       ; return (add_join_info (mk_id uniq rhs_ty))
+       ; return (add_evald $ add_join_info $ mk_id uniq rhs_ty)
        }
   where
+    add_evald var
+      | exprIsHNF de_tagged_rhs = var `setIdUnfolding` evaldUnfolding
+      | otherwise               = var
     add_join_info var = var `asJoinId_maybe` join_arity_maybe
     de_tagged_rhs = deTagExpr lvld_rhs
     rhs_ty        = exprType de_tagged_rhs


=====================================
compiler/GHC/Core/Subst.hs
=====================================
@@ -519,7 +519,9 @@ substUnfolding subst df@(DFunUnfolding { df_bndrs = bndrs, df_args = args })
 substUnfolding subst unf@(CoreUnfolding { uf_tmpl = tmpl, uf_src = src })
   -- Retain stable unfoldings
   | not (isStableSource src)  -- Zap an unstable unfolding, to save substitution work
-  = NoUnfolding
+  = if isEvaldUnfolding unf
+    then evaldUnfolding
+    else NoUnfolding
   | otherwise                 -- But keep a stable one!
   = seqExpr new_tmpl `seq`
     unf { uf_tmpl = new_tmpl }


=====================================
compiler/GHC/Core/TyCo/Subst.hs
=====================================
@@ -22,6 +22,7 @@ module GHC.Core.TyCo.Subst
         extendCvSubst, extendCvSubstWithClone,
         extendTvSubst, extendTvSubstWithClone,
         extendTvSubstList, extendTvSubstAndInScope,
+        extendCvSubstAndInScope,
         extendTCvSubstList,
         unionSubst, zipTyEnv, zipCoEnv,
         zipTvSubst, zipCvSubst,
@@ -408,6 +409,14 @@ extendTvSubstAndInScope (Subst in_scope ids tenv cenv) tv ty
              (extendVarEnv tenv tv ty)
              cenv
 
+extendCvSubstAndInScope :: Subst -> CoVar -> Coercion -> Subst
+-- Also extends the in-scope set
+extendCvSubstAndInScope (Subst in_scope ids tenv cenv) cv co
+  = Subst (in_scope `extendInScopeSetSet` tyCoVarsOfCo co)
+             ids
+             tenv
+             (extendVarEnv cenv cv co)
+
 -- | Adds multiple 'TyVar' substitutions to the 'Subst': see also 'extendTvSubst'
 extendTvSubstList :: Subst -> [(TyVar,Type)] -> Subst
 extendTvSubstList subst vrs


=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -74,9 +74,11 @@ import GHC.Core.Ppr
 import GHC.Core.FVs( bindFreeVars )
 import GHC.Core.DataCon
 import GHC.Core.Type as Type
+import GHC.Core.TyCo.Rep as Type
 import GHC.Core.Predicate( isCoVarType )
 import GHC.Core.FamInstEnv
 import GHC.Core.TyCo.Compare( eqType, eqTypeX )
+import GHC.Core.TyCo.Subst
 import GHC.Core.Coercion
 import GHC.Core.Reduction
 import GHC.Core.TyCon
@@ -1814,11 +1816,9 @@ expr_ok fun_ok primop_ok (Tick tickish e)
 expr_ok _ _ (Let {}) = False
 -- See W3 in the Haddock comment for exprOkForSpeculation
 
-expr_ok fun_ok primop_ok (Case scrut bndr _ alts)
+expr_ok fun_ok primop_ok (Case scrut _ _ alts)
   =  -- See Note [exprOkForSpeculation: case expressions]
      expr_ok fun_ok primop_ok scrut
-  && isUnliftedType (idType bndr)
-      -- OK to call isUnliftedType: binders always have a fixed RuntimeRep
   && all (\(Alt _ _ rhs) -> expr_ok fun_ok primop_ok rhs) alts
   && altsAreExhaustive alts
 
@@ -1847,7 +1847,7 @@ app_ok fun_ok primop_ok fun args
 
   | idArity fun > n_val_args
   -- Partial application: just check passing the arguments is OK
-  = args_ok
+  = args_ok notCBV
 
   | otherwise
   = case idDetails fun of
@@ -1857,9 +1857,10 @@ app_ok fun_ok primop_ok fun args
 
       DataConWorkId dc
         | isLazyDataConRep dc
-        -> args_ok
+        -> args_ok notCBV
         | otherwise
-        -> fields_ok (dataConRepStrictness dc)
+        -> args_ok (dataConRepStrictness dc)
+            -- See (SFC1) of Note [Strict fields in Core]
 
       ClassOpId _ is_terminating_result
         | is_terminating_result -- See Note [exprOkForSpeculation and type classes]
@@ -1881,7 +1882,7 @@ app_ok fun_ok primop_ok fun args
               -- Often there is a literal divisor, and this
               -- can get rid of a thunk in an inner loop
 
-        | otherwise -> primop_ok op && args_ok
+        | otherwise -> primop_ok op && args_ok notCBV
 
       _other  -- Unlifted and terminating types;
               -- Also c.f. the Var case of exprIsHNF
@@ -1898,37 +1899,54 @@ app_ok fun_ok primop_ok fun args
          -- See (U12) of Note [Implementing unsafeCoerce]
          | fun `hasKey` unsafeEqualityProofIdKey -> True
 
-         | otherwise -> False
-             -- NB: even in the nullary case, do /not/ check
-             --     for evaluated-ness of the fun;
-             --     see Note [exprOkForSpeculation and evaluated variables]
+         | 0 <- n_val_args
+         , isEvaldUnfolding (idUnfolding fun)
+         -> -- pprTrace "yes" (ppr fun)
+            True
+
+         | otherwise -> -- pprTrace "no" (ppr fun <+> ppr args)
+                        False
   where
     fun_ty       = idType fun
     n_val_args   = valArgCount args
-    (arg_tys, _) = splitPiTys fun_ty
 
     -- Even if a function call itself is OK, any unlifted
-    -- args are still evaluated eagerly and must be checked
-    args_ok = all2Prefix arg_ok arg_tys args
-    arg_ok :: PiTyVarBinder -> CoreExpr -> Bool
-    arg_ok (Named _) _ = True   -- A type argument
-    arg_ok (Anon ty _) arg      -- A term argument
-       | definitelyLiftedType (scaledThing ty)
-       = True -- lifted args are not evaluated eagerly
+    -- args are still evaluated eagerly and must be checked.
+    -- Furthermore, for saturated calls, we must check CBV args (strict fields
+    -- of DataCons!)
+    args_ok str_marks = relevantAppArgsSatisfy arg_ok fun_ty args str_marks
+    arg_ok :: Type -> CoreExpr -> StrictnessMark -> Bool
+    arg_ok ty arg str
+       | NotMarkedStrict <- str   -- iff it's not a CBV arg
+       , definitelyLiftedType ty  -- and its type is lifted
+       = True                     -- then the worker app does not eval
        | otherwise
        = expr_ok fun_ok primop_ok arg
 
-    -- Used for strict DataCon worker arguments
-    -- See (SFC1) of Note [Strict fields in Core]
-    fields_ok str_marks = all3Prefix field_ok arg_tys str_marks args
-    field_ok :: PiTyVarBinder -> StrictnessMark -> CoreExpr -> Bool
-    field_ok (Named _)   _   _ = True
-    field_ok (Anon ty _) str arg
-       | NotMarkedStrict <- str                 -- iff it's a lazy field
-       , definitelyLiftedType (scaledThing ty)  -- and its type is lifted
-       = True                                   -- then the worker app does not eval
-       | otherwise
-       = expr_ok fun_ok primop_ok arg
+notCBV :: [StrictnessMark]
+notCBV = repeat NotMarkedStrict
+
+relevantAppArgsSatisfy :: (Type -> CoreExpr -> StrictnessMark -> Bool) -> Type -> [CoreExpr] -> [StrictnessMark] -> Bool
+-- This calls the predicate on every non-Type CoreExpr arg.
+-- We could just do `exprType arg` for every such arg, but carrying around a
+-- substitution is much more efficient.
+-- The obvious definition regresses T16577 by 30% so we don't do it.
+relevantAppArgsSatisfy p ty = go (mkEmptySubst in_scope) ty
+  where
+    in_scope = mkInScopeSet (tyCoVarsOfType ty)
+    go subst (ForAllTy b res) (Type ty : args) strs
+      = go (extendTvSubstAndInScope subst (binderVar b) ty) res args strs
+    go subst (ForAllTy b res) (Coercion co : args) strs
+      = go (extendCvSubstAndInScope subst (binderVar b) co) res args strs
+    go subst (FunTy { ft_arg = arg, ft_res = res }) (e : args) (str : strs)
+      = p (substTy subst arg) e str && go subst res args strs
+    go subst ty args@(_:_) strs@(_:_)
+      | Just ty' <- coreView (substTy subst ty)
+      = go (mkEmptySubst (getSubstInScope subst)) ty' args strs
+      | otherwise
+      = pprPanic "Should see more argument tys" (ppr ty $$ ppr subst $$ ppr args $$ ppr (take 10 strs))
+    go _ _ _ _ = True
+{-# INLINE relevantAppArgsSatisfy #-}
 
 -----------------------------
 altsAreExhaustive :: [Alt b] -> Bool
@@ -1985,6 +2003,8 @@ GHC.Types.Id.Make.mkDictSelId for where this field is initialised.
 
 Note [exprOkForSpeculation: case expressions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+SG: I don't get what is so "very special" about this case. I find it very reasonable.
+
 exprOkForSpeculation accepts very special case expressions.
 Reason: (a ==# b) is ok-for-speculation, but the litEq rules
 in GHC.Core.Opt.ConstantFold convert it (a ==# 3#) to
@@ -1994,39 +2014,22 @@ for excellent reasons described in
 So, annoyingly, we want that case expression to be
 ok-for-speculation too. Bother.
 
-But we restrict it sharply:
-
-* We restrict it to unlifted scrutinees. Consider this:
-     case x of y {
-       DEFAULT -> ... (let v::Int# = case y of { True  -> e1
-                                               ; False -> e2 }
-                       in ...) ...
-
-  Does the RHS of v satisfy the let-can-float invariant?  Previously we said
-  yes, on the grounds that y is evaluated.  But the binder-swap done
-  by GHC.Core.Opt.SetLevels would transform the inner alternative to
-     DEFAULT -> ... (let v::Int# = case x of { ... }
-                     in ...) ....
-  which does /not/ satisfy the let-can-float invariant, because x is
-  not evaluated. See Note [Binder-swap during float-out]
-  in GHC.Core.Opt.SetLevels.  To avoid this awkwardness it seems simpler
-  to stick to unlifted scrutinees where the issue does not
-  arise.
-
-* We restrict it to exhaustive alternatives. A non-exhaustive
-  case manifestly isn't ok-for-speculation. for example,
-  this is a valid program (albeit a slightly dodgy one)
-    let v = case x of { B -> ...; C -> ... }
-    in case x of
-         A -> ...
-         _ ->  ...v...v....
-  Should v be considered ok-for-speculation?  Its scrutinee may be
-  evaluated, but the alternatives are incomplete so we should not
-  evaluate it strictly.
-
-  Now, all this is for lifted types, but it'd be the same for any
-  finite unlifted type. We don't have many of them, but we might
-  add unlifted algebraic types in due course.
+SG: Again, I don't see why we need to list a specific example.
+Clearly, we want to detect as many expressions as ok-for-spec as possible!
+
+But we restrict it to exhaustive alternatives. A non-exhaustive
+case manifestly isn't ok-for-speculation. For example,
+this is a valid program (albeit a slightly dodgy one)
+  let v = case x of { B -> ...; C -> ... }
+  in case x of
+       A -> ...
+       _ ->  ...v...v....
+Should v be considered ok-for-speculation?  Its scrutinee may be
+evaluated, but the alternatives are incomplete so we should not
+evaluate it strictly.
+
+Now, all this is for lifted types, but it'd be the same for any
+finite unlifted type.
 
 
 ----- Historical note: #15696: --------
@@ -2073,37 +2076,6 @@ points do the job nicely.
 ------- End of historical note ------------
 
 
-Note [exprOkForSpeculation and evaluated variables]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider these examples:
- * case x of y { DEFAULT -> ....y.... }
-   Should 'y' (alone) be considered ok-for-speculation?
-
- * case x of y { DEFAULT -> ....let z = dataToTagLarge# y... }
-   Should (dataToTagLarge# y) be considered ok-for-spec? Recall that
-     dataToTagLarge# :: forall a. a -> Int#
-   must always evaluate its argument. (See also Note [DataToTag overview].)
-
-You could argue 'yes', because in the case alternative we know that
-'y' is evaluated.  But the binder-swap transformation, which is
-extremely useful for float-out, changes these expressions to
-   case x of y { DEFAULT -> ....x.... }
-   case x of y { DEFAULT -> ....let z = dataToTagLarge# x... }
-
-And now the expression does not obey the let-can-float invariant!  Yikes!
-Moreover we really might float (dataToTagLarge# x) outside the case,
-and then it really, really doesn't obey the let-can-float invariant.
-
-The solution is simple: exprOkForSpeculation does not try to take
-advantage of the evaluated-ness of (lifted) variables.  And it returns
-False (always) for primops that perform evaluation.  We achieve the latter
-by marking the relevant primops as "ThrowsException" or
-"ReadWriteEffect"; see also Note [Classifying primop effects] in
-GHC.Builtin.PrimOps.
-
-Note that exprIsHNF /can/ and does take advantage of evaluated-ness;
-it doesn't have the trickiness of the let-can-float invariant to worry about.
-
 ************************************************************************
 *                                                                      *
              exprIsHNF, exprIsConLike
@@ -2185,66 +2157,59 @@ exprIsHNFlike is_con is_con_unf e
                                    && is_hnf_like e
                                       -- See Note [exprIsHNF Tick]
     is_hnf_like (Cast e _)       = is_hnf_like e
-    is_hnf_like (App e a)
-      | isValArg a               = app_is_value e [a]
-      | otherwise                = is_hnf_like e
     is_hnf_like (Let _ e)        = is_hnf_like e  -- Lazy let(rec)s don't affect us
     is_hnf_like (Case e b _ as)
       | Just rhs <- isUnsafeEqualityCase e b as
       = is_hnf_like rhs
-    is_hnf_like _                = False
-
-    -- Collect arguments through Casts and Ticks and call id_app_is_value
-    app_is_value :: CoreExpr -> [CoreArg] -> Bool
-    app_is_value (Var f)    as = id_app_is_value f as
-    app_is_value (Tick _ f) as = app_is_value f as
-    app_is_value (Cast f _) as = app_is_value f as
-    app_is_value (App f a)  as | isValArg a = app_is_value f (a:as)
-                               | otherwise  = app_is_value f as
-    app_is_value _          _  = False
-
-    id_app_is_value id val_args =
+    is_hnf_like e
+      | (fun, args) <- collectArgs e
+      = case stripTicksTopE (not . tickishCounts) fun of
+            Var f -> id_app_is_value f args
+
+            -- 'LitRubbish' is the only literal that can occur in the head of an
+            -- application and will not be matched by the above case (Var /= Lit).
+            -- See Note [How a rubbish literal can be the head of an application]
+            -- in GHC.Types.Literal
+            Lit lit | debugIsOn, not (isLitRubbish lit)
+                     -> pprPanic "Non-rubbish lit in app head" (ppr lit)
+                     | otherwise
+                     -> True
+
+            _ -> False
+
+    id_app_is_value id args =
       -- See Note [exprIsHNF for function applications]
       --   for the specification and examples
-      case compare (idArity id) (length val_args) of
+      case compare (idArity id) n_val_args of
         EQ | is_con id ->      -- Saturated app of a DataCon/CONLIKE Id
           case mb_str_marks id of
             Just str_marks ->  -- with strict fields; see (SFC1) of Note [Strict fields in Core]
-              assert (val_args `equalLength` str_marks) $
-              fields_hnf str_marks
+              args_hnf str_marks
             Nothing ->         -- without strict fields: like PAP
-              args_hnf         -- NB: CONLIKEs are lazy!
+              args_hnf notCBV  -- NB: CONLIKEs are lazy!
 
-        GT ->                  -- PAP: Check unlifted val_args
-          args_hnf
+        GT ->                  -- PAP: Check unlifted args
+          args_hnf notCBV
 
         _  -> False
 
       where
-        -- Saturated, Strict DataCon: Check unlifted val_args and strict fields
-        fields_hnf str_marks = all3Prefix check_field val_arg_tys str_marks val_args
-
-        -- PAP: Check unlifted val_args
-        args_hnf             = all2Prefix check_arg   val_arg_tys           val_args
-
         fun_ty = idType id
-        val_arg_tys = mapMaybe anonPiTyBinderType_maybe (collectPiTyBinders fun_ty)
-          -- val_arg_tys = map exprType val_args, but much less costly.
-          -- The obvious definition regresses T16577 by 30% so we don't do it.
-
-        check_arg a_ty a
+        n_val_args   = valArgCount args
+        -- Check the args for HNFness.
+        args_hnf str_marks = relevantAppArgsSatisfy check_arg fun_ty args str_marks
+        --   * Unlifted args must always be HNF
+        --   * CBV args (strict fields!) must be HNF for saturated calls,
+        --     indicated by str_marks
+        check_arg a_ty a str
           | mightBeUnliftedType a_ty = is_hnf_like a
+          | isMarkedStrict str       = is_hnf_like a
           | otherwise                = True
          -- Check unliftedness; for example f (x /# 12#) where f has arity two,
          -- and the first argument is unboxed. This is not a value!
          -- But  f 34#  is a value, so check args for HNFs.
          -- NB: We check arity (and CONLIKEness) first because it's cheaper
          --     and we reject quickly on saturated apps.
-        check_field a_ty str a
-          | mightBeUnliftedType a_ty = is_hnf_like a
-          | isMarkedStrict str       = is_hnf_like a
-          | otherwise                = True
-          -- isMarkedStrict: Respect Note [Strict fields in Core]
 
         mb_str_marks id
           | Just dc <- isDataConWorkId_maybe id



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f37d307ca17c6cd1e680fb569fbb714fecf6070

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 07:19:33 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 03:19:33 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] whitespace
Message-ID: <671f3b05475ff_33a64710da2449677@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
819bb9dc by Hassan Al-Awwadi at 2024-10-28T08:19:15+01:00
whitespace

- - - - -


1 changed file:

- compiler/GHC/Tc/Deriv/Generics.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Generics.hs
=====================================
@@ -377,7 +377,7 @@ mkBindsRep dflags gk loc dit@(DerivInstTys{dit_rep_tc = tycon}) = (binds, sigs)
                max_fields = maximum $ map dataConSourceArity datacons
 
            inline1 f = L loc'' . InlineSig noAnn (L loc' f)
-                     $ set_pragma_activation alwaysInlinePragma (ActiveAfter NoSourceText 1) 
+                     $ set_pragma_activation alwaysInlinePragma (ActiveAfter NoSourceText 1)
 
         -- The topmost M1 (the datatype metadata) has the exact same type
         -- across all cases of a from/to definition, and can be factored out



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/819bb9dc74e83540d032e94c09651d981d25618e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 09:29:34 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 05:29:34 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] Can't have type families in class
 instances.
Message-ID: <671f597e3b30a_30bde110f9505026d@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
1a7812a5 by Hassan Al-Awwadi at 2024-10-28T10:29:14+01:00
Can't have type families in class instances.

I keep trying to do it like a fool...

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2350,7 +2350,7 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (LOverlapMode (GhcPass p)) where
+instance ExactPrint (LocatedP (OverlapMode (GhcPass p))) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a7812a525017f46958e555b08e75765a6e7545c

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 12:12:29 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 08:12:29 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] unavoidable duplication of
 mkOr.
Message-ID: <671f7fad48fbb_1362afbc3f449781@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
31f8781e by Hassan Al-Awwadi at 2024-10-28T13:12:08+01:00
unavoidable duplication of mkOr.

- - - - -


2 changed files:

- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -222,9 +222,12 @@ data IfaceBooleanFormula
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
+  deriving Eq
 
 -- | note that this makes unbound names, so if you actually want
 -- proper Names, you'll need to properly Rename it (lookupIfaceTop).
+-- You want proper Names for most things, except pretty printing
+-- and the like.
 fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
 fromIfaceBooleanFormula = go
   where


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -135,13 +135,13 @@ import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List(nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
-import GHC.CoreToIface(toIfaceBooleanFormula)
 
-import Language.Haskell.Syntax.BooleanFormula (mkOr, BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
 import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
@@ -306,12 +306,35 @@ mergeIfaceDecl d1 d2
 
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . mkOr . map (noLocA . fromIfaceBooleanFormula) $ [ bf1, bf2]
+                ifMinDef = mkOr [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
     -- we merge, see 'mergeSignatures'
     | otherwise              = d1 `withRolesFrom` d2
+      where
+        -- | the reason we need to duplicate mkOr here, instead of
+        -- using BooleanFormula's mkOr and just doing the loop like:
+        -- `toIfaceBooleanFormula . mkOr . fromIfaceBooleanFormula`
+        -- is quite subtle. Say we have the following minimal pragma:
+        -- {-# MINIMAL f | g #-}. If we use fromIfaceBooleanFormula
+        -- first, we will end up doing
+        -- `nub [Var (mkUnboundName f), Var (mkUnboundName g)]`,
+        -- which might seem fine, but Name equallity is decided by
+        -- their Unique, which will be identical since mkUnboundName
+        -- just stuffs the mkUnboundKey unqiue into both.
+        -- So the result will be {-# MINIMAL f #-}, oopsie.
+        -- Duplication it is.
+        mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+        mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+          where
+          -- See Note [Simplification of BooleanFormulas]
+          fromOr bf = case bf of
+            (IfOr xs)  -> Just xs
+            (IfAnd []) -> Nothing
+            _        -> Just [bf]
+          mkOr' [x] = x
+          mkOr' xs = IfOr xs
 
 -- Note [Role merging]
 -- ~~~~~~~~~~~~~~~~~~~



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/31f8781e90f6c1fa484f356f77f0ac0df19c895a

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 12:21:21 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Mon, 28 Oct 2024 08:21:21 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] 13 commits: EPA: reduce [AddEpann] in
 AnnList
Message-ID: <671f81c170b67_1362af21026450318@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
fb3f3990 by Sjoerd Visscher at 2024-10-28T13:16:21+01:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -
5c046b1e by Sjoerd Visscher at 2024-10-28T13:21:12+01:00
Concentrate boot extension logic in Finder

With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required.

- - - - -


30 changed files:

- .ghcid
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ee10a07d94b86f0bf883b039e63b6d44d68d2ff1...5c046b1e58181d8f5edf62efc7f8ca0c8ccc46e2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ee10a07d94b86f0bf883b039e63b6d44d68d2ff1...5c046b1e58181d8f5edf62efc7f8ca0c8ccc46e2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 12:42:20 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Mon, 28 Oct 2024 08:42:20 -0400
Subject: [Git][ghc/ghc][wip/sv/T25246-a] 5 commits: Add a missing tidy in
 UnivCo
Message-ID: <671f86acacda6_1362af34f7385078c@gitlab.mail>



Sjoerd Visscher pushed to branch wip/sv/T25246-a at Glasgow Haskell Compiler / GHC


Commits:
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
324162fa by Sjoerd Visscher at 2024-10-28T13:42:07+01:00
Don't store boot locations in finder cache

Partially reverts commit fff55592a7b

Amends add(Home)ModuleToFinder so that locations for boot files are not stored in the finder cache.

Removes InstalledModule field from InstalledFound constructor since it's the same as the key that was searched for.

- - - - -
36659cf2 by Sjoerd Visscher at 2024-10-28T13:42:08+01:00
Concentrate boot extension logic in Finder

With new mkHomeModLocation that takes an extra HscSource to add boot extensions if required.

- - - - -


14 changed files:

- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Phases.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Env.hs
- compiler/GHC/Unit/Module/Location.hs
- compiler/GHC/Unit/Types.hs
- hadrian/src/Settings/Warnings.hs
- libraries/text


Changes:

=====================================
compiler/GHC/Core/TyCo/Tidy.hs
=====================================
@@ -336,16 +336,18 @@ tidyCo env co
     go (AppCo co1 co2)       = (AppCo $! go co1) $! go co2
     go (ForAllCo tv visL visR h co)
       = ((((ForAllCo $! tvp) $! visL) $! visR) $! (go h)) $! (tidyCo envp co)
-                               where (envp, tvp) = tidyVarBndr env tv
+      where (envp, tvp) = tidyVarBndr env tv
             -- the case above duplicates a bit of work in tidying h and the kind
             -- of tv. But the alternative is to use coercionKind, which seems worse.
     go (FunCo r afl afr w co1 co2) = ((FunCo r afl afr $! go w) $! go co1) $! go co2
     go (CoVarCo cv)          = CoVarCo $! go_cv cv
     go (HoleCo h)            = HoleCo $! go_hole h
     go (AxiomCo ax cos)      = AxiomCo ax $ strictMap go cos
-    go co@(UnivCo { uco_lty  = t1, uco_rty = t2 })
-                             = co { uco_lty = tidyType env t1, uco_rty = tidyType env t2 }
-                               -- Don't bother to tidy the uco_deps field
+    go (UnivCo prov role t1 t2 cos)
+                             = ((UnivCo prov role
+                                $! tidyType env t1)
+                                $! tidyType env t2)
+                                $! strictMap go cos
     go (SymCo co)            = SymCo $! go co
     go (TransCo co1 co2)     = (TransCo $! go co1) $! go co2
     go (SelCo d co)          = SelCo d $! go co


=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -781,7 +781,7 @@ summariseRequirement pn mod_name = do
     let loc = srcLocSpan (mkSrcLoc (mkFastString (bkp_filename env)) 1 1)
 
     let fc = hsc_FC hsc_env
-    mod <- liftIO $ addHomeModuleToFinder fc home_unit (notBoot mod_name) location
+    mod <- liftIO $ addHomeModuleToFinder fc home_unit mod_name location HsigFile
 
     extra_sig_imports <- liftIO $ findExtraSigImports hsc_env HsigFile mod_name
 
@@ -854,17 +854,14 @@ hsModuleToModSummary home_keys pn hsc_src modname
     -- To add insult to injury, we don't even actually use
     -- these filenames to figure out where the hi files go.
     -- A travesty!
-    let location0 = mkHomeModLocation2 fopts modname
+    let location = mkHomeModLocation fopts modname
                              (unsafeEncodeUtf $ unpackFS unit_fs 
                               moduleNameSlashes modname)
-                              (case hsc_src of
+                             (case hsc_src of
                                 HsigFile   -> os "hsig"
                                 HsBootFile -> os "hs-boot"
                                 HsSrcFile  -> os "hs")
-    -- DANGEROUS: bootifying can POISON the module finder cache
-    let location = case hsc_src of
-                        HsBootFile -> addBootSuffixLocnOut location0
-                        _ -> location0
+                             hsc_src
     -- This duplicates a pile of logic in GHC.Driver.Make
     hi_timestamp <- liftIO $ modificationTimeIfExists (ml_hi_file location)
     hie_timestamp <- liftIO $ modificationTimeIfExists (ml_hie_file location)
@@ -893,7 +890,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
     this_mod <- liftIO $ do
       let home_unit = hsc_home_unit hsc_env
       let fc        = hsc_FC hsc_env
-      addHomeModuleToFinder fc home_unit (GWIB modname (hscSourceToIsBoot hsc_src)) location
+      addHomeModuleToFinder fc home_unit modname location hsc_src
     let ms = ModSummary {
             ms_mod = this_mod,
             ms_hsc_src = hsc_src,


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -2123,38 +2123,23 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf
             <- getPreprocessedImports hsc_env src_fn mb_phase maybe_buf
 
         let fopts = initFinderOpts (hsc_dflags hsc_env)
-            src_path = unsafeEncodeUtf src_fn
+            (basename, extension) = splitExtension src_fn
 
-            is_boot = case takeExtension src_fn of
-              ".hs-boot" -> IsBoot
-              ".lhs-boot" -> IsBoot
-              _ -> NotBoot
-
-            (path_without_boot, hsc_src)
-              | isHaskellSigFilename src_fn = (src_path, HsigFile)
-              | IsBoot <- is_boot = (removeBootSuffix src_path, HsBootFile)
-              | otherwise = (src_path, HsSrcFile)
-
-            -- Make a ModLocation for the Finder, who only has one entry for
-            -- each @ModuleName@, and therefore needs to use the locations for
-            -- the non-boot files.
-            location_without_boot =
-              mkHomeModLocation fopts pi_mod_name path_without_boot
+            hsc_src
+              | isHaskellSigSuffix (drop 1 extension) = HsigFile
+              | isHaskellBootSuffix (drop 1 extension) = HsBootFile
+              | otherwise = HsSrcFile
 
             -- Make a ModLocation for this file, adding the @-boot@ suffix to
             -- all paths if the original was a boot file.
-            location
-              | IsBoot <- is_boot
-              = addBootSuffixLocn location_without_boot
-              | otherwise
-              = location_without_boot
+            location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf extension) hsc_src
 
         -- Tell the Finder cache where it is, so that subsequent calls
         -- to findModule will find it, even if it's not on any search path
         mod <- liftIO $ do
           let home_unit = hsc_home_unit hsc_env
           let fc        = hsc_FC hsc_env
-          addHomeModuleToFinder fc home_unit (GWIB pi_mod_name is_boot) location
+          addHomeModuleToFinder fc home_unit pi_mod_name location hsc_src
 
         liftIO $ makeNewModSummary hsc_env $ MakeNewModSummary
             { nms_src_fn = src_fn
@@ -2184,14 +2169,10 @@ checkSummaryHash
            -- and it was likely flushed in depanal. This is not technically
            -- needed when we're called from sumariseModule but it shouldn't
            -- hurt.
-           -- Also, only add to finder cache for non-boot modules as the finder cache
-           -- makes sure to add a boot suffix for boot files.
-           _ <- do
-              let fc = hsc_FC hsc_env
-                  gwib = GWIB (ms_mod old_summary) (isBootSummary old_summary)
-              case ms_hsc_src old_summary of
-                HsSrcFile -> addModuleToFinder fc gwib location
-                _ -> return ()
+           let fc      = hsc_FC hsc_env
+               mod     = ms_mod old_summary
+               hsc_src = ms_hsc_src old_summary
+           addModuleToFinder fc mod location hsc_src
 
            hi_timestamp <- modificationTimeIfExists (ml_hi_file location)
            hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
@@ -2243,7 +2224,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     find_it :: IO SummariseResult
 
     find_it = do
-        found <- findImportedModule hsc_env wanted_mod mb_pkg
+        found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
         case found of
              Found location mod
                 | isJust (ml_hs_file location) ->
@@ -2261,10 +2242,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
     just_found location mod = do
                 -- Adjust location to point to the hs-boot source file,
                 -- hi file, object file, when is_boot says so
-        let location' = case is_boot of
-              IsBoot -> addBootSuffixLocn location
-              NotBoot -> location
-            src_fn = expectJust "summarise2" (ml_hs_file location')
+        let src_fn = expectJust "summarise2" (ml_hs_file location)
 
                 -- Check that it exists
                 -- It might have been deleted since the Finder last found it
@@ -2274,7 +2252,7 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
           -- .hs-boot file doesn't exist.
           Nothing -> return NotThere
           Just h  -> do
-            fresult <- new_summary_cache_check location' mod src_fn h
+            fresult <- new_summary_cache_check location mod src_fn h
             return $ case fresult of
               Left err -> FoundHomeWithError (moduleUnitId mod, err)
               Right ms -> FoundHome ms


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -292,12 +292,12 @@ findDependency  :: HscEnv
 findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do
   -- Find the module; this will be fast because
   -- we've done it once during downsweep
-  r <- findImportedModule hsc_env imp pkg
+  r <- findImportedModuleWithIsBoot hsc_env imp is_boot pkg
   case r of
     Found loc _
         -- Home package: just depend on the .hi or hi-boot file
         | isJust (ml_hs_file loc) || include_pkg_deps
-        -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc)))
+        -> return (Just (unsafeDecodeUtf $ ml_hi_file_ospath loc))
 
         -- Not in this package: we don't need a dependency
         | otherwise


=====================================
compiler/GHC/Driver/Phases.hs
=====================================
@@ -23,6 +23,7 @@ module GHC.Driver.Phases (
    isDynLibSuffix,
    isHaskellUserSrcSuffix,
    isHaskellSigSuffix,
+   isHaskellBootSuffix,
    isSourceSuffix,
 
    isHaskellishTarget,
@@ -234,7 +235,7 @@ phaseInputExt Js                  = "js"
 phaseInputExt StopLn              = "o"
 
 haskellish_src_suffixes, backpackish_suffixes, haskellish_suffixes, cish_suffixes,
-    js_suffixes, haskellish_user_src_suffixes, haskellish_sig_suffixes
+    js_suffixes, haskellish_user_src_suffixes, haskellish_sig_suffixes, haskellish_boot_suffixes
  :: [String]
 -- When a file with an extension in the haskellish_src_suffixes group is
 -- loaded in --make mode, its imports will be loaded too.
@@ -247,7 +248,8 @@ js_suffixes                  = [ "js" ]
 
 -- Will not be deleted as temp files:
 haskellish_user_src_suffixes =
-  haskellish_sig_suffixes ++ [ "hs", "lhs", "hs-boot", "lhs-boot" ]
+  haskellish_sig_suffixes ++ haskellish_boot_suffixes ++ [ "hs", "lhs" ]
+haskellish_boot_suffixes     = [ "hs-boot", "lhs-boot" ]
 haskellish_sig_suffixes      = [ "hsig", "lhsig" ]
 backpackish_suffixes         = [ "bkp" ]
 
@@ -265,11 +267,12 @@ dynlib_suffixes platform = case platformOS platform of
   _         -> ["so"]
 
 isHaskellishSuffix, isBackpackishSuffix, isHaskellSrcSuffix, isCishSuffix,
-    isHaskellUserSrcSuffix, isJsSuffix, isHaskellSigSuffix
+    isHaskellUserSrcSuffix, isJsSuffix, isHaskellSigSuffix, isHaskellBootSuffix
  :: String -> Bool
 isHaskellishSuffix     s = s `elem` haskellish_suffixes
 isBackpackishSuffix    s = s `elem` backpackish_suffixes
 isHaskellSigSuffix     s = s `elem` haskellish_sig_suffixes
+isHaskellBootSuffix    s = s `elem` haskellish_boot_suffixes
 isHaskellSrcSuffix     s = s `elem` haskellish_src_suffixes
 isCishSuffix           s = s `elem` cish_suffixes
 isJsSuffix             s = s `elem` js_suffixes


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -734,7 +734,7 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   mod <- do
     let home_unit = hsc_home_unit hsc_env
     let fc        = hsc_FC hsc_env
-    addHomeModuleToFinder fc home_unit (GWIB mod_name (hscSourceToIsBoot src_flavour)) location
+    addHomeModuleToFinder fc home_unit mod_name location src_flavour
 
   -- Make the ModSummary to hand to hscMain
   let
@@ -777,24 +777,18 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod
 mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
     let PipeEnv{ src_basename=basename,
              src_suffix=suff } = pipe_env
-    let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff)
-
-    -- Boot-ify it if necessary
-    let location2
-          | HsBootFile <- src_flavour = addBootSuffixLocnOut location1
-          | otherwise                 = location1
-
+    let location1 = mkHomeModLocation fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) src_flavour
 
     -- Take -ohi into account if present
     -- This can't be done in mkHomeModuleLocation because
     -- it only applies to the module being compiles
     let ohi = outputHi dflags
-        location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf  fn }
-                  | otherwise      = location2
+        location2 | Just fn <- ohi = location1{ ml_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise      = location1
 
     let dynohi = dynOutputHi dflags
-        location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
-                  | otherwise         = location3
+        location3 | Just fn <- dynohi = location2{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn }
+                  | otherwise         = location2
 
     -- Take -o into account if present
     -- Very like -ohi, but we must *only* do this if we aren't linking
@@ -807,11 +801,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do
         location5 | Just ofile <- expl_o_file
                   , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file
                   , isNoLink (ghcLink dflags)
-                  = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile
+                  = location3 { ml_obj_file_ospath = unsafeEncodeUtf ofile
                               , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
                   | Just dyn_ofile <- expl_dyn_o_file
-                  = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
-                  | otherwise = location4
+                  = location3 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile }
+                  | otherwise = location3
     return location5
     where
       fopts = initFinderOpts dflags


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -896,9 +896,9 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
       else do
           let fopts = initFinderOpts dflags
           -- Look for the file
-          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod)
+          mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
           case mb_found of
-              InstalledFound (addBootSuffixLocn_maybe hi_boot_file -> loc) mod -> do
+              InstalledFound loc -> do
                   -- See Note [Home module load error]
                   case mhome_unit of
                     Just home_unit


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -15,6 +15,7 @@ module GHC.Unit.Finder (
     FinderCache(..),
     initFinderCache,
     findImportedModule,
+    findImportedModuleWithIsBoot,
     findPluginModule,
     findExactModule,
     findHomeModule,
@@ -55,6 +56,7 @@ import GHC.Utils.Panic
 
 import GHC.Linker.Types
 import GHC.Types.PkgQual
+import GHC.Types.SourceFile
 
 import GHC.Fingerprint
 import Data.IORef
@@ -103,28 +105,28 @@ InstalledNotFound.
 
 initFinderCache :: IO FinderCache
 initFinderCache = do
-  mod_cache <- newIORef emptyInstalledModuleWithIsBootEnv
+  mod_cache <- newIORef emptyInstalledModuleEnv
   file_cache <- newIORef M.empty
   let flushFinderCaches :: UnitEnv -> IO ()
       flushFinderCaches ue = do
-        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleWithIsBootEnv is_ext fm, ())
+        atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
         atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
        where
-        is_ext mod _ = not (isUnitEnvInstalledModule ue (gwib_mod mod))
+        is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
 
-      addToFinderCache :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+      addToFinderCache :: InstalledModule -> InstalledFindResult -> IO ()
       addToFinderCache key val =
         atomicModifyIORef' mod_cache $ \c ->
-          case (lookupInstalledModuleWithIsBootEnv c key, val) of
+          case (lookupInstalledModuleEnv c key, val) of
             -- Don't overwrite an InstalledFound with an InstalledNotFound
             -- See [Note Monotonic addToFinderCache]
             (Just InstalledFound{}, InstalledNotFound{}) -> (c, ())
-            _ -> (extendInstalledModuleWithIsBootEnv c key val, ())
+            _ -> (extendInstalledModuleEnv c key val, ())
 
-      lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+      lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
       lookupFinderCache key = do
          c <- readIORef mod_cache
-         return $! lookupInstalledModuleWithIsBootEnv c key
+         return $! lookupInstalledModuleEnv c key
 
       lookupFileCache :: FilePath -> IO Fingerprint
       lookupFileCache key = do
@@ -156,6 +158,13 @@ findImportedModule hsc_env mod pkg_qual =
   in do
     findImportedModuleNoHsc fc fopts (hsc_unit_env hsc_env) mhome_unit mod pkg_qual
 
+findImportedModuleWithIsBoot :: HscEnv -> ModuleName -> IsBootInterface -> PkgQual -> IO FindResult
+findImportedModuleWithIsBoot hsc_env mod is_boot pkg_qual = do
+  res <- findImportedModule hsc_env mod pkg_qual
+  case (res, is_boot) of
+    (Found loc mod, IsBoot) -> return (Found (addBootSuffixLocn loc) mod)
+    _ -> return res
+
 findImportedModuleNoHsc
   :: FinderCache
   -> FinderOpts
@@ -228,15 +237,19 @@ findPluginModule fc fopts units Nothing mod_name =
 -- reading the interface for a module mentioned by another interface,
 -- for example (a "system import").
 
-findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod = do
-  case mhome_unit of
+findExactModule :: FinderCache -> FinderOpts ->  UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
+  res <- case mhome_unit of
     Just home_unit
      | isHomeInstalledModule home_unit mod
         -> findInstalledHomeModule fc fopts (homeUnitId home_unit) (moduleName mod)
      | Just home_fopts <- unitEnv_lookup_maybe (moduleUnit mod) other_fopts
         -> findInstalledHomeModule fc home_fopts (moduleUnit mod) (moduleName mod)
     _ -> findPackageModule fc unit_state fopts mod
+  case (res, is_boot) of
+    (InstalledFound loc, IsBoot) -> return (InstalledFound (addBootSuffixLocn loc))
+    _ -> return res
+
 
 -- -----------------------------------------------------------------------------
 -- Helpers
@@ -274,7 +287,7 @@ orIfNotFound this or_this = do
 homeSearchCache :: FinderCache -> UnitId -> ModuleName -> IO InstalledFindResult -> IO InstalledFindResult
 homeSearchCache fc home_unit mod_name do_this = do
   let mod = mkModule home_unit mod_name
-  modLocationCache fc (notBoot mod) do_this
+  modLocationCache fc mod do_this
 
 findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
 findExposedPackageModule fc fopts units mod_name mb_pkg =
@@ -296,7 +309,7 @@ findLookupResult fc fopts r = case r of
         -- with just the location of the thing that was
         -- instantiated; you probably also need all of the
         -- implicit locations from the instances
-        InstalledFound loc   _ -> return (Found loc m)
+        InstalledFound loc     -> return (Found loc m)
         InstalledNoPackage   _ -> return (NoPackage (moduleUnit m))
         InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m)
                                          , fr_pkgs_hidden = []
@@ -331,7 +344,7 @@ findLookupResult fc fopts r = case r of
                        , fr_unusables = []
                        , fr_suggestions = suggest' })
 
-modLocationCache :: FinderCache -> InstalledModuleWithIsBoot -> IO InstalledFindResult -> IO InstalledFindResult
+modLocationCache :: FinderCache -> InstalledModule -> IO InstalledFindResult -> IO InstalledFindResult
 modLocationCache fc mod do_this = do
   m <- lookupFinderCache fc mod
   case m of
@@ -341,17 +354,19 @@ modLocationCache fc mod do_this = do
         addToFinderCache fc mod result
         return result
 
-addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
-addModuleToFinder fc mod loc = do
-  let imod = fmap toUnitId <$> mod
-  addToFinderCache fc imod (InstalledFound loc (gwib_mod imod))
+addModuleToFinder :: FinderCache -> Module -> ModLocation -> HscSource -> IO ()
+addModuleToFinder fc mod loc src_flavour = do
+  let imod = toUnitId <$> mod
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc imod (InstalledFound loc)
 
 -- This returns a module because it's more convenient for users
-addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
-addHomeModuleToFinder fc home_unit mod_name loc = do
-  let mod = mkHomeInstalledModule home_unit <$> mod_name
-  addToFinderCache fc mod (InstalledFound loc (gwib_mod mod))
-  return (mkHomeModule home_unit (gwib_mod mod_name))
+addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleName -> ModLocation -> HscSource -> IO Module
+addHomeModuleToFinder fc home_unit mod_name loc src_flavour = do
+  let mod = mkHomeInstalledModule home_unit mod_name
+  unless (src_flavour == HsBootFile) $
+    addToFinderCache fc mod (InstalledFound loc)
+  return (mkHomeModule home_unit mod_name)
 
 -- -----------------------------------------------------------------------------
 --      The internal workers
@@ -361,7 +376,7 @@ findHomeModule fc fopts  home_unit mod_name = do
   let uid       = homeUnitAsUnit home_unit
   r <- findInstalledHomeModule fc fopts (homeUnitId home_unit) mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name)
+    InstalledFound loc -> Found loc (mkHomeModule home_unit mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -386,7 +401,7 @@ findHomePackageModule fc fopts  home_unit mod_name = do
   let uid       = RealUnit (Definite home_unit)
   r <- findInstalledHomeModule fc fopts home_unit mod_name
   return $ case r of
-    InstalledFound loc _ -> Found loc (mkModule uid mod_name)
+    InstalledFound loc -> Found loc (mkModule uid mod_name)
     InstalledNoPackage _ -> NoPackage uid -- impossible
     InstalledNotFound fps _ -> NotFound {
         fr_paths = fmap unsafeDecodeUtf fps,
@@ -456,7 +471,7 @@ findInstalledHomeModule fc fopts home_unit mod_name = do
    -- This is important only when compiling the base package (where GHC.Prim
    -- is a home module).
    if mod `installedModuleEq` gHC_PRIM
-         then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+         then return (InstalledFound (error "GHC.Prim ModLocation"))
          else searchPathExts search_dirs mod exts
 
 -- | Prepend the working directory to the search path.
@@ -485,11 +500,11 @@ findPackageModule_ :: FinderCache -> FinderOpts -> InstalledModule -> UnitInfo -
 findPackageModule_ fc fopts mod pkg_conf = do
   massertPpr (moduleUnit mod == unitId pkg_conf)
              (ppr (moduleUnit mod) <+> ppr (unitId pkg_conf))
-  modLocationCache fc (notBoot mod) $
+  modLocationCache fc mod $
 
     -- special case for GHC.Prim; we won't find it in the filesystem.
     if mod `installedModuleEq` gHC_PRIM
-          then return (InstalledFound (error "GHC.Prim ModLocation") mod)
+          then return (InstalledFound (error "GHC.Prim ModLocation"))
           else
 
     let
@@ -513,7 +528,7 @@ findPackageModule_ fc fopts mod pkg_conf = do
             -- don't bother looking for it.
             let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod)
                 loc = mk_hi_loc one basename
-            in return $ InstalledFound loc mod
+            in return $ InstalledFound loc
       _otherwise ->
             searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
@@ -547,7 +562,7 @@ searchPathExts paths mod exts = search to_search
     search ((file, loc) : rest) = do
       b <- doesFileExist file
       if b
-        then return $ InstalledFound loc mod
+        then return $ InstalledFound loc
         else search rest
 
 mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt
@@ -589,10 +604,12 @@ mkHomeModLocationSearched fopts mod suff path basename =
 -- ext
 --      The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
-mkHomeModLocation dflags mod src_filename =
-   let (basename,extension) = OsPath.splitExtension src_filename
-   in mkHomeModLocation2 dflags mod basename extension
+mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> FileExt -> HscSource -> ModLocation
+mkHomeModLocation dflags mod src_basename ext hsc_src =
+   let loc = mkHomeModLocation2 dflags mod src_basename ext
+   in case hsc_src of
+     HsBootFile -> addBootSuffixLocnOut loc
+     _ -> loc
 
 mkHomeModLocation2 :: FinderOpts
                    -> ModuleName


=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -30,9 +30,9 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                -- ^ remove all the home modules from the cache; package modules are
                                -- assumed to not move around during a session; also flush the file hash
                                -- cache.
-                               , addToFinderCache  :: InstalledModuleWithIsBoot -> InstalledFindResult -> IO ()
+                               , addToFinderCache  :: InstalledModule -> InstalledFindResult -> IO ()
                                -- ^ Add a found location to the cache for the module.
-                               , lookupFinderCache :: InstalledModuleWithIsBoot -> IO (Maybe InstalledFindResult)
+                               , lookupFinderCache :: InstalledModule -> IO (Maybe InstalledFindResult)
                                -- ^ Look for a location in the cache.
                                , lookupFileCache   :: FilePath -> IO Fingerprint
                                -- ^ Look for the hash of a file in the cache. This should add it to the
@@ -40,7 +40,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
                                }
 
 data InstalledFindResult
-  = InstalledFound ModLocation InstalledModule
+  = InstalledFound ModLocation
   | InstalledNoPackage UnitId
   | InstalledNotFound [OsPath] (Maybe UnitId)
 


=====================================
compiler/GHC/Unit/Module/Env.hs
=====================================
@@ -33,17 +33,6 @@ module GHC.Unit.Module.Env
    , mergeInstalledModuleEnv
    , plusInstalledModuleEnv
    , installedModuleEnvElts
-
-     -- * InstalledModuleWithIsBootEnv
-   , InstalledModuleWithIsBootEnv
-   , emptyInstalledModuleWithIsBootEnv
-   , lookupInstalledModuleWithIsBootEnv
-   , extendInstalledModuleWithIsBootEnv
-   , filterInstalledModuleWithIsBootEnv
-   , delInstalledModuleWithIsBootEnv
-   , mergeInstalledModuleWithIsBootEnv
-   , plusInstalledModuleWithIsBootEnv
-   , installedModuleWithIsBootEnvElts
    )
 where
 
@@ -294,56 +283,3 @@ plusInstalledModuleEnv :: (elt -> elt -> elt)
 plusInstalledModuleEnv f (InstalledModuleEnv xm) (InstalledModuleEnv ym) =
   InstalledModuleEnv $ Map.unionWith f xm ym
 
-
-
---------------------------------------------------------------------
--- InstalledModuleWithIsBootEnv
---------------------------------------------------------------------
-
--- | A map keyed off of 'InstalledModuleWithIsBoot'
-newtype InstalledModuleWithIsBootEnv elt = InstalledModuleWithIsBootEnv (Map InstalledModuleWithIsBoot elt)
-
-instance Outputable elt => Outputable (InstalledModuleWithIsBootEnv elt) where
-  ppr (InstalledModuleWithIsBootEnv env) = ppr env
-
-
-emptyInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a
-emptyInstalledModuleWithIsBootEnv = InstalledModuleWithIsBootEnv Map.empty
-
-lookupInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> Maybe a
-lookupInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = Map.lookup m e
-
-extendInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> a -> InstalledModuleWithIsBootEnv a
-extendInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m x = InstalledModuleWithIsBootEnv (Map.insert m x e)
-
-filterInstalledModuleWithIsBootEnv :: (InstalledModuleWithIsBoot -> a -> Bool) -> InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBootEnv a
-filterInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv e) =
-  InstalledModuleWithIsBootEnv (Map.filterWithKey f e)
-
-delInstalledModuleWithIsBootEnv :: InstalledModuleWithIsBootEnv a -> InstalledModuleWithIsBoot -> InstalledModuleWithIsBootEnv a
-delInstalledModuleWithIsBootEnv (InstalledModuleWithIsBootEnv e) m = InstalledModuleWithIsBootEnv (Map.delete m e)
-
-installedModuleWithIsBootEnvElts :: InstalledModuleWithIsBootEnv a -> [(InstalledModuleWithIsBoot, a)]
-installedModuleWithIsBootEnvElts (InstalledModuleWithIsBootEnv e) = Map.assocs e
-
-mergeInstalledModuleWithIsBootEnv
-  :: (elta -> eltb -> Maybe eltc)
-  -> (InstalledModuleWithIsBootEnv elta -> InstalledModuleWithIsBootEnv eltc)  -- map X
-  -> (InstalledModuleWithIsBootEnv eltb -> InstalledModuleWithIsBootEnv eltc) -- map Y
-  -> InstalledModuleWithIsBootEnv elta
-  -> InstalledModuleWithIsBootEnv eltb
-  -> InstalledModuleWithIsBootEnv eltc
-mergeInstalledModuleWithIsBootEnv f g h (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym)
-  = InstalledModuleWithIsBootEnv $ Map.mergeWithKey
-      (\_ x y -> (x `f` y))
-      (coerce g)
-      (coerce h)
-      xm ym
-
-plusInstalledModuleWithIsBootEnv :: (elt -> elt -> elt)
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-  -> InstalledModuleWithIsBootEnv elt
-plusInstalledModuleWithIsBootEnv f (InstalledModuleWithIsBootEnv xm) (InstalledModuleWithIsBootEnv ym) =
-  InstalledModuleWithIsBootEnv $ Map.unionWith f xm ym
-


=====================================
compiler/GHC/Unit/Module/Location.hs
=====================================
@@ -13,8 +13,6 @@ module GHC.Unit.Module.Location
     )
    , pattern ModLocation
    , addBootSuffix
-   , addBootSuffix_maybe
-   , addBootSuffixLocn_maybe
    , addBootSuffixLocn
    , addBootSuffixLocnOut
    , removeBootSuffix
@@ -25,7 +23,6 @@ where
 import GHC.Prelude
 
 import GHC.Data.OsPath
-import GHC.Unit.Types
 import GHC.Types.SrcLoc
 import GHC.Utils.Outputable
 import GHC.Data.FastString (mkFastString)
@@ -99,26 +96,10 @@ removeBootSuffix pathWithBootSuffix =
     Just path -> path
     Nothing -> error "removeBootSuffix: no -boot suffix"
 
--- | Add the @-boot@ suffix if the @Bool@ argument is @True@
-addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath
-addBootSuffix_maybe is_boot path = case is_boot of
-  IsBoot -> addBootSuffix path
-  NotBoot -> path
-
-addBootSuffixLocn_maybe :: IsBootInterface -> ModLocation -> ModLocation
-addBootSuffixLocn_maybe is_boot locn = case is_boot of
-  IsBoot -> addBootSuffixLocn locn
-  _ -> locn
-
 -- | Add the @-boot@ suffix to all file paths associated with the module
 addBootSuffixLocn :: ModLocation -> ModLocation
 addBootSuffixLocn locn
-  = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn)
-         , ml_hi_file_ospath  = addBootSuffix (ml_hi_file_ospath locn)
-         , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn)
-         , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn)
-         , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn)
-         , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) }
+  = addBootSuffixLocnOut locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) }
 
 -- | Add the @-boot@ suffix to all output file paths associated with the
 -- module, not including the input file itself


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -84,8 +84,6 @@ module GHC.Unit.Types
    , GenWithIsBoot (..)
    , ModuleNameWithIsBoot
    , ModuleWithIsBoot
-   , InstalledModuleWithIsBoot
-   , notBoot
    )
 where
 
@@ -720,8 +718,6 @@ type ModuleNameWithIsBoot = GenWithIsBoot ModuleName
 
 type ModuleWithIsBoot = GenWithIsBoot Module
 
-type InstalledModuleWithIsBoot = GenWithIsBoot InstalledModule
-
 instance Binary a => Binary (GenWithIsBoot a) where
   put_ bh (GWIB { gwib_mod, gwib_isBoot }) = do
     put_ bh gwib_mod
@@ -735,6 +731,3 @@ instance Outputable a => Outputable (GenWithIsBoot a) where
   ppr (GWIB  { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
     IsBoot -> [ text "{-# SOURCE #-}" ]
     NotBoot -> []
-
-notBoot :: mod -> GenWithIsBoot mod
-notBoot gwib_mod = GWIB {gwib_mod, gwib_isBoot = NotBoot}


=====================================
hadrian/src/Settings/Warnings.hs
=====================================
@@ -66,7 +66,9 @@ ghcWarningsArgs = do
         , package primitive    ? pure [ "-Wno-unused-imports"
                                       , "-Wno-deprecations" ]
         , package rts          ? pure [ "-Wcpp-undef" ]
-        , package text         ? pure [ "-Wno-deprecations", "-Wno-deriving-typeable" ]
+        , package text         ? pure [ "-Wno-deprecations"
+                                      , "-Wno-deriving-typeable"
+                                      , "-Wno-unused-imports" ]
         , package terminfo     ? pure [ "-Wno-unused-imports", "-Wno-deriving-typeable" ]
         , package stm          ? pure [ "-Wno-deriving-typeable" ]
         , package osString     ? pure [ "-Wno-deriving-typeable" ]


=====================================
libraries/text
=====================================
@@ -1 +1 @@
-Subproject commit cdb9e13b39079904eed9d75cd332b66ee0cad0c0
+Subproject commit ee0a8f8b9a4bd3fdad23e9ac0db56e7f08ce35cd



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c046b1e58181d8f5edf62efc7f8ca0c8ccc46e2...36659cf2d0aab2df73c56441e4610f63c5275fff

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c046b1e58181d8f5edf62efc7f8ca0c8ccc46e2...36659cf2d0aab2df73c56441e4610f63c5275fff
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 13:49:13 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 09:49:13 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] 2 commits: IfaceOverlapFlag
 introduced
Message-ID: <671f965944ab7_1362af677ab459944@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
e49bd65c by Hassan Al-Awwadi at 2024-10-28T14:47:37+01:00
IfaceOverlapFlag introduced

this felt like the principled thing to do because we want interface file generation to only deal with simple types.

- - - - -
f940806f by Hassan Al-Awwadi at 2024-10-28T14:48:45+01:00
whitespace

- - - - -


6 changed files:

- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/OverlapPragma.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -41,7 +41,9 @@ module GHC.CoreToIface
     , toIfaceCon
     , toIfaceApp
     , toIfaceVar
-    -- * InlinePragma
+    -- * Pragmas
+    , toIfaceOverlapFlag
+    , toIfaceOverlapMode
     , toIfaceActivation
     , toIfaceInlineSpec
     , toIfaceInlinePragma
@@ -89,6 +91,7 @@ import GHC.Types.Cpr ( topCprSig )
 
 import GHC.Hs.Extension ( GhcPass )
 import GHC.Hs.InlinePragma
+import GHC.Hs.OverlapPragma
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
@@ -671,14 +674,18 @@ toIfaceVar v
     noinline_id | isConstraintKind (typeKind ty) = noinlineConstraintIdName
                 | otherwise                      = noinlineIdName
 
---------------------
-toIfaceActivation :: Activation (GhcPass p) -> IfaceActivation
-toIfaceActivation (AlwaysActive _         ) = IfAlwaysActive
-toIfaceActivation (ActiveBefore src phase ) = IfActiveBefore src phase
-toIfaceActivation (ActiveAfter  src phase)  = IfActiveAfter src phase
-toIfaceActivation (FinalActive  _         ) = IfFinalActive
-toIfaceActivation (NeverActive  _         ) = IfNeverActive
-toIfaceActivation (XActivation  impossible) = dataConCantHappen impossible
+{-
+************************************************************************
+*                                                                      *
+        Conversion of Pragmas
+*                                                                      *
+************************************************************************
+-}
+
+toIfaceInlinePragma :: InlinePragma (GhcPass p) -> IfaceInlinePragma
+toIfaceInlinePragma (InlinePragma s a b c)
+  = IfInlinePragma (inl_txt s) (toIfaceInlineSpec a) (inl_arr s) (toIfaceActivation b) c
+toIfaceInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible
 
 toIfaceInlineSpec :: InlineSpec (GhcPass p) -> IfaceInlineSpec
 toIfaceInlineSpec (Inline    src)          = IfInline    src
@@ -688,10 +695,25 @@ toIfaceInlineSpec (Opaque    src)          = IfOpaque    src
 toIfaceInlineSpec (NoUserInlinePrag _)     = IfNoUserInlinePrag
 toIfaceInlineSpec (XInlineSpec impossible) = dataConCantHappen impossible
 
-toIfaceInlinePragma :: InlinePragma (GhcPass p) -> IfaceInlinePragma
-toIfaceInlinePragma (InlinePragma s a b c)
-  = IfInlinePragma (inl_txt s) (toIfaceInlineSpec a) (inl_arr s) (toIfaceActivation b) c
-toIfaceInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible
+toIfaceActivation :: Activation (GhcPass p) -> IfaceActivation
+toIfaceActivation (AlwaysActive _         ) = IfAlwaysActive
+toIfaceActivation (ActiveBefore src phase ) = IfActiveBefore src phase
+toIfaceActivation (ActiveAfter  src phase)  = IfActiveAfter src phase
+toIfaceActivation (FinalActive  _         ) = IfFinalActive
+toIfaceActivation (NeverActive  _         ) = IfNeverActive
+toIfaceActivation (XActivation  impossible) = dataConCantHappen impossible
+
+toIfaceOverlapFlag :: OverlapFlag -> IfaceOverlapFlag
+toIfaceOverlapFlag (OverlapFlag overlap safe)
+  = IfOverlapFlag (toIfaceOverlapMode overlap) safe
+
+toIfaceOverlapMode :: OverlapMode (GhcPass p) -> IfaceOverlapMode
+toIfaceOverlapMode (NoOverlap sourceText)                   = IfNoOverlap sourceText
+toIfaceOverlapMode (Overlappable sourceText)                = IfOverlappable sourceText
+toIfaceOverlapMode (Overlapping sourceText)                 = IfOverlapping sourceText
+toIfaceOverlapMode (Overlaps sourceText)                    = IfOverlaps sourceText
+toIfaceOverlapMode (Incoherent sourceText)                  = IfIncoherent sourceText
+toIfaceOverlapMode (XOverlapMode (NonCanonical sourceText)) = IfNonCanonical sourceText
 
 ---------------------
 toIfaceLFInfo :: Name -> LambdaFormInfo -> IfaceLFInfo


=====================================
compiler/GHC/Hs/OverlapPragma.hs
=====================================
@@ -84,33 +84,6 @@ instance Outputable (OverlapMode (GhcPass p)) where
 instance Outputable OverlapFlag where
    ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag)
 
--- might want to make an explicit IfaceOverlapMode, I guess
-instance Binary (OverlapMode (GhcPass p)) where
-    put_ bh (NoOverlap    s)                = putByte bh 0 >> put_ bh s
-    put_ bh (Overlaps     s)                = putByte bh 1 >> put_ bh s
-    put_ bh (Incoherent   s)                = putByte bh 2 >> put_ bh s
-    put_ bh (Overlapping  s)                = putByte bh 3 >> put_ bh s
-    put_ bh (Overlappable s)                = putByte bh 4 >> put_ bh s
-    put_ bh (XOverlapMode (NonCanonical s)) = putByte bh 5 >> put_ bh s
-    get bh = do
-        h <- getByte bh
-        case h of
-            0 -> (get bh) >>= \s -> return $ NoOverlap s
-            1 -> (get bh) >>= \s -> return $ Overlaps s
-            2 -> (get bh) >>= \s -> return $ Incoherent s
-            3 -> (get bh) >>= \s -> return $ Overlapping s
-            4 -> (get bh) >>= \s -> return $ Overlappable s
-            5 -> (get bh) >>= \s -> return $ XOverlapMode (NonCanonical s)
-            _ -> panic ("get OverlapMode" ++ show h)
-
-
-instance Binary OverlapFlag where
-    put_ bh flag = do put_ bh (overlapMode flag)
-                      put_ bh (isSafeOverlap flag)
-    get bh = do
-        h <- get bh
-        b <- get bh
-        return OverlapFlag { overlapMode = h, isSafeOverlap = b }
 
 
 ------------------------


=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -427,7 +427,7 @@ instanceToIfaceInst (ClsInst { is_dfun = dfun_id, is_flag = oflag
                              , is_warn = warn })
   = assert (cls_name == className cls) $
     IfaceClsInst { ifDFun     = idName dfun_id
-                 , ifOFlag    = oflag
+                 , ifOFlag    = toIfaceOverlapFlag oflag
                  , ifInstCls  = cls_name
                  , ifInstTys  = ifaceRoughMatchTcs $ tail rough_tcs
                    -- N.B. Drop the class name from the rough match template


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -18,6 +18,7 @@ module GHC.Iface.Syntax (
         IfaceInfoItem(..), IfaceRule(..), IfaceAnnotation(..), IfaceAnnTarget,
         IfaceWarnings(..), IfaceWarningTxt(..), IfaceStringLiteral(..),
         IfaceDefault(..), IfaceClsInst(..), IfaceFamInst(..), IfaceTickish(..),
+        IfaceOverlapFlag(..), IfaceOverlapMode(..),
         IfaceClassBody(..), IfaceBooleanFormula(..),
         IfaceInlinePragma(..), IfaceInlineSpec(..), IfaceActivation(..),
         IfaceBang(..),
@@ -36,6 +37,9 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
+
+        fromIfaceOverlapFlag,
+        fromIfaceOverlapMode,
         fromIfaceBooleanFormula,
         fromIfaceActivation,
         fromIfaceInlineSpec,
@@ -342,7 +346,7 @@ data IfaceClsInst
   = IfaceClsInst { ifInstCls  :: IfExtName,                -- See comments with
                    ifInstTys  :: [Maybe IfaceTyCon],       -- the defn of ClsInst
                    ifDFun     :: IfExtName,                -- The dfun
-                   ifOFlag    :: OverlapFlag,              -- Overlap flag
+                   ifOFlag    :: IfaceOverlapFlag,              -- Overlap flag
                    ifInstOrph :: IsOrphan,                 -- See Note [Orphans] in GHC.Core.InstEnv
                    ifInstWarn :: Maybe IfaceWarningTxt }
                      -- Warning emitted when the instance is used
@@ -355,6 +359,33 @@ data IfaceClsInst
         -- If this instance decl is *used*, we'll record a usage on the dfun;
         -- and if the head does not change it won't be used if it wasn't before
 
+
+
+data IfaceOverlapFlag
+  = IfOverlapFlag { ifOverlapMode   :: IfaceOverlapMode
+                     , ifisSafeOverlap :: Bool
+                     }
+
+fromIfaceOverlapFlag :: IfaceOverlapFlag -> OverlapFlag
+fromIfaceOverlapFlag (IfOverlapFlag overlap safe)
+  = OverlapFlag (fromIfaceOverlapMode overlap) safe
+
+data IfaceOverlapMode
+  = IfNoOverlap SourceText
+  | IfOverlappable SourceText
+  | IfOverlapping SourceText
+  | IfOverlaps SourceText
+  | IfIncoherent SourceText
+  | IfNonCanonical SourceText
+
+fromIfaceOverlapMode :: IfaceOverlapMode -> OverlapMode (GhcPass p)
+fromIfaceOverlapMode (IfNoOverlap sourceText)    = NoOverlap sourceText
+fromIfaceOverlapMode (IfOverlappable sourceText) = Overlappable sourceText
+fromIfaceOverlapMode (IfOverlapping sourceText)  = Overlapping sourceText
+fromIfaceOverlapMode (IfOverlaps sourceText)     = Overlaps sourceText
+fromIfaceOverlapMode (IfIncoherent sourceText)   = Incoherent sourceText
+fromIfaceOverlapMode (IfNonCanonical sourceText) = XOverlapMode (NonCanonical sourceText)
+
 -- The ifFamInstTys field of IfaceFamInst contains a list of the rough
 -- match types
 data IfaceFamInst
@@ -1476,7 +1507,7 @@ instance Outputable IfaceClsInst where
   ppr (IfaceClsInst { ifDFun = dfun_id, ifOFlag = flag
                     , ifInstCls = cls, ifInstTys = mb_tcs
                     , ifInstOrph = orph })
-    = hang (text "instance" <+> ppr flag
+    = hang (text "instance" <+> ppr (fromIfaceOverlapFlag flag)
               <+> (if isOrphan orph then text "[orphan]" else Outputable.empty)
               <+> ppr cls <+> brackets (pprWithCommas ppr_rough mb_tcs))
          2 (equals <+> ppr dfun_id)
@@ -2453,6 +2484,34 @@ instance Binary IfaceClsInst where
         warn <- get bh
         return (IfaceClsInst cls tys dfun flag orph warn)
 
+instance Binary IfaceOverlapFlag where
+    put_ bh flag = do put_ bh (ifOverlapMode flag)
+                      put_ bh (ifisSafeOverlap flag)
+    get bh = do
+        h <- get bh
+        b <- get bh
+        return IfOverlapFlag { ifOverlapMode = h, ifisSafeOverlap = b }
+
+instance Binary IfaceOverlapMode where
+    put_ bh (IfNoOverlap    s) = putByte bh 0 >> put_ bh s
+    put_ bh (IfOverlaps     s) = putByte bh 1 >> put_ bh s
+    put_ bh (IfIncoherent   s) = putByte bh 2 >> put_ bh s
+    put_ bh (IfOverlapping  s) = putByte bh 3 >> put_ bh s
+    put_ bh (IfOverlappable s) = putByte bh 4 >> put_ bh s
+    put_ bh (IfNonCanonical s) = putByte bh 5 >> put_ bh s
+    get bh = do
+        h <- getByte bh
+        case h of
+            0 -> (get bh) >>= \s -> return $ IfNoOverlap s
+            1 -> (get bh) >>= \s -> return $ IfOverlaps s
+            2 -> (get bh) >>= \s -> return $ IfIncoherent s
+            3 -> (get bh) >>= \s -> return $ IfOverlapping s
+            4 -> (get bh) >>= \s -> return $ IfOverlappable s
+            5 -> (get bh) >>= \s -> return $ IfNonCanonical s
+            _ -> panic ("get OverlapMode" ++ show h)
+
+
+
 instance Binary IfaceFamInst where
     put_ bh (IfaceFamInst fam tys name orph) = do
         put_ bh fam


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -1266,7 +1266,7 @@ tcIfaceInst (IfaceClsInst { ifDFun = dfun_name, ifOFlag = oflag
                     fmap tyThingId (tcIfaceImplicit dfun_name)
        ; let mb_tcs' = map tcRoughTyCon mb_tcs
              warn = fmap fromIfaceWarningTxt iface_warn
-       ; return (mkImportedClsInst cls mb_tcs' dfun_name dfun oflag orph warn) }
+       ; return (mkImportedClsInst cls mb_tcs' dfun_name dfun (fromIfaceOverlapFlag oflag) orph warn) }
 
 tcIfaceFamInst :: IfaceFamInst -> IfL FamInst
 tcIfaceFamInst (IfaceFamInst { ifFamInstFam = fam, ifFamInstTys = mb_tcs


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2118,13 +2118,13 @@ instance ExactPrint (RuleDecl GhcPs) where
 
 
 markActivationL :: (Monad m, Monoid w)
-  => a -> Lens a ActivationAnn -> Activation -> EP w m a
+  => a -> Lens a ActivationAnn -> Activation (GhcPass p) -> EP w m a
 markActivationL a l act = do
   new <- markActivation (view l a) act
   return (set l new a)
 
 markActivation :: (Monad m, Monoid w)
-  => ActivationAnn -> Activation -> EP w m ActivationAnn
+  => ActivationAnn -> Activation (GhcPass p) -> EP w m ActivationAnn
 markActivation (ActivationAnn o c t v) act = do
   case act of
     ActiveBefore src phase -> do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1a7812a525017f46958e555b08e75765a6e7545c...f940806f888655821a79d482873617ff00cbbc38

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1a7812a525017f46958e555b08e75765a6e7545c...f940806f888655821a79d482873617ff00cbbc38
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 14:21:21 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 10:21:21 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] redundent import because of moved
 class instance for Binary OverlapMode
Message-ID: <671f9de1c5294_23387924731862631@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
606eabf1 by Hassan Al-Awwadi at 2024-10-28T15:21:06+01:00
redundent import because of moved class instance for Binary OverlapMode

- - - - -


1 changed file:

- compiler/GHC/Hs/OverlapPragma.hs


Changes:

=====================================
compiler/GHC/Hs/OverlapPragma.hs
=====================================
@@ -22,10 +22,8 @@ import GHC.Hs.Extension (GhcPass, GhcTc)
 
 import GHC.Types.SourceText
 
-import GHC.Utils.Binary
 import GHC.Utils.Outputable
 
-import GHC.Utils.Panic (panic)
 
 ------------------------
 -- type family instances
@@ -84,8 +82,6 @@ instance Outputable (OverlapMode (GhcPass p)) where
 instance Outputable OverlapFlag where
    ppr flag = ppr (overlapMode flag) <+> pprSafeOverlap (isSafeOverlap flag)
 
-
-
 ------------------------
 -- helper functions
 hasIncoherentFlag :: OverlapMode (GhcPass p) -> Bool



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/606eabf190f98fc0ece53349829ca8c00eee4013

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 15:22:34 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Mon, 28 Oct 2024 11:22:34 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/selectors
Message-ID: <671fac3a71509_2338795eeafc6505e@gitlab.mail>



Andreas Klebinger pushed new branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/selectors
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 15:23:02 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Mon, 28 Oct 2024 11:23:02 -0400
Subject: [Git][ghc/ghc][wip/andreask/selectors] ghc-heap: Fix incomplete
 selector warnings.
Message-ID: <671fac5660ed4_2338795af92465284@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC


Commits:
0d8e312f by Andreas Klebinger at 2024-10-28T16:03:40+01:00
ghc-heap: Fix incomplete selector warnings.

Instead of using  use  to read the info table.

Part of fixing #25380.

- - - - -


4 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -86,6 +86,7 @@ import qualified Data.Sequence as Seq
 import Data.Sequence (viewl, ViewL(..))
 import Foreign hiding (shiftL, shiftR)
 import System.IO.Unsafe
+import GHC.Exts.Heap.Closures (getClosureInfoTbl_maybe)
 
 ---------------------------------------------
 -- * A representation of semi evaluated Terms
@@ -128,6 +129,11 @@ isFullyEvaluatedTerm NewtypeWrap{wrapped_term=t} = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm RefWrap{wrapped_term=t}     = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm _                  = False
 
+-- | Gives an error if the term doesn't have subterms
+expectSubTerms :: Term -> [Term]
+expectSubTerms (Term { subTerms = subTerms} ) = subTerms
+expectSubTerms _                              = panic "expectSubTerms"
+
 instance Outputable (Term) where
  ppr t | Just doc <- cPprTerm cPprTermBase t = doc
        | otherwise = panic "Outputable Term instance"
@@ -332,8 +338,8 @@ cPprTermBase :: forall m. Monad m => CustomTermPrinter m
 cPprTermBase y =
   [ ifTerm (isTupleTy.ty) (\_p -> liftM (parens . hcat . punctuate comma)
                                       . mapM (y (-1))
-                                      . subTerms)
-  , ifTerm (\t -> isTyCon listTyCon (ty t) && subTerms t `lengthIs` 2)
+                                      . expectSubTerms)
+  , ifTerm (\t -> isTyCon listTyCon (ty t) && expectSubTerms t `lengthIs` 2)
            ppr_list
   , ifTerm' (isTyCon intTyCon     . ty) ppr_int
   , ifTerm' (isTyCon charTyCon    . ty) ppr_char
@@ -768,7 +774,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
     traceTR (text "Gave up reconstructing a term after" <>
                   int max_depth <> text " steps")
     clos <- trIO $ GHCi.getClosure interp a
-    return (Suspension (tipe (info clos)) my_ty a Nothing)
+    return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
   go !max_depth my_ty old_ty a = do
     let monomorphic = not(isTyVarTy my_ty)
     -- This ^^^ is a convention. The ancestor tests for
@@ -862,9 +868,13 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
 
 -- The otherwise case: can be a Thunk,AP,PAP,etc.
       _ -> do
+         let info_tbl =
+                case heapClosureInfo_maybe clos of
+                  Nothing -> error "cvObtainTerm"
+
          traceTR (text "Unknown closure:" <+>
                   text (show (fmap (const ()) clos)))
-         return (Suspension (tipe (info clos)) my_ty a Nothing)
+         return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
 
   -- insert NewtypeWraps around newtypes
   expandNewtypes = foldTerm idTermFold { fTerm = worker } where


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -44,6 +44,10 @@ Cmm
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+* The functions `getClosureInfoTbl_maybe`` and `getClosureInfoTbl` have been added
+  to allow reading the info table of a closure without relying on partial selector
+  functions.
+
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -29,6 +29,8 @@ module GHC.Exts.Heap (
     , WhyBlocked(..)
     , TsoFlags(..)
     , HasHeapRep(getClosureData)
+    , getClosureInfoTbl_maybe
+    , getClosureInfoTbl
     , getClosureDataFromHeapRep
     , getClosureDataFromHeapRepPrim
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -8,12 +8,16 @@
 {-# LANGUAGE DeriveTraversable #-}
 -- Late cost centres introduce a thunk in the asBox function, which leads to
 -- an additional wrapper being added to any value placed inside a box.
+-- This can be removed once our boot compiler is no longer affected by #25212
 {-# OPTIONS_GHC -fno-prof-late  #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Exts.Heap.Closures (
     -- * Closures
       Closure
     , GenClosure(..)
+    , getClosureInfoTbl_maybe
+    , getClosureInfoTbl
     , PrimType(..)
     , WhatNext(..)
     , WhyBlocked(..)
@@ -67,6 +71,7 @@ import Data.Word
 import GHC.Exts
 import GHC.Generics
 import Numeric
+import GHC.Stack (HasCallStack)
 
 ------------------------------------------------------------------------
 -- Boxes
@@ -382,6 +387,57 @@ data GenClosure b
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
 
+-- Ideally we would refactor GenClosure into two types or a GADT differentiating:
+-- * Heap objects
+-- * Primitive values with no info table.
+
+-- But for now we just do this:
+
+-- | Get the info table for a heap closure, or Nothing for a prim value
+getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosureInfoTbl_maybe #-} -- Ensure we can get rid of the just box
+getClosureInfoTbl_maybe closure = case closure of
+  ConstrClosure{info} ->Just info
+  FunClosure{info} ->Just info
+  ThunkClosure{info} ->Just info
+  SelectorClosure{info} ->Just info
+  PAPClosure{info} ->Just info
+  APClosure{info} ->Just info
+  APStackClosure{info} ->Just info
+  IndClosure{info} ->Just info
+  BCOClosure{info} ->Just info
+  BlackholeClosure{info} ->Just info
+  ArrWordsClosure{info} ->Just info
+  MutArrClosure{info} ->Just info
+  SmallMutArrClosure{info} ->Just info
+  MVarClosure{info} ->Just info
+  IOPortClosure{info} ->Just info
+  MutVarClosure{info} ->Just info
+  BlockingQueueClosure{info} ->Just info
+  WeakClosure{info} ->Just info
+  TSOClosure{info} ->Just info
+  StackClosure{info} ->Just info
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{info} -> Just info
+  UnsupportedClosure {info} -> Just info
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
+getClosureInfoTbl closure = case getClosureInfoTbl_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosureInfoTbl - Closure without info table"
+
 type StgStackClosure = GenStgStackClosure Box
 
 -- | A decoded @StgStack@ with `StackFrame`s



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0d8e312ffe4fd6cef9302a5cfa7ffd826fd1e265

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 15:26:12 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Mon, 28 Oct 2024 11:26:12 -0400
Subject: [Git][ghc/ghc][wip/andreask/selectors] ghc-heap: Fix incomplete
 selector warnings.
Message-ID: <671fad14fe2f_23387957e9286709c@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC


Commits:
fb277d82 by Andreas Klebinger at 2024-10-28T16:06:57+01:00
ghc-heap: Fix incomplete selector warnings.

Instead of using  use  to read the info table.

Part of fixing #25380.

- - - - -


4 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -86,6 +86,7 @@ import qualified Data.Sequence as Seq
 import Data.Sequence (viewl, ViewL(..))
 import Foreign hiding (shiftL, shiftR)
 import System.IO.Unsafe
+import GHC.Exts.Heap.Closures (getClosureInfoTbl_maybe)
 
 ---------------------------------------------
 -- * A representation of semi evaluated Terms
@@ -128,6 +129,11 @@ isFullyEvaluatedTerm NewtypeWrap{wrapped_term=t} = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm RefWrap{wrapped_term=t}     = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm _                  = False
 
+-- | Gives an error if the term doesn't have subterms
+expectSubTerms :: Term -> [Term]
+expectSubTerms (Term { subTerms = subTerms} ) = subTerms
+expectSubTerms _                              = panic "expectSubTerms"
+
 instance Outputable (Term) where
  ppr t | Just doc <- cPprTerm cPprTermBase t = doc
        | otherwise = panic "Outputable Term instance"
@@ -332,8 +338,8 @@ cPprTermBase :: forall m. Monad m => CustomTermPrinter m
 cPprTermBase y =
   [ ifTerm (isTupleTy.ty) (\_p -> liftM (parens . hcat . punctuate comma)
                                       . mapM (y (-1))
-                                      . subTerms)
-  , ifTerm (\t -> isTyCon listTyCon (ty t) && subTerms t `lengthIs` 2)
+                                      . expectSubTerms)
+  , ifTerm (\t -> isTyCon listTyCon (ty t) && expectSubTerms t `lengthIs` 2)
            ppr_list
   , ifTerm' (isTyCon intTyCon     . ty) ppr_int
   , ifTerm' (isTyCon charTyCon    . ty) ppr_char
@@ -768,7 +774,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
     traceTR (text "Gave up reconstructing a term after" <>
                   int max_depth <> text " steps")
     clos <- trIO $ GHCi.getClosure interp a
-    return (Suspension (tipe (info clos)) my_ty a Nothing)
+    return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
   go !max_depth my_ty old_ty a = do
     let monomorphic = not(isTyVarTy my_ty)
     -- This ^^^ is a convention. The ancestor tests for
@@ -862,9 +868,13 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
 
 -- The otherwise case: can be a Thunk,AP,PAP,etc.
       _ -> do
+         let info_tbl =
+                case heapClosureInfo_maybe clos of
+                  Nothing -> error "cvObtainTerm"
+
          traceTR (text "Unknown closure:" <+>
                   text (show (fmap (const ()) clos)))
-         return (Suspension (tipe (info clos)) my_ty a Nothing)
+         return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
 
   -- insert NewtypeWraps around newtypes
   expandNewtypes = foldTerm idTermFold { fTerm = worker } where


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -44,6 +44,10 @@ Cmm
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+* The functions `getClosureInfoTbl_maybe`` and `getClosureInfoTbl` have been added
+  to allow reading the info table of a closure without relying on partial selector
+  functions.
+
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -29,6 +29,8 @@ module GHC.Exts.Heap (
     , WhyBlocked(..)
     , TsoFlags(..)
     , HasHeapRep(getClosureData)
+    , getClosureInfoTbl_maybe
+    , getClosureInfoTbl
     , getClosureDataFromHeapRep
     , getClosureDataFromHeapRepPrim
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -8,12 +8,16 @@
 {-# LANGUAGE DeriveTraversable #-}
 -- Late cost centres introduce a thunk in the asBox function, which leads to
 -- an additional wrapper being added to any value placed inside a box.
+-- This can be removed once our boot compiler is no longer affected by #25212
 {-# OPTIONS_GHC -fno-prof-late  #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Exts.Heap.Closures (
     -- * Closures
       Closure
     , GenClosure(..)
+    , getClosureInfoTbl_maybe
+    , getClosureInfoTbl
     , PrimType(..)
     , WhatNext(..)
     , WhyBlocked(..)
@@ -67,6 +71,7 @@ import Data.Word
 import GHC.Exts
 import GHC.Generics
 import Numeric
+import GHC.Stack (HasCallStack)
 
 ------------------------------------------------------------------------
 -- Boxes
@@ -382,6 +387,61 @@ data GenClosure b
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
 
+-- Ideally we would refactor GenClosure into two types or a GADT differentiating:
+-- * Heap objects
+-- * Primitive values with no info table.
+
+-- But for now we just do this:
+
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosureInfoTbl_maybe #-} -- Ensure we can get rid of the just box
+getClosureInfoTbl_maybe closure = case closure of
+  ConstrClosure{info} ->Just info
+  FunClosure{info} ->Just info
+  ThunkClosure{info} ->Just info
+  SelectorClosure{info} ->Just info
+  PAPClosure{info} ->Just info
+  APClosure{info} ->Just info
+  APStackClosure{info} ->Just info
+  IndClosure{info} ->Just info
+  BCOClosure{info} ->Just info
+  BlackholeClosure{info} ->Just info
+  ArrWordsClosure{info} ->Just info
+  MutArrClosure{info} ->Just info
+  SmallMutArrClosure{info} ->Just info
+  MVarClosure{info} ->Just info
+  IOPortClosure{info} ->Just info
+  MutVarClosure{info} ->Just info
+  BlockingQueueClosure{info} ->Just info
+  WeakClosure{info} ->Just info
+  TSOClosure{info} ->Just info
+  StackClosure{info} ->Just info
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{info} -> Just info
+  UnsupportedClosure {info} -> Just info
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
+getClosureInfoTbl closure = case getClosureInfoTbl_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosureInfoTbl - Closure without info table"
+
 type StgStackClosure = GenStgStackClosure Box
 
 -- | A decoded @StgStack@ with `StackFrame`s



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 17:25:31 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Mon, 28 Oct 2024 13:25:31 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 8 commits: Improve performance of
 deriving Show
Message-ID: <671fc90b5745f_233879b28504761cc@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
d14fb4db by Rodrigo Mesquita at 2024-10-28T17:24:30+00:00
Improve performance of deriving Show

Significantly improves performance of deriving Show instances by
avoiding using the very polymorphic `.` operator in favour of inlining
its definition. We were generating tons of applications of it, each
which had 3 type arguments!

Improves on #9557

- - - - -
8c21d4a6 by Rodrigo Mesquita at 2024-10-28T17:24:38+00:00
Deriving Ord: compare and <= only

Since the implementation of CLC proposal #24, the default
implementations of Ord's `<`, `>`, and `>=` are given in terms of `<=`.

This means we no longer need to generate implementations for these
methods when stock deriving `Ord`. Rather, just derive the
implementation of `compare` and `<=`, and rely on the default
implementations for the others.

Progress towards #9557

- - - - -
637fdb5b by Rodrigo Mesquita at 2024-10-28T17:24:42+00:00
Dont' eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

- - - - -
ac5656fb by Rodrigo Mesquita at 2024-10-28T17:24:46+00:00
X WRNOG BRANCH

- - - - -
c333577d by Rodrigo Mesquita at 2024-10-28T17:24:49+00:00
Revert "X WRNOG BRANCH"

This reverts commit 407f922cbfebaeeca8c924c651b4fdbb5b6c12e9.

- - - - -
12e8e83e by Rodrigo Mesquita at 2024-10-28T17:24:54+00:00
deriving Traversable: Eta reduce more constructor

- - - - -
af62a1eb by Rodrigo Mesquita at 2024-10-28T17:24:55+00:00
Revert "Deriving Ord: compare and <= only"

This reverts commit 6ba798876891693425edc4b3352f201bde14ddd5.

- - - - -
36c10986 by Rodrigo Mesquita at 2024-10-28T17:24:57+00:00
restore b_expr

- - - - -


3 changed files:

- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -56,7 +56,7 @@ module GHC.Hs.Utils(
   nlHsTyApp, nlHsTyApps, nlHsVar, nlHsDataCon,
   nlHsLit, nlHsApp, nlHsApps, nlHsSyntaxApps,
   nlHsIntLit, nlHsVarApps,
-  nlHsDo, nlHsOpApp, nlHsPar, nlHsIf, nlHsCase, nlList,
+  nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList,
   mkLHsTupleExpr, mkLHsVarTuple, missingTupArg,
   mkLocatedList, nlAscribe,
 
@@ -598,11 +598,15 @@ nlHsDo ctxt stmts = noLocA (mkHsDo ctxt (noLocA stmts))
 nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
 nlHsOpApp e1 op e2 = noLocA (mkHsOpApp e1 op e2)
 
+nlHsLam  :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
 nlHsPar  :: IsPass p => LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
 nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)]
          -> LHsExpr GhcPs
 nlList   :: [LHsExpr GhcPs] -> LHsExpr GhcPs
 
+nlHsLam match = noLocA $ HsLam noAnn LamSingle
+                  $ mkMatchGroup (Generated OtherExpansion SkipPmc) (noLocA [match])
+
 nlHsPar e     = noLocA (gHsPar e)
 
 -- nlHsIf should generate if-expressions which are NOT subject to


=====================================
compiler/GHC/Tc/Deriv/Functor.hs
=====================================
@@ -689,9 +689,16 @@ mkSimpleConMatch2 ctxt fold extra_pats con insides = do
         con_expr
           | null asWithTyVar = nlHsApps con_name asWithoutTyVar
           | otherwise =
-              let bs   = filterByList  argTysTyVarInfo bs_RDRs
-                  vars = filterByLists argTysTyVarInfo bs_Vars as_Vars
-              in mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
+              let -- All trailing b-args can be eta-reduced:
+                  -- (\b1 b2 b3 -> A b1 a2 b2 b3) ==> (\b1 -> A b1 a2)
+                  -- We do this by counting the n of args to keep
+                  keep_n = length $ dropWhile (== True) $ reverse argTysTyVarInfo
+                  bs   = filterByList (take keep_n argTysTyVarInfo) bs_RDRs
+                  vars = take keep_n $
+                         filterByLists argTysTyVarInfo bs_Vars as_Vars
+               in if keep_n == 0
+                    then nlHsVar con_name
+                    else mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
 
     rhs <- fold con_expr exps
     return $ mkMatch ctxt (noLocA (extra_pats ++ [pat])) rhs emptyLocalBinds


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1407,7 +1407,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1427,16 +1427,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid
@@ -2528,11 +2529,14 @@ showParen_Expr
 showParen_Expr e1 e2 = nlHsApp (nlHsApp (nlHsVar showParen_RDR) e1) e2
 
 nested_compose_Expr :: [LHsExpr GhcPs] -> LHsExpr GhcPs
-
-nested_compose_Expr []  = panic "nested_compose_expr"   -- Arg is always non-empty
-nested_compose_Expr [e] = parenify e
-nested_compose_Expr (e:es)
-  = nlHsApp (nlHsApp (nlHsVar compose_RDR) (parenify e)) (nested_compose_Expr es)
+nested_compose_Expr =
+  nlHsLam . mkSimpleMatch (LamAlt LamSingle) (noLocA [z_Pat]) . go
+  where
+    -- Inlined nested applications of (`.`) to speed up deriving!
+    go []  = panic "nested_compose_expr"   -- Arg is always non-empty
+    go [e] = nlHsApp (parenify e) z_Expr
+    go (e:es)
+      = nlHsApp (parenify e) (go es)
 
 -- impossible_Expr is used in case RHSs that should never happen.
 -- We generate these to keep the desugarer from complaining that they *might* happen!



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa1bf18ef4111055c4b4d22c473b9715d3b7f909...36c10986dd71c60e106891dfe333f93255cd0332

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa1bf18ef4111055c4b4d22c473b9715d3b7f909...36c10986dd71c60e106891dfe333f93255cd0332
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 17:48:37 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 13:48:37 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 2 commits: made
 fromIfaceBooleanFormula local
Message-ID: <671fce7546523_233879c643c8783a4@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
1ed93755 by Hassan Al-Awwadi at 2024-10-28T17:15:37+01:00
made fromIfaceBooleanFormula local

- - - - -
01d86e8f by Hassan Al-Awwadi at 2024-10-28T18:48:22+01:00
no Haddock style comment here

- - - - -


2 changed files:

- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs


Changes:

=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -37,7 +37,6 @@ module GHC.Iface.Syntax (
         ifaceDeclFingerprints,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
-        fromIfaceBooleanFormula,
         -- Free Names
         freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
         freeNamesIfConDecls,
@@ -224,17 +223,6 @@ data IfaceBooleanFormula
   | IfParens IfaceBooleanFormula
   deriving Eq
 
--- | note that this makes unbound names, so if you actually want
--- proper Names, you'll need to properly Rename it (lookupIfaceTop).
--- You want proper Names for most things, except pretty printing
--- and the like.
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
-fromIfaceBooleanFormula = go
-  where
-   go (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
-   go (IfAnd bfs  ) = And    $ map (noLocA . go) bfs
-   go (IfOr bfs   ) = Or     $ map (noLocA . go) bfs
-   go (IfParens bf) = Parens $     (noLocA . go) bf
 
 data IfaceTyConParent
   = IfNoParent
@@ -1056,6 +1044,13 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
           (\_ def -> let fs = getOccFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+      fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
+      fromIfaceBooleanFormula = go
+        where
+         go (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
+         go (IfAnd bfs  ) = And    $ map (noLocA . go) bfs
+         go (IfOr bfs   ) = Or     $ map (noLocA . go) bfs
+         go (IfParens bf) = Parens $     (noLocA . go) bf
 
 
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -313,7 +313,7 @@ mergeIfaceDecl d1 d2
     -- we merge, see 'mergeSignatures'
     | otherwise              = d1 `withRolesFrom` d2
       where
-        -- | the reason we need to duplicate mkOr here, instead of
+        -- The reason we need to duplicate mkOr here, instead of
         -- using BooleanFormula's mkOr and just doing the loop like:
         -- `toIfaceBooleanFormula . mkOr . fromIfaceBooleanFormula`
         -- is quite subtle. Say we have the following minimal pragma:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/31f8781e90f6c1fa484f356f77f0ac0df19c895a...01d86e8fbaab6759b499c1aa6bdd880574760984

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/31f8781e90f6c1fa484f356f77f0ac0df19c895a...01d86e8fbaab6759b499c1aa6bdd880574760984
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 17:59:27 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 13:59:27 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] 4 commits: make XCInlinePragma
 strict since its dataConCantHappen
Message-ID: <671fd0ff1e305_233879d8a8b078992@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
9a620c77 by Hassan Al-Awwadi at 2024-10-28T17:38:43+01:00
make XCInlinePragma strict since its dataConCantHappen

- - - - -
846d96d9 by Hassan Al-Awwadi at 2024-10-28T17:51:31+01:00
no GHC.prelude in InlinePragma

- - - - -
6e92f6ee by Hassan Al-Awwadi at 2024-10-28T17:56:00+01:00
cleanup stray NonCanonical

- - - - -
e6c990bc by Hassan Al-Awwadi at 2024-10-28T18:11:13+01:00
remove explicit imports

- - - - -


2 changed files:

- compiler/Language/Haskell/Syntax/InlinePragma.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/Language/Haskell/Syntax/InlinePragma.hs
=====================================
@@ -1,22 +1,10 @@
 module Language.Haskell.Syntax.InlinePragma where
 
-import GHC.Prelude
-
+import Data.Eq
+import Data.Int (Int)
+import Data.Bool (Bool(..))
+import Text.Show (Show)
 import Language.Haskell.Syntax.Extension
-    ( XActiveAfter,
-      XActiveBefore,
-      XAlwaysActive,
-      XFinalActive,
-      XInlinable,
-      XInline,
-      XInlinePragma,
-      XNeverActive,
-      XNoInline,
-      XNoUserInlinePrag,
-      XOpaque,
-      XXActivation,
-      XXCInlinePragma,
-      XXInlineSpec )
 
 data InlinePragma p -- Note [InlinePragma] in GHC.Hs.InlinePragma
   = InlinePragma
@@ -26,7 +14,7 @@ data InlinePragma p -- Note [InlinePragma] in GHC.Hs.InlinePragma
                                       -- See Note [inl_inline and inl_act] in GHC.Hs.InlinePragma
       , inl_rule   :: RuleMatchInfo   -- Should the function be treated like a constructor?
     }
-  | XCInlinePragma (XXCInlinePragma p)
+  | XCInlinePragma !(XXCInlinePragma p)
 
 
 -- | Inline Specification


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2380,7 +2380,7 @@ instance ExactPrint (LocatedP (OverlapMode (GhcPass p))) where
     c' <- markAnnCloseP'' c
     return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))
 
-  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (NonCanonical src)) = do
+  exact (L (EpAnn l (AnnPragma o c s l1 l2 t m) cs) (XOverlapMode (NonCanonical src))) = do
     o' <- markAnnOpen'' o src "{-# INCOHERENT"
     c' <- markAnnCloseP'' c
     return (L (EpAnn l (AnnPragma o' c' s l1 l2 t m) cs) (Incoherent src))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/606eabf190f98fc0ece53349829ca8c00eee4013...e6c990bcdb31be117fa85d28dc2708f82d10874f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/606eabf190f98fc0ece53349829ca8c00eee4013...e6c990bcdb31be117fa85d28dc2708f82d10874f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 18:56:34 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Mon, 28 Oct 2024 14:56:34 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] 2 commits: Removed matches on
 XCInlinePragma since ghc understands those are impossible
Message-ID: <671fde62951e5_233879105826881478@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
0b50be42 by Hassan Al-Awwadi at 2024-10-28T19:55:31+01:00
Removed matches on XCInlinePragma since ghc understands those are impossible

- - - - -
b8c8b323 by Hassan Al-Awwadi at 2024-10-28T19:56:12+01:00
whitespace

- - - - -


16 changed files:

- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/InlinePragma.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs


Changes:

=====================================
compiler/GHC/Core/Opt/CSE.hs
=====================================
@@ -513,7 +513,7 @@ noCSE id
    where
      unf = idUnfolding id
      user_activation_control = not (isAlwaysActive (idInlineActivation id))
-                            && not (noUserInlineSpec (inlinePragmaSpec (idInlinePragma id)))
+                            && not (noUserInlineSpec (inl_inline (idInlinePragma id)))
      yes_cse = False
      no_cse  = True
 


=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -70,8 +70,6 @@ import GHC.Utils.Monad  ( mapAccumLM, liftIO )
 import GHC.Utils.Logger
 import GHC.Utils.Misc
 
-import Language.Haskell.Syntax.Extension (dataConCantHappen)
-
 import Control.Monad
 
 {-
@@ -657,7 +655,6 @@ tryCastWorkerWrapper env _ _ bndr rhs  -- All other bindings
         ; return (mkFloatBind env (NonRec bndr rhs)) }
 
 mkCastWrapperInlinePrag :: InlinePragma (GhcPass p) -> InlinePragma (GhcPass p)
-mkCastWrapperInlinePrag  (XCInlinePragma impossible) = dataConCantHappen impossible
 -- See Note [Cast worker/wrapper]
 mkCastWrapperInlinePrag (InlinePragma { inl_inline = fn_inl, inl_act = fn_act, inl_rule = rule_info })
   = InlinePragma { inl_ext    = InlExt (SourceText $ fsLit "{-# INLINE") Nothing


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -1490,7 +1490,7 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env
     one_occ _                                     = False
 
     pre_inline_unconditionally = sePreInline env
-    active = isActive (sePhase env) (inlinePragmaActivation inline_prag)
+    active = isActive (sePhase env) (inl_act inline_prag)
              -- See Note [pre/postInlineUnconditionally in gentle mode]
     inline_prag = idInlinePragma bndr
 


=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -1668,7 +1668,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
     fn_arity  = idArity fn
     fn_unf    = realIdUnfolding fn  -- Ignore loop-breaker-ness here
     inl_prag  = idInlinePragma fn
-    inl_act   = inlinePragmaActivation inl_prag
+    activat   = inl_act inl_prag
     is_local  = isLocalId fn
     is_dfun   = isDFunId fn
     dflags    = se_dflags env
@@ -1681,7 +1681,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
 
     already_covered :: SpecEnv -> [CoreRule] -> [CoreExpr] -> Bool
     already_covered env new_rules args      -- Note [Specialisations already covered]
-       = isJust (specLookupRule env fn args (beginPhase inl_act)
+       = isJust (specLookupRule env fn args (beginPhase activat)
                                 (new_rules ++ existing_rules))
          -- Rules: we look both in the new_rules (generated by this invocation
          --   of specCalls), and in existing_rules (passed in to specCalls)
@@ -1799,7 +1799,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
                        | otherwise = -- Specialising local fn
                                      text "SPEC"
 
-                spec_rule = mkSpecRule dflags this_mod True inl_act
+                spec_rule = mkSpecRule dflags this_mod True activat
                                     herald fn rule_bndrs rule_lhs_args
                                     (mkVarApps (Var spec_fn) spec_bndrs)
 


=====================================
compiler/GHC/Core/Opt/WorkWrap.hs
=====================================
@@ -40,7 +40,6 @@ import GHC.Utils.Panic
 import GHC.Utils.Monad
 import GHC.Core.DataCon
 import GHC.Hs.Extension (GhcTc)
-import Language.Haskell.Syntax.Extension (dataConCantHappen)
 
 {-
 We take Core bindings whose binders have:
@@ -831,8 +830,8 @@ mkWWBindPair ww_opts fn_id fn_info fn_args fn_body work_uniq div
 
     work_rhs = work_fn (mkLams fn_args fn_body)
     work_act = case fn_inline_spec of  -- See Note [Worker activation]
-                   NoInline _  -> inl_act' fn_inl_prag
-                   _           -> inl_act' wrap_prag
+                   NoInline _  -> inl_act fn_inl_prag
+                   _           -> inl_act wrap_prag
 
     work_prag = InlinePragma { inl_ext = InlExt (SourceText $ fsLit "{-# INLINE") Nothing
                              , inl_inline = fn_inline_spec
@@ -893,19 +892,11 @@ mkWWBindPair ww_opts fn_id fn_info fn_args fn_body work_uniq div
                         -- about a loop breaker with an INLINE rule
 
     fn_inl_prag     = inlinePragInfo fn_info
-    fn_inline_spec  = inl_inline' fn_inl_prag
+    fn_inline_spec  = inl_inline fn_inl_prag
     fn_unfolding    = realUnfoldingInfo fn_info
     fn_rules        = ruleInfoRules (ruleInfo fn_info)
 
-    inl_inline' (XCInlinePragma imp) = dataConCantHappen imp
-    inl_inline' (InlinePragma{ inl_inline = inline }) = inline
-
-    inl_act' (XCInlinePragma imp) = dataConCantHappen imp
-    inl_act' (InlinePragma{ inl_act = act }) = act
-
-
 mkStrWrapperInlinePrag :: InlinePragma GhcTc -> [CoreRule] -> InlinePragma GhcTc
-mkStrWrapperInlinePrag (XCInlinePragma impossible) _ = dataConCantHappen impossible
 mkStrWrapperInlinePrag (InlinePragma { inl_inline = fn_inl
                                      , inl_act    = fn_act
                                      , inl_rule   = rule_info }) rules


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -685,7 +685,6 @@ toIfaceVar v
 toIfaceInlinePragma :: InlinePragma (GhcPass p) -> IfaceInlinePragma
 toIfaceInlinePragma (InlinePragma s a b c)
   = IfInlinePragma (inl_txt s) (toIfaceInlineSpec a) (inl_arr s) (toIfaceActivation b) c
-toIfaceInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible
 
 toIfaceInlineSpec :: InlineSpec (GhcPass p) -> IfaceInlineSpec
 toIfaceInlineSpec (Inline    src)          = IfInline    src


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -866,7 +866,6 @@ ppr_sig (SpecSig _ var ty inl@(InlinePragma { inl_inline = spec }))
       pragmaSrc = case spec of
         NoUserInlinePrag _ -> "{-# " ++ extractSpecPragName (inl_src inl)
         _                  -> "{-# " ++ extractSpecPragName (inl_src inl)  ++ "_INLINE"
-ppr_sig (InlineSig _ _   (XCInlinePragma imp)) = dataConCantHappen imp
 ppr_sig (InlineSig _ var inl@(InlinePragma{}))
   = ppr_pfx <+> pprInline inl <+> pprPrefixOcc (unLoc var) <+> text "#-}"
     where
@@ -899,7 +898,6 @@ ppr_sig (CompleteMatchSig (_, src) cs mty)
 ppr_sig (XSig x) = case ghcPass @p of
                       GhcRn | IdSig id <- x -> pprVarSig [id] (ppr (varType id))
                       GhcTc | IdSig id <- x -> pprVarSig [id] (ppr (varType id))
-ppr_sig (SpecSig _ _ _ (XCInlinePragma impossible)) = dataConCantHappen impossible
 
 hsSigDoc :: forall p. IsPass p => Sig (GhcPass p) -> SDoc
 hsSigDoc (TypeSig {})           = text "type signature"
@@ -908,9 +906,7 @@ hsSigDoc (ClassOpSig _ is_deflt _ _)
  | is_deflt                     = text "default type signature"
  | otherwise                    = text "class method signature"
 hsSigDoc (SpecSig _ _ _ (InlinePragma{inl_inline = spec}))   = inlinePragmaName spec <+> text "pragma"
-hsSigDoc (SpecSig _ _ _ (XCInlinePragma imp))                = dataConCantHappen imp
 hsSigDoc (InlineSig _ _ (InlinePragma{inl_inline = spec}))   = inlinePragmaName spec <+> text "pragma"
-hsSigDoc (InlineSig _ _ (XCInlinePragma imp))                = dataConCantHappen imp
 -- Using the 'inlinePragmaName' function ensures that the pragma name for any
 -- one of the INLINE/INLINABLE/NOINLINE pragmas are printed after being extracted
 -- from the InlineSpec field of the pragma.


=====================================
compiler/GHC/Hs/InlinePragma.hs
=====================================
@@ -21,13 +21,9 @@ module GHC.Hs.InlinePragma(
         isAnyInlinePragma, alwaysInlineConLikePragma,
         inlinePragmaSource,
         inlinePragmaName, inlineSpecSource,
-        inlinePragmaSpec, inlinePragmaSat,
-        inlinePragmaActivation, inlinePragmaRuleMatchInfo,
-        setInlinePragmaActivation, setInlinePragmaRuleMatchInfo,
+        setInlinePragmaActivation, setInlinePragmaRuleMatchInfo, setInlinePragmaArity,
         pprInline, pprInlineDebug,
         convertInlinePragma, convertInlineSpec, convertActivation,
-
-        set_pragma_activation, set_pragma_rule, set_pragma_sat
 ) where
 
 import GHC.Prelude
@@ -223,15 +219,12 @@ data InlinePragmaExt = InlExt
   deriving Eq
 
 inl_src  :: InlinePragma (GhcPass p) -> SourceText
-inl_src (XCInlinePragma impossible) = dataConCantHappen impossible
 inl_src (InlinePragma s _ _ _)      = inl_txt s
 
 inl_sat  :: InlinePragma (GhcPass p) -> Maybe Arity
-inl_sat (XCInlinePragma impossible) = dataConCantHappen impossible
 inl_sat (InlinePragma s _ _ _)      = inl_arr s
 
 convertInlinePragma :: InlinePragma (GhcPass p) -> InlinePragma (GhcPass p')
-convertInlinePragma (XCInlinePragma impossible) = XCInlinePragma impossible
 convertInlinePragma (InlinePragma s a b c)    = InlinePragma s (convertInlineSpec a) (convertActivation b) c
 
 convertInlineSpec :: InlineSpec (GhcPass p) -> InlineSpec (GhcPass p')
@@ -246,8 +239,7 @@ noUserInlineSpec :: InlineSpec (GhcPass p) -> Bool
 noUserInlineSpec (NoUserInlinePrag _) = True
 noUserInlineSpec _                = False
 
-defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma
-  :: InlinePragma (GhcPass p)
+defaultInlinePragma :: InlinePragma (GhcPass p)
 defaultInlinePragma = InlinePragma { inl_ext = InlExt (SourceText $ fsLit "{-# INLINE") Nothing
                                    , inl_act = AlwaysActive noExtField
                                    , inl_rule = FunLike
@@ -256,33 +248,17 @@ defaultInlinePragma = InlinePragma { inl_ext = InlExt (SourceText $ fsLit "{-# I
 
 set_pragma_inline :: InlinePragma (GhcPass p) -> InlineSpec (GhcPass p) -> InlinePragma (GhcPass p)
 set_pragma_inline inl@(InlinePragma{}) spec = inl{ inl_inline = spec}
-set_pragma_inline (XCInlinePragma imp) _    = dataConCantHappen imp
-
-set_pragma_activation :: InlinePragma (GhcPass p) -> Activation (GhcPass p) -> InlinePragma (GhcPass p)
-set_pragma_activation inl@(InlinePragma{}) act = inl{ inl_act = act}
-set_pragma_activation (XCInlinePragma imp) _   = dataConCantHappen imp
-
-set_pragma_rule :: InlinePragma (GhcPass p) -> RuleMatchInfo -> InlinePragma (GhcPass p)
-set_pragma_rule inl@(InlinePragma{}) act = inl{ inl_rule = act}
-set_pragma_rule (XCInlinePragma imp) _    = dataConCantHappen imp
-
-set_pragma_sat :: InlinePragma (GhcPass p) -> Maybe Arity -> InlinePragma (GhcPass p)
-set_pragma_sat inl@(InlinePragma{ inl_ext = ext}) sat = inl{ inl_ext = ext{inl_arr = sat} }
-set_pragma_sat (XCInlinePragma imp) _    = dataConCantHappen imp
 
+alwaysInlinePragma :: InlinePragma (GhcPass p)
 alwaysInlinePragma = set_pragma_inline defaultInlinePragma $ Inline (inlinePragmaSource defaultInlinePragma)
 
-neverInlinePragma  = set_pragma_activation defaultInlinePragma $ NeverActive noExtField
+neverInlinePragma :: InlinePragma (GhcPass p)
+neverInlinePragma  = setInlinePragmaActivation defaultInlinePragma $ NeverActive noExtField
 
 alwaysInlineConLikePragma :: InlinePragma (GhcPass p)
-alwaysInlineConLikePragma = set_pragma_rule alwaysInlinePragma ConLike
-
-inlinePragmaSpec :: InlinePragma (GhcPass p) -> InlineSpec (GhcPass p)
-inlinePragmaSpec inl@(InlinePragma{}) = inl_inline inl
-inlinePragmaSpec (XCInlinePragma imp) = dataConCantHappen imp
+alwaysInlineConLikePragma = setInlinePragmaRuleMatchInfo alwaysInlinePragma ConLike
 
 inlinePragmaSource :: InlinePragma (GhcPass p) -> SourceText
-inlinePragmaSource (XCInlinePragma imp) = dataConCantHappen imp
 inlinePragmaSource prag = case inl_inline prag of
                             Inline    x        -> x
                             Inlinable y        -> y
@@ -304,9 +280,10 @@ inlineSpecSource spec = case spec of
 -- exprIsConApp_maybe can "see" its unfolding
 -- (However, its actual Unfolding is a DFunUnfolding, which is
 --  never inlined other than via exprIsConApp_maybe.)
+dfunInlinePragma :: InlinePragma (GhcPass p)
 dfunInlinePragma = let
-  always_active         = set_pragma_activation defaultInlinePragma (AlwaysActive noExtField)
-  always_active_conlike = set_pragma_rule always_active ConLike
+  always_active         = setInlinePragmaActivation defaultInlinePragma (AlwaysActive noExtField)
+  always_active_conlike = setInlinePragmaRuleMatchInfo always_active ConLike
   in always_active_conlike
 
 isDefaultInlinePragma :: InlinePragma (GhcPass p) -> Bool
@@ -314,27 +291,23 @@ isDefaultInlinePragma (InlinePragma { inl_act = activation
                                     , inl_rule = match_info
                                     , inl_inline = inline })
   = noUserInlineSpec inline && isAlwaysActive activation && isFunLike match_info
-isDefaultInlinePragma (XCInlinePragma impossible) = dataConCantHappen impossible
 
 isInlinePragma :: InlinePragma (GhcPass p) -> Bool
 isInlinePragma prag@(InlinePragma{}) = case inl_inline prag of
                         Inline _  -> True
                         _         -> False
-isInlinePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isInlinablePragma :: InlinePragma (GhcPass p) -> Bool
 isInlinablePragma prag@(InlinePragma{}) =
   case inl_inline prag of
     Inlinable _  -> True
     _            -> False
-isInlinablePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isNoInlinePragma :: InlinePragma (GhcPass p) -> Bool
 isNoInlinePragma prag@(InlinePragma{}) =
   case inl_inline prag of
     NoInline _   -> True
     _            -> False
-isNoInlinePragma (XCInlinePragma imp) = dataConCantHappen imp
 
 isAnyInlinePragma :: InlinePragma (GhcPass p) -> Bool
 -- INLINE or INLINABLE
@@ -343,35 +316,22 @@ isAnyInlinePragma prag@(InlinePragma{}) =
     Inline    _   -> True
     Inlinable _   -> True
     _             -> False
-isAnyInlinePragma (XCInlinePragma imp)  = dataConCantHappen imp
 
 isOpaquePragma :: InlinePragma (GhcPass p) -> Bool
 isOpaquePragma prag@(InlinePragma{}) =
   case inl_inline prag of
     Opaque _ -> True
     _        -> False
-isOpaquePragma (XCInlinePragma imp)  = dataConCantHappen imp
-
-inlinePragmaSat :: InlinePragma (GhcPass p) -> Maybe Arity
-inlinePragmaSat prag@(InlinePragma{}) = inl_sat prag
-inlinePragmaSat (XCInlinePragma imp)  = dataConCantHappen imp
-
-inlinePragmaActivation :: InlinePragma (GhcPass p) -> Activation (GhcPass p)
-inlinePragmaActivation (InlinePragma { inl_act = activation }) = activation
-inlinePragmaActivation (XCInlinePragma impossible)             = dataConCantHappen impossible
 
-inlinePragmaRuleMatchInfo :: InlinePragma (GhcPass p) -> RuleMatchInfo
-inlinePragmaRuleMatchInfo (InlinePragma { inl_rule = info }) = info
-inlinePragmaRuleMatchInfo (XCInlinePragma impossible)        = dataConCantHappen impossible
 
 setInlinePragmaActivation :: InlinePragma (GhcPass p) -> Activation (GhcPass p) -> InlinePragma (GhcPass p)
 setInlinePragmaActivation prag@(InlinePragma{}) activation = prag { inl_act = activation }
-setInlinePragmaActivation (XCInlinePragma impossible)  _   = dataConCantHappen impossible
 
 setInlinePragmaRuleMatchInfo :: InlinePragma (GhcPass p) -> RuleMatchInfo -> InlinePragma (GhcPass p)
 setInlinePragmaRuleMatchInfo prag@(InlinePragma{}) rule = prag { inl_rule = rule }
-setInlinePragmaRuleMatchInfo (XCInlinePragma impossible)  _   = dataConCantHappen impossible
 
+setInlinePragmaArity :: InlinePragma (GhcPass p) -> Maybe Arity -> InlinePragma (GhcPass p)
+setInlinePragmaArity inl@(InlinePragma{ inl_ext = ext}) sat = inl{ inl_ext = ext{inl_arr = sat} }
 
 {-
 ************************************************************************
@@ -609,7 +569,6 @@ pprInline' emptyInline (InlinePragma
              | otherwise           = empty
       pp_info | isFunLike info = empty
               | otherwise      = ppr info
-pprInline' _ (XCInlinePragma impossible) = dataConCantHappen impossible
 
 instance Binary RuleMatchInfo where
     put_ bh FunLike = putByte bh 0


=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -443,7 +443,6 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs
 
   | otherwise
   = case inline_prag of
-      XCInlinePragma imp              -> dataConCantHappen imp
       InlinePragma{inl_inline = spec} -> case spec of
           NoUserInlinePrag{} -> (gbl_id, rhs)
           NoInline  {}       -> (gbl_id, rhs)
@@ -456,7 +455,7 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs
     inline_prag   = idInlinePragma gbl_id
     inlinable_unf = mkInlinableUnfolding simpl_opts StableUserSrc rhs
     inline_pair
-       | Just arity <- inlinePragmaSat inline_prag
+       | Just arity <- inl_sat inline_prag
         -- Add an Unfolding for an INLINE (but not for NOINLINE)
         -- And eta-expand the RHS; see Note [Eta-expanding INLINE things]
        , let real_arity = dict_arity + arity
@@ -895,16 +894,16 @@ dsSpec mb_poly_rhs (L loc (SpecPrag poly_id spec_co spec_inl))
      -- Get the INLINE pragma from SPECIALISE declaration, or,
      -- failing that, from the original Id
 
-    spec_prag_act = inlinePragmaActivation spec_inl
+    spec_prag_act = inl_act spec_inl
 
     -- See Note [Activation pragmas for SPECIALISE]
     -- no_act_spec is True if the user didn't write an explicit
     -- phase specification in the SPECIALISE pragma
-    no_act_spec = case inlinePragmaSpec spec_inl of
+    no_act_spec = case inl_inline spec_inl of
                     NoInline _   -> isNeverActive  spec_prag_act
                     Opaque _     -> isNeverActive  spec_prag_act
                     _            -> isAlwaysActive spec_prag_act
-    rule_act | no_act_spec = inlinePragmaActivation id_inl   -- Inherit
+    rule_act | no_act_spec = inl_act id_inl   -- Inherit
              | otherwise   = spec_prag_act                   -- Specified by user
 
 


=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -1075,7 +1075,6 @@ rep_inline :: LocatedN Name
            -> InlinePragma (GhcPass p)      -- Never defaultInlinePragma
            -> SrcSpan
            -> MetaM [(SrcSpan, Core (M TH.Dec))]
-rep_inline _  (XCInlinePragma imp) _ = dataConCantHappen imp
 rep_inline nm ispec loc
   | Opaque {} <- inl_inline ispec
   = do { nm1    <- lookupLOcc nm
@@ -1094,7 +1093,6 @@ rep_inline nm ispec loc
 rep_specialise :: LocatedN Name -> LHsSigType GhcRn -> InlinePragma (GhcPass p)
                -> SrcSpan
                -> MetaM [(SrcSpan, Core (M TH.Dec))]
-rep_specialise _  _ (XCInlinePragma imp) _ = dataConCantHappen imp
 rep_specialise nm ty ispec loc
   = do { nm1 <- lookupLOcc nm
        ; ty1 <- repHsSigType ty


=====================================
compiler/GHC/Iface/Tidy.hs
=====================================
@@ -90,7 +90,7 @@ import GHC.Types.Tickish
 import GHC.Types.TypeEnv
 import GHC.Tc.Utils.TcType (tcSplitNestedSigmaTys)
 
-import GHC.Hs.InlinePragma(isNeverActive, inlinePragmaActivation)
+import GHC.Hs.InlinePragma(isNeverActive, InlinePragma(..))
 
 import GHC.Unit.Module
 import GHC.Unit.Module.ModGuts
@@ -803,7 +803,7 @@ addExternal opts id
     idinfo         = idInfo id
     unfolding      = realUnfoldingInfo idinfo
     show_unfold    = show_unfolding unfolding
-    never_active   = isNeverActive (inlinePragmaActivation (inlinePragInfo idinfo))
+    never_active   = isNeverActive (inl_act (inlinePragInfo idinfo))
     loop_breaker   = isStrongLoopBreaker (occInfo idinfo)
     -- bottoming_fn: don't inline bottoming functions, unless the
     -- RHS is very small or trivial (UnfWhen), in which case we


=====================================
compiler/GHC/Tc/Deriv/Generics.hs
=====================================
@@ -377,7 +377,7 @@ mkBindsRep dflags gk loc dit@(DerivInstTys{dit_rep_tc = tycon}) = (binds, sigs)
                max_fields = maximum $ map dataConSourceArity datacons
 
            inline1 f = L loc'' . InlineSig noAnn (L loc' f)
-                     $ set_pragma_activation alwaysInlinePragma (ActiveAfter NoSourceText 1)
+                     $ setInlinePragmaActivation alwaysInlinePragma (ActiveAfter NoSourceText 1)
 
         -- The topmost M1 (the datatype metadata) has the exact same type
         -- across all cases of a from/to definition, and can be factored out


=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -589,10 +589,9 @@ addInlinePragArity _ sig = sig
 add_inl_arity :: Arity -> InlinePragma (GhcPass p) -> InlinePragma (GhcPass p)
 add_inl_arity ar prag@(InlinePragma { inl_inline = inl_spec })
   | Inline {} <- inl_spec  -- Add arity only for real INLINE pragmas, not INLINABLE
-  = set_pragma_sat prag (Just ar)
+  = setInlinePragmaArity prag (Just ar)
   | otherwise
   = prag
-add_inl_arity _ (XCInlinePragma imp) = dataConCantHappen imp
 
 lhsBindArity :: LHsBind GhcRn -> NameEnv Arity -> NameEnv Arity
 lhsBindArity (L _ (FunBind { fun_id = id, fun_matches = ms })) env
@@ -615,8 +614,8 @@ addInlinePrags poly_id prags_for_me
     warn_multiple_inlines _ [] = return ()
 
     warn_multiple_inlines inl1@(L loc prag1) (inl2@(L _ prag2) : inls)
-       | inlinePragmaActivation prag1 == inlinePragmaActivation prag2
-       , noUserInlineSpec (inlinePragmaSpec prag1)
+       | inl_act prag1 == inl_act prag2
+       , noUserInlineSpec (inl_inline prag1)
        =    -- Tiresome: inl1 is put there by virtue of being in a hs-boot loop
             -- and inl2 is a user NOINLINE pragma; we don't want to complain
          warn_multiple_inlines inl2 inls


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1378,7 +1378,7 @@ addDFunPrags :: DFunId -> [Id] -> DFunId
 addDFunPrags dfun_id sc_meth_ids
  | is_newtype
   = dfun_id `setIdUnfolding`  mkInlineUnfoldingWithArity defaultSimpleOpts StableSystemSrc 0 con_app
-            `setInlinePragma` (alwaysInlinePragma `set_pragma_sat` Just 0)
+            `setInlinePragma` (alwaysInlinePragma `setInlinePragmaArity` Just 0)
  | otherwise
  = dfun_id `setIdUnfolding`  mkDFunUnfolding dfun_bndrs dict_con dict_args
            `setInlinePragma` dfunInlinePragma


=====================================
compiler/GHC/Types/Id.hs
=====================================
@@ -950,13 +950,13 @@ modifyInlinePragma :: Id -> (InlinePragma GhcTc -> InlinePragma GhcTc) -> Id
 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
 
 idInlineActivation :: Id -> Activation GhcTc
-idInlineActivation id = inlinePragmaActivation (idInlinePragma id)
+idInlineActivation id = inl_act (idInlinePragma id)
 
 setInlineActivation :: Id -> Activation GhcTc -> Id
 setInlineActivation id act = modifyInlinePragma id (\prag -> setInlinePragmaActivation prag act)
 
 idRuleMatchInfo :: Id -> RuleMatchInfo
-idRuleMatchInfo id = inlinePragmaRuleMatchInfo (idInlinePragma id)
+idRuleMatchInfo id = inl_rule (idInlinePragma id)
 
 isConLikeId :: Id -> Bool
 isConLikeId id = isConLike (idRuleMatchInfo id)


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -618,7 +618,7 @@ mkDataConWorkId wkr_name data_con
                       -- See Note [Strict fields in Core]
                    `setLFInfo`             wkr_lf_info
 
-    wkr_inline_prag = set_pragma_rule defaultInlinePragma ConLike
+    wkr_inline_prag = setInlinePragmaRuleMatchInfo defaultInlinePragma ConLike
     wkr_arity = dataConRepArity data_con
 
     wkr_sig = mkClosedDmdSig wkr_dmds topDiv



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6c990bcdb31be117fa85d28dc2708f82d10874f...b8c8b323b7dc24b5a891894571d3628709a2cb91

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e6c990bcdb31be117fa85d28dc2708f82d10874f...b8c8b323b7dc24b5a891894571d3628709a2cb91
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Mon Oct 28 21:44:00 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Mon, 28 Oct 2024 17:44:00 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-remove-annkeywordid
Message-ID: <672005a075b79_23387915e418c95210@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-remove-annkeywordid at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-remove-annkeywordid
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 07:11:10 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 03:11:10 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Add a
 missing tidy in UnivCo
Message-ID: <67208a8e32cd9_23387927496201165d5@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -


21 changed files:

- compiler/GHC.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/Language/Haskell/Syntax.hs
- compiler/Language/Haskell/Syntax/Binds.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/311f6a08f517f1ec909c744d293aba8b5ebaeb23...d5e7990ca9637ebee2293b22815fa0c393231baf

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/311f6a08f517f1ec909c744d293aba8b5ebaeb23...d5e7990ca9637ebee2293b22815fa0c393231baf
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 09:22:46 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Tue, 29 Oct 2024 05:22:46 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] remove trace
Message-ID: <6720a96686e25_204ac712f20063177@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
448086cf by Matthew Pickering at 2024-10-29T09:22:21+00:00
remove trace

- - - - -


1 changed file:

- compiler/GHC/Tc/Utils/Monad.hs


Changes:

=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -2089,7 +2089,7 @@ getStageAndBindLevel name
                 -- TODO: What happens if someone generates [|| GHC.Magic.dataToTag# ||]
                 then do
                   env <- getGlobalRdrEnv
-                  pprTrace "NO_LVLS" (ppr env $$ ppr name) (return Nothing)
+                  pprTrace "NO_LVLS" (ppr name) (return Nothing)
                 else return (Just (TopLevel, lvls, getLclEnvThStage env))
            Just (top_lvl, bind_lvl) -> return (Just (top_lvl, Set.singleton bind_lvl, getLclEnvThStage env)) }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/448086cf11757197607b892c24b4c40622dd332f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 10:49:53 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 29 Oct 2024 06:49:53 -0400
Subject: [Git][ghc/ghc][wip/fix-bytecode-stubs] 16 commits: EPA: reduce
 [AddEpann] in AnnList
Message-ID: <6720bdd1a9ba6_204ac747cc8c66174@gitlab.mail>



Cheng Shao pushed to branch wip/fix-bytecode-stubs at Glasgow Haskell Compiler / GHC


Commits:
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
91b6f6cf by Cheng Shao at 2024-10-29T10:13:47+00:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
c7900ac6 by Cheng Shao at 2024-10-29T10:49:34+00:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -


30 changed files:

- .ghcid
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/677e3aa56e905524071fc9717a88ad2cd1bc2951...c7900ac6e1bf5288f03ba388f124ceafd9d79b6f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/677e3aa56e905524071fc9717a88ad2cd1bc2951...c7900ac6e1bf5288f03ba388f124ceafd9d79b6f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 10:56:46 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 06:56:46 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] specialized exactprint of
 Activation/OverlapMode to be of GhcPs
Message-ID: <6720bf6e5bdb1_204ac75e73c4691b5@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
d265eeea by Hassan Al-Awwadi at 2024-10-29T11:56:29+01:00
specialized exactprint of Activation/OverlapMode to be of GhcPs

- - - - -


1 changed file:

- utils/check-exact/ExactPrint.hs


Changes:

=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2118,13 +2118,13 @@ instance ExactPrint (RuleDecl GhcPs) where
 
 
 markActivationL :: (Monad m, Monoid w)
-  => a -> Lens a ActivationAnn -> Activation (GhcPass p) -> EP w m a
+  => a -> Lens a ActivationAnn -> Activation GhcPs -> EP w m a
 markActivationL a l act = do
   new <- markActivation (view l a) act
   return (set l new a)
 
 markActivation :: (Monad m, Monoid w)
-  => ActivationAnn -> Activation (GhcPass p) -> EP w m ActivationAnn
+  => ActivationAnn -> Activation GhcPs -> EP w m ActivationAnn
 markActivation (ActivationAnn o c t v) act = do
   case act of
     ActiveBefore src phase -> do
@@ -2138,7 +2138,7 @@ markActivation (ActivationAnn o c t v) act = do
       v' <- mapM (\val -> printStringAtAA val (toSourceTextWithSuffix src (show phase) "")) v
       c' <- markEpToken c -- ']'
       return (ActivationAnn o' c' t v')
-    NeverActive -> do
+    NeverActive _ -> do
       o' <- markEpToken o --  '['
       t' <- mapM markEpToken t -- ~
       c' <- markEpToken c -- ']'
@@ -2350,7 +2350,7 @@ instance ExactPrint (TyFamInstDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (LocatedP (OverlapMode (GhcPass p))) where
+instance ExactPrint (LocatedP (OverlapMode GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
 



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 11:11:36 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 07:11:36 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove AddEpAnn Commit 8/final
Message-ID: <6720c2e84abb2_204ac75fd3907462d@gitlab.mail>



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


Commits:
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -


30 changed files:

- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- testsuite/tests/ghc-api/exactprint/T22919.stderr
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/ghc-api/exactprint/ZeroWidthSemi.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpParsedAstComments.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15279.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_compile/T20718.stderr
- testsuite/tests/parser/should_compile/T20846.stderr
- testsuite/tests/parser/should_compile/T23315/T23315.stderr
- testsuite/tests/printer/Test20297.stdout
- testsuite/tests/printer/Test24533.stdout
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Transform.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a6691c3a947a21c7dcc9772d6cc396894c4756f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 11:12:25 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 07:12:25 -0400
Subject: [Git][ghc/ghc][master] EPA: Remove AnnKeywordId.
Message-ID: <6720c31930ab2_204ac7730ba4814a@gitlab.mail>



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


Commits:
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -


30 changed files:

- compiler/GHC.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/Language/Haskell/Syntax.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Type.hs
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 11:28:27 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 07:28:27 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] 6 commits: Add a missing tidy
 in UnivCo
Message-ID: <6720c6db42542_204ac7c48b50834db@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
24e9c876 by Hassan Al-Awwadi at 2024-10-29T12:27:16+01:00
 Refactored BooleanFormula to be in line with TTG

There are two parts to this commit.
* We moved the definition of BooleanFormula over to L.H.S.BooleanFormula
* We parameterized the BooleanFormula over the pass

The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula.
Because its parameterized over the pass its no longer a functor or
traversable, but we defined bfMap and bfTraverse for the cases where we
needed fmap and traverse originally. Most other changes are just churn.

-------------------------
Metric Decrease:
    MultiLayerModulesTH_OneShot
-------------------------

- - - - -


22 changed files:

- compiler/GHC.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/01d86e8fbaab6759b499c1aa6bdd880574760984...24e9c876acd0bbef62a0e4006d433e325fd78847

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/01d86e8fbaab6759b499c1aa6bdd880574760984...24e9c876acd0bbef62a0e4006d433e325fd78847
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 11:33:37 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 29 Oct 2024 07:33:37 -0400
Subject: [Git][ghc/ghc][wip/fix-bytecode-stubs] 4 commits: EPA: Remove
 AddEpAnn Commit 8/final
Message-ID: <6720c811cb2bc_204ac7c506c084092@gitlab.mail>



Cheng Shao pushed to branch wip/fix-bytecode-stubs at Glasgow Haskell Compiler / GHC


Commits:
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
4cc709c1 by Cheng Shao at 2024-10-29T11:13:07+00:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
fed9f6e1 by Cheng Shao at 2024-10-29T11:33:21+00:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -


22 changed files:

- compiler/GHC.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Dump.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/Language/Haskell/Syntax.hs
- compiler/Language/Haskell/Syntax/Binds.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c7900ac6e1bf5288f03ba388f124ceafd9d79b6f...fed9f6e1703711b779f4983f57b1556b8990c6fe

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c7900ac6e1bf5288f03ba388f124ceafd9d79b6f...fed9f6e1703711b779f4983f57b1556b8990c6fe
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 11:59:10 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Tue, 29 Oct 2024 07:59:10 -0400
Subject: [Git][ghc/ghc][wip/andreask/selectors] ghc-heap: Fix incomplete
 selector warnings.
Message-ID: <6720ce0e64fb6_204ac7f94d18943a7@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC


Commits:
e82dc79f by Andreas Klebinger at 2024-10-29T12:39:14+01:00
ghc-heap: Fix incomplete selector warnings.

Use utility functions instead of selectors to read partial attributes.

Part of fixing #25380.

- - - - -


4 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -86,6 +86,7 @@ import qualified Data.Sequence as Seq
 import Data.Sequence (viewl, ViewL(..))
 import Foreign hiding (shiftL, shiftR)
 import System.IO.Unsafe
+import GHC.Exts.Heap.Closures (getClosureInfoTbl_maybe)
 
 ---------------------------------------------
 -- * A representation of semi evaluated Terms
@@ -128,6 +129,11 @@ isFullyEvaluatedTerm NewtypeWrap{wrapped_term=t} = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm RefWrap{wrapped_term=t}     = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm _                  = False
 
+-- | Gives an error if the term doesn't have subterms
+expectSubTerms :: Term -> [Term]
+expectSubTerms (Term { subTerms = subTerms} ) = subTerms
+expectSubTerms _                              = panic "expectSubTerms"
+
 instance Outputable (Term) where
  ppr t | Just doc <- cPprTerm cPprTermBase t = doc
        | otherwise = panic "Outputable Term instance"
@@ -332,8 +338,8 @@ cPprTermBase :: forall m. Monad m => CustomTermPrinter m
 cPprTermBase y =
   [ ifTerm (isTupleTy.ty) (\_p -> liftM (parens . hcat . punctuate comma)
                                       . mapM (y (-1))
-                                      . subTerms)
-  , ifTerm (\t -> isTyCon listTyCon (ty t) && subTerms t `lengthIs` 2)
+                                      . expectSubTerms)
+  , ifTerm (\t -> isTyCon listTyCon (ty t) && expectSubTerms t `lengthIs` 2)
            ppr_list
   , ifTerm' (isTyCon intTyCon     . ty) ppr_int
   , ifTerm' (isTyCon charTyCon    . ty) ppr_char
@@ -768,7 +774,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
     traceTR (text "Gave up reconstructing a term after" <>
                   int max_depth <> text " steps")
     clos <- trIO $ GHCi.getClosure interp a
-    return (Suspension (tipe (info clos)) my_ty a Nothing)
+    return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
   go !max_depth my_ty old_ty a = do
     let monomorphic = not(isTyVarTy my_ty)
     -- This ^^^ is a convention. The ancestor tests for
@@ -862,9 +868,13 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
 
 -- The otherwise case: can be a Thunk,AP,PAP,etc.
       _ -> do
+         let info_tbl =
+                case heapClosureInfo_maybe clos of
+                  Nothing -> error "cvObtainTerm"
+
          traceTR (text "Unknown closure:" <+>
                   text (show (fmap (const ()) clos)))
-         return (Suspension (tipe (info clos)) my_ty a Nothing)
+         return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
 
   -- insert NewtypeWraps around newtypes
   expandNewtypes = foldTerm idTermFold { fTerm = worker } where
@@ -918,7 +928,7 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
 
     go_rep ptr_i arr_i ty rep
       | isGcPtrRep rep = do
-          t <- recurse ty $ (ptrArgs clos)!!ptr_i
+          t <- recurse ty $ (getClosurePtrArgs clos)!!ptr_i
           return (ptr_i + 1, arr_i, t)
       | otherwise = do
           -- This is a bit involved since we allow packing multiple fields


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -44,6 +44,11 @@ Cmm
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+* The functions `getClosureInfoTbl_maybe`, and `getClosureInfoTbl`,
+ `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow
+  reading of the relevant Closure attributes without reliance on incomplete
+  selectors.
+
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -29,6 +29,8 @@ module GHC.Exts.Heap (
     , WhyBlocked(..)
     , TsoFlags(..)
     , HasHeapRep(getClosureData)
+    , getClosureInfoTbl_maybe
+    , getClosureInfoTbl
     , getClosureDataFromHeapRep
     , getClosureDataFromHeapRepPrim
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -8,12 +8,18 @@
 {-# LANGUAGE DeriveTraversable #-}
 -- Late cost centres introduce a thunk in the asBox function, which leads to
 -- an additional wrapper being added to any value placed inside a box.
+-- This can be removed once our boot compiler is no longer affected by #25212
 {-# OPTIONS_GHC -fno-prof-late  #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Exts.Heap.Closures (
     -- * Closures
       Closure
     , GenClosure(..)
+    , getClosureInfoTbl
+    , getClosureInfoTbl_maybe
+    , getClosurePtrArgs
+    , getClosurePtrArgs_maybe
     , PrimType(..)
     , WhatNext(..)
     , WhyBlocked(..)
@@ -67,6 +73,7 @@ import Data.Word
 import GHC.Exts
 import GHC.Generics
 import Numeric
+import GHC.Stack (HasCallStack)
 
 ------------------------------------------------------------------------
 -- Boxes
@@ -382,6 +389,104 @@ data GenClosure b
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
 
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosureInfoTbl_maybe #-} -- Ensure we can get rid of the just box
+getClosureInfoTbl_maybe closure = case closure of
+  ConstrClosure{info} ->Just info
+  FunClosure{info} ->Just info
+  ThunkClosure{info} ->Just info
+  SelectorClosure{info} ->Just info
+  PAPClosure{info} ->Just info
+  APClosure{info} ->Just info
+  APStackClosure{info} ->Just info
+  IndClosure{info} ->Just info
+  BCOClosure{info} ->Just info
+  BlackholeClosure{info} ->Just info
+  ArrWordsClosure{info} ->Just info
+  MutArrClosure{info} ->Just info
+  SmallMutArrClosure{info} ->Just info
+  MVarClosure{info} ->Just info
+  IOPortClosure{info} ->Just info
+  MutVarClosure{info} ->Just info
+  BlockingQueueClosure{info} ->Just info
+  WeakClosure{info} ->Just info
+  TSOClosure{info} ->Just info
+  StackClosure{info} ->Just info
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{info} -> Just info
+  UnsupportedClosure {info} -> Just info
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
+getClosureInfoTbl closure = case getClosureInfoTbl_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosureInfoTbl - Closure without info table"
+
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosurePtrArgs_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosurePtrArgs_maybe #-} -- Ensure we can get rid of the just box
+getClosurePtrArgs_maybe closure = case closure of
+  ConstrClosure{} -> Nothing
+  FunClosure{} -> Nothing
+  ThunkClosure{} -> Nothing
+  SelectorClosure{} -> Nothing
+  PAPClosure{} -> Nothing
+  APClosure{} -> Nothing
+  APStackClosure{} -> Nothing
+  IndClosure{} -> Nothing
+  BCOClosure{} -> Nothing
+  BlackholeClosure{} -> Nothing
+  ArrWordsClosure{} -> Nothing
+  MutArrClosure{} -> Nothing
+  SmallMutArrClosure{} -> Nothing
+  MVarClosure{} -> Nothing
+  IOPortClosure{} -> Nothing
+  MutVarClosure{} -> Nothing
+  BlockingQueueClosure{} -> Nothing
+  WeakClosure{} -> Nothing
+  TSOClosure{} -> Nothing
+  StackClosure{} -> Nothing
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{} -> Nothing
+  UnsupportedClosure{} -> Nothing
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosurePtrArgs :: HasCallStack => GenClosure b -> StgInfoTable
+getClosurePtrArgs closure = case getClosurePtrArgs_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosurePtrArgs - Closure without ptrArgs table"
+
 type StgStackClosure = GenStgStackClosure Box
 
 -- | A decoded @StgStack@ with `StackFrame`s



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 12:06:34 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Tue, 29 Oct 2024 08:06:34 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/unicode-16
Message-ID: <6720cfcac1843_204ac71166d309929f@gitlab.mail>



Matthew Pickering pushed new branch wip/unicode-16 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/unicode-16
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 12:12:11 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 29 Oct 2024 08:12:11 -0400
Subject: [Git][ghc/ghc][wip/fix-bytecode-stubs] driver: fix foreign stub
 handling logic in hscParsedDecls
Message-ID: <6720d11b792a1_204ac7126b050100852@gitlab.mail>



Cheng Shao pushed to branch wip/fix-bytecode-stubs at Glasgow Haskell Compiler / GHC


Commits:
e93dc025 by Cheng Shao at 2024-10-29T12:11:52+00:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -


3 changed files:

- compiler/GHC/Driver/Main.hs
- compiler/GHC/Linker/Loader.hs
- testsuite/tests/ghci/scripts/all.T


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2525,46 +2525,21 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
     (tidy_cg, mod_details) <- liftIO $ hscTidy hsc_env simpl_mg
 
     let !CgGuts{ cg_module    = this_mod,
-                 cg_binds     = core_binds,
-                 cg_tycons    = tycons,
-                 cg_modBreaks = mod_breaks,
-                 cg_spt_entries = spt_entries
+                 cg_binds     = core_binds
                  } = tidy_cg
 
         !ModDetails { md_insts     = cls_insts
                     , md_fam_insts = fam_insts } = mod_details
             -- Get the *tidied* cls_insts and fam_insts
 
-        data_tycons = filter isDataTyCon tycons
-
-    {- Prepare For Code Generation -}
-    -- Do saturation and convert to A-normal form
-    prepd_binds <- {-# SCC "CorePrep" #-} liftIO $ do
-      cp_cfg <- initCorePrepConfig hsc_env
-      corePrepPgm
-        (hsc_logger hsc_env)
-        cp_cfg
-        (initCorePrepPgmConfig (hsc_dflags hsc_env) (interactiveInScope $ hsc_IC hsc_env))
-        this_mod iNTERACTIVELoc core_binds data_tycons
-
-    (stg_binds_with_deps, _infotable_prov, _caf_ccs__caf_cc_stacks, _stg_cg_info)
-        <- {-# SCC "CoreToStg" #-}
-           liftIO $ myCoreToStg (hsc_logger hsc_env)
-                                (hsc_dflags hsc_env)
-                                (interactiveInScope (hsc_IC hsc_env))
-                                True
-                                this_mod
-                                iNTERACTIVELoc
-                                prepd_binds
-
-    let (stg_binds,_stg_deps) = unzip stg_binds_with_deps
-
-    {- Generate byte code -}
-    cbc <- liftIO $ byteCodeGen hsc_env this_mod
-                                stg_binds data_tycons mod_breaks spt_entries
+    {- Generate byte code & foreign stubs -}
+    linkable <- liftIO $ generateFreshByteCode hsc_env
+      (moduleName this_mod)
+      (mkCgInteractiveGuts tidy_cg)
+      iNTERACTIVELoc
 
     let src_span = srcLocSpan interactiveSrcLoc
-    _ <- liftIO $ loadDecls interp hsc_env src_span cbc
+    _ <- liftIO $ loadDecls interp hsc_env src_span linkable
 
     {- Load static pointer table entries -}
     liftIO $ hscAddSptEntries hsc_env (cg_spt_entries tidy_cg)
@@ -2843,7 +2818,9 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do
                 [] -- spt entries
 
       {- load it -}
-      (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan bcos
+      bco_time <- getCurrentTime
+      (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
+        Linkable bco_time this_mod $ NE.singleton $ BCOs bcos
       {- Get the HValue for the root -}
       return (expectJust "hscCompileCoreExpr'"
          $ lookup (idName binding_id) fv_hvs, mods_needed, units_needed)


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -669,32 +669,40 @@ initLinkDepsOpts hsc_env = opts
 
   ********************************************************************* -}
 
-loadDecls :: Interp -> HscEnv -> SrcSpan -> CompiledByteCode -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
-loadDecls interp hsc_env span cbc at CompiledByteCode{..} = do
+loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
+loadDecls interp hsc_env span linkable = do
     -- Initialise the linker (if it's not been done already)
     initLoaderState interp hsc_env
 
     -- Take lock for the actual work.
     modifyLoaderState interp $ \pls0 -> do
+      -- Link the foreign objects first; BCOs in linkable are ignored here.
+      (pls1, objs_ok) <- loadObjects interp hsc_env pls0 [linkable]
+      when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
+
       -- Link the packages and modules required
-      (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 span needed_mods
+      (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
       if failed ok
         then throwGhcExceptionIO (ProgramError "")
         else do
           -- Link the expression itself
           let le  = linker_env pls
-              le2 = le { itbl_env = plusNameEnv (itbl_env le) bc_itbls
-                       , addr_env = plusNameEnv (addr_env le) bc_strs }
+              le2 = le { itbl_env = foldl' (\acc cbc -> plusNameEnv acc (bc_itbls cbc)) (itbl_env le) cbcs
+                       , addr_env = foldl' (\acc cbc -> plusNameEnv acc (bc_strs cbc)) (addr_env le) cbcs }
 
           -- Link the necessary packages and linkables
-          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 [cbc]
+          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
           nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
           let ce2  = extendClosureEnv (closure_env le2) nms_fhvs
               !pls2 = pls { linker_env = le2 { closure_env = ce2 } }
           return (pls2, (nms_fhvs, links_needed, units_needed))
   where
+    cbcs = linkableBCOs linkable
+
     free_names = uniqDSetToList $
-      foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet bc_bcos
+      foldl'
+        (\acc cbc -> foldl' (\acc' bco -> bcoFreeNames bco `unionUniqDSets` acc') acc (bc_bcos cbc))
+        emptyUniqDSet cbcs
 
     needed_mods :: [Module]
     needed_mods = [ nameModule n | n <- free_names,


=====================================
testsuite/tests/ghci/scripts/all.T
=====================================
@@ -360,7 +360,7 @@ test('T20455', normal, ghci_script, ['T20455.script'])
 test('shadow-bindings', normal, ghci_script, ['shadow-bindings.script'])
 test('T925', normal, ghci_script, ['T925.script'])
 test('T7388', normal, ghci_script, ['T7388.script'])
-test('T25414', [expect_broken(25414)], ghci_script, ['T25414.script'])
+test('T25414', normal, ghci_script, ['T25414.script'])
 test('T20627', normal, ghci_script, ['T20627.script'])
 test('T20473a', normal, ghci_script, ['T20473a.script'])
 test('T20473b', normal, ghci_script, ['T20473b.script'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 12:14:43 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 08:14:43 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] Move types from GHC.Types.Basic
 to L.H.S.*
Message-ID: <6720d1b3b7027_204ac7127143c10252c@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
fb6071f3 by Hassan Al-Awwadi at 2024-10-29T13:03:19+01:00
Move types from GHC.Types.Basic to L.H.S.*

Basically this cuts a few different edges between L.H.S and GHC.Types.Basic

* RuleName is moved to L.H.S.Basic
* fdTopLevel (TopLevelFlag) has been moved to the extension field of FamilyDecl
* OverlapMode has been moved to L.H.S.OverlapPragma
  * SourceText has been moved to its extension fields
  * NonCanonical has been moved to its extension constructor
* InlinePragma has been moved to L.H.S.InlinePragma
  * SourceText and Arity have been moved to its extension point
  * Activation and InlineSpec have also been moved to L.H.S.InlinePragma
* And some general churn as functions and instances move to new locations
  * GHC.Hs.OverlapPragma contains ghc specifics for L.H.S.OverlapPragma and
  * GHC.Hs.InlinePragma contains ghc specifics for L.H.S.InlinePragma
  * TyConFlavour definition is moved to GHC.Hs.Basic to avoid cyclical dependency

- - - - -


30 changed files:

- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Basic.hs
- compiler/GHC/Hs/Binds.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 12:29:36 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Tue, 29 Oct 2024 08:29:36 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/compress_since
Message-ID: <6720d5306a3f2_1ade1177ff0207d3@gitlab.mail>



Andreas Klebinger pushed new branch wip/andreask/compress_since at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/compress_since
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 12:41:45 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Tue, 29 Oct 2024 08:41:45 -0400
Subject: [Git][ghc/ghc][wip/fix-T25413] 21 commits: Improve heap overflow
 exception message (#25198)
Message-ID: <6720d809f0419_1ade12ff44025394@gitlab.mail>



Cheng Shao pushed to branch wip/fix-T25413 at Glasgow Haskell Compiler / GHC


Commits:
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
01430910 by Cheng Shao at 2024-10-29T13:41:36+01:00
testsuite: add T25413 test marked as broken

- - - - -
d28b52a7 by Cheng Shao at 2024-10-29T13:41:36+01:00
driver: fix recompilation check for foreign files added by qAddForeignFilePath

This patch fixes a recompilation checking bug: when a user specified
non-temporary foreign file is added by `qAddForeignFilePath`, when the
file changes it should trigger a recompilation. Fixes #25413.

- - - - -


30 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5aa19464ed565ad2f672d877d5831459716ee35...d28b52a7a72ec7fe17c48460dcfcc93dd9bac9c9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5aa19464ed565ad2f672d877d5831459716ee35...d28b52a7a72ec7fe17c48460dcfcc93dd9bac9c9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 13:05:19 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Tue, 29 Oct 2024 09:05:19 -0400
Subject: [Git][ghc/ghc][wip/unicode-16] ghc-internal: Update to Unicode 16
Message-ID: <6720dd8f22c4_1ade15de300316f5@gitlab.mail>



Matthew Pickering pushed to branch wip/unicode-16 at Glasgow Haskell Compiler / GHC


Commits:
b67548ec by Matthew Pickering at 2024-10-29T13:03:22+00:00
ghc-internal: Update to Unicode 16

This patch updates the automatically generated code for querying unicode
properties to unicode 16.

Fixes #25402

- - - - -


4 changed files:

- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.hs
- libraries/base/tests/unicode003.stdout
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs


The diff was not included because it is too large.


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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 16:18:01 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 29 Oct 2024 12:18:01 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 4 commits: Dont' eta expand cons when
 deriving Data
Message-ID: <67210ab9584af_bf1bbf0f54106452@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
d3f89b92 by Rodrigo Mesquita at 2024-10-28T17:30:54+00:00
Dont' eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

- - - - -
48cc6c0c by Rodrigo Mesquita at 2024-10-29T11:30:37+00:00
deriving Traversable: Eta reduce more constructor

- - - - -
21fcec77 by Rodrigo Mesquita at 2024-10-29T15:53:54+00:00
X WRNOG BRANCH

- - - - -
8cfd8dd4 by Rodrigo Mesquita at 2024-10-29T15:53:57+00:00
Revert "X WRNOG BRANCH"

This reverts commit 21fcec778136c0e9dbe8274c3329befee1136da9.

- - - - -


2 changed files:

- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Functor.hs
=====================================
@@ -689,9 +689,16 @@ mkSimpleConMatch2 ctxt fold extra_pats con insides = do
         con_expr
           | null asWithTyVar = nlHsApps con_name asWithoutTyVar
           | otherwise =
-              let bs   = filterByList  argTysTyVarInfo bs_RDRs
-                  vars = filterByLists argTysTyVarInfo bs_Vars as_Vars
-              in mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
+              let -- All trailing b-args can be eta-reduced:
+                  -- (\b1 b2 b3 -> A b1 a2 b2 b3) ==> (\b1 -> A b1 a2)
+                  -- We do this by counting the n of args to keep
+                  keep_n = length $ dropWhile (== True) $ reverse argTysTyVarInfo
+                  bs   = filterByList (take keep_n argTysTyVarInfo) bs_RDRs
+                  vars = take keep_n $
+                         filterByLists argTysTyVarInfo bs_Vars as_Vars
+               in if keep_n == 0
+                    then nlHsVar con_name
+                    else mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
 
     rhs <- fold con_expr exps
     return $ mkMatch ctxt (noLocA (extra_pats ++ [pat])) rhs emptyLocalBinds


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1404,7 +1404,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1424,16 +1424,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36c10986dd71c60e106891dfe333f93255cd0332...8cfd8dd40b50bd5302092982abdad1ffa34f8a38

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36c10986dd71c60e106891dfe333f93255cd0332...8cfd8dd40b50bd5302092982abdad1ffa34f8a38
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 16:20:24 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Tue, 29 Oct 2024 12:20:24 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 2 commits: Don't eta expand cons when
 deriving Data
Message-ID: <67210b48d8cbb_bf1bb7f48010682b@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
8a3fc7eb by Rodrigo Mesquita at 2024-10-29T16:18:26+00:00
Don't eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

- - - - -
a5845212 by Rodrigo Mesquita at 2024-10-29T16:18:30+00:00
deriving Traversable: Eta reduce more constructor

We were generating unnecessarily eta-expanded lambdas in derived
Traversable instances (via mkSimpleConMatch2).

We can generate smaller code by eta-reducing all trailing arguments
which do mention the last type variable

- - - - -


2 changed files:

- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs


Changes:

=====================================
compiler/GHC/Tc/Deriv/Functor.hs
=====================================
@@ -689,9 +689,16 @@ mkSimpleConMatch2 ctxt fold extra_pats con insides = do
         con_expr
           | null asWithTyVar = nlHsApps con_name asWithoutTyVar
           | otherwise =
-              let bs   = filterByList  argTysTyVarInfo bs_RDRs
-                  vars = filterByLists argTysTyVarInfo bs_Vars as_Vars
-              in mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
+              let -- All trailing b-args can be eta-reduced:
+                  -- (\b1 b2 b3 -> A b1 a2 b2 b3) ==> (\b1 -> A b1 a2)
+                  -- We do this by counting the n of args to keep
+                  keep_n = length $ dropWhile (== True) $ reverse argTysTyVarInfo
+                  bs   = filterByList (take keep_n argTysTyVarInfo) bs_RDRs
+                  vars = take keep_n $
+                         filterByLists argTysTyVarInfo bs_Vars as_Vars
+               in if keep_n == 0
+                    then nlHsVar con_name
+                    else mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
 
     rhs <- fold con_expr exps
     return $ mkMatch ctxt (noLocA (extra_pats ++ [pat])) rhs emptyLocalBinds


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -1404,7 +1404,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1424,16 +1424,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cfd8dd40b50bd5302092982abdad1ffa34f8a38...a5845212f06c5c6186f9ca492ccd6a3dbe893a19

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8cfd8dd40b50bd5302092982abdad1ffa34f8a38...a5845212f06c5c6186f9ca492ccd6a3dbe893a19
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 16:47:11 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 12:47:11 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] There are two parts to this
 commit.
Message-ID: <6721118ef1c99_bf1beb0d5c10748c@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
d52d2654 by Hassan Al-Awwadi at 2024-10-29T17:46:26+01:00
There are two parts to this commit.
* We moved the definition of BooleanFormula over to L.H.S.BooleanFormula
* We parameterized the BooleanFormula over the pass

The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula.
Because its parameterized over the pass its no longer a functor or
traversable, but we defined bfMap and bfTraverse for the cases where we
needed fmap and traverse originally. Most other changes are just churn.

-------------------------
Metric Decrease:
    MultiLayerModulesTH_OneShot
-------------------------

- - - - -


23 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
+import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -35,7 +36,7 @@ import GHC.Utils.Panic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
 import GHC.Utils.Outputable
-import GHC.Data.BooleanFormula (BooleanFormula, mkTrue)
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula, mkTrue )
 
 import qualified Data.Data as Data
 
@@ -131,7 +132,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula Name -- Required methods
+type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -43,6 +43,7 @@ module GHC.CoreToIface
     , toIfaceVar
       -- * Other stuff
     , toIfaceLFInfo
+    , toIfaceBooleanFormula
       -- * CgBreakInfo
     , dehydrateCgBreakInfo
     ) where
@@ -69,6 +70,7 @@ import GHC.Builtin.Types ( heqTyCon )
 
 import GHC.Iface.Syntax
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula qualified as BF(BooleanFormula(..))
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -82,11 +84,14 @@ import GHC.Types.Var.Set
 import GHC.Types.Tickish
 import GHC.Types.Demand ( isNopSig )
 import GHC.Types.Cpr ( topCprSig )
+import GHC.Types.SrcLoc (unLoc)
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Misc
 
+import GHC.Hs.Extension (GhcRn)
+
 import Data.Maybe ( isNothing, catMaybes )
 
 {- Note [Avoiding space leaks in toIface*]
@@ -537,6 +542,14 @@ toIfGuidance src guidance
   , isStableSource src = IfWhen arity unsat_ok boring_ok
   | otherwise          = IfNoGuidance
 
+toIfaceBooleanFormula :: BF.BooleanFormula GhcRn -> IfaceBooleanFormula
+toIfaceBooleanFormula = go
+  where
+    go (BF.Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
+    go (BF.And bfs  ) = IfAnd    $ map (go . unLoc) bfs
+    go (BF.Or bfs   ) = IfOr     $ map (go . unLoc) bfs
+    go (BF.Parens bf) = IfParens $     (go . unLoc) bf
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,5 +1,6 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable  #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
 -- | Boolean formulas without quantifiers and without negation.
@@ -8,73 +9,62 @@
 -- This module is used to represent minimal complete definitions for classes.
 --
 module GHC.Data.BooleanFormula (
-        BooleanFormula(..), LBooleanFormula,
-        mkFalse, mkTrue, mkAnd, mkOr, mkVar,
+        module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
+        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
-        pprBooleanFormula, pprBooleanFormulaNice
+        pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
   ) where
 
-import GHC.Prelude hiding ( init, last )
-
-import Data.List ( nub, intersperse )
+import Data.List ( intersperse )
 import Data.List.NonEmpty ( NonEmpty (..), init, last )
-import Data.Data
 
-import GHC.Utils.Monad
-import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( LocatedL )
-import GHC.Types.SrcLoc
+import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
+import GHC.Types.SrcLoc (unLoc)
+import GHC.Utils.Outputable
+import GHC.Parser.Annotation ( SrcSpanAnnL )
+import GHC.Hs.Extension (GhcPass (..), OutputableBndrId)
+import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
+import Language.Haskell.Syntax.BooleanFormula
+
 
 ----------------------------------------------------------------------
 -- Boolean formula type and smart constructors
 ----------------------------------------------------------------------
 
-type LBooleanFormula a = LocatedL (BooleanFormula a)
-
-data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a]
-                      | Parens (LBooleanFormula a)
-  deriving (Eq, Data, Functor, Foldable, Traversable)
-
-mkVar :: a -> BooleanFormula a
-mkVar = Var
+type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
-mkFalse, mkTrue :: BooleanFormula a
-mkFalse = Or []
-mkTrue = And []
+-- if we had Functor/Traversable (LbooleanFormula p) we could use that
+-- as a constraint and we wouldn't need to specialize to just GhcPass p,
+-- but becuase LBooleanFormula is a type synonym such a constraint is
+-- impossible.
 
--- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula a
-mkBool False = mkFalse
-mkBool True  = mkTrue
-
--- Make a conjunction, and try to simplify
-mkAnd :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkAnd = maybe mkFalse (mkAnd' . nub) . concatMapM fromAnd
+-- BooleanFormula can't be an instance of functor because it can't lift
+-- arbitrary functions `a -> b`, only functions of type `LIdP a -> LIdP b`
+-- ditto for Traversable.
+bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
+      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
+bfMap f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula a -> Maybe [LBooleanFormula a]
-  fromAnd (L _ (And xs)) = Just xs
-     -- assume that xs are already simplified
-     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
-  fromAnd (L _ (Or [])) = Nothing
-     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
-  fromAnd x = Just [x]
-  mkAnd' [x] = unLoc x
-  mkAnd' xs = And xs
-
-mkOr :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkOr = maybe mkTrue (mkOr' . nub) . concatMapM fromOr
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (fmap go) bfs
+    go (Or     bfs) = Or      $ map (fmap go) bfs
+    go (Parens bf ) = Parens  $ fmap go bf
+
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (GhcPass p'))
+bfTraverse f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromOr (L _ (Or xs)) = Just xs
-  fromOr (L _ (And [])) = Nothing
-  fromOr x = Just [x]
-  mkOr' [x] = unLoc x
-  mkOr' xs = Or xs
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 
 
 {-
@@ -115,15 +105,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula a -> Bool
+isFalse :: BooleanFormula (GhcPass p) -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula a -> Bool
+isTrue :: BooleanFormula (GhcPass p) -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (a -> Bool) -> BooleanFormula a -> Bool
+eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
 eval f (Var x)  = f x
 eval f (And xs) = all (eval f . unLoc) xs
 eval f (Or xs)  = any (eval f . unLoc) xs
@@ -131,18 +121,24 @@ eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: Eq a => (a -> Maybe Bool) -> BooleanFormula a -> BooleanFormula a
+simplify :: forall p. Eq (LIdP (GhcPass p))
+          => (LIdP (GhcPass p) ->  Maybe Bool)
+          -> BooleanFormula (GhcPass p)
+          -> BooleanFormula (GhcPass p)
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (\(L l x) -> L l (simplify f x)) xs)
-simplify f (Or xs) = mkOr (map (\(L l x) -> L l (simplify f x)) xs)
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
 simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq a => (a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
+isUnsatisfied :: Eq (LIdP (GhcPass p))
+              => (LIdP (GhcPass p) -> Bool)
+              -> BooleanFormula (GhcPass p)
+              -> Maybe (BooleanFormula (GhcPass p))
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -155,42 +151,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq a => BooleanFormula a -> a -> Bool
-Var x  `impliesAtom` y = x == y
-And xs `impliesAtom` y = any (\x -> (unLoc x) `impliesAtom` y) xs
+impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
            -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> (unLoc x) `impliesAtom` y) xs
-Parens x `impliesAtom` y = (unLoc x) `impliesAtom` y
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
-implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
+implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable a => Clause a -> Clause a -> Bool
+    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms x r -> True
-                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms (unLoc x) r -> True
+                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
             And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms x l -> True
-                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
+            Var x | memberClauseAtoms (unLoc x) l -> True
+                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = unLoc con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause a = Clause {
-        clauseAtoms :: UniqSet a,
-        clauseExprs :: [BooleanFormula a]
+data Clause p = Clause {
+        clauseAtoms :: UniqSet (IdP p),
+        clauseExprs :: [BooleanFormula p]
     }
-extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
+extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
+memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -199,28 +195,29 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula' :: (Rational -> a -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
-  go p (And []) = cparen (p > 0) $ empty
+  go p (And []) = cparen (p > 0) empty
   go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
   go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
   go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
+pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -230,15 +227,14 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance (OutputableBndr a) => Outputable (BooleanFormula a) where
+instance OutputableBndrId p => Outputable (BooleanFormula (GhcPass p)) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: (OutputableBndr a)
-                        => BooleanFormula a -> SDoc
+pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc x
+    go (Var x)    = pprPrefixOcc (unLoc x)
     go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)
-    go (Parens x) = parens (go $ unLoc x)
+    go (Parens x) = parens (go $ unLoc x)
\ No newline at end of file


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,6 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -47,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Var
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.Name
 
 import GHC.Utils.Outputable
@@ -968,9 +968,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: (OutputableBndr name)
-              => LBooleanFormula (GenLocated l name) -> SDoc
-pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -110,6 +110,7 @@ module GHC.Hs.Decls (
 import GHC.Prelude
 
 import Language.Haskell.Syntax.Decls
+import Language.Haskell.Syntax.Extension
 
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprUntypedSplice )
         -- Because Expr imports Decls via HsBracket
@@ -119,7 +120,7 @@ import GHC.Hs.Type
 import GHC.Hs.Doc
 import GHC.Types.Basic
 import GHC.Core.Coercion
-import Language.Haskell.Syntax.Extension
+
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
 import GHC.Types.Name


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -33,6 +33,8 @@ import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
+import GHC.Data.BooleanFormula (BooleanFormula(..))
+import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -590,3 +592,6 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+
+deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -13,7 +13,6 @@
 module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
-   , toIfaceBooleanFormula
    )
 where
 
@@ -33,21 +32,17 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
 import GHC.Types.TyThing
-import GHC.Types.SrcLoc
 
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
 import GHC.Data.Maybe
-import GHC.Data.BooleanFormula
-
 import Data.List ( findIndex, mapAccumL )
 
 {-
@@ -287,7 +282,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula $ fmap (mkIfLclName . getOccFS) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -335,10 +330,3 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
-
-toIfaceBooleanFormula :: BooleanFormula IfLclName -> IfaceBooleanFormula
-toIfaceBooleanFormula = \case
-    Var nm    -> IfVar    nm
-    And bfs   -> IfAnd    (map (toIfaceBooleanFormula . unLoc) bfs)
-    Or bfs    -> IfOr     (map (toIfaceBooleanFormula . unLoc) bfs)
-    Parens bf -> IfParens (toIfaceBooleanFormula . unLoc $ bf)


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2041,8 +2041,9 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance ToHie (LBooleanFormula (LocatedN Name)) where
-  toHie (L span form) = concatM $ makeNode form (locA span) : case form of
+instance (HiePass p, Data (IdGhcP p))
+  => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -35,10 +35,8 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
-        fromIfaceBooleanFormula,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
-
         -- Free Names
         freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
         freeNamesIfConDecls,
@@ -51,7 +49,10 @@ module GHC.Iface.Syntax (
 
 import GHC.Prelude
 
+import GHC.Builtin.Names(mkUnboundName)
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula (pprBooleanFormula, isTrue)
+
 import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey,
                            constraintKindTyConKey )
 import GHC.Types.Unique ( hasKey )
@@ -62,9 +63,9 @@ import GHC.Types.Demand
 import GHC.Types.Cpr
 import GHC.Core.Class
 import GHC.Types.FieldLabel
-import GHC.Types.Name.Set
 import GHC.Core.Coercion.Axiom ( BranchIndex )
 import GHC.Types.Name
+import GHC.Types.Name.Set
 import GHC.Types.Name.Reader
 import GHC.Types.CostCentre
 import GHC.Types.Literal
@@ -75,7 +76,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
@@ -94,6 +94,8 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
                        seqList, zipWithEqual )
 
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
+
 import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
@@ -213,18 +215,14 @@ data IfaceClassBody
      ifMinDef    :: IfaceBooleanFormula       -- Minimal complete definition
     }
 
+-- See also 'BooleanFormula'
 data IfaceBooleanFormula
   = IfVar IfLclName
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
+  deriving Eq
 
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
-fromIfaceBooleanFormula = \case
-    IfVar nm     -> Var    nm
-    IfAnd ibfs   -> And    (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfOr ibfs    -> Or     (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfParens ibf -> Parens (noLocA . fromIfaceBooleanFormula $ ibf)
 
 data IfaceTyConParent
   = IfNoParent
@@ -1039,13 +1037,21 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | showSub ss sg = Just $  pprIfaceClassOp ss sg
         | otherwise     = Nothing
 
-      pprMinDef :: BooleanFormula IfLclName -> SDoc
+      pprMinDef :: BooleanFormula GhcRn -> SDoc
       pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
         pprBooleanFormula
-          (\_ def -> cparen (isLexSym def) (ppr def)) 0 (fmap ifLclNameFS minDef) <+>
+          (\_ def -> let fs = getOccFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+      fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
+      -- `mkUnboundName` here is fine because the Name generated is only used for pretty printing and nothing else.
+      fromIfaceBooleanFormula (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
+      fromIfaceBooleanFormula (IfAnd bfs  ) = And    $ map (noLocA . fromIfaceBooleanFormula) bfs
+      fromIfaceBooleanFormula (IfOr bfs   ) = Or     $ map (noLocA . fromIfaceBooleanFormula) bfs
+      fromIfaceBooleanFormula (IfParens bf) = Parens $     (noLocA . fromIfaceBooleanFormula) bf
+
+
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -32,6 +32,7 @@ module GHC.IfaceToCore (
         hydrateCgBreakInfo
  ) where
 
+
 import GHC.Prelude
 
 import GHC.ByteCode.Types
@@ -43,7 +44,6 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (toIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -123,20 +123,26 @@ import GHC.Types.Tickish
 import GHC.Types.TyThing
 import GHC.Types.Error
 
+import GHC.Parser.Annotation (noLocA)
+
+import GHC.Hs.Extension ( GhcRn )
+
 import GHC.Fingerprint
-import qualified GHC.Data.BooleanFormula as BF
 
 import Control.Monad
-import GHC.Parser.Annotation
 import GHC.Driver.Env.KnotVars
 import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List(nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
+
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
 {-
@@ -297,14 +303,38 @@ mergeIfaceDecl d1 d2
                   plusNameEnv_C mergeIfaceClassOp
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
+
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . BF.mkOr . map (noLocA . fromIfaceBooleanFormula) $ [bf1, bf2]
+                ifMinDef = mkOr [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
     -- we merge, see 'mergeSignatures'
     | otherwise              = d1 `withRolesFrom` d2
+      where
+        -- The reason we need to duplicate mkOr here, instead of
+        -- using BooleanFormula's mkOr and just doing the loop like:
+        -- `toIfaceBooleanFormula . mkOr . fromIfaceBooleanFormula`
+        -- is quite subtle. Say we have the following minimal pragma:
+        -- {-# MINIMAL f | g #-}. If we use fromIfaceBooleanFormula
+        -- first, we will end up doing
+        -- `nub [Var (mkUnboundName f), Var (mkUnboundName g)]`,
+        -- which might seem fine, but Name equallity is decided by
+        -- their Unique, which will be identical since mkUnboundName
+        -- just stuffs the mkUnboundKey unqiue into both.
+        -- So the result will be {-# MINIMAL f #-}, oopsie.
+        -- Duplication it is.
+        mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+        mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+          where
+          -- See Note [Simplification of BooleanFormulas]
+          fromOr bf = case bf of
+            (IfOr xs)  -> Just xs
+            (IfAnd []) -> Nothing
+            _        -> Just [bf]
+          mkOr' [x] = x
+          mkOr' xs = IfOr xs
 
 -- Note [Role merging]
 -- ~~~~~~~~~~~~~~~~~~~
@@ -795,8 +825,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef_occ = fromIfaceBooleanFormula if_mindef
-    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) mindef_occ
+    ; mindef <- tc_boolean_formula if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)
@@ -845,6 +874,12 @@ tc_iface_decl _parent ignore_prags
                   -- e.g.   type AT a; type AT b = AT [b]   #8002
           return (ATI tc mb_def)
 
+   tc_boolean_formula :: IfaceBooleanFormula -> IfL (BooleanFormula GhcRn)
+   tc_boolean_formula (IfAnd ibfs  ) = BF.And    . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfOr ibfs   ) = BF.Or     . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfParens ibf) = BF.Parens .     noLocA <$>          tc_boolean_formula ibf
+   tc_boolean_formula (IfVar nm    ) = BF.Var    .     noLocA <$> lookupIfaceTop . mkVarOccFS . ifLclNameFS nm
+
    mk_sc_doc pred = text "Superclass" <+> ppr pred
    mk_at_doc tc = text "Associated type" <+> ppr tc
    mk_op_doc op_name op_ty = text "Class op" <+> sep [ppr op_name, ppr op_ty]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -39,9 +39,9 @@ module GHC.Parser
 where
 
 -- base
-import Control.Monad    ( unless, liftM, when, (<=<) )
+import Control.Monad      ( unless, liftM, when, (<=<) )
 import GHC.Exts
-import Data.Maybe       ( maybeToList )
+import Data.Maybe         ( maybeToList )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
@@ -3712,27 +3712,27 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
         | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { LBooleanFormula (LocatedN RdrName) }
-        : name_boolformula_and                      { $1 }
+name_boolformula :: { LBooleanFormula GhcPs }
+        : name_boolformula_and      { $1 }
         | name_boolformula_and '|' name_boolformula
                            {% do { h <- addTrailingVbarL $1 (epTok $2)
                                  ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
         : name_boolformula_and_list
                   { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula (LocatedN RdrName)] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
         : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
             {% do { h <- addTrailingCommaL $1 (epTok $2)
                   ; return (h : $3) } }
 
-name_boolformula_atom :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
         : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
                                       (AnnList Nothing (ListParens (epTok $1) (epTok $3)) [] noAnn []) }
         | name_var                  { sL1a $1 (Var $1) }
@@ -4706,4 +4706,4 @@ combineHasLocs a b = combineSrcSpans (getHasLoc a) (getHasLoc b)
 fromTrailingN :: SrcSpanAnnN -> SrcSpanAnnA
 fromTrailingN (EpAnn anc ann cs)
     = EpAnn anc (AnnListItem (nann_trailing ann)) cs
-}
+}
\ No newline at end of file


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,6 +80,7 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
+import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1137,7 +1138,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
-  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just (fmap unLoc bf)
-    toMinimalDef _                               = Nothing
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef _                             = Nothing
 
 {-
 Note [Polymorphic methods]
@@ -603,4 +603,4 @@ warnMissingAT name
                   $ InvalidAssoc $ InvalidAssocInstance
                   $ AssocInstanceMissing name
        ; diagnosticTc  (warn && hsc_src == HsSrcFile) diag
-                       }
+                       }
\ No newline at end of file


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -26,15 +26,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   ( LHsExpr
   , MatchGroup
   , GRHSs )
-import {-# SOURCE #-} Language.Haskell.Syntax.Pat
-  ( LPat )
-
+import {-# SOURCE #-} Language.Haskell.Syntax.Pat( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
 import Language.Haskell.Syntax.Basic ( Fixity )
 
 import GHC.Types.Basic (InlinePragma)
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 
 import Data.Void
@@ -379,7 +377,7 @@ data Sig pass
         -- | A minimal complete definition pragma
         --
         -- > {-# MINIMAL a | (b, c | (d | e)) #-}
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -0,0 +1,62 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+
+module Language.Haskell.Syntax.BooleanFormula(
+  BooleanFormula(..), LBooleanFormula,
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr
+  ) where
+
+import Prelude hiding ( init, last )
+import Data.List ( nub )
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+
+
+-- types
+type LBooleanFormula p = XRec p (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
+
+-- instances
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+
+-- smart constructors
+-- see note [Simplification of BooleanFormulas]
+mkVar :: LIdP p -> BooleanFormula p
+mkVar = Var
+
+mkFalse, mkTrue :: BooleanFormula p
+mkFalse = Or []
+mkTrue = And []
+
+-- Convert a Bool to a BooleanFormula
+mkBool :: Bool -> BooleanFormula p
+mkBool False = mkFalse
+mkBool True  = mkTrue
+
+-- Make a conjunction, and try to simplify
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
+    (And xs) -> Just xs
+     -- assume that xs are already simplified
+     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
+    (Or [])  -> Nothing
+     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
+    _        -> Just [bf]
+  mkAnd' [x] = unXRec @p x
+  mkAnd' xs = And xs
+
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromOr bf = case unXRec @p bf of
+    (Or xs)  -> Just xs
+    (And []) -> Nothing
+    _        -> Just [bf]
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
compiler/ghc.cabal.in
=====================================
@@ -991,6 +991,7 @@ Library
         Language.Haskell.Syntax
         Language.Haskell.Syntax.Basic
         Language.Haskell.Syntax.Binds
+        Language.Haskell.Syntax.BooleanFormula
         Language.Haskell.Syntax.Decls
         Language.Haskell.Syntax.Expr
         Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -234,6 +234,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -258,6 +258,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2817,7 +2817,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4537,7 +4537,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -45,6 +45,7 @@ import GHC.Builtin.Types
   , promotedNilDataCon
   , unitTy
   )
+
 import GHC.Builtin.Types.Prim (alphaTyVars)
 import GHC.Core.Class
 import GHC.Core.Coercion.Axiom
@@ -176,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA . fmap noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -19,6 +19,8 @@
 -- Portability :  portable
 module Haddock.Interface.Rename (renameInterface) where
 
+import Prelude hiding (mapM)
+
 import Control.Applicative ()
 import Control.DeepSeq (force)
 import Control.Monad hiding (mapM)
@@ -28,12 +30,13 @@ import Data.Foldable (traverse_)
 import qualified Data.Map.Strict as Map
 import qualified Data.Set as Set
 import Data.Traversable (mapM)
+
 import GHC hiding (NoLink)
 import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName)
 import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
-import Prelude hiding (mapM)
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -770,11 +773,22 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- traverse (traverse lookupRn) s
+    s' <- bfTraverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP DocNameI))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula DocNameI)
+bfTraverse f = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do
   lname' <- renameNameL lname


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -53,6 +53,7 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 import GHC
 import qualified GHC.Data.Strict as Strict
+import GHC.Data.BooleanFormula (BooleanFormula)
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
@@ -819,6 +820,7 @@ type instance Anno (HsDecl DocNameI) = SrcSpanAnnA
 type instance Anno (FamilyResultSig DocNameI) = EpAnn NoEpAnns
 type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
+type instance Anno (BooleanFormula DocNameI) = SrcSpanAnnL
 
 type XRecCond a =
   ( XParTy a ~ (EpToken "(", EpToken ")")



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 17:43:09 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 13:43:09 -0400
Subject: [Git][ghc/ghc][wip/ttg-booleanformula] Refactored BooleanFormula to
 be in line with TTG (#21592)
Message-ID: <67211ead58220_249fdb19f98826040@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg-booleanformula at Glasgow Haskell Compiler / GHC


Commits:
f19fced7 by Hassan Al-Awwadi at 2024-10-29T18:41:40+01:00
Refactored BooleanFormula to be in line with TTG (#21592)

There are two parts to this commit.
* We moved the definition of BooleanFormula over to L.H.S.BooleanFormula
* We parameterized the BooleanFormula over the pass

The GHC specific details of BooleanFormula remain in Ghc.Data.BooleanFormula.
Because its parameterized over the pass its no longer a functor or
traversable, but we defined bfMap and bfTraverse for the cases where we
needed fmap and traverse originally. Most other changes are just churn.

-------------------------
Metric Decrease:
    MultiLayerModulesTH_OneShot
-------------------------

- - - - -


24 changed files:

- compiler/GHC/Core/Class.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- + compiler/Language/Haskell/Syntax/BooleanFormula.hs
- compiler/ghc.cabal.in
- libraries/text
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
compiler/GHC/Core/Class.hs
=====================================
@@ -26,6 +26,7 @@ import GHC.Prelude
 import {-# SOURCE #-} GHC.Core.TyCon    ( TyCon )
 import {-# SOURCE #-} GHC.Core.TyCo.Rep ( Type, PredType )
 import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType )
+import GHC.Hs.Extension (GhcRn)
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
@@ -35,7 +36,7 @@ import GHC.Utils.Panic
 import GHC.Types.SrcLoc
 import GHC.Types.Var.Set
 import GHC.Utils.Outputable
-import GHC.Data.BooleanFormula (BooleanFormula, mkTrue)
+import Language.Haskell.Syntax.BooleanFormula ( BooleanFormula, mkTrue )
 
 import qualified Data.Data as Data
 
@@ -131,7 +132,7 @@ data TyFamEqnValidityInfo
       -- Note [Type-checking default assoc decls] in GHC.Tc.TyCl.
     }
 
-type ClassMinimalDef = BooleanFormula Name -- Required methods
+type ClassMinimalDef = BooleanFormula GhcRn -- Required methods
 
 data ClassBody
   = AbstractClass


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -43,6 +43,7 @@ module GHC.CoreToIface
     , toIfaceVar
       -- * Other stuff
     , toIfaceLFInfo
+    , toIfaceBooleanFormula
       -- * CgBreakInfo
     , dehydrateCgBreakInfo
     ) where
@@ -69,6 +70,7 @@ import GHC.Builtin.Types ( heqTyCon )
 
 import GHC.Iface.Syntax
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula qualified as BF(BooleanFormula(..))
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -82,11 +84,14 @@ import GHC.Types.Var.Set
 import GHC.Types.Tickish
 import GHC.Types.Demand ( isNopSig )
 import GHC.Types.Cpr ( topCprSig )
+import GHC.Types.SrcLoc (unLoc)
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Misc
 
+import GHC.Hs.Extension (GhcRn)
+
 import Data.Maybe ( isNothing, catMaybes )
 
 {- Note [Avoiding space leaks in toIface*]
@@ -537,6 +542,14 @@ toIfGuidance src guidance
   , isStableSource src = IfWhen arity unsat_ok boring_ok
   | otherwise          = IfNoGuidance
 
+toIfaceBooleanFormula :: BF.BooleanFormula GhcRn -> IfaceBooleanFormula
+toIfaceBooleanFormula = go
+  where
+    go (BF.Var nm   ) = IfVar    $ mkIfLclName . getOccFS . unLoc $  nm
+    go (BF.And bfs  ) = IfAnd    $ map (go . unLoc) bfs
+    go (BF.Or bfs   ) = IfOr     $ map (go . unLoc) bfs
+    go (BF.Parens bf) = IfParens $     (go . unLoc) bf
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Data/BooleanFormula.hs
=====================================
@@ -1,5 +1,6 @@
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveTraversable  #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE TypeFamilies #-}
 
 --------------------------------------------------------------------------------
 -- | Boolean formulas without quantifiers and without negation.
@@ -8,73 +9,62 @@
 -- This module is used to represent minimal complete definitions for classes.
 --
 module GHC.Data.BooleanFormula (
-        BooleanFormula(..), LBooleanFormula,
-        mkFalse, mkTrue, mkAnd, mkOr, mkVar,
+        module Language.Haskell.Syntax.BooleanFormula,
         isFalse, isTrue,
+        bfMap, bfTraverse,
         eval, simplify, isUnsatisfied,
         implies, impliesAtom,
-        pprBooleanFormula, pprBooleanFormulaNice
+        pprBooleanFormula, pprBooleanFormulaNice, pprBooleanFormulaNormal
   ) where
 
-import GHC.Prelude hiding ( init, last )
-
-import Data.List ( nub, intersperse )
+import Data.List ( intersperse )
 import Data.List.NonEmpty ( NonEmpty (..), init, last )
-import Data.Data
 
-import GHC.Utils.Monad
-import GHC.Utils.Outputable
-import GHC.Parser.Annotation ( LocatedL )
-import GHC.Types.SrcLoc
+import GHC.Prelude hiding ( init, last )
 import GHC.Types.Unique
 import GHC.Types.Unique.Set
+import GHC.Types.SrcLoc (unLoc)
+import GHC.Utils.Outputable
+import GHC.Parser.Annotation ( SrcSpanAnnL )
+import GHC.Hs.Extension (GhcPass (..), OutputableBndrId)
+import Language.Haskell.Syntax.Extension (Anno, LIdP, IdP)
+import Language.Haskell.Syntax.BooleanFormula
+
 
 ----------------------------------------------------------------------
 -- Boolean formula type and smart constructors
 ----------------------------------------------------------------------
 
-type LBooleanFormula a = LocatedL (BooleanFormula a)
-
-data BooleanFormula a = Var a | And [LBooleanFormula a] | Or [LBooleanFormula a]
-                      | Parens (LBooleanFormula a)
-  deriving (Eq, Data, Functor, Foldable, Traversable)
-
-mkVar :: a -> BooleanFormula a
-mkVar = Var
+type instance Anno (BooleanFormula (GhcPass p)) = SrcSpanAnnL
 
-mkFalse, mkTrue :: BooleanFormula a
-mkFalse = Or []
-mkTrue = And []
+-- if we had Functor/Traversable (LbooleanFormula p) we could use that
+-- as a constraint and we wouldn't need to specialize to just GhcPass p,
+-- but becuase LBooleanFormula is a type synonym such a constraint is
+-- impossible.
 
--- Convert a Bool to a BooleanFormula
-mkBool :: Bool -> BooleanFormula a
-mkBool False = mkFalse
-mkBool True  = mkTrue
-
--- Make a conjunction, and try to simplify
-mkAnd :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkAnd = maybe mkFalse (mkAnd' . nub) . concatMapM fromAnd
+-- BooleanFormula can't be an instance of functor because it can't lift
+-- arbitrary functions `a -> b`, only functions of type `LIdP a -> LIdP b`
+-- ditto for Traversable.
+bfMap :: (LIdP (GhcPass p) -> LIdP (GhcPass p'))
+      -> BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p')
+bfMap f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromAnd :: LBooleanFormula a -> Maybe [LBooleanFormula a]
-  fromAnd (L _ (And xs)) = Just xs
-     -- assume that xs are already simplified
-     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
-  fromAnd (L _ (Or [])) = Nothing
-     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
-  fromAnd x = Just [x]
-  mkAnd' [x] = unLoc x
-  mkAnd' xs = And xs
-
-mkOr :: Eq a => [LBooleanFormula a] -> BooleanFormula a
-mkOr = maybe mkTrue (mkOr' . nub) . concatMapM fromOr
+    go (Var    a  ) = Var     $ f a
+    go (And    bfs) = And     $ map (fmap go) bfs
+    go (Or     bfs) = Or      $ map (fmap go) bfs
+    go (Parens bf ) = Parens  $ fmap go bf
+
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP (GhcPass p')))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula (GhcPass p'))
+bfTraverse f = go
   where
-  -- See Note [Simplification of BooleanFormulas]
-  fromOr (L _ (Or xs)) = Just xs
-  fromOr (L _ (And [])) = Nothing
-  fromOr x = Just [x]
-  mkOr' [x] = unLoc x
-  mkOr' xs = Or xs
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 
 
 {-
@@ -115,15 +105,15 @@ We don't show a ridiculous error message like
 -- Evaluation and simplification
 ----------------------------------------------------------------------
 
-isFalse :: BooleanFormula a -> Bool
+isFalse :: BooleanFormula (GhcPass p) -> Bool
 isFalse (Or []) = True
 isFalse _ = False
 
-isTrue :: BooleanFormula a -> Bool
+isTrue :: BooleanFormula (GhcPass p) -> Bool
 isTrue (And []) = True
 isTrue _ = False
 
-eval :: (a -> Bool) -> BooleanFormula a -> Bool
+eval :: (LIdP (GhcPass p) -> Bool) -> BooleanFormula (GhcPass p) -> Bool
 eval f (Var x)  = f x
 eval f (And xs) = all (eval f . unLoc) xs
 eval f (Or xs)  = any (eval f . unLoc) xs
@@ -131,18 +121,24 @@ eval f (Parens x) = eval f (unLoc x)
 
 -- Simplify a boolean formula.
 -- The argument function should give the truth of the atoms, or Nothing if undecided.
-simplify :: Eq a => (a -> Maybe Bool) -> BooleanFormula a -> BooleanFormula a
+simplify :: forall p. Eq (LIdP (GhcPass p))
+          => (LIdP (GhcPass p) ->  Maybe Bool)
+          -> BooleanFormula (GhcPass p)
+          -> BooleanFormula (GhcPass p)
 simplify f (Var a) = case f a of
   Nothing -> Var a
   Just b  -> mkBool b
-simplify f (And xs) = mkAnd (map (\(L l x) -> L l (simplify f x)) xs)
-simplify f (Or xs) = mkOr (map (\(L l x) -> L l (simplify f x)) xs)
+simplify f (And xs) = mkAnd (map (fmap (simplify f)) xs)
+simplify f (Or xs)  = mkOr  (map (fmap (simplify f)) xs)
 simplify f (Parens x) = simplify f (unLoc x)
 
 -- Test if a boolean formula is satisfied when the given values are assigned to the atoms
 -- if it is, returns Nothing
 -- if it is not, return (Just remainder)
-isUnsatisfied :: Eq a => (a -> Bool) -> BooleanFormula a -> Maybe (BooleanFormula a)
+isUnsatisfied :: Eq (LIdP (GhcPass p))
+              => (LIdP (GhcPass p) -> Bool)
+              -> BooleanFormula (GhcPass p)
+              -> Maybe (BooleanFormula (GhcPass p))
 isUnsatisfied f bf
     | isTrue bf' = Nothing
     | otherwise  = Just bf'
@@ -155,42 +151,42 @@ isUnsatisfied f bf
 --   eval f x == False  <==>  isFalse (simplify (Just . f) x)
 
 -- If the boolean formula holds, does that mean that the given atom is always true?
-impliesAtom :: Eq a => BooleanFormula a -> a -> Bool
-Var x  `impliesAtom` y = x == y
-And xs `impliesAtom` y = any (\x -> (unLoc x) `impliesAtom` y) xs
+impliesAtom :: Eq (IdP (GhcPass p)) => BooleanFormula (GhcPass p) -> LIdP (GhcPass p) -> Bool
+Var x  `impliesAtom` y = (unLoc x) == (unLoc y)
+And xs `impliesAtom` y = any (\x -> unLoc x `impliesAtom` y) xs
            -- we have all of xs, so one of them implying y is enough
-Or  xs `impliesAtom` y = all (\x -> (unLoc x) `impliesAtom` y) xs
-Parens x `impliesAtom` y = (unLoc x) `impliesAtom` y
+Or  xs `impliesAtom` y = all (\x -> unLoc x `impliesAtom` y) xs
+Parens x `impliesAtom` y = unLoc x `impliesAtom` y
 
-implies :: Uniquable a => BooleanFormula a -> BooleanFormula a -> Bool
+implies :: (Uniquable (IdP (GhcPass p))) => BooleanFormula (GhcPass p) -> BooleanFormula (GhcPass p) -> Bool
 implies e1 e2 = go (Clause emptyUniqSet [e1]) (Clause emptyUniqSet [e2])
   where
-    go :: Uniquable a => Clause a -> Clause a -> Bool
+    go :: Uniquable (IdP (GhcPass p)) => Clause (GhcPass p) -> Clause (GhcPass p) -> Bool
     go l at Clause{ clauseExprs = hyp:hyps } r =
         case hyp of
-            Var x | memberClauseAtoms x r -> True
-                  | otherwise -> go (extendClauseAtoms l x) { clauseExprs = hyps } r
+            Var x | memberClauseAtoms (unLoc x) r -> True
+                  | otherwise -> go (extendClauseAtoms l (unLoc x)) { clauseExprs = hyps } r
             Parens hyp' -> go l { clauseExprs = unLoc hyp':hyps }     r
             And hyps'  -> go l { clauseExprs = map unLoc hyps' ++ hyps } r
             Or hyps'   -> all (\hyp' -> go l { clauseExprs = unLoc hyp':hyps } r) hyps'
     go l r at Clause{ clauseExprs = con:cons } =
         case con of
-            Var x | memberClauseAtoms x l -> True
-                  | otherwise -> go l (extendClauseAtoms r x) { clauseExprs = cons }
+            Var x | memberClauseAtoms (unLoc x) l -> True
+                  | otherwise -> go l (extendClauseAtoms r (unLoc x)) { clauseExprs = cons }
             Parens con' -> go l r { clauseExprs = unLoc con':cons }
             And cons'   -> all (\con' -> go l r { clauseExprs = unLoc con':cons }) cons'
             Or cons'    -> go l r { clauseExprs = map unLoc cons' ++ cons }
     go _ _ = False
 
 -- A small sequent calculus proof engine.
-data Clause a = Clause {
-        clauseAtoms :: UniqSet a,
-        clauseExprs :: [BooleanFormula a]
+data Clause p = Clause {
+        clauseAtoms :: UniqSet (IdP p),
+        clauseExprs :: [BooleanFormula p]
     }
-extendClauseAtoms :: Uniquable a => Clause a -> a -> Clause a
+extendClauseAtoms :: Uniquable (IdP p) => Clause p -> IdP p -> Clause p
 extendClauseAtoms c x = c { clauseAtoms = addOneToUniqSet (clauseAtoms c) x }
 
-memberClauseAtoms :: Uniquable a => a -> Clause a -> Bool
+memberClauseAtoms :: Uniquable (IdP p) => IdP p -> Clause p -> Bool
 memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 ----------------------------------------------------------------------
@@ -199,28 +195,29 @@ memberClauseAtoms x c = x `elementOfUniqSet` clauseAtoms c
 
 -- Pretty print a BooleanFormula,
 -- using the arguments as pretty printers for Var, And and Or respectively
-pprBooleanFormula' :: (Rational -> a -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> (Rational -> [SDoc] -> SDoc)
-                   -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula'  :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> (Rational -> [SDoc] -> SDoc)
+                    -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula' pprVar pprAnd pprOr = go
   where
   go p (Var x)  = pprVar p x
-  go p (And []) = cparen (p > 0) $ empty
+  go p (And []) = cparen (p > 0) empty
   go p (And xs) = pprAnd p (map (go 3 . unLoc) xs)
   go _ (Or  []) = keyword $ text "FALSE"
   go p (Or  xs) = pprOr p (map (go 2 . unLoc) xs)
   go p (Parens x) = go p (unLoc x)
 
 -- Pretty print in source syntax, "a | b | c,d,e"
-pprBooleanFormula :: (Rational -> a -> SDoc) -> Rational -> BooleanFormula a -> SDoc
+pprBooleanFormula :: (Rational -> LIdP (GhcPass p) -> SDoc)
+                  -> Rational -> BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormula pprVar = pprBooleanFormula' pprVar pprAnd pprOr
   where
   pprAnd p = cparen (p > 3) . fsep . punctuate comma
   pprOr  p = cparen (p > 2) . fsep . intersperse vbar
 
 -- Pretty print human in readable format, "either `a' or `b' or (`c', `d' and `e')"?
-pprBooleanFormulaNice :: Outputable a => BooleanFormula a -> SDoc
+pprBooleanFormulaNice :: Outputable (LIdP (GhcPass p)) => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   where
   pprVar _ = quotes . ppr
@@ -230,15 +227,14 @@ pprBooleanFormulaNice = pprBooleanFormula' pprVar pprAnd pprOr 0
   pprAnd' (x:xs) = fsep (punctuate comma (init (x:|xs))) <> text ", and" <+> last (x:|xs)
   pprOr p xs = cparen (p > 1) $ text "either" <+> sep (intersperse (text "or") xs)
 
-instance (OutputableBndr a) => Outputable (BooleanFormula a) where
+instance OutputableBndrId p => Outputable (BooleanFormula (GhcPass p)) where
   ppr = pprBooleanFormulaNormal
 
-pprBooleanFormulaNormal :: (OutputableBndr a)
-                        => BooleanFormula a -> SDoc
+pprBooleanFormulaNormal :: OutputableBndrId p => BooleanFormula (GhcPass p) -> SDoc
 pprBooleanFormulaNormal = go
   where
-    go (Var x)    = pprPrefixOcc x
+    go (Var x)    = pprPrefixOcc (unLoc x)
     go (And xs)   = fsep $ punctuate comma (map (go . unLoc) xs)
     go (Or [])    = keyword $ text "FALSE"
     go (Or xs)    = fsep $ intersperse vbar (map (go . unLoc) xs)
-    go (Parens x) = parens (go $ unLoc x)
+    go (Parens x) = parens (go $ unLoc x)
\ No newline at end of file


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -36,6 +36,7 @@ import Language.Haskell.Syntax.Binds
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind )
 import {-# SOURCE #-} GHC.Hs.Pat  (pprLPat )
 
+import GHC.Data.BooleanFormula ( LBooleanFormula, pprBooleanFormulaNormal )
 import GHC.Types.Tickish
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
@@ -47,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.SourceText
 import GHC.Types.SrcLoc as SrcLoc
 import GHC.Types.Var
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.Name
 
 import GHC.Utils.Outputable
@@ -968,9 +968,8 @@ instance Outputable TcSpecPrag where
   ppr (SpecPrag var _ inl)
     = text (extractSpecPragName $ inl_src inl) <+> pprSpec var (text "") inl
 
-pprMinimalSig :: (OutputableBndr name)
-              => LBooleanFormula (GenLocated l name) -> SDoc
-pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
+pprMinimalSig :: OutputableBndrId p  => LBooleanFormula (GhcPass p) -> SDoc
+pprMinimalSig (L _ bf) = pprBooleanFormulaNormal bf
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -110,6 +110,7 @@ module GHC.Hs.Decls (
 import GHC.Prelude
 
 import Language.Haskell.Syntax.Decls
+import Language.Haskell.Syntax.Extension
 
 import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprUntypedSplice )
         -- Because Expr imports Decls via HsBracket
@@ -119,7 +120,7 @@ import GHC.Hs.Type
 import GHC.Hs.Doc
 import GHC.Types.Basic
 import GHC.Core.Coercion
-import Language.Haskell.Syntax.Extension
+
 import GHC.Hs.Extension
 import GHC.Parser.Annotation
 import GHC.Types.Name


=====================================
compiler/GHC/Hs/Instances.hs
=====================================
@@ -33,6 +33,8 @@ import GHC.Hs.Type
 import GHC.Hs.Pat
 import GHC.Hs.ImpExp
 import GHC.Parser.Annotation
+import GHC.Data.BooleanFormula (BooleanFormula(..))
+import Language.Haskell.Syntax.Extension (Anno)
 
 -- ---------------------------------------------------------------------
 -- Data derivations from GHC.Hs-----------------------------------------
@@ -590,3 +592,6 @@ deriving instance Data XXPatGhcTc
 deriving instance Data XViaStrategyPs
 
 -- ---------------------------------------------------------------------
+
+deriving instance (Typeable p, Data (Anno (IdGhcP p)), Data (IdGhcP p)) => Data (BooleanFormula (GhcPass p))
+---------------------------------------------------------------------
\ No newline at end of file


=====================================
compiler/GHC/Iface/Decl.hs
=====================================
@@ -13,7 +13,6 @@
 module GHC.Iface.Decl
    ( coAxiomToIfaceDecl
    , tyThingToIfaceDecl -- Converting things to their Iface equivalents
-   , toIfaceBooleanFormula
    )
 where
 
@@ -33,21 +32,17 @@ import GHC.Core.DataCon
 import GHC.Core.Type
 import GHC.Core.Multiplicity
 
-
 import GHC.Types.Id
 import GHC.Types.Var.Env
 import GHC.Types.Var
 import GHC.Types.Name
 import GHC.Types.Basic
 import GHC.Types.TyThing
-import GHC.Types.SrcLoc
 
 import GHC.Utils.Panic.Plain
 import GHC.Utils.Misc
 
 import GHC.Data.Maybe
-import GHC.Data.BooleanFormula
-
 import Data.List ( findIndex, mapAccumL )
 
 {-
@@ -287,7 +282,7 @@ classToIfaceDecl env clas
                 ifClassCtxt   = tidyToIfaceContext env1 sc_theta,
                 ifATs    = map toIfaceAT clas_ats,
                 ifSigs   = map toIfaceClassOp op_stuff,
-                ifMinDef = toIfaceBooleanFormula $ fmap (mkIfLclName . getOccFS) (classMinimalDef clas)
+                ifMinDef = toIfaceBooleanFormula (classMinimalDef clas)
             }
 
     (env1, tc_binders) = tidyTyConBinders env (tyConBinders tycon)
@@ -335,10 +330,3 @@ tidyTyConBinders = mapAccumL tidyTyConBinder
 
 tidyTyVar :: TidyEnv -> TyVar -> IfLclName
 tidyTyVar (_, subst) tv = toIfaceTyVar (lookupVarEnv subst tv `orElse` tv)
-
-toIfaceBooleanFormula :: BooleanFormula IfLclName -> IfaceBooleanFormula
-toIfaceBooleanFormula = \case
-    Var nm    -> IfVar    nm
-    And bfs   -> IfAnd    (map (toIfaceBooleanFormula . unLoc) bfs)
-    Or bfs    -> IfOr     (map (toIfaceBooleanFormula . unLoc) bfs)
-    Parens bf -> IfParens (toIfaceBooleanFormula . unLoc $ bf)


=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -2041,8 +2041,9 @@ instance ToHie PendingRnSplice where
 instance ToHie PendingTcSplice where
   toHie (PendingTcSplice _ e) = toHie e
 
-instance ToHie (LBooleanFormula (LocatedN Name)) where
-  toHie (L span form) = concatM $ makeNode form (locA span) : case form of
+instance (HiePass p, Data (IdGhcP p))
+  => ToHie (GenLocated SrcSpanAnnL (BooleanFormula (GhcPass p))) where
+    toHie (L span form) =  concatM $ makeNode form (locA span) : case form of
       Var a ->
         [ toHie $ C Use a
         ]


=====================================
compiler/GHC/Iface/Syntax.hs
=====================================
@@ -35,10 +35,8 @@ module GHC.Iface.Syntax (
         -- Misc
         ifaceDeclImplicitBndrs, visibleIfConDecls,
         ifaceDeclFingerprints,
-        fromIfaceBooleanFormula,
         fromIfaceWarnings,
         fromIfaceWarningTxt,
-
         -- Free Names
         freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst,
         freeNamesIfConDecls,
@@ -51,7 +49,10 @@ module GHC.Iface.Syntax (
 
 import GHC.Prelude
 
+import GHC.Builtin.Names(mkUnboundName)
 import GHC.Data.FastString
+import GHC.Data.BooleanFormula (pprBooleanFormula, isTrue)
+
 import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey,
                            constraintKindTyConKey )
 import GHC.Types.Unique ( hasKey )
@@ -62,9 +63,9 @@ import GHC.Types.Demand
 import GHC.Types.Cpr
 import GHC.Core.Class
 import GHC.Types.FieldLabel
-import GHC.Types.Name.Set
 import GHC.Core.Coercion.Axiom ( BranchIndex )
 import GHC.Types.Name
+import GHC.Types.Name.Set
 import GHC.Types.Name.Reader
 import GHC.Types.CostCentre
 import GHC.Types.Literal
@@ -75,7 +76,6 @@ import GHC.Unit.Module
 import GHC.Unit.Module.Warnings
 import GHC.Types.SrcLoc
 import GHC.Types.SourceText
-import GHC.Data.BooleanFormula ( BooleanFormula(..), pprBooleanFormula, isTrue )
 import GHC.Types.Var( VarBndr(..), binderVar, tyVarSpecToBinders, visArgTypeLike )
 import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag )
 import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..))
@@ -94,6 +94,8 @@ import GHC.Utils.Panic
 import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith,
                        seqList, zipWithEqual )
 
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
+
 import Control.Monad
 import System.IO.Unsafe
 import Control.DeepSeq
@@ -213,18 +215,14 @@ data IfaceClassBody
      ifMinDef    :: IfaceBooleanFormula       -- Minimal complete definition
     }
 
+-- See also 'BooleanFormula'
 data IfaceBooleanFormula
   = IfVar IfLclName
   | IfAnd [IfaceBooleanFormula]
   | IfOr [IfaceBooleanFormula]
   | IfParens IfaceBooleanFormula
+  deriving Eq
 
-fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula IfLclName
-fromIfaceBooleanFormula = \case
-    IfVar nm     -> Var    nm
-    IfAnd ibfs   -> And    (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfOr ibfs    -> Or     (map (noLocA . fromIfaceBooleanFormula) ibfs)
-    IfParens ibf -> Parens (noLocA . fromIfaceBooleanFormula $ ibf)
 
 data IfaceTyConParent
   = IfNoParent
@@ -1039,13 +1037,21 @@ pprIfaceDecl ss (IfaceClass { ifName  = clas
         | showSub ss sg = Just $  pprIfaceClassOp ss sg
         | otherwise     = Nothing
 
-      pprMinDef :: BooleanFormula IfLclName -> SDoc
+      pprMinDef :: BooleanFormula GhcRn -> SDoc
       pprMinDef minDef = ppUnless (isTrue minDef) $ -- hide empty definitions
         text "{-# MINIMAL" <+>
         pprBooleanFormula
-          (\_ def -> cparen (isLexSym def) (ppr def)) 0 (fmap ifLclNameFS minDef) <+>
+          (\_ def -> let fs = getOccFS def in cparen (isLexSym fs) (ppr fs)) 0 minDef <+>
         text "#-}"
 
+      fromIfaceBooleanFormula :: IfaceBooleanFormula -> BooleanFormula GhcRn
+      -- `mkUnboundName` here is fine because the Name generated is only used for pretty printing and nothing else.
+      fromIfaceBooleanFormula (IfVar nm   ) = Var    $ noLocA . mkUnboundName . mkVarOccFS . ifLclNameFS $ nm
+      fromIfaceBooleanFormula (IfAnd bfs  ) = And    $ map (noLocA . fromIfaceBooleanFormula) bfs
+      fromIfaceBooleanFormula (IfOr bfs   ) = Or     $ map (noLocA . fromIfaceBooleanFormula) bfs
+      fromIfaceBooleanFormula (IfParens bf) = Parens $     (noLocA . fromIfaceBooleanFormula) bf
+
+
       -- See Note [Suppressing binder signatures] in GHC.Iface.Type
       suppress_bndr_sig = SuppressBndrSig True
 


=====================================
compiler/GHC/IfaceToCore.hs
=====================================
@@ -32,6 +32,7 @@ module GHC.IfaceToCore (
         hydrateCgBreakInfo
  ) where
 
+
 import GHC.Prelude
 
 import GHC.ByteCode.Types
@@ -43,7 +44,6 @@ import GHC.Driver.Config.Core.Lint ( initLintConfig )
 import GHC.Builtin.Types.Literals(typeNatCoAxiomRules)
 import GHC.Builtin.Types
 
-import GHC.Iface.Decl (toIfaceBooleanFormula)
 import GHC.Iface.Syntax
 import GHC.Iface.Load
 import GHC.Iface.Env
@@ -123,20 +123,26 @@ import GHC.Types.Tickish
 import GHC.Types.TyThing
 import GHC.Types.Error
 
+import GHC.Parser.Annotation (noLocA)
+
+import GHC.Hs.Extension ( GhcRn )
+
 import GHC.Fingerprint
-import qualified GHC.Data.BooleanFormula as BF
 
 import Control.Monad
-import GHC.Parser.Annotation
 import GHC.Driver.Env.KnotVars
 import GHC.Unit.Module.WholeCoreBindings
 import Data.IORef
 import Data.Foldable
 import Data.Function ( on )
+import Data.List(nub)
 import Data.List.NonEmpty ( NonEmpty )
 import qualified Data.List.NonEmpty as NE
 import GHC.Builtin.Names (ioTyConName, rOOT_MAIN)
 import GHC.Iface.Errors.Types
+
+import Language.Haskell.Syntax.BooleanFormula (BooleanFormula)
+import Language.Haskell.Syntax.BooleanFormula qualified as BF(BooleanFormula(..))
 import Language.Haskell.Syntax.Extension (NoExtField (NoExtField))
 
 {-
@@ -297,14 +303,38 @@ mergeIfaceDecl d1 d2
                   plusNameEnv_C mergeIfaceClassOp
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops1 ])
                     (mkNameEnv [ (n, op) | op@(IfaceClassOp n _ _) <- ops2 ])
+
       in d1 { ifBody = (ifBody d1) {
                 ifSigs  = ops,
-                ifMinDef = toIfaceBooleanFormula . BF.mkOr . map (noLocA . fromIfaceBooleanFormula) $ [bf1, bf2]
+                ifMinDef = mkOr [ bf1, bf2]
                 }
             } `withRolesFrom` d2
     -- It doesn't matter; we'll check for consistency later when
     -- we merge, see 'mergeSignatures'
     | otherwise              = d1 `withRolesFrom` d2
+      where
+        -- The reason we need to duplicate mkOr here, instead of
+        -- using BooleanFormula's mkOr and just doing the loop like:
+        -- `toIfaceBooleanFormula . mkOr . fromIfaceBooleanFormula`
+        -- is quite subtle. Say we have the following minimal pragma:
+        -- {-# MINIMAL f | g #-}. If we use fromIfaceBooleanFormula
+        -- first, we will end up doing
+        -- `nub [Var (mkUnboundName f), Var (mkUnboundName g)]`,
+        -- which might seem fine, but Name equallity is decided by
+        -- their Unique, which will be identical since mkUnboundName
+        -- just stuffs the mkUnboundKey unqiue into both.
+        -- So the result will be {-# MINIMAL f #-}, oopsie.
+        -- Duplication it is.
+        mkOr :: [IfaceBooleanFormula] -> IfaceBooleanFormula
+        mkOr = maybe (IfAnd []) (mkOr' . nub . concat) . mapM fromOr
+          where
+          -- See Note [Simplification of BooleanFormulas]
+          fromOr bf = case bf of
+            (IfOr xs)  -> Just xs
+            (IfAnd []) -> Nothing
+            _        -> Just [bf]
+          mkOr' [x] = x
+          mkOr' xs = IfOr xs
 
 -- Note [Role merging]
 -- ~~~~~~~~~~~~~~~~~~~
@@ -795,8 +825,7 @@ tc_iface_decl _parent ignore_prags
     ; sigs <- mapM tc_sig rdr_sigs
     ; fds  <- mapM tc_fd rdr_fds
     ; traceIf (text "tc-iface-class3" <+> ppr tc_name)
-    ; let mindef_occ = fromIfaceBooleanFormula if_mindef
-    ; mindef <- traverse (lookupIfaceTop . mkVarOccFS . ifLclNameFS) mindef_occ
+    ; mindef <- tc_boolean_formula if_mindef
     ; cls  <- fixM $ \ cls -> do
               { ats  <- mapM (tc_at cls) rdr_ats
               ; traceIf (text "tc-iface-class4" <+> ppr tc_name)
@@ -845,6 +874,12 @@ tc_iface_decl _parent ignore_prags
                   -- e.g.   type AT a; type AT b = AT [b]   #8002
           return (ATI tc mb_def)
 
+   tc_boolean_formula :: IfaceBooleanFormula -> IfL (BooleanFormula GhcRn)
+   tc_boolean_formula (IfAnd ibfs  ) = BF.And    . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfOr ibfs   ) = BF.Or     . map noLocA <$> traverse tc_boolean_formula ibfs
+   tc_boolean_formula (IfParens ibf) = BF.Parens .     noLocA <$>          tc_boolean_formula ibf
+   tc_boolean_formula (IfVar nm    ) = BF.Var    .     noLocA <$> (lookupIfaceTop . mkVarOccFS . ifLclNameFS $ nm)
+
    mk_sc_doc pred = text "Superclass" <+> ppr pred
    mk_at_doc tc = text "Associated type" <+> ppr tc
    mk_op_doc op_name op_ty = text "Class op" <+> sep [ppr op_name, ppr op_ty]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -39,9 +39,9 @@ module GHC.Parser
 where
 
 -- base
-import Control.Monad    ( unless, liftM, when, (<=<) )
+import Control.Monad      ( unless, liftM, when, (<=<) )
 import GHC.Exts
-import Data.Maybe       ( maybeToList )
+import Data.Maybe         ( maybeToList )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import qualified Data.List.NonEmpty as NE
 import qualified Prelude -- for happy-generated code
@@ -3712,27 +3712,27 @@ overloaded_label :: { Located (SourceText, FastString) }
 -----------------------------------------------------------------------------
 -- Warnings and deprecations
 
-name_boolformula_opt :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_opt :: { LBooleanFormula GhcPs }
         : name_boolformula          { $1 }
         | {- empty -}               { noLocA mkTrue }
 
-name_boolformula :: { LBooleanFormula (LocatedN RdrName) }
-        : name_boolformula_and                      { $1 }
+name_boolformula :: { LBooleanFormula GhcPs }
+        : name_boolformula_and      { $1 }
         | name_boolformula_and '|' name_boolformula
                            {% do { h <- addTrailingVbarL $1 (epTok $2)
                                  ; return (sLLa $1 $> (Or [h,$3])) } }
 
-name_boolformula_and :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_and :: { LBooleanFormula GhcPs }
         : name_boolformula_and_list
                   { sLLa (head $1) (last $1) (And ($1)) }
 
-name_boolformula_and_list :: { [LBooleanFormula (LocatedN RdrName)] }
+name_boolformula_and_list :: { [LBooleanFormula GhcPs] }
         : name_boolformula_atom                               { [$1] }
         | name_boolformula_atom ',' name_boolformula_and_list
             {% do { h <- addTrailingCommaL $1 (epTok $2)
                   ; return (h : $3) } }
 
-name_boolformula_atom :: { LBooleanFormula (LocatedN RdrName) }
+name_boolformula_atom :: { LBooleanFormula GhcPs }
         : '(' name_boolformula ')'  {% amsr (sLL $1 $> (Parens $2))
                                       (AnnList Nothing (ListParens (epTok $1) (epTok $3)) [] noAnn []) }
         | name_var                  { sL1a $1 (Var $1) }
@@ -4706,4 +4706,4 @@ combineHasLocs a b = combineSrcSpans (getHasLoc a) (getHasLoc b)
 fromTrailingN :: SrcSpanAnnN -> SrcSpanAnnA
 fromTrailingN (EpAnn anc ann cs)
     = EpAnn anc (AnnListItem (nann_trailing ann)) cs
-}
+}
\ No newline at end of file


=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -80,6 +80,7 @@ import Control.Monad
 import Data.List          ( partition )
 import Data.List.NonEmpty ( NonEmpty(..) )
 import GHC.Types.Unique.DSet (mkUniqDSet)
+import GHC.Data.BooleanFormula (bfTraverse)
 
 {-
 -- ToDo: Put the annotations into the monad, so that they arrive in the proper
@@ -1137,7 +1138,7 @@ renameSig ctxt (FixSig _ fsig)
         ; return (FixSig noAnn new_fsig, emptyFVs) }
 
 renameSig ctxt sig@(MinimalSig (_, s) (L l bf))
-  = do new_bf <- traverse (lookupSigOccRnN ctxt sig) bf
+  = do new_bf <- bfTraverse (lookupSigOccRnN ctxt sig) bf
        return (MinimalSig (noAnn, s) (L l new_bf), emptyFVs)
 
 renameSig ctxt sig@(PatSynSig _ vs ty)


=====================================
compiler/GHC/Tc/TyCl/Class.hs
=====================================
@@ -344,7 +344,7 @@ tcClassMinimalDef _clas sigs op_info
   where
     -- By default require all methods without a default implementation
     defMindef :: ClassMinimalDef
-    defMindef = mkAnd [ noLocA (mkVar name)
+    defMindef = mkAnd [ noLocA (mkVar (noLocA name))
                       | (name, _, Nothing) <- op_info ]
 
 instantiateMethod :: Class -> TcId -> [TcType] -> TcType
@@ -402,8 +402,8 @@ findMinimalDef :: [LSig GhcRn] -> Maybe ClassMinimalDef
 findMinimalDef = firstJusts . map toMinimalDef
   where
     toMinimalDef :: LSig GhcRn -> Maybe ClassMinimalDef
-    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just (fmap unLoc bf)
-    toMinimalDef _                               = Nothing
+    toMinimalDef (L _ (MinimalSig _ (L _ bf))) = Just bf
+    toMinimalDef _                             = Nothing
 
 {-
 Note [Polymorphic methods]
@@ -603,4 +603,4 @@ warnMissingAT name
                   $ InvalidAssoc $ InvalidAssocInstance
                   $ AssocInstanceMissing name
        ; diagnosticTc  (warn && hsc_src == HsSrcFile) diag
-                       }
+                       }
\ No newline at end of file


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -1889,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
         --
         -- See Note [Implementation of Unsatisfiable constraints] in GHC.Tc.Errors,
         -- point (D).
-        whenIsJust (isUnsatisfied methodExists (classMinimalDef clas)) $
+        whenIsJust (isUnsatisfied (methodExists . unLoc) (classMinimalDef clas)) $
         warnUnsatisfiedMinimalDefinition
 
     methodExists meth = isJust (findMethodBind meth binds prag_fn)


=====================================
compiler/Language/Haskell/Syntax/Binds.hs
=====================================
@@ -26,15 +26,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr
   ( LHsExpr
   , MatchGroup
   , GRHSs )
-import {-# SOURCE #-} Language.Haskell.Syntax.Pat
-  ( LPat )
-
+import {-# SOURCE #-} Language.Haskell.Syntax.Pat( LPat )
+import Language.Haskell.Syntax.BooleanFormula (LBooleanFormula)
 import Language.Haskell.Syntax.Extension
 import Language.Haskell.Syntax.Type
 import Language.Haskell.Syntax.Basic ( Fixity )
 
 import GHC.Types.Basic (InlinePragma)
-import GHC.Data.BooleanFormula (LBooleanFormula)
 import GHC.Types.SourceText (StringLiteral)
 
 import Data.Void
@@ -379,7 +377,7 @@ data Sig pass
         -- | A minimal complete definition pragma
         --
         -- > {-# MINIMAL a | (b, c | (d | e)) #-}
-  | MinimalSig (XMinimalSig pass) (LBooleanFormula (LIdP pass))
+  | MinimalSig (XMinimalSig pass) (LBooleanFormula pass)
 
         -- | A "set cost centre" pragma for declarations
         --


=====================================
compiler/Language/Haskell/Syntax/BooleanFormula.hs
=====================================
@@ -0,0 +1,62 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+
+module Language.Haskell.Syntax.BooleanFormula(
+  BooleanFormula(..), LBooleanFormula,
+  mkVar, mkFalse, mkTrue, mkBool, mkAnd, mkOr
+  ) where
+
+import Prelude hiding ( init, last )
+import Data.List ( nub )
+import Language.Haskell.Syntax.Extension (XRec, UnXRec (..), LIdP)
+
+
+-- types
+type LBooleanFormula p = XRec p (BooleanFormula p)
+data BooleanFormula p = Var (LIdP p) | And [LBooleanFormula p] | Or [LBooleanFormula p]
+                      | Parens (LBooleanFormula p)
+
+-- instances
+deriving instance (Eq (LIdP p), Eq (LBooleanFormula p)) => Eq (BooleanFormula p)
+
+-- smart constructors
+-- see note [Simplification of BooleanFormulas]
+mkVar :: LIdP p -> BooleanFormula p
+mkVar = Var
+
+mkFalse, mkTrue :: BooleanFormula p
+mkFalse = Or []
+mkTrue = And []
+
+-- Convert a Bool to a BooleanFormula
+mkBool :: Bool -> BooleanFormula p
+mkBool False = mkFalse
+mkBool True  = mkTrue
+
+-- Make a conjunction, and try to simplify
+mkAnd :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkAnd = maybe mkFalse (mkAnd' . nub . concat) . mapM fromAnd
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromAnd :: LBooleanFormula p -> Maybe [LBooleanFormula p]
+  fromAnd bf = case unXRec @p bf of
+    (And xs) -> Just xs
+     -- assume that xs are already simplified
+     -- otherwise we would need: fromAnd (And xs) = concat <$> traverse fromAnd xs
+    (Or [])  -> Nothing
+     -- in case of False we bail out, And [..,mkFalse,..] == mkFalse
+    _        -> Just [bf]
+  mkAnd' [x] = unXRec @p x
+  mkAnd' xs = And xs
+
+mkOr :: forall p. (UnXRec p, Eq (LIdP p), Eq (LBooleanFormula p)) => [LBooleanFormula p] -> BooleanFormula p
+mkOr = maybe mkTrue (mkOr' . nub . concat) . mapM fromOr
+  where
+  -- See Note [Simplification of BooleanFormulas]
+  fromOr bf = case unXRec @p bf of
+    (Or xs)  -> Just xs
+    (And []) -> Nothing
+    _        -> Just [bf]
+  mkOr' [x] = unXRec @p x
+  mkOr' xs = Or xs


=====================================
compiler/ghc.cabal.in
=====================================
@@ -991,6 +991,7 @@ Library
         Language.Haskell.Syntax
         Language.Haskell.Syntax.Basic
         Language.Haskell.Syntax.Binds
+        Language.Haskell.Syntax.BooleanFormula
         Language.Haskell.Syntax.Decls
         Language.Haskell.Syntax.Expr
         Language.Haskell.Syntax.Extension


=====================================
libraries/text
=====================================
@@ -1 +1 @@
-Subproject commit ee0a8f8b9a4bd3fdad23e9ac0db56e7f08ce35cd
+Subproject commit cdb9e13b39079904eed9d75cd332b66ee0cad0c0


=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -234,6 +234,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -258,6 +258,7 @@ GHC.Utils.Word64
 Language.Haskell.Syntax
 Language.Haskell.Syntax.Basic
 Language.Haskell.Syntax.Binds
+Language.Haskell.Syntax.BooleanFormula
 Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -2817,7 +2817,7 @@ instance ExactPrint (AnnDecl GhcPs) where
 
 -- ---------------------------------------------------------------------
 
-instance ExactPrint (BF.BooleanFormula (LocatedN RdrName)) where
+instance ExactPrint (BF.BooleanFormula GhcPs) where
   getAnnotationEntry = const NoEntryVal
   setAnnotationAnchor a _ _ _ = a
 
@@ -4537,7 +4537,7 @@ instance ExactPrint (LocatedL [LocatedA (ConDeclField GhcPs)]) where
     (an', fs') <- markAnnList an (markAnnotated fs)
     return (L an' fs')
 
-instance ExactPrint (LocatedL (BF.BooleanFormula (LocatedN RdrName))) where
+instance ExactPrint (LocatedL (BF.BooleanFormula GhcPs)) where
   getAnnotationEntry = entryFromLocatedA
   setAnnotationAnchor = setAnchorAn
   exact (L an bf) = do


=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -45,6 +45,7 @@ import GHC.Builtin.Types
   , promotedNilDataCon
   , unitTy
   )
+
 import GHC.Builtin.Types.Prim (alphaTyVars)
 import GHC.Core.Class
 import GHC.Core.Coercion.Axiom
@@ -176,7 +177,7 @@ tyThingToLHsDecl prr t = case t of
                       $ snd
                       $ classTvsFds cl
                 , tcdSigs =
-                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA . fmap noLocA $ classMinimalDef cl)
+                    noLocA (MinimalSig (noAnn, NoSourceText) . noLocA $ classMinimalDef cl)
                       : [ noLocA tcdSig
                         | clsOp <- classOpItems cl
                         , tcdSig <- synifyTcIdSig vs clsOp


=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -19,6 +19,8 @@
 -- Portability :  portable
 module Haddock.Interface.Rename (renameInterface) where
 
+import Prelude hiding (mapM)
+
 import Control.Applicative ()
 import Control.DeepSeq (force)
 import Control.Monad hiding (mapM)
@@ -28,12 +30,13 @@ import Data.Foldable (traverse_)
 import qualified Data.Map.Strict as Map
 import qualified Data.Set as Set
 import Data.Traversable (mapM)
+
 import GHC hiding (NoLink)
 import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName)
 import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
 import GHC.Types.Name
 import GHC.Types.Name.Reader (RdrName (Exact))
-import Prelude hiding (mapM)
+import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
 
 import Haddock.Backends.Hoogle (ppExportD)
 import Haddock.GhcUtils
@@ -770,11 +773,22 @@ renameSig sig = case sig of
     lnames' <- mapM renameNameL lnames
     return $ FixSig noExtField (FixitySig noExtField lnames' fixity)
   MinimalSig _ (L l s) -> do
-    s' <- traverse (traverse lookupRn) s
+    s' <- bfTraverse (traverse lookupRn) s
     return $ MinimalSig noExtField (L l s')
   -- we have filtered out all other kinds of signatures in Interface.Create
   _ -> error "expected TypeSig"
 
+bfTraverse  :: Applicative f
+            => (LIdP (GhcPass p) -> f (LIdP DocNameI))
+            -> BooleanFormula (GhcPass p)
+            -> f (BooleanFormula DocNameI)
+bfTraverse f = go
+  where
+    go (Var    a  ) = Var    <$> f a
+    go (And    bfs) = And    <$> traverse @[] (traverse go) bfs
+    go (Or     bfs) = Or     <$> traverse @[] (traverse go) bfs
+    go (Parens bf ) = Parens <$> traverse go bf
+
 renameForD :: ForeignDecl GhcRn -> RnM (ForeignDecl DocNameI)
 renameForD (ForeignImport _ lname ltype x) = do
   lname' <- renameNameL lname


=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -53,6 +53,7 @@ import qualified Data.Map as Map
 import qualified Data.Set as Set
 import GHC
 import qualified GHC.Data.Strict as Strict
+import GHC.Data.BooleanFormula (BooleanFormula)
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
@@ -819,6 +820,7 @@ type instance Anno (HsDecl DocNameI) = SrcSpanAnnA
 type instance Anno (FamilyResultSig DocNameI) = EpAnn NoEpAnns
 type instance Anno (HsOuterTyVarBndrs Specificity DocNameI) = SrcSpanAnnA
 type instance Anno (HsSigType DocNameI) = SrcSpanAnnA
+type instance Anno (BooleanFormula DocNameI) = SrcSpanAnnL
 
 type XRecCond a =
   ( XParTy a ~ (EpToken "(", EpToken ")")



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 17:43:30 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 29 Oct 2024 13:43:30 -0400
Subject: [Git][ghc/ghc][wip/T20264] Progress
Message-ID: <67211ec252eb_249fdb19c1ac26698@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
151ac275 by Simon Peyton Jones at 2024-10-29T17:43:02+00:00
Progress

- - - - -


19 changed files:

- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Seq.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Id/Info.hs
- compiler/GHC/Types/Var.hs


Changes:

=====================================
compiler/GHC/Core/FVs.hs
=====================================
@@ -32,7 +32,7 @@ module GHC.Core.FVs (
         idFVs,
         idRuleVars, stableUnfoldingVars,
         ruleFreeVars, rulesFreeVars,
-        rulesFreeVarsDSet, mkRuleInfo,
+        mkRuleInfo,
         ruleLhsFreeIds, ruleLhsFreeIdsList,
         ruleRhsFreeVars, rulesRhsFreeIds,
 
@@ -472,11 +472,6 @@ ruleLhsFreeIdsList = fvVarList . filterFV isLocalId . ruleFVs LhsOnly
 ruleFreeVars :: CoreRule -> VarSet
 ruleFreeVars = fvVarSet . ruleFVs BothSides
 
--- | Those variables free in the both the left right hand sides of rules
--- returned as a deterministic set
-rulesFreeVarsDSet :: [CoreRule] -> DVarSet
-rulesFreeVarsDSet rules = fvDVarSet $ rulesFVs BothSides rules
-
 -- | Those variables free in both the left right hand sides of several rules
 rulesFreeVars :: [CoreRule] -> VarSet
 rulesFreeVars rules = fvVarSet $ rulesFVs BothSides rules
@@ -484,7 +479,7 @@ rulesFreeVars rules = fvVarSet $ rulesFVs BothSides rules
 -- | Make a 'RuleInfo' containing a number of 'CoreRule's, suitable
 -- for putting into an 'IdInfo'
 mkRuleInfo :: [CoreRule] -> RuleInfo
-mkRuleInfo rules = RuleInfo rules (rulesFreeVarsDSet rules)
+mkRuleInfo rules = RuleInfo rules
 
 {-
 Note [Rule free var hack]  (Not a hack any more)
@@ -632,7 +627,9 @@ idRuleVars id = fvVarSet $ idRuleFVs id
 
 idRuleFVs :: Id -> FV
 idRuleFVs id = assert (isId id) $
-  FV.mkFVs (dVarSetElems $ ruleInfoFreeVars (idSpecialisation id))
+               rulesFVs BothSides $
+               ruleInfoRules (idSpecialisation id)
+  -- BothSides: see Note [Rule dependency info] in OccurAnal
 
 idUnfoldingVars :: Id -> VarSet
 -- Produce free vars for an unfolding, but NOT for an ordinary


=====================================
compiler/GHC/Core/Make.hs
=====================================
@@ -8,7 +8,7 @@ module GHC.Core.Make (
         mkCoreLams, mkWildCase, mkIfThenElse,
         mkWildValBinder,
         mkSingleAltCase,
-        sortQuantVars, castBottomExpr,
+        castBottomExpr,
 
         -- * Constructing boxed literals
         mkLitRubbish,
@@ -69,7 +69,6 @@ import GHC.Core.Utils ( exprType, mkSingleAltCase, bindNonRec )
 import GHC.Core.Type
 import GHC.Core.Predicate    ( isCoVarType )
 import GHC.Core.TyCo.Compare ( eqType )
-import GHC.Core.Coercion     ( isCoVar )
 import GHC.Core.DataCon      ( DataCon, dataConWorkId )
 import GHC.Core.Multiplicity
 
@@ -84,7 +83,6 @@ import GHC.Utils.Panic
 import GHC.Settings.Constants( mAX_TUPLE_SIZE )
 import GHC.Data.FastString
 
-import Data.List        ( partition )
 import Data.Char        ( ord )
 
 infixl 4 `mkCoreApp`, `mkCoreApps`
@@ -99,15 +97,6 @@ infixl 4 `mkCoreApp`, `mkCoreApps`
 -- | Sort the variables, putting type and covars first, in scoped order,
 -- and then other Ids
 --
--- It is a deterministic sort, meaning it doesn't look at the values of
--- Uniques. For explanation why it's important See Note [Unique Determinism]
--- in GHC.Types.Unique.
-sortQuantVars :: [Var] -> [Var]
-sortQuantVars vs = sorted_tcvs ++ ids
-  where
-    (tcvs, ids) = partition (isTyVar <||> isCoVar) vs
-    sorted_tcvs = scopedSort tcvs
-
 -- | Bind a binding group over an expression, using a @let@ or @case@ as
 -- appropriate (see "GHC.Core#let_can_float_invariant")
 mkCoreLet :: CoreBind -> CoreExpr -> CoreExpr


=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -1716,8 +1716,8 @@ makeNode !env _imp_rule_edges bndr_set (bndr, rhs@(Type rhs_ty))
 
     rhs_env = setNonTailCtxt OccRhs env
     -- WUD unf_uds mb_unf'
-    --   | Just unf <- tyVarUnfolding bndr = Just <$> occAnalTy rhs_env unf
-    --   | otherwise                       = WUD emptyUDs Nothing
+    --   | Just unf <- tyVarUnfolding_maybe bndr = Just <$> occAnalTy rhs_env unf
+    --   | otherwise                             = WUD emptyUDs Nothing
     rhs_uds = occAnalTy rhs_env rhs_ty
 
     inl_uds   = rhs_uds -- `andUDs` unf_uds


=====================================
compiler/GHC/Core/Opt/SetLevels.hs
=====================================
@@ -89,13 +89,11 @@ import GHC.Core
 import GHC.Core.Opt.Monad ( FloatOutSwitches(..) )
 import GHC.Core.Utils
 import GHC.Core.Opt.Arity   ( exprBotStrictness_maybe, isOneShotBndr )
+import GHC.Core.TyCo.FVs    ( tyCoVarsOfTypeDSet, scopedSort )
+import GHC.Core.TyCo.Subst  ( substTy, mkTvSubstPrs )
 import GHC.Core.FVs     -- all of it
 import GHC.Core.Subst
-import GHC.Core.Make    ( sortQuantVars )
-import GHC.Core.Type    ( Type, tyCoVarsOfType
-                        , mightBeUnliftedType, closeOverKindsDSet
-                        , typeHasFixedRuntimeRep
-                        )
+import GHC.Core.Type    ( Type, tyCoVarsOfType, mightBeUnliftedType, typeHasFixedRuntimeRep )
 import GHC.Core.Multiplicity     ( pattern ManyTy )
 
 import GHC.Types.Id
@@ -127,6 +125,7 @@ import GHC.Utils.Outputable
 import GHC.Utils.Panic
 
 import Data.Maybe
+import Data.List        ( partition )
 
 {-
 ************************************************************************
@@ -638,7 +637,7 @@ lvlMFE env strict_ctxt ann_expr
        ; var <- newLvlVar expr1 NotJoinPoint is_mk_static
        ; let var2 = annotateBotStr var float_n_lams mb_bot_str
        ; return (Let (NonRec (TB var2 (FloatMe dest_lvl)) expr1)
-                     (mkVarApps (Var var2) abs_vars)) }
+                     (mkAbsVarApps (Var var2) abs_vars)) }
 
   -- OK, so the float has an unlifted type (not top-level bindable)
   --     and no new value lambdas (float_is_new_lam is False)
@@ -652,13 +651,13 @@ lvlMFE env strict_ctxt ann_expr
   , let [bx_bndr, ubx_bndr] = mkTemplateLocals [box_ty, expr_ty]
   = do { expr1 <- lvlExpr rhs_env ann_expr
        ; let l1r       = incMinorLvlFrom rhs_env
-             float_rhs = mkLams abs_vars_w_lvls $
+             float_rhs = mkAbsLams abs_vars_w_lvls $
                          Case expr1 (stayPut l1r ubx_bndr) box_ty
                              [Alt DEFAULT [] (App boxing_expr (Var ubx_bndr))]
 
        ; var <- newLvlVar float_rhs NotJoinPoint is_mk_static
        ; let l1u      = incMinorLvlFrom env
-             use_expr = Case (mkVarApps (Var var) abs_vars)
+             use_expr = Case (mkAbsVarApps (Var var) abs_vars)
                              (stayPut l1u bx_bndr) expr_ty
                              [Alt (DataAlt box_dc) [stayPut l1u ubx_bndr] (Var ubx_bndr)]
        ; return (Let (NonRec (TB var (FloatMe dest_lvl)) float_rhs)
@@ -1309,7 +1308,7 @@ lvlBind env (AnnRec pairs)
     new_rhs_body <- lvlRhs body_env2 Recursive is_bot NotJoinPoint rhs_body
     (poly_env, [poly_bndr]) <- newPolyBndrs dest_lvl env abs_vars [bndr]
     return (Rec [(TB poly_bndr (FloatMe dest_lvl)
-                 , mkLams abs_vars_w_lvls $
+                 , mkAbsLams abs_vars_w_lvls $
                    mkLams lam_bndrs2 $
                    Let (Rec [( TB new_bndr (StayPut rhs_lvl)
                              , mkLams lam_bndrs2 new_rhs_body)])
@@ -1399,7 +1398,7 @@ lvlRhs env rec_flag is_bot mb_join_arity expr
   = lvlFloatRhs [] (le_ctxt_lvl env) env
                 rec_flag is_bot mb_join_arity expr
 
-lvlFloatRhs :: [OutVar] -> Level -> LevelEnv -> RecFlag
+lvlFloatRhs :: AbsVars -> Level -> LevelEnv -> RecFlag
             -> Bool   -- Binding is for a bottoming function
             -> JoinPointHood
             -> CoreExprWithFVs
@@ -1410,7 +1409,7 @@ lvlFloatRhs abs_vars dest_lvl env rec is_bot mb_join_arity rhs
                      && any isId bndrs
                   then lvlMFE  body_env True body
                   else lvlExpr body_env      body
-       ; return (mkLams bndrs' body') }
+       ; return (mkAbsLams bndrs' body') }
   where
     (bndrs, body)     | JoinPoint join_arity <- mb_join_arity
                       = collectNAnnBndrs join_arity rhs
@@ -1754,24 +1753,68 @@ lookupVar le v = case lookupVarEnv (le_env le) v of
                     Just (_, expr) -> expr
                     _              -> Var v
 
-abstractVars :: Level -> LevelEnv -> DVarSet -> [OutVar]
-        -- Find the variables in fvs, free vars of the target expression,
-        -- whose level is greater than the destination level
-        -- These are the ones we are going to abstract out
-        --
-        -- Note that to get reproducible builds, the variables need to be
-        -- abstracted in deterministic order, not dependent on the values of
-        -- Uniques. This is achieved by using DVarSets, deterministic free
-        -- variable computation and deterministic sort.
-        -- See Note [Unique Determinism] in GHC.Types.Unique for explanation of why
-        -- Uniques are not deterministic.
+type AbsVars = [Var]
+  -- A list of variables to abstract, in the correct dependency order
+  -- May include type variables with unfoldings:
+  --    when abstracting, use a let
+  --    when applying, ignore
+  -- E.g   [a, b=[a], x:a]
+  -- We might make
+  --    f = /\a let @b=[a] in  \(x:a). blah
+  -- and at an application site say
+  --    f @ty arg
+
+mkAbsLams :: [LevelledBndr]  -> Expr LevelledBndr -> Expr LevelledBndr
+mkAbsLams [] body = body
+mkAbsLams (bndr@(TB v _) : bndrs) body
+  | Just ty <- tyVarUnfolding_maybe v
+  = Let (NonRec bndr (Type ty)) (mkAbsLams bndrs body)
+  | otherwise
+  = Lam bndr (mkAbsLams bndrs body)
+
+mkAbsLamTypes :: AbsVars -> Type -> Type
+mkAbsLamTypes abs_vars ty
+  = pprTrace "mkAbsLamTypes" (
+      vcat [ text "abs_vars" <+> ppr abs_vars
+           , text "abs_lam_vars" <+> ppr abs_lam_vars
+           , text "tv_unf_prs" <+> ppr tv_unf_prs
+           , text "ty" <+> ppr ty
+           , text "mkLam" <+> ppr (mkLamTypes abs_lam_vars ty)
+           , text "res" <+> ppr res ]) res
+    -- We can apply the subst at the end there is no shadowing in abs_vars
+  where
+    res = substTy subst (mkLamTypes abs_lam_vars ty)
+    abs_lam_vars   = [ v       | v <- abs_vars, isNothing (tyVarUnfolding_maybe v) ]
+    tv_unf_prs = [ (tv,ty) | tv <- abs_vars, Just ty <- [tyVarUnfolding_maybe tv] ]
+    subst = mkTvSubstPrs tv_unf_prs
+
+
+mkAbsVarApps :: Expr LevelledBndr -> AbsVars -> Expr LevelledBndr
+mkAbsVarApps fun [] = fun
+mkAbsVarApps fun (a:as)
+  | Just {} <- tyVarUnfolding_maybe a = mkAbsVarApps fun                         as
+  | otherwise                         = mkAbsVarApps (App fun (varToCoreExpr a)) as
+
+abstractVars :: Level -> LevelEnv -> DVarSet -> AbsVars
+-- Find the variables in fvs, free vars of the target expression,
+-- whose level is greater than the destination level
+-- These are the ones we are going to abstract out
+--
+-- Note that to get reproducible builds, the variables need to be
+-- abstracted in deterministic order, not dependent on the values of
+-- Uniques. This is achieved by using DVarSets, deterministic free
+-- variable computation and deterministic sort.
+-- See Note [Unique Determinism] in GHC.Types.Unique for explanation of why
+-- Uniques are not deterministic.
 abstractVars dest_lvl (LE { le_subst = subst, le_lvl_env = lvl_env }) in_fvs
   =  -- NB: sortQuantVars might not put duplicates next to each other
-    map zap $ sortQuantVars $
+    map zap                 $
+    dep_anal                $
     filter abstract_me      $
     dVarSetElems            $
-    closeOverKindsDSet      $
-    substDVarSet subst in_fvs
+    mapUnionDVarSet close   $
+    substFreeVars subst     $
+    dVarSetElems in_fvs
         -- NB: it's important to call abstract_me only on the OutIds the
         -- come from substDVarSet (not on fv, which is an InId)
   where
@@ -1779,44 +1822,59 @@ abstractVars dest_lvl (LE { le_subst = subst, le_lvl_env = lvl_env }) in_fvs
                         Just lvl -> dest_lvl `ltLvl` lvl
                         Nothing  -> False
 
-        -- We are going to lambda-abstract, so nuke any IdInfo,
-        -- and add the tyvars of the Id (if necessary)
-    zap v | isId v = warnPprTrace (isStableUnfolding (idUnfolding v) ||
-                           not (isEmptyRuleInfo (idSpecialisation v)))
-                           "absVarsOf: discarding info on" (ppr v) $
-                     setIdInfo v vanillaIdInfo
+
+    zap :: Var -> Var
+    -- zap: We are going to lambda-abstract, so nuke any IdInfo
+    -- But leave TyVar unfoldings alone
+    zap v | isId v    = setIdInfo v vanillaIdInfo
           | otherwise = v
 
+    close_set :: DVarSet -> DVarSet
+    close_set s = mapUnionDVarSet close (dVarSetElems s)
+
+    close :: Var -> DVarSet
+    close v | Just ty <- tyVarUnfolding_maybe v
+            = close_set (tyCoVarsOfTypeDSet ty) `extendDVarSet` v
+            | otherwise
+            = close_set (tyCoVarsOfTypeDSet (varType v)) `extendDVarSet` v
+
+    dep_anal vs = scopedSort tcvs ++ ids
+      where
+         (tcvs, ids) = partition (isTyVar <||> isCoVar) vs
+      -- NB: scopedSort is a deterministic sort, meaning it doesn't look at the values
+      -- of Uniques. For explanation why it's important See Note [Unique Determinism]
+      -- in GHC.Types.Unique.
+
+-----------------------------------------
 type LvlM result = UniqSM result
 
 initLvl :: UniqSupply -> UniqSM a -> a
 initLvl = initUs_
 
-newPolyBndrs :: Level -> LevelEnv -> [OutVar] -> [InId]
+newPolyBndrs :: Level -> LevelEnv -> AbsVars -> [InId]
              -> LvlM (LevelEnv, [OutId])
 -- The envt is extended to bind the new bndrs to dest_lvl, but
 -- the le_ctxt_lvl is unaffected
 newPolyBndrs dest_lvl
              env@(LE { le_lvl_env = lvl_env, le_subst = subst, le_env = id_env })
              abs_vars bndrs
- = assert (all (not . isCoVar) bndrs) $   -- What would we add to the CoSubst in this case. No easy answer.
+ = assert (all (\b -> not (isCoVar b || isTyVar b)) bndrs) $   -- What would we add to the CoSubst in this case. No easy answer.
    do { uniqs <- getUniquesM
       ; let new_bndrs = zipWith mk_poly_bndr bndrs uniqs
             bndr_prs  = bndrs `zip` new_bndrs
             env' = env { le_lvl_env = addLvls dest_lvl lvl_env new_bndrs
-                       , le_subst   = foldl' add_subst subst   bndr_prs
                        , le_env     = foldl' add_id    id_env  bndr_prs }
       ; return (env', new_bndrs) }
   where
-    add_subst env (v, v') = extendIdSubst env v (mkVarApps (Var v') abs_vars)
-    add_id    env (v, v') = extendVarEnv env v ((v':abs_vars), mkVarApps (Var v') abs_vars)
+    add_id env (v, v') = extendVarEnv env v ((v':abs_vars), mkAbsVarApps (Var v') abs_vars)
 
     mk_poly_bndr bndr uniq = transferPolyIdInfo bndr abs_vars $ -- Note [transferPolyIdInfo] in GHC.Types.Id
                              transfer_join_info bndr $
                              mkSysLocal str uniq (idMult bndr) poly_ty
                            where
                              str     = fsLit "poly_" `appendFS` occNameFS (getOccName bndr)
-                             poly_ty = mkLamTypes abs_vars (substTyUnchecked subst (idType bndr))
+                             poly_ty = mkAbsLamTypes abs_vars            $
+                                       substTyUnchecked subst (idType bndr)
 
     -- If we are floating a join point to top level, it stops being
     -- a join point.  Otherwise it continues to be a join point,


=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -1185,7 +1185,7 @@ specVar env@(SE { se_subst = Core.Subst in_scope ids _ _ }) v
   --           probably has little effect, but it's the right thing.
   --           We need zapSubst because `e` is an OutExpr
 
-specExpr :: SpecEnv -> CoreExpr -> SpecM (CoreExpr, UsageDetails)
+specExpr, specExpr' :: SpecEnv -> CoreExpr -> SpecM (CoreExpr, UsageDetails)
 
 ---------------- First the easy cases --------------------
 specExpr env e = -- pprTrace "specExpr" (ppr e) $


=====================================
compiler/GHC/Core/Rules.hs
=====================================
@@ -49,7 +49,7 @@ import GHC.Core         -- All of it
 import GHC.Core.Subst
 import GHC.Core.SimpleOpt ( exprIsLambda_maybe )
 import GHC.Core.FVs       ( exprFreeVars, bindFreeVars
-                          , rulesFreeVarsDSet, orphNamesOfExprs )
+                          , orphNamesOfExprs )
 import GHC.Core.Utils     ( exprType, mkTick, mkTicks
                           , stripTicksTopT, stripTicksTopE
                           , isJoinBind, mkCastMCo )
@@ -336,12 +336,10 @@ pprRulesForUser rules
 -}
 
 extendRuleInfo :: RuleInfo -> [CoreRule] -> RuleInfo
-extendRuleInfo (RuleInfo rs1 fvs1) rs2
-  = RuleInfo (rs2 ++ rs1) (rulesFreeVarsDSet rs2 `unionDVarSet` fvs1)
+extendRuleInfo (RuleInfo rs1) rs2 = RuleInfo (rs2 ++ rs1)
 
 addRuleInfo :: RuleInfo -> RuleInfo -> RuleInfo
-addRuleInfo (RuleInfo rs1 fvs1) (RuleInfo rs2 fvs2)
-  = RuleInfo (rs1 ++ rs2) (fvs1 `unionDVarSet` fvs2)
+addRuleInfo (RuleInfo rs1) (RuleInfo rs2) = RuleInfo (rs1 ++ rs2)
 
 addIdSpecialisations :: Id -> [CoreRule] -> Id
 addIdSpecialisations id rules


=====================================
compiler/GHC/Core/Seq.hs
=====================================
@@ -45,7 +45,7 @@ seqOneShot :: OneShotInfo -> ()
 seqOneShot l = l `seq` ()
 
 seqRuleInfo :: RuleInfo -> ()
-seqRuleInfo (RuleInfo rules fvs) = seqRules rules `seq` seqDVarSet fvs
+seqRuleInfo (RuleInfo rules) = seqRules rules
 
 seqCaf :: CafInfo -> ()
 seqCaf c = c `seq` ()


=====================================
compiler/GHC/Core/Subst.hs
=====================================
@@ -16,7 +16,7 @@ module GHC.Core.Subst (
         substTyUnchecked, substCo, substExpr, substExprSC, substBind, substBindSC,
         substUnfolding, substUnfoldingSC,
         lookupIdSubst, lookupIdSubst_maybe, substIdType, substIdOcc,
-        substTickish, substDVarSet, substIdInfo,
+        substTickish, substFreeVars, substIdInfo,
 
         -- ** Operations on substitutions
         emptySubst, mkEmptySubst, mkTCvSubst, mkOpenSubst, isEmptySubst,
@@ -524,9 +524,8 @@ substIdOcc subst v = case lookupIdSubst subst v of
 ------------------
 -- | Substitutes for the 'Id's within the 'RuleInfo' given the new function 'Id'
 substRuleInfo :: Subst -> Id -> RuleInfo -> RuleInfo
-substRuleInfo subst new_id (RuleInfo rules rhs_fvs)
+substRuleInfo subst new_id (RuleInfo rules)
   = RuleInfo (map (substRule subst subst_ru_fn) rules)
-                  (substDVarSet subst rhs_fvs)
   where
     subst_ru_fn = const (idName new_id)
 
@@ -562,9 +561,9 @@ substRule subst subst_ru_fn rule@(Rule { ru_bndrs = bndrs, ru_args = args
     (subst', bndrs') = substBndrs subst bndrs
 
 ------------------
-substDVarSet :: HasDebugCallStack => Subst -> DVarSet -> DVarSet
-substDVarSet subst@(Subst _ _ tv_env cv_env) fvs
-  = mkDVarSet $ fst $ foldr subst_fv ([], emptyVarSet) $ dVarSetElems fvs
+substFreeVars :: HasDebugCallStack => Subst -> [Var] -> [Var]
+substFreeVars subst@(Subst _ _ tv_env cv_env) fvs
+  = fst $ foldr subst_fv ([], emptyVarSet) $ fvs
   where
   subst_fv :: Var -> ([Var], VarSet) -> ([Var], VarSet)
   subst_fv fv acc


=====================================
compiler/GHC/Core/Tidy.hs
=====================================
@@ -331,7 +331,7 @@ tidyLetBndr rec_tidy_env env@(tidy_env, var_env) tv
     let
         ki'      = tidyType env (tyVarKind tv)
         name'    = mkInternalName (varUnique tv) occ' noSrcSpan
-        mb_unf   = tyVarUnfolding tv
+        mb_unf   = tyVarUnfolding_maybe tv
         occ_info = tyVarOccInfo tv
         tv' | Just unf <- mb_unf = mkTyVarWithUnfolding name' ki' (tidyType rec_tidy_env unf)
             | otherwise          = mkTyVar name' ki'


=====================================
compiler/GHC/Core/TyCo/FVs.hs
=====================================
@@ -1077,7 +1077,10 @@ scopedSort = go [] []
       | otherwise
       = (tv:a:as, fvs `unionVarSet` fv_tv : fvs : fvss)
       where
-        fv_tv = tyCoVarsOfType (tyVarKind tv)
+        -- If tv has an unfolding, expand it instead of looking at its kind
+        fv_tv = case tyVarUnfolding_maybe tv of
+                   Just ty -> tyCoVarsOfType ty
+                   Nothing -> tyCoVarsOfType (tyVarKind tv)
 
        -- lists not in correspondence
     insert _ _ _ = panic "scopedSort"


=====================================
compiler/GHC/Core/TyCo/Subst.hs
=====================================
@@ -1103,14 +1103,13 @@ cloneTyVarBndr subst@(Subst in_scope id_env tv_env cv_env) tv uniq
     , tv')
   where
     old_ki  = tyVarKind tv
-    old_unf = tyVarUnfolding tv
 
     tv1 | not (noFreeVarsOfType old_ki)   -- Kind is not closed
         = setTyVarKind tv (substTy subst old_ki)
         | otherwise
         = tv
 
-    tv2 | Just unf <- old_unf
+    tv2 | Just unf <- tyVarUnfolding_maybe tv
         , not (noFreeVarsOfType unf)  -- Unfolding is not closed
         = tv1 `setTyVarUnfolding` substTy subst unf
 


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -365,7 +365,7 @@ import GHC.Data.Maybe   ( orElse, isJust, firstJust )
 unfoldView :: Type -> Maybe Type
 -- Look through type variables, see Note [Type and coercion lets] in GHC.Core
 {-# INLINE unfoldView #-}
-unfoldView (TyVarTy tv) = tyVarUnfolding tv
+unfoldView (TyVarTy tv) = tyVarUnfolding_maybe tv
 unfoldView _ = Nothing
 
 rewriterView :: Type -> Maybe Type
@@ -378,7 +378,7 @@ rewriterView (TyConApp tc tys)
   | isTypeSynonymTyCon tc
   , isForgetfulSynTyCon tc || not (isFamFreeTyCon tc)
   = expandSynTyConApp_maybe tc tys
-rewriterView (TyVarTy tv) = tyVarUnfolding tv
+rewriterView (TyVarTy tv) = tyVarUnfolding_maybe tv
 rewriterView _other
   = Nothing
 
@@ -392,7 +392,7 @@ coreView :: Type -> Maybe Type
 -- By being non-recursive and inlined, this case analysis gets efficiently
 -- joined onto the case analysis that the caller is already doing
 coreView (TyConApp tc tys) = expandSynTyConApp_maybe tc tys
-coreView (TyVarTy tv)      = tyVarUnfolding tv  -- c.f. unfoldView
+coreView (TyVarTy tv)      = tyVarUnfolding_maybe tv  -- c.f. unfoldView
 coreView _                 = Nothing
 -- See Note [Inlining coreView].
 {-# INLINE coreView #-}
@@ -406,7 +406,7 @@ coreFullView ty@(TyConApp tc _)
   | isTypeSynonymTyCon tc = core_full_view ty
 coreFullView (TyVarTy tv)
   -- c.f. unfoldView
-  | Just ty <- tyVarUnfolding tv = core_full_view ty
+  | Just ty <- tyVarUnfolding_maybe tv = core_full_view ty
 coreFullView ty = ty
 {-# INLINE coreFullView #-}
 
@@ -2732,7 +2732,7 @@ sORTKind_maybe :: Kind -> Maybe (TypeOrConstraint, Type)
 -- This is a "hot" function.  Do not call splitTyConApp_maybe here,
 -- to avoid the faff with FunTy
 sORTKind_maybe (TyVarTy tv)
-  | Just ty <- tyVarUnfolding tv
+  | Just ty <- tyVarUnfolding_maybe tv
   = sORTKind_maybe ty
 sORTKind_maybe (TyConApp tc tys)
   -- First, short-cuts for Type and Constraint that do no allocation
@@ -2883,8 +2883,8 @@ isConcreteTypeWith :: TyVarSet -> Type -> Bool
 isConcreteTypeWith conc_tvs = go
   where
     go (TyVarTy tv)
-      | Just ty <- tyVarUnfolding tv = go ty
-      | otherwise                    = isConcreteTyVar tv || tv `elemVarSet` conc_tvs
+      | Just ty <- tyVarUnfolding_maybe tv = go ty
+      | otherwise                          = isConcreteTyVar tv || tv `elemVarSet` conc_tvs
     go (AppTy ty1 ty2)     = go ty1 && go ty2
     go (TyConApp tc tys)   = go_tc tc tys
     go ForAllTy{}          = False


=====================================
compiler/GHC/CoreToIface.hs
=====================================
@@ -438,8 +438,8 @@ toIfaceLetBndr tv
                                (toIfaceKind (tyVarKind tv))
                                info
   where
-    info | Just unf <- tyVarUnfolding tv = [HsTypeUnfold (toIfaceType unf)]
-         | otherwise                     = []
+    info | Just unf <- tyVarUnfolding_maybe tv = [HsTypeUnfold (toIfaceType unf)]
+         | otherwise                           = []
 
 toIfaceLetBndr id  = IfLetBndr (mkIfLclName (occNameFS (getOccName id)))
                                (toIfaceType (idType id))


=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -690,8 +690,7 @@ ds_app (XExpr (ConLikeTc con tvs tys)) _hs_args core_args
        ; let core_fun = mkLams tvs $ mkLams ids $
                         ds_con `mkTyApps` mkTyVarTys tvs
                                `mkVarApps` ids
-       ; pprTrace "ds_conl" (ppr tvs) $
-         return (mkApps core_fun core_args) }
+       ; return (mkApps core_fun core_args) }
 
 ds_app (XExpr (HsRecSelTc (FieldOcc { foLabel = L _ sel_id }))) _hs_args core_args
   = ds_app_rec_sel sel_id sel_id core_args


=====================================
compiler/GHC/Iface/Type.hs
=====================================
@@ -1064,7 +1064,7 @@ pprArrow (mb_conc, ppr_mult) af mult
 ppr_tv_occ :: TyVar -> SDoc
 ppr_tv_occ tv
   = sdocOption sdocPrintTyVarUnfoldings $ \print_unf ->
-    ppr tv <> case tyVarUnfolding tv of
+    ppr tv <> case tyVarUnfolding_maybe tv of
                 Just ty | print_unf -> braces (ppr ty)
                 _                   -> empty
 


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -3689,7 +3689,7 @@ tcConDecl new_or_data dd_info rep_tycon tc_bndrs res_kind tag_map
        ; let bang_opts = SrcBangOpts (initBangOpts dflags)
        ; dc <- buildDataCon fam_envs bang_opts name is_infix rep_nm
                             stricts field_lbls
-                            tc_tvs ex_tvs user_tvbs
+                            (binderVars tc_bndrs) ex_tvs user_tvbs
                             [{- no eq_preds -}] ctxt arg_tys
                             user_res_ty rep_tycon tag_map
                   -- NB:  we put data_tc, the type constructor gotten from the


=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -1089,8 +1089,7 @@ zonkExpr (XExpr (ExpandedThingTc thing e))
 zonkExpr (XExpr (ConLikeTc con tvs tys))
   = runZonkBndrT (zonkTyBndrsX tvs) $ \ tvs' ->
     do { tys' <- mapM zonkScaledTcTypeToTypeX tys
-       ; pprTrace "zok-conl" (ppr tvs') $
-         return (XExpr (ConLikeTc con tvs' tys')) }
+       ; return (XExpr (ConLikeTc con tvs' tys')) }
     -- The tvs come straight from the data-con, and so are strictly redundant
     -- See Wrinkles of Note [Typechecking data constructors] in GHC.Tc.Gen.Head
 


=====================================
compiler/GHC/Types/Id/Info.hs
=====================================
@@ -73,8 +73,7 @@ module GHC.Types.Id.Info (
         -- ** The RuleInfo type
         RuleInfo(..),
         emptyRuleInfo,
-        isEmptyRuleInfo, ruleInfoFreeVars,
-        ruleInfoRules, setRuleInfoHead,
+        isEmptyRuleInfo, ruleInfoRules, setRuleInfoHead,
         ruleInfo, setRuleInfo, tagSigInfo,
 
         -- ** The CAFInfo type
@@ -98,7 +97,6 @@ import GHC.Core
 import GHC.Core.Class
 import {-# SOURCE #-} GHC.Builtin.PrimOps (PrimOp)
 import GHC.Types.Name
-import GHC.Types.Var.Set
 import GHC.Types.Basic
 import GHC.Core.DataCon
 import GHC.Core.TyCon
@@ -768,33 +766,21 @@ and put in the global list.
 --
 -- Records the specializations of this 'Id' that we know about
 -- in the form of rewrite 'CoreRule's that target them
-data RuleInfo
-  = RuleInfo
-        [CoreRule]
-        DVarSet         -- Locally-defined free vars of *both* LHS and RHS
-                        -- of rules.  I don't think it needs to include the
-                        -- ru_fn though.
-                        -- Note [Rule dependency info] in "GHC.Core.Opt.OccurAnal"
+newtype RuleInfo = RuleInfo [CoreRule]
 
 -- | Assume that no specializations exist: always safe
 emptyRuleInfo :: RuleInfo
-emptyRuleInfo = RuleInfo [] emptyDVarSet
+emptyRuleInfo = RuleInfo []
 
 isEmptyRuleInfo :: RuleInfo -> Bool
-isEmptyRuleInfo (RuleInfo rs _) = null rs
-
--- | Retrieve the locally-defined free variables of both the left and
--- right hand sides of the specialization rules
-ruleInfoFreeVars :: RuleInfo -> DVarSet
-ruleInfoFreeVars (RuleInfo _ fvs) = fvs
+isEmptyRuleInfo (RuleInfo rs) = null rs
 
 ruleInfoRules :: RuleInfo -> [CoreRule]
-ruleInfoRules (RuleInfo rules _) = rules
+ruleInfoRules (RuleInfo rules) = rules
 
 -- | Change the name of the function the rule is keyed on all of the 'CoreRule's
 setRuleInfoHead :: Name -> RuleInfo -> RuleInfo
-setRuleInfoHead fn (RuleInfo rules fvs)
-  = RuleInfo (map (setRuleIdName fn) rules) fvs
+setRuleInfoHead fn (RuleInfo rules) = RuleInfo (map (setRuleIdName fn) rules)
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Types/Var.hs
=====================================
@@ -104,7 +104,7 @@ module GHC.Types.Var (
         mkTyVar, mkTyVarWithUnfolding, mkTcTyVar,
 
         -- ** Taking 'TyVar's apart
-        tyVarName, tyVarKind, tyVarUnfolding, tyVarOccInfo, tcTyVarDetails, setTcTyVarDetails,
+        tyVarName, tyVarKind, tyVarUnfolding_maybe, tyVarOccInfo, tcTyVarDetails, setTcTyVarDetails,
 
         -- ** Modifying 'TyVar's
         setTyVarName, setTyVarUnique, setTyVarKind, setTyVarUnfolding, setTyVarOccInfo,
@@ -470,6 +470,7 @@ updateVarTypeM upd var
     result = do { ty' <- upd (varType var)
                 ; return (var { varType = ty' }) }
 
+
 {- *********************************************************************
 *                                                                      *
 *                   FunTyFlag
@@ -1018,9 +1019,9 @@ tyVarName = varName
 tyVarKind :: TyVar -> Kind
 tyVarKind = varType
 
-tyVarUnfolding :: TyVar -> Maybe Type
-tyVarUnfolding (TyVar { tv_unfolding = unf }) = unf
-tyVarUnfolding _ = Nothing
+tyVarUnfolding_maybe :: TyVar -> Maybe Type
+tyVarUnfolding_maybe (TyVar { tv_unfolding = unf }) = unf
+tyVarUnfolding_maybe _ = Nothing
 
 tyVarOccInfo :: TyVar -> OccInfo
 tyVarOccInfo (TcTyVar {}) = noOccInfo
@@ -1057,7 +1058,7 @@ updateTyVarKindM update tv
 
 updateTyVarUnfolding :: (Type -> Type) -> TyVar -> TyVar
 updateTyVarUnfolding update tv
-  | Just unf <- tyVarUnfolding tv
+  | Just unf <- tyVarUnfolding_maybe tv
   = tv {tv_unfolding = Just (update unf)}
 
   | otherwise
@@ -1065,7 +1066,7 @@ updateTyVarUnfolding update tv
 
 updateTyVarUnfoldingM :: (Monad m) => (Type -> m Type) -> TyVar -> m TyVar
 updateTyVarUnfoldingM update tv
-  | Just unf <- tyVarUnfolding tv
+  | Just unf <- tyVarUnfolding_maybe tv
   = do { unf' <- update unf
        ; return $ tv {tv_unfolding = Just unf'} }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/151ac2750e063f2bf76c5d9f15465b92fe3161ed

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 18:02:15 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 14:02:15 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] The ast has shifted around a
 little but this should be fine.
Message-ID: <672123279388b_249fdb3d1e4028577@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
de0fe228 by Hassan Al-Awwadi at 2024-10-29T19:00:17+01:00
The ast has shifted around a little but this should be fine.

- - - - -


6 changed files:

- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr


Changes:

=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -100,8 +100,10 @@ GHC.Hs.DocString
 GHC.Hs.Expr
 GHC.Hs.Extension
 GHC.Hs.ImpExp
+GHC.Hs.InlinePragma
 GHC.Hs.Instances
 GHC.Hs.Lit
+GHC.Hs.OverlapPragma
 GHC.Hs.Pat
 GHC.Hs.Specificity
 GHC.Hs.Type
@@ -238,8 +240,10 @@ Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension
 Language.Haskell.Syntax.ImpExp
+Language.Haskell.Syntax.InlinePragma
 Language.Haskell.Syntax.Lit
 Language.Haskell.Syntax.Module.Name
+Language.Haskell.Syntax.OverlapPragma
 Language.Haskell.Syntax.Pat
 Language.Haskell.Syntax.Specificity
 Language.Haskell.Syntax.Type


=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -103,8 +103,10 @@ GHC.Hs.DocString
 GHC.Hs.Expr
 GHC.Hs.Extension
 GHC.Hs.ImpExp
+GHC.Hs.InlinePragma
 GHC.Hs.Instances
 GHC.Hs.Lit
+GHC.Hs.OverlapPragma
 GHC.Hs.Pat
 GHC.Hs.Specificity
 GHC.Hs.Type
@@ -262,8 +264,10 @@ Language.Haskell.Syntax.Decls
 Language.Haskell.Syntax.Expr
 Language.Haskell.Syntax.Extension
 Language.Haskell.Syntax.ImpExp
+Language.Haskell.Syntax.InlinePragma
 Language.Haskell.Syntax.Lit
 Language.Haskell.Syntax.Module.Name
+Language.Haskell.Syntax.OverlapPragma
 Language.Haskell.Syntax.Pat
 Language.Haskell.Syntax.Specificity
 Language.Haskell.Syntax.Type


=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
=====================================
@@ -891,22 +891,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:22:20-23 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:22:20-23 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:22:25-26 })
@@ -1273,22 +1274,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:28:20-23 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:28:20-23 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:28:25-26 })
@@ -1655,22 +1657,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:34:20-23 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:34:20-23 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:34:25-26 })
@@ -2037,22 +2040,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:40:20-23 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:40:20-23 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:40:25-26 })
@@ -2419,22 +2423,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:46:20-23 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:46:20-23 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:46:25-26 })
@@ -2801,22 +2806,23 @@
          (EpaComments
           []))
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (EpTok
-           (EpaSpan { T17544.hs:52:21-24 }))
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (EpTok
+            (EpaSpan { T17544.hs:52:21-24 }))
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (NotTopLevel))
          (DataFamily)
-         (NotTopLevel)
          (L
           (EpAnn
            (EpaSpan { T17544.hs:52:26-28 })


=====================================
testsuite/tests/parser/should_compile/DumpParsedAst.stderr
=====================================
@@ -308,24 +308,26 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       (AnnFamilyDecl
-        []
-        []
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:10:1-4 }))
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:10:6-11 }))
-        (EpUniTok
-         (EpaSpan { DumpParsedAst.hs:10:32-33 })
-         (NormalSyntax))
-        (NoEpTok)
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:10:41-45 }))
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok))
+       ((,)
+        (AnnFamilyDecl
+         []
+         []
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:10:1-4 }))
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:10:6-11 }))
+         (EpUniTok
+          (EpaSpan { DumpParsedAst.hs:10:32-33 })
+          (NormalSyntax))
+         (NoEpTok)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:10:41-45 }))
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok))
+        (TopLevel))
        (ClosedTypeFamily
         (Just
          [(L
@@ -576,7 +578,6 @@
                  []))
                (Unqual
                 {OccName: Zero}))))))]))
-       (TopLevel)
        (L
         (EpAnn
          (EpaSpan { DumpParsedAst.hs:10:13-18 })
@@ -1067,24 +1068,26 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       (AnnFamilyDecl
-        []
-        []
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:18:1-4 }))
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:18:6-11 }))
-        (EpUniTok
-         (EpaSpan { DumpParsedAst.hs:18:42-43 })
-         (NormalSyntax))
-        (NoEpTok)
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:18:50-54 }))
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok))
+       ((,)
+        (AnnFamilyDecl
+         []
+         []
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:18:1-4 }))
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:18:6-11 }))
+         (EpUniTok
+          (EpaSpan { DumpParsedAst.hs:18:42-43 })
+          (NormalSyntax))
+         (NoEpTok)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:18:50-54 }))
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok))
+        (TopLevel))
        (ClosedTypeFamily
         (Just
          [(L
@@ -1280,7 +1283,6 @@
                    []))
                  (Unqual
                   {OccName: a}))))))))]))
-       (TopLevel)
        (L
         (EpAnn
          (EpaSpan { DumpParsedAst.hs:18:13-14 })
@@ -1463,25 +1465,26 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       (AnnFamilyDecl
-        []
-        []
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:21:1-4 }))
-        (EpTok
-         (EpaSpan { DumpParsedAst.hs:21:6-11 }))
-        (EpUniTok
-         (EpaSpan { DumpParsedAst.hs:21:17-18 })
-         (NormalSyntax))
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok))
+       ((,)
+        (AnnFamilyDecl
+         []
+         []
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:21:1-4 }))
+         (EpTok
+          (EpaSpan { DumpParsedAst.hs:21:6-11 }))
+         (EpUniTok
+          (EpaSpan { DumpParsedAst.hs:21:17-18 })
+          (NormalSyntax))
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok))
+        (TopLevel))
        (DataFamily)
-       (TopLevel)
        (L
         (EpAnn
          (EpaSpan { DumpParsedAst.hs:21:13-15 })


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -257,19 +257,21 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (TopLevel))
          (ClosedTypeFamily
           (Just
            [(L
@@ -500,7 +502,6 @@
                   (EpaComments
                    []))
                  {Name: DumpRenamedAst.Zero})))))]))
-         (TopLevel)
          (L
           (EpAnn
            (EpaSpan { DumpRenamedAst.hs:12:13-18 })
@@ -699,21 +700,22 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (TopLevel))
          (DataFamily)
-         (TopLevel)
          (L
           (EpAnn
            (EpaSpan { DumpRenamedAst.hs:16:13-15 })
@@ -1513,19 +1515,21 @@
        (FamDecl
         (NoExtField)
         (FamilyDecl
-         (AnnFamilyDecl
-          []
-          []
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpUniTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok)
-          (NoEpTok))
+         ((,)
+          (AnnFamilyDecl
+           []
+           []
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpUniTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok)
+           (NoEpTok))
+          (TopLevel))
          (ClosedTypeFamily
           (Just
            [(L
@@ -1711,7 +1715,6 @@
                     (EpaComments
                      []))
                    {Name: a})))))))]))
-         (TopLevel)
          (L
           (EpAnn
            (EpaSpan { DumpRenamedAst.hs:25:13-14 })
@@ -2081,21 +2084,22 @@
            (EpaComments
             []))
           (FamilyDecl
-           (AnnFamilyDecl
-            []
-            []
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpUniTok)
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpTok)
-            (NoEpTok))
+           ((,)
+            (AnnFamilyDecl
+             []
+             []
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpUniTok)
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok)
+             (NoEpTok))
+            (NotTopLevel))
            (OpenTypeFamily)
-           (NotTopLevel)
            (L
             (EpAnn
              (EpaSpan { DumpRenamedAst.hs:29:8 })


=====================================
testsuite/tests/parser/should_compile/KindSigs.stderr
=====================================
@@ -84,22 +84,24 @@
      (FamDecl
       (NoExtField)
       (FamilyDecl
-       (AnnFamilyDecl
-        []
-        []
-        (EpTok
-         (EpaSpan { KindSigs.hs:11:1-4 }))
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { KindSigs.hs:11:6-11 }))
-        (NoEpUniTok)
-        (NoEpTok)
-        (NoEpTok)
-        (EpTok
-         (EpaSpan { KindSigs.hs:11:19-23 }))
-        (NoEpTok)
-        (NoEpTok)
-        (NoEpTok))
+       ((,)
+        (AnnFamilyDecl
+         []
+         []
+         (EpTok
+          (EpaSpan { KindSigs.hs:11:1-4 }))
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:11:6-11 }))
+         (NoEpUniTok)
+         (NoEpTok)
+         (NoEpTok)
+         (EpTok
+          (EpaSpan { KindSigs.hs:11:19-23 }))
+         (NoEpTok)
+         (NoEpTok)
+         (NoEpTok))
+        (TopLevel))
        (ClosedTypeFamily
         (Just
          [(L
@@ -197,7 +199,6 @@
                    []))
                  (Unqual
                   {OccName: Type}))))))))]))
-       (TopLevel)
        (L
         (EpAnn
          (EpaSpan { KindSigs.hs:11:13-15 })



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 18:20:25 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Tue, 29 Oct 2024 14:20:25 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-explicitsum-sumpat
Message-ID: <672127697b64a_249fdb4def5430777@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-explicitsum-sumpat at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-explicitsum-sumpat
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 18:51:19 2024
From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits))
Date: Tue, 29 Oct 2024 14:51:19 -0400
Subject: [Git][ghc/ghc][wip/torsten.schmits/package-deps-bytecode-squashed] 2
 commits: Link interface bytecode from package DBs if possible
Message-ID: <67212ea7b22d1_249fdb826a4041359@gitlab.mail>



Torsten Schmits pushed to branch wip/torsten.schmits/package-deps-bytecode-squashed at Glasgow Haskell Compiler / GHC


Commits:
be1b06b5 by Torsten Schmits at 2024-10-29T19:49:47+01:00
Link interface bytecode from package DBs if possible

Part of #25090.

MR !13068

When splices are executed with `-fprefer-byte-code`, the loader will
compile Core bindings to bytecode if those are present in interfaces of
module dependencies.

So far, this only applied to local modules (i.e. home modules in make
mode and non-package deps in oneshot mode).

This patch extends support to interfaces loaded from a package DB.
In `getLinkDeps`, the dependencies chosen for recursion were restricted
to `dep_direct_mods`, which has been changed to include external
dependencies, stored in a new field named `dep_direct_pkg_mods`.
In order to unify treatment of the different link variants across
make/oneshot mode, the algorithm's intermediate results have been
abstracted into the data types `LinkDep` and `LinkModule`.

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -
f3c844d2 by Torsten Schmits at 2024-10-29T19:49:47+01:00
add new field to iface for package deps

Metric Decrease:
    MultiLayerModulesTH_Make
    MultiLayerModulesTH_OneShot

- - - - -


23 changed files:

- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- docs/users_guide/phases.rst
- + testsuite/tests/bytecode/T25090/Dep.hs
- + testsuite/tests/bytecode/T25090/DepApi.hs
- + testsuite/tests/bytecode/T25090/Local.hs
- testsuite/tests/bytecode/T25090/Makefile
- + testsuite/tests/bytecode/T25090/Num.hs
- + testsuite/tests/bytecode/T25090/Num.hs-boot
- + testsuite/tests/bytecode/T25090/PkgBytecode.hs
- + testsuite/tests/bytecode/T25090/PkgBytecode.stdout
- testsuite/tests/bytecode/T25090/all.T
- + testsuite/tests/bytecode/T25090/dep.conf
- + testsuite/tests/bytecode/T25090/prep.bash
- + testsuite/tests/bytecode/T25090/run.bash
- + testsuite/tests/bytecode/T25090/unit1
- + testsuite/tests/bytecode/T25090/unit2


Changes:

=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -843,6 +843,7 @@ data GeneralFlag
    | Opt_BuildDynamicToo
    | Opt_WriteIfSimplifiedCore
    | Opt_UseBytecodeRatherThanObjects
+   | Opt_PackageDbBytecode
 
    -- safe haskell flags
    | Opt_DistrustAllPackages


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2543,6 +2543,7 @@ fFlagsDeps = [
   flagSpec "link-rts"                         Opt_LinkRts,
   flagSpec "byte-code-and-object-code"        Opt_ByteCodeAndObjectCode,
   flagSpec "prefer-byte-code"                 Opt_UseBytecodeRatherThanObjects,
+  flagSpec "package-db-byte-code"             Opt_PackageDbBytecode,
   flagSpec' "compact-unwind"                  Opt_CompactUnwind
       (\turn_on -> updM (\dflags -> do
         unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)


=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -117,6 +117,7 @@ import System.Directory
 import GHC.Driver.Env.KnotVars
 import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
 import GHC.Iface.Errors.Types
+import GHC.Runtime.Context (emptyInteractiveContext)
 import Data.Function ((&))
 
 {-
@@ -533,12 +534,22 @@ loadInterface doc_str mod from
               --
               -- See Note [Interface Files with Core Definitions]
               add_bytecode old
-                | Just action <- loadIfaceByteCode purged_hsc_env iface loc (mkNameEnv new_eps_decls)
+                | Just action <- loadIfaceByteCode hydration_env iface loc (mkNameEnv new_eps_decls)
                 = extendModuleEnv old mod action
                 -- Don't add an entry if the iface doesn't have 'extra_decls'
                 -- so 'get_link_deps' knows that it should load object code.
                 | otherwise
                 = old
+                where
+                  -- @dontLeakTheHUG@ purges @InteractiveContext@, but when
+                  -- bytecode is compiled in @hscInteractive@ with CoreLint
+                  -- enabled, the context is used to find variables defined in
+                  -- GHCi to prevent false positives.
+                  -- Since code loaded from interface Core bindings cannot
+                  -- depend on variables in the interactive session, we provide
+                  -- an empty context here.
+                  hydration_env =
+                    purged_hsc_env {hsc_IC = emptyInteractiveContext (hsc_dflags purged_hsc_env)}
 
         ; warnPprTrace bad_boot "loadInterface" (ppr mod) $
           updateEps_  $ \ eps ->


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -6,6 +6,7 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Linker.Deps
   ( LinkDepsOpts (..)
@@ -22,12 +23,12 @@ import GHC.Runtime.Interpreter
 
 import GHC.Linker.Types
 
-import GHC.Types.SourceFile
 import GHC.Types.SrcLoc
 import GHC.Types.Unique.DSet
 import GHC.Types.Unique.DFM
 
 import GHC.Utils.Outputable
+import qualified GHC.Utils.Outputable as Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Error
 
@@ -47,15 +48,19 @@ import GHC.Utils.Misc
 import GHC.Unit.Home
 import GHC.Data.Maybe
 
-import Control.Monad
 import Control.Applicative
+import Control.Monad.IO.Class (MonadIO (liftIO))
+import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
 
+import Data.Foldable (traverse_)
 import qualified Data.Set as Set
 import qualified Data.Map as M
 import Data.List (isSuffixOf)
 
 import System.FilePath
 import System.Directory
+import GHC.Utils.Logger (Logger)
+import Control.Monad ((<$!>))
 
 data LinkDepsOpts = LinkDepsOpts
   { ldObjSuffix   :: !String                        -- ^ Suffix of .o files
@@ -64,19 +69,23 @@ data LinkDepsOpts = LinkDepsOpts
   , ldUnitEnv     :: !UnitEnv
   , ldPprOpts     :: !SDocContext                   -- ^ Rendering options for error messages
   , ldUseByteCode :: !Bool                          -- ^ Use bytecode rather than objects
+  , ldPkgByteCode :: !Bool                          -- ^ Use bytecode for external packages
   , ldMsgOpts     :: !(DiagnosticOpts IfaceMessage) -- ^ Options for diagnostics
   , ldWays        :: !Ways                          -- ^ Enabled ways
-  , ldFinderCache :: !FinderCache
-  , ldFinderOpts  :: !FinderOpts
-  , ldLoadIface   :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError ModIface))
-  , ldLoadByteCode :: !(Module -> IO (Maybe Linkable))
+  , ldLoadIface :: !(SDoc -> Module -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)))
+  -- ^ When linking oneshot or package dependencies, we need interfaces and
+  -- locations to find object files and traverse dependencies.
+  , ldLoadByteCode :: !(Module -> IO (Maybe (IO Linkable)))
+  -- ^ Consult the EPS about the given module, return an action that compiles
+  -- Core bindings to bytecode if it's available.
+  , ldLogger :: !Logger
   }
 
 data LinkDeps = LinkDeps
   { ldNeededLinkables :: [Linkable]
   , ldAllLinkables    :: [Linkable]
-  , ldUnits           :: [UnitId]
-  , ldNeededUnits     :: UniqDSet UnitId
+  , ldNeededUnits     :: [UnitId]
+  , ldAllUnits        :: UniqDSet UnitId
   }
 
 -- | Find all the packages and linkables that a set of modules depends on
@@ -100,9 +109,80 @@ getLinkDeps opts interp pls span mods = do
       -- then we need to find & link object files built the "normal" way.
       maybe_normal_osuf <- checkNonStdWay opts interp span
 
-      get_link_deps opts pls maybe_normal_osuf span mods
-
+      withTiming (ldLogger opts) (text "getLinkDeps" <+> brackets (ppr span)) (const ()) $
+        get_link_deps opts pls maybe_normal_osuf span mods
+
+-- | Determine which parts of a module and its dependencies should be linked
+-- when resolving external dependencies.
+data LinkExternalDetails =
+  -- | A module that should be linked, including its dependencies in the home
+  -- unit and external packages.
+  -- Can be a home module in oneshot mode or a package dependency module in
+  -- either mode.
+  LinkAllDeps
+  |
+  -- | A home module whose package dependencies should be linked, but not the
+  -- module itself or its home unit dependencies.
+  -- Can either be a direct target or the implementation module corresponding to
+  -- a target boot module, but only in make mode.
+  -- The 'ModIface' is taken from the 'HomeModInfo', avoiding another lookup in
+  -- 'external_deps'.
+  -- The importing module and its home unit dependencies are not processed by
+  -- 'external_deps', since the readily available 'HomeModInfo's can be linked
+  -- without further analysis.
+  LinkOnlyPackages !ModIface
+
+instance Outputable LinkExternalDetails where
+  ppr = \case
+    LinkAllDeps -> text "all"
+    LinkOnlyPackages _ -> text "only-packages"
+
+-- | A module that should be examined by 'external_deps' to decide how to link
+-- it and its dependencies.
+data LinkExternal =
+  LinkExternal {
+    le_details :: LinkExternalDetails,
+    le_module :: !Module
+  }
 
+instance Outputable LinkExternal where
+  ppr LinkExternal {..} = ppr le_module <> brackets (ppr le_details)
+
+-- | The decision about the linking method used for a given module.
+data LinkModule =
+  -- | In make mode, we can use 'HomeModInfo' without any further analysis.
+  LinkHomeModule !HomeModInfo
+  |
+  -- | A module that must be linked as native code, because bytecode is disabled
+  -- or unavailable.
+  LinkObjectModule !Module !ModLocation
+  |
+  -- | A module that has bytecode available.
+  -- The 'IO' that compiles the bytecode from Core bindings is obtained from the
+  -- EPS.
+  -- See Note [Interface Files with Core Definitions].
+  LinkByteCodeModule !Module !(IO Linkable)
+
+link_module :: LinkModule -> Module
+link_module = \case
+  LinkHomeModule hmi -> mi_module (hm_iface hmi)
+  LinkObjectModule mod _ -> mod
+  LinkByteCodeModule mod _ -> mod
+
+instance Outputable LinkModule where
+  ppr = \case
+    LinkHomeModule hmi -> ppr (mi_module (hm_iface hmi)) <+> brackets (text "HMI")
+    LinkObjectModule mod _ -> ppr mod
+    LinkByteCodeModule mod _ -> ppr mod <+> brackets (text "BC")
+
+-- | Compute the linkables for the given module set's dependencies.
+--
+-- Home modules in make mode are treated separately in a preprocessing step,
+-- then all the remaining external deps are processed for both modes.
+-- If bytecode is available, transitive external deps are included, otherwise
+-- the module's library is linked and processing stops.
+--
+-- The results are split into sets of needed/loaded modules/packages.
 get_link_deps
   :: LinkDepsOpts
   -> LoaderState
@@ -111,46 +191,36 @@ get_link_deps
   -> [Module]
   -> IO LinkDeps
 get_link_deps opts pls maybe_normal_osuf span mods = do
-        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-        -- (omitting modules from the interactive package, which is already linked)
-      (mods_s, pkgs_s) <-
-          -- Why two code paths here? There is a significant amount of repeated work
-          -- performed calculating transitive dependencies
-          -- if --make uses the oneShot code path (see MultiLayerModulesTH_* tests)
-          if ldOneShotMode opts
-            then follow_deps (filterOut isInteractiveModule mods)
-                              emptyUniqDSet emptyUniqDSet;
-            else do
-              (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
-              return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-
-      let
-        -- 2.  Exclude ones already linked
-        --      Main reason: avoid findModule calls in get_linkable
-            (mods_needed, links_got) = partitionWith split_mods mods_s
-            pkgs_needed = eltsUDFM $ getUniqDSet pkgs_s `minusUDFM` pkgs_loaded pls
-
-            split_mods mod =
-                let is_linked = lookupModuleEnv (objs_loaded pls) mod
-                                <|> lookupModuleEnv (bcos_loaded pls) mod
-                in case is_linked of
-                     Just linkable -> Right linkable
-                     Nothing -> Left mod
-
-        -- 3.  For each dependent module, find its linkable
-        --     This will either be in the HPT or (in the case of one-shot
-        --     compilation) we may need to use maybe_getFileLinkable
-      lnks_needed <- mapM (get_linkable (ldObjSuffix opts)) mods_needed
-
-      return $ LinkDeps
-        { ldNeededLinkables = lnks_needed
-        , ldAllLinkables    = links_got ++ lnks_needed
-        , ldUnits           = pkgs_needed
-        , ldNeededUnits     = pkgs_s
-        }
+  (link_deps_home, module_deps_external) <- separate_home_deps
+  link_deps_external <- external_deps opts module_deps_external
+  let (loaded_modules, needed_modules, ldAllUnits, ldNeededUnits) =
+        classify_deps pls link_deps_home link_deps_external
+  ldNeededLinkables <- mapM module_linkable needed_modules
+  pure LinkDeps {
+    ldNeededLinkables,
+    ldAllLinkables = loaded_modules ++ ldNeededLinkables,
+    ldNeededUnits,
+    ldAllUnits
+  }
   where
     mod_graph = ldModuleGraph opts
     unit_env  = ldUnitEnv     opts
+    noninteractive = filterOut isInteractiveModule mods
+
+    -- Preprocess the dependencies in make mode to remove all home modules,
+    -- since the transitive dependency closure is already cached for those in
+    -- the HUG (see MultiLayerModulesTH_* tests for the performance impact).
+    --
+    -- Returns the remaining, external, dependencies on the right, which is the
+    -- entire set for oneshot mode.
+    separate_home_deps =
+      if ldOneShotMode opts
+      then pure ([], LinkExternal LinkAllDeps <$!> noninteractive)
+      else make_deps
+
+    make_deps = do
+      (dep_ext, mmods) <- unzip <$> mapM get_mod_info all_home_mods
+      pure (mmods, init_ext ++ dep_ext)
 
     -- This code is used in `--make` mode to calculate the home package and unit dependencies
     -- for a set of modules.
@@ -160,9 +230,9 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
 
     -- It is also a matter of correctness to use the module graph so that dependencies between home units
     -- is resolved correctly.
-    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+    make_deps_loop :: ([LinkExternal], Set.Set NodeKey) -> [ModNodeKeyWithUid] -> ([LinkExternal], Set.Set NodeKey)
     make_deps_loop found [] = found
-    make_deps_loop found@(found_units, found_mods) (nk:nexts)
+    make_deps_loop found@(external, found_mods) (nk:nexts)
       | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
       | otherwise =
         case M.lookup (NodeKey_Module nk) (mgTransDeps mod_graph) of
@@ -171,93 +241,46 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
                   -- See #936 and the ghci.prog007 test for why we have to continue traversing through
                   -- boot modules.
                   todo_boot_mods = [ModNodeKeyWithUid (GWIB mn NotBoot) uid | NodeKey_Module (ModNodeKeyWithUid (GWIB mn IsBoot) uid) <- Set.toList trans_deps]
-              in make_deps_loop (found_units, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
+              in make_deps_loop (external, deps `Set.union` found_mods) (todo_boot_mods ++ nexts)
             Nothing ->
-              let (ModNodeKeyWithUid _ uid) = nk
-              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+              let (ModNodeKeyWithUid (GWIB mod_name _) uid) = nk
+                  mod = Module (RealUnit (Definite uid)) mod_name
+              in make_deps_loop (LinkExternal LinkAllDeps mod : external, found_mods) nexts
 
     mkNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
-    (init_pkg_set, all_deps) = make_deps_loop (emptyUniqDSet, Set.empty) $ map mkNk (filterOut isInteractiveModule mods)
+    (init_ext, all_deps) = make_deps_loop ([], Set.empty) $ map mkNk noninteractive
 
     all_home_mods = [with_uid | NodeKey_Module with_uid <- Set.toList all_deps]
 
     get_mod_info (ModNodeKeyWithUid gwib uid) =
       case lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) of
-        Just hmi ->
-          let iface = (hm_iface hmi)
-              mmod = case mi_hsc_src iface of
-                      HsBootFile -> link_boot_mod_error (mi_module iface)
-                      _          -> return $ Just (mi_module iface)
-
-          in (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface),) <$>  mmod
+        Just hmi -> do
+          let iface = hm_iface hmi
+          pure (LinkExternal (LinkOnlyPackages iface) (mi_module iface), hmi)
         Nothing -> throwProgramError opts $
           text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
 
-
-       -- This code is used in one-shot mode to traverse downwards through the HPT
-       -- to find all link dependencies.
-       -- The ModIface contains the transitive closure of the module dependencies
-       -- within the current package, *except* for boot modules: if we encounter
-       -- a boot module, we have to find its real interface and discover the
-       -- dependencies of that.  Hence we need to traverse the dependency
-       -- tree recursively.  See bug #936, testcase ghci/prog007.
-    follow_deps :: [Module]             -- modules to follow
-                -> UniqDSet Module         -- accum. module dependencies
-                -> UniqDSet UnitId          -- accum. package dependencies
-                -> IO ([Module], UniqDSet UnitId) -- result
-    follow_deps []     acc_mods acc_pkgs
-        = return (uniqDSetToList acc_mods, acc_pkgs)
-    follow_deps (mod:mods) acc_mods acc_pkgs
-        = do
-          mb_iface <- ldLoadIface opts msg mod
-          iface <- case mb_iface of
-                    Failed err      -> throwProgramError opts $
-                      missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
-                    Succeeded iface -> return iface
-
-          when (mi_boot iface == IsBoot) $ link_boot_mod_error mod
-
-          let
-            pkg = moduleUnit mod
-            deps  = mi_deps iface
-
-            pkg_deps = dep_direct_pkgs deps
-            (boot_deps, mod_deps) = flip partitionWith (Set.toList (dep_direct_mods deps)) $
-              \case
-                (_, GWIB m IsBoot)  -> Left m
-                (_, GWIB m NotBoot) -> Right m
-
-            mod_deps' = case ue_homeUnit unit_env of
-                          Nothing -> []
-                          Just home_unit -> filter (not . (`elementOfUniqDSet` acc_mods)) (map (mkHomeModule home_unit) $ (boot_deps ++ mod_deps))
-            acc_mods'  = case ue_homeUnit unit_env of
-                          Nothing -> acc_mods
-                          Just home_unit -> addListToUniqDSet acc_mods (mod : map (mkHomeModule home_unit) mod_deps)
-            acc_pkgs'  = addListToUniqDSet acc_pkgs (Set.toList pkg_deps)
-
-          case ue_homeUnit unit_env of
-            Just home_unit | isHomeUnit home_unit pkg ->  follow_deps (mod_deps' ++ mods)
-                                                                      acc_mods' acc_pkgs'
-            _ ->  follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' (toUnitId pkg))
-        where
-           msg = text "need to link module" <+> ppr mod <+>
-                  text "due to use of Template Haskell"
-
-
-
-    link_boot_mod_error :: Module -> IO a
-    link_boot_mod_error mod = throwProgramError opts $
-            text "module" <+> ppr mod <+>
-            text "cannot be linked; it is only available as a boot module"
-
     no_obj :: Outputable a => a -> IO b
     no_obj mod = dieWith opts span $
-                     text "cannot find object file for module " <>
+                     text "cannot find object file for module" <+>
                         quotes (ppr mod) $$
                      while_linking_expr
 
     while_linking_expr = text "while linking an interpreted expression"
 
+  -- Extract the 'Linkable's for unlinked modules from the intermediate
+  -- results.
+    module_linkable = \case
+      LinkHomeModule hmi ->
+        adjust_linkable (expectJust "getLinkDeps" (homeModLinkable hmi))
+
+      LinkObjectModule mod loc -> do
+        findObjectLinkableMaybe mod loc >>= \case
+          Nothing  -> no_obj mod
+          Just lnk -> adjust_linkable lnk
+
+      LinkByteCodeModule _ load_bytecode ->
+        load_bytecode
 
     -- See Note [Using Byte Code rather than Object Code for Template Haskell]
     homeModLinkable :: HomeModInfo -> Maybe Linkable
@@ -266,57 +289,244 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
         then homeModInfoByteCode hmi <|> homeModInfoObject hmi
         else homeModInfoObject hmi   <|> homeModInfoByteCode hmi
 
-    get_linkable osuf mod      -- A home-package module
-        | Just mod_info <- lookupHugByModule mod (ue_home_unit_graph unit_env)
-        = adjust_linkable (expectJust "getLinkDeps" (homeModLinkable mod_info))
-        | otherwise
-        = do    -- It's not in the HPT because we are in one shot mode,
-                -- so use the Finder to get a ModLocation...
-             case ue_homeUnit unit_env of
-              Nothing -> no_obj mod
-              Just home_unit -> do
-                from_bc <- ldLoadByteCode opts mod
-                maybe (fallback_no_bytecode home_unit mod) pure from_bc
-        where
-
-            fallback_no_bytecode home_unit mod = do
-              let fc = ldFinderCache opts
-              let fopts = ldFinderOpts opts
-              mb_stuff <- findHomeModule fc fopts home_unit (moduleName mod)
-              case mb_stuff of
-                Found loc _ -> do
-                  mb_lnk <- findObjectLinkableMaybe mod loc
-                  case mb_lnk of
-                    Nothing  -> no_obj mod
-                    Just lnk -> adjust_linkable lnk
-                _ -> no_obj (moduleName mod)
-
-            adjust_linkable lnk
-                | Just new_osuf <- maybe_normal_osuf = do
-                        new_parts <- mapM (adjust_part new_osuf)
-                                        (linkableParts lnk)
-                        return lnk{ linkableParts=new_parts }
-                | otherwise =
-                        return lnk
-
-            adjust_part new_osuf part = case part of
-              DotO file ModuleObject -> do
-                massert (osuf `isSuffixOf` file)
-                let file_base = fromJust (stripExtension osuf file)
-                    new_file = file_base <.> new_osuf
-                ok <- doesFileExist new_file
-                if (not ok)
-                   then dieWith opts span $
-                          text "cannot find object file "
-                                <> quotes (text new_file) $$ while_linking_expr
-                   else return (DotO new_file ModuleObject)
-              DotO file ForeignObject -> pure (DotO file ForeignObject)
-              DotA fp    -> panic ("adjust_ul DotA " ++ show fp)
-              DotDLL fp  -> panic ("adjust_ul DotDLL " ++ show fp)
-              BCOs {}    -> pure part
-              LazyBCOs{} -> pure part
-              CoreBindings WholeCoreBindings {wcb_module} ->
-                pprPanic "Unhydrated core bindings" (ppr wcb_module)
+    adjust_linkable lnk
+        | Just new_osuf <- maybe_normal_osuf = do
+                new_uls <- mapM (adjust_part (ldObjSuffix opts) new_osuf)
+                                (linkableParts lnk)
+                return lnk {linkableParts = new_uls}
+        | otherwise =
+                return lnk
+
+    adjust_part osuf new_osuf part = case part of
+      DotO file ModuleObject -> do
+        massert (osuf `isSuffixOf` file)
+        let file_base = fromJust (stripExtension osuf file)
+            new_file = file_base <.> new_osuf
+        ok <- doesFileExist new_file
+        if (not ok)
+            then dieWith opts span $
+                  text "cannot find object file"
+                        <+> quotes (text new_file) $$ while_linking_expr
+            else return (DotO new_file ModuleObject)
+      DotO file ForeignObject -> pure (DotO file ForeignObject)
+      DotA fp    -> panic ("adjust_part DotA " ++ show fp)
+      DotDLL fp  -> panic ("adjust_part DotDLL " ++ show fp)
+      BCOs {}    -> pure part
+      LazyBCOs{} -> pure part
+      CoreBindings WholeCoreBindings {wcb_module} ->
+        pprPanic "Unhydrated core bindings" (ppr wcb_module)
+
+data LinkDep =
+  LinkModules !(UniqDFM ModuleName LinkModule)
+  |
+  LinkLibrary !UnitId
+
+instance Outputable LinkDep where
+  ppr = \case
+    LinkModules mods -> text "modules:" <+> ppr (eltsUDFM mods)
+    LinkLibrary uid -> text "library:" <+> ppr uid
+
+data OneshotError =
+  NoInterface !MissingInterfaceError
+  |
+  LinkBootModule !Module
+
+-- | Compute the transitive dependency closure of the given modules.
+--
+-- Used for all oneshot mode dependencies and for external dependencies of home
+-- modules in make mode.
+external_deps ::
+  LinkDepsOpts ->
+  -- | Modules whose imports to follow
+  [LinkExternal] ->
+  IO [LinkDep]
+external_deps opts mods =
+  runExceptT (external_deps_loop opts mods emptyUDFM) >>= \case
+    Right a -> pure (eltsUDFM a)
+    Left err -> throwProgramError opts (message err)
+  where
+    message = \case
+      NoInterface err ->
+        missingInterfaceErrorDiagnostic (ldMsgOpts opts) err
+      LinkBootModule mod ->
+        link_boot_mod_error mod
+
+external_deps_loop ::
+  LinkDepsOpts ->
+  [LinkExternal] ->
+  UniqDFM UnitId LinkDep ->
+  ExceptT OneshotError IO (UniqDFM UnitId LinkDep)
+external_deps_loop _ [] acc =
+  pure acc
+external_deps_loop opts (job at LinkExternal {le_module = mod, ..} : mods) acc = do
+  (new_acc, new_mods, action) <-
+    if already_seen
+    then done
+    else process_module le_details
+  traverse_ debug_log action
+  external_deps_loop opts (new_mods ++ mods) new_acc
+  where
+    debug_log action =
+      liftIO $ debugTraceMsg (ldLogger opts) 3 $
+      text "TH dep" <+> ppr job <+>
+      brackets (sep (punctuate comma [
+        if is_home then text "home" else Outputable.empty,
+        text action
+      ]))
+
+    done = pure (acc, [], Nothing)
+
+    -- Decide how this module needs to be processed.
+    -- We only need an interface if we want to load bytecode or if we have to
+    -- link an object file (which happens for home unit modules, since those
+    -- have no libraries).
+    process_module = \case
+      LinkAllDeps | is_home || package_bc -> try_iface
+                  | otherwise -> add_library
+
+    -- @LinkOnlyPackages@ is used for make mode home modules, so all imports
+    -- that are not external are already processed otherwise.
+      LinkOnlyPackages iface -> with_deps acc iface False "only packages"
+
+    -- Check whether the current module was processed before.
+    -- Since the accumulator is keyed by unit ID, we have to perform two
+    -- lookups.
+    -- If another module from this module's unit has been determined to be
+    -- linked as a library previously, we skip this module, assuming that no
+    -- bytecode is available for the entire package.
+    already_seen
+      | Just (LinkModules mods) <- mod_dep
+      = elemUDFM mod_name mods
+      | Just (LinkLibrary _) <- mod_dep
+      = True
+      | otherwise
+      = False
+
+    -- Load the iface and attempt to get bytecode from Core bindings.
+    try_iface =
+      liftIO (ldLoadIface opts load_reason mod) >>= \case
+        Failed err -> throwE (NoInterface err)
+        Succeeded (iface, loc) -> do
+          mb_load_bc <- liftIO (ldLoadByteCode opts (mi_module iface))
+          with_iface iface loc mb_load_bc
+
+    -- Decide how to link this module.
+    -- If bytecode or an object file is available, use those in that order.
+    -- Otherwise fall back to linking a library.
+    with_iface iface loc mb_load_bc
+      | IsBoot <- mi_boot iface
+      = throwE (LinkBootModule mod)
+
+      | ldUseByteCode opts
+      , is_home || package_bc
+      , Just load_bc <- mb_load_bc
+      = add_module iface (LinkByteCodeModule mod load_bc) "bytecode"
+
+      | is_home
+      = add_module iface (LinkObjectModule mod loc) "object"
+
+      | otherwise
+      = add_library
+
+    add_library =
+      pure (addToUDFM acc mod_unit_id (LinkLibrary mod_unit_id), [], Just "library")
+
+    add_module iface lmod action =
+      with_deps with_mod iface True action
+      where
+        with_mod = alterUDFM (add_package_module lmod) acc mod_unit_id
+
+    add_package_module lmod = \case
+      Just (LinkLibrary u) -> Just (LinkLibrary u)
+      Just (LinkModules old) -> Just (LinkModules (addToUDFM old mod_name lmod))
+      Nothing -> Just (LinkModules (unitUDFM mod_name lmod))
+
+    with_deps acc iface local action =
+      pure (addListToUDFM acc link, new_local ++ new_package, Just action)
+      where
+        !(!link, !new_package) = package_deps iface
+        new_local = if local then local_deps iface else []
+
+    local_deps iface =
+      [
+        LinkExternal LinkAllDeps (mkModule mod_unit m)
+        | (_, GWIB m _) <- Set.toList (dep_direct_mods (mi_deps iface))
+      ]
+
+    -- If bytecode linking of external dependencies is enabled, add them to the
+    -- jobs passed to the next iteration of 'external_deps_loop'.
+    -- Otherwise, link all package deps as libraries.
+    package_deps iface
+      | package_bc
+      = ([], [LinkExternal LinkAllDeps m | m <- Set.toList (dep_direct_pkg_mods (mi_deps iface))])
+      | otherwise
+      = ([(u, LinkLibrary u) | u <- Set.toList (dep_direct_pkgs (mi_deps iface))], [])
+
+    load_reason =
+      text "need to link module" <+> ppr mod <+>
+      text "due to use of Template Haskell"
+
+    package_bc = ldPkgByteCode opts
+
+    -- In multiple home unit mode, this only considers modules from the same
+    -- unit as the splice's module to be eligible for linking bytecode when
+    -- @-fpackage-db-byte-code@ is off.
+    -- For make mode, this is irrelevant, since any bytecode from the HUG is
+    -- obtained directly, not going through 'external_deps'.
+    is_home
+      | Just home <- ue_homeUnit (ldUnitEnv opts)
+      = homeUnitAsUnit home == mod_unit
+      | otherwise
+      = False
+
+    mod_dep = lookupUDFM acc mod_unit_id
+    mod_name = moduleName mod
+    mod_unit_id = moduleUnitId mod
+    mod_unit = moduleUnit mod
+
+link_boot_mod_error :: Module -> SDoc
+link_boot_mod_error mod =
+  text "module" <+> ppr mod <+>
+  text "cannot be linked; it is only available as a boot module"
+
+-- | Split link dependencies into the sets of modules and packages that have
+-- been linked previously and those that need to be linked now by checking for
+-- their presence in the 'LoaderState':
+--
+-- - For module dependencies, in the sets of loaded objects and BCOs
+--   ('objs_loaded' and 'bcos_loaded')
+-- - For package dependencies, in the set of loaded packages ('pkgs_loaded')
+classify_deps ::
+  LoaderState ->
+  [HomeModInfo] ->
+  [LinkDep] ->
+  ([Linkable], [LinkModule], UniqDSet UnitId, [UnitId])
+classify_deps pls hmis deps =
+  (loaded_modules' ++ loaded_modules'', needed_modules' ++ needed_modules'', all_packages, needed_packages)
+  where
+    (loaded_modules', needed_modules') = partitionWith loaded_or_needed_home_module hmis
+    (loaded_modules'', needed_modules'') =
+      partitionWith loaded_or_needed_module (concatMap eltsUDFM modules)
+
+    needed_packages =
+      eltsUDFM (getUniqDSet all_packages `minusUDFM` pkgs_loaded pls)
+
+    all_packages = mkUniqDSet packages
+
+    (modules, packages) = flip partitionWith deps $ \case
+      LinkModules mods -> Left mods
+      LinkLibrary lib -> Right lib
+
+    loaded_or_needed_home_module lm =
+      maybe (Right (LinkHomeModule lm)) Left (loaded_module (mi_module (hm_iface lm)))
+
+    loaded_or_needed_module lm =
+      maybe (Right lm) Left (loaded_module (link_module lm))
+
+    loaded_module mod =
+      lookupModuleEnv (objs_loaded pls) mod
+      <|>
+      lookupModuleEnv (bcos_loaded pls) mod
 
 {-
 Note [Using Byte Code rather than Object Code for Template Haskell]


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -77,11 +77,13 @@ import GHC.Utils.TmpFs
 
 import GHC.Unit.Env
 import GHC.Unit.External (ExternalPackageState (EPS, eps_iface_bytecode))
+import GHC.Unit.Finder
 import GHC.Unit.Module
 import GHC.Unit.State as Packages
 
 import qualified GHC.Data.ShortText as ST
 import GHC.Data.FastString
+import qualified GHC.Data.Maybe as Maybe
 
 import GHC.Linker.Deps
 import GHC.Linker.MacOS
@@ -94,6 +96,7 @@ import Control.Monad
 import qualified Data.Set as Set
 import Data.Char (isSpace)
 import qualified Data.Foldable as Foldable
+import Data.Functor ((<&>))
 import Data.IORef
 import Data.List (intercalate, isPrefixOf, nub, partition)
 import Data.Maybe
@@ -231,10 +234,10 @@ loadDependencies interp hsc_env pls span needed_mods = do
    -- Find what packages and linkables are required
    deps <- getLinkDeps opts interp pls span needed_mods
 
-   let this_pkgs_needed = ldNeededUnits deps
+   let this_pkgs_needed = ldAllUnits deps
 
    -- Link the packages and modules required
-   pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
+   pls1 <- loadPackages' interp hsc_env (ldNeededUnits deps) pls
    (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
    let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
        all_pkgs_loaded = pkgs_loaded pls2
@@ -643,21 +646,40 @@ initLinkDepsOpts hsc_env = opts
             , ldModuleGraph = hsc_mod_graph hsc_env
             , ldUnitEnv     = hsc_unit_env hsc_env
             , ldPprOpts     = initSDocContext dflags defaultUserStyle
-            , ldFinderCache = hsc_FC hsc_env
-            , ldFinderOpts  = initFinderOpts dflags
             , ldUseByteCode = gopt Opt_UseBytecodeRatherThanObjects dflags
+            , ldPkgByteCode = gopt Opt_PackageDbBytecode dflags
             , ldMsgOpts     = initIfaceMessageOpts dflags
             , ldWays        = ways dflags
             , ldLoadIface
             , ldLoadByteCode
+            , ldLogger = hsc_logger hsc_env
             }
     dflags = hsc_dflags hsc_env
-    ldLoadIface msg mod = initIfaceCheck (text "loader") hsc_env
-                          $ loadInterface msg mod (ImportByUser NotBoot)
+
+    ldLoadIface msg mod =
+      initIfaceCheck (text "loader") hsc_env (loadInterface msg mod (ImportByUser NotBoot)) >>= \case
+        Maybe.Failed err -> pure (Maybe.Failed err)
+        Maybe.Succeeded iface ->
+          find_location mod <&> \case
+            InstalledFound loc _ -> Maybe.Succeeded (iface, loc)
+            err -> Maybe.Failed $
+                   cannotFindInterface unit_state home_unit
+                   (targetProfile dflags) (moduleName mod) err
+
+    find_location mod =
+      liftIO $
+      findExactModule (hsc_FC hsc_env) (initFinderOpts dflags)
+      other_fopts unit_state home_unit (toUnitId <$> mod)
+
+    other_fopts = initFinderOpts . homeUnitEnv_dflags <$> hsc_HUG hsc_env
+
+    unit_state = hsc_units hsc_env
+
+    home_unit = ue_homeUnit (hsc_unit_env hsc_env)
 
     ldLoadByteCode mod = do
       EPS {eps_iface_bytecode} <- hscEPS hsc_env
-      sequence (lookupModuleEnv eps_iface_bytecode mod)
+      pure (lookupModuleEnv eps_iface_bytecode mod)
 
 
 


=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -753,7 +753,7 @@ mkStubPaths fopts mod location = do
     src_basename = OsPath.dropExtension <$> ml_hs_file_ospath location
 
 -- -----------------------------------------------------------------------------
--- findLinkable isn't related to the other stuff in here,
+-- findObjectLinkable isn't related to the other stuff in here,
 -- but there's no other obvious place for it
 
 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)


=====================================
compiler/GHC/Unit/Module/Deps.hs
=====================================
@@ -4,6 +4,7 @@ module GHC.Unit.Module.Deps
    , mkDependencies
    , noDependencies
    , dep_direct_mods
+   , dep_direct_pkg_mods
    , dep_direct_pkgs
    , dep_sig_mods
    , dep_trusted_pkgs
@@ -35,6 +36,7 @@ import GHC.Utils.Fingerprint
 import GHC.Utils.Binary
 import GHC.Utils.Outputable
 
+import qualified Data.Map.Strict as Map
 import Data.List (sortBy, sort, partition)
 import Data.Set (Set)
 import qualified Data.Set as Set
@@ -99,6 +101,9 @@ data Dependencies = Deps
       -- does NOT include us, unlike 'imp_finsts'. See Note
       -- [The type family instance consistency story].
 
+   -- TODO strict?
+   , dep_direct_pkg_mods :: Set Module
+
    }
    deriving( Eq )
         -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints
@@ -145,6 +150,8 @@ mkDependencies home_unit mod imports plugin_mods =
 
       sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports
 
+      dep_direct_pkg_mods = Set.filter ((homeUnitAsUnit home_unit /=) . moduleUnit) (Map.keysSet (imp_mods imports))
+
   in Deps { dep_direct_mods  = direct_mods
           , dep_direct_pkgs  = direct_pkgs
           , dep_plugin_pkgs  = plugin_units
@@ -155,6 +162,7 @@ mkDependencies home_unit mod imports plugin_mods =
           , dep_finsts       = sortBy stableModuleCmp (imp_finsts imports)
             -- sort to get into canonical order
             -- NB. remember to use lexicographic ordering
+          , dep_direct_pkg_mods
           }
 
 -- | Update module dependencies containing orphans (used by Backpack)
@@ -179,6 +187,7 @@ instance Binary Dependencies where
                       put_ bh (dep_boot_mods deps)
                       put_ bh (dep_orphs deps)
                       put_ bh (dep_finsts deps)
+                      put_ bh (dep_direct_pkg_mods deps)
 
     get bh = do dms <- get bh
                 dps <- get bh
@@ -188,14 +197,16 @@ instance Binary Dependencies where
                 sms <- get bh
                 os <- get bh
                 fis <- get bh
+                dep_direct_pkg_mods <- get bh
                 return (Deps { dep_direct_mods = dms
                              , dep_direct_pkgs = dps
                              , dep_plugin_pkgs = plugin_pkgs
                              , dep_sig_mods = hsigms
                              , dep_boot_mods = sms
                              , dep_trusted_pkgs = tps
-                             , dep_orphs = os,
-                               dep_finsts = fis })
+                             , dep_orphs = os
+                             , dep_finsts = fis
+                             , dep_direct_pkg_mods })
 
 noDependencies :: Dependencies
 noDependencies = Deps
@@ -207,6 +218,7 @@ noDependencies = Deps
   , dep_trusted_pkgs = Set.empty
   , dep_orphs        = []
   , dep_finsts       = []
+  , dep_direct_pkg_mods = Set.empty
   }
 
 -- | Pretty-print unit dependencies


=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -68,7 +68,7 @@ traverses a splice's or GHCi expression's dependencies and collects the needed
 build artifacts, which can be objects or bytecode, depending on the build
 settings.
 
-1. In make mode, all eligible modules are part of the dependency graph.
+1. In make mode, all eligible home modules are part of the dependency graph.
    Their interfaces are loaded unconditionally and in dependency order by the
    compilation manager, and each module's bytecode is prepared before its
    dependents are compiled, in one of two ways:
@@ -88,9 +88,10 @@ settings.
 2. In oneshot mode, which compiles individual modules without a shared home unit
    graph, a previously compiled module is not reprocessed as described for make
    mode above.
-   When 'get_link_deps' encounters a dependency on a local module, it requests
-   its bytecode from the External Package State, who loads the interface
-   on-demand.
+   'get_link_deps' requests the bytecode of dependencies from the External
+   Package State, who loads the interface on-demand.
+   This works for modules in local directories (via @-i@ and @-hidir@) as well
+   as those exposed from a package DB.
 
    Since the EPS stores interfaces for all package dependencies in addition to
    local modules in oneshot mode, it has a substantial memory footprint.
@@ -109,6 +110,18 @@ settings.
    storing the intermediate representation as rehydrated Core bindings, since
    the latter have a significantly greater memory footprint.
 
+3. In both of the above modes, whenever a module from an external package
+   (loaded from a package DB) is encountered, the workflow is the same as for
+   oneshot mode if the flag @-fpackage-db-byte-code@ is enabled; otherwise, object
+   code is loaded.
+   Interfaces for external modules are stored together with local oneshot mode
+   modules, so almost no special treatment is necessary, with the exception of:
+   - When external package modules are compiled, the @InteractiveContext@ in
+     @HscEnv@ is accessed, which is not available due to its impact on retention
+     of outdated build products.
+     This is solved by writing an empty @InteractiveContext@ to the env used for
+     compilation.
+
 Note [Size of Interface Files with Core Definitions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
@@ -210,7 +223,9 @@ If the 'HomeModLinkable' already contains bytecode (case 1), this is a no-op.
 Otherwise, the stub objects from the interface are compiled to objects in
 'generateByteCode' and added to the 'HomeModLinkable' as well.
 
-Case 3 is not implemented yet (!13042).
+In case 3, Core bindings are loaded from the EPS, where stubs only exist in
+their serialized form in the interface, so they must be regenerated like in case
+2.
 
 Problem 3:
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -826,6 +826,17 @@ Options affecting code generation
     will generate byte-code rather than object code.
 
 
+.. ghc-flag:: -fpackage-db-byte-code
+    :shortdesc: Use byte-code from package DB dependencies
+    :type: dynamic
+    :category: codegen
+
+    GHC normally only considers local modules to be eligible for loading
+    bytecode from interfaces for splices with :ghc-flag:`-fprefer-byte-code`.
+    When this flag is specified additionally, bytecode will be loaded from
+    interfaces for all external package dependencies that provide it.
+
+
 .. _options-linker:
 
 Options affecting linking


=====================================
testsuite/tests/bytecode/T25090/Dep.hs
=====================================
@@ -0,0 +1,15 @@
+module Dep where
+
+data A = A Int
+
+used :: Int
+used = 9681
+
+dep :: A
+dep = A used
+
+unused1 :: A
+unused1 = A 1
+
+unused2 :: A
+unused2 = unused1


=====================================
testsuite/tests/bytecode/T25090/DepApi.hs
=====================================
@@ -0,0 +1,7 @@
+module DepApi (A (A), dep) where
+
+import Dep (A (A))
+import qualified Dep
+
+dep :: A
+dep = Dep.dep


=====================================
testsuite/tests/bytecode/T25090/Local.hs
=====================================
@@ -0,0 +1,15 @@
+{-# language PackageImports #-}
+
+module Local where
+
+import GHC.Prim
+import Language.Haskell.TH (ExpQ)
+import Language.Haskell.TH.Syntax (lift)
+-- just to be sure that the file isn't accidentally picked up locally
+import "dep" DepApi (dep, A (A))
+import {-# source #-} Num (num)
+
+splc :: ExpQ
+splc = lift @_ @Int (num + d)
+  where
+    A d = dep


=====================================
testsuite/tests/bytecode/T25090/Makefile
=====================================
@@ -19,3 +19,35 @@ T25090a:
 T25090b:
 	$(TEST_HC) -fbyte-code-and-object-code -fprefer-byte-code A -o exe -v0
 	./exe
+
+DB := -package-db db -package dep
+BASIC := $(TEST_HC_OPTS) $(DB) -this-unit-id=pkgdep -v0
+BC := -fprefer-byte-code -fbyte-code-and-object-code
+ARGS := $(BASIC) $(BC)
+
+T25090_pkg:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_empty:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared-empty"
+	./run.bash "$(TEST_HC)" "$(ARGS) -dynamic"
+
+T25090_pkg_nolib:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "none"
+	./run.bash "$(TEST_HC)" "$(ARGS)"
+
+T25090_pkg_obj_code:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	./run.bash "$(TEST_HC)" "$(BASIC) -dynamic -fbyte-code-and-object-code"
+
+T25090_pkg_multi_unit:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "shared"
+	mkdir -p unit2-src/
+	mv Local.hs Num.hs Num.hs-boot unit2-src/
+	"$(TEST_HC)" $(TEST_HC_OPTS) $(ARGS) -fpackage-db-byte-code -dynamic -unit @unit1 -unit @unit2
+	./PkgBytecode
+
+T25090_pkg_archive:
+	./prep.bash "$(TEST_HC)" "$(TEST_HC_OPTS)" "$(GHC_PKG)" "$(dllext)" "archive"
+	./run.bash "$(TEST_HC)" "$(ARGS)"


=====================================
testsuite/tests/bytecode/T25090/Num.hs
=====================================
@@ -0,0 +1,4 @@
+module Num where
+
+num :: Int
+num = 48332


=====================================
testsuite/tests/bytecode/T25090/Num.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module Num where
+
+num :: Int


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.hs
=====================================
@@ -0,0 +1,12 @@
+{-# language TemplateHaskell #-}
+
+module Main where
+
+import GHC.Prim
+import Local (splc)
+
+a :: Int
+a = $(splc)
+
+main :: IO ()
+main = putStrLn (show a)


=====================================
testsuite/tests/bytecode/T25090/PkgBytecode.stdout
=====================================
@@ -0,0 +1 @@
+58013


=====================================
testsuite/tests/bytecode/T25090/all.T
=====================================
@@ -16,3 +16,36 @@ def test_T25090(name):
 
 test_T25090('T25090a')
 test_T25090('T25090b')
+
+def test_pkg(name, files = []):
+    test(
+        name,
+        [
+            extra_files([
+                'PkgBytecode.hs',
+                'Local.hs',
+                'Dep.hs',
+                'DepApi.hs',
+                'Num.hs',
+                'Num.hs-boot',
+                'dep.conf',
+                'prep.bash',
+                'run.bash',
+            ] + files),
+            req_th,
+            js_skip,
+            windows_skip,
+            use_specs({'stdout': 'PkgBytecode.stdout'}),
+        ],
+        makefile_test,
+        [],
+    )
+
+test_pkg('T25090_pkg')
+test_pkg('T25090_pkg_empty')
+test_pkg('T25090_pkg_nolib')
+test_pkg('T25090_pkg_obj_code')
+test_pkg('T25090_pkg_multi_unit', ['unit1', 'unit2'])
+# TODO this doesn't work, because `locateLib` ignores static archives when the interpreter is dynamic, even though a
+# comment says "search for .so libraries _first_" (rather than "only").
+# test_pkg('T25090_pkg_archive')


=====================================
testsuite/tests/bytecode/T25090/dep.conf
=====================================
@@ -0,0 +1,8 @@
+name: dep
+version: 1.0
+id: dep-1.0
+key: dep-1.0
+exposed: True
+exposed-modules: DepApi
+import-dirs: ${pkgroot}/dep
+library-dirs: ${pkgroot}/dep


=====================================
testsuite/tests/bytecode/T25090/prep.bash
=====================================
@@ -0,0 +1,59 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+ghc_pkg_cmd="$3"
+so_ext="$4"
+library="$5"
+
+base="$PWD"
+db="$base/db"
+dep="$base/dep"
+conf_dep="${dep}/dep.conf"
+
+mkdir -p "$dep" "$db"
+mv Dep.hs DepApi.hs "$dep/"
+cp dep.conf "$dep/"
+
+ghc_pkg()
+{
+  eval "${ghc_pkg_cmd at Q} --no-user-package-db --package-db=${db at Q} $@"
+}
+
+ghc()
+{
+  eval "${ghc_cmd at Q} ${ghc_opts/-rtsopts/} -package-db ${db at Q} -hidir ${dep at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code $@"
+}
+
+version=$(ghc "--numeric-version")
+
+ghc_pkg recache
+
+ghc "-c ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+ghc "-dynamic -c -osuf dyn_o -hisuf dyn_hi ${dep at Q}/Dep.hs ${dep at Q}/DepApi.hs"
+
+if [[ "$library" == 'shared' ]]
+then
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} ${dep at Q}/Dep.dyn_o ${dep at Q}/DepApi.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'shared-empty' ]]
+then
+  echo 'module Dummy where' > Dummy.hs
+  ghc "-dynamic-too -c Dummy.hs"
+  ghc "-dynamic -shared -o ${dep at Q}/libHSdep-1.0-ghc${version}${so_ext} Dummy.dyn_o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'archive' ]]
+then
+  $AR cqs "${dep}/libHSdep-1.0.a" "${dep}/Dep.o" "${dep}/DepApi.o"
+  echo 'hs-libraries: HSdep-1.0' >> "$conf_dep"
+elif [[ "$library" == 'none' ]]
+then
+  :
+else
+  echo "Invalid argument for 'library': $library"
+  exit 1
+fi
+
+ghc_pkg -v0 register "${conf_dep at Q}"


=====================================
testsuite/tests/bytecode/T25090/run.bash
=====================================
@@ -0,0 +1,16 @@
+#!/usr/bin/env bash
+
+set -eu
+
+ghc_cmd="$1"
+ghc_opts="$2"
+
+ghc()
+{
+  eval "${ghc_cmd at Q} $ghc_opts $@"
+}
+
+ghc -c Num.hs-boot Num.hs Local.hs
+ghc -fpackage-db-byte-code -c PkgBytecode.hs
+ghc PkgBytecode.o -o PkgBytecode
+./PkgBytecode


=====================================
testsuite/tests/bytecode/T25090/unit1
=====================================
@@ -0,0 +1 @@
+-i -i. PkgBytecode -this-unit-id unit1 -package-id unit2


=====================================
testsuite/tests/bytecode/T25090/unit2
=====================================
@@ -0,0 +1 @@
+-i -i./unit2-src Local Num -this-unit-id unit2



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca0cef6d45cef6ff7cf5ff772b82207f02f845fa...f3c844d266353e0d6faaf90c092eace5afa60e3c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca0cef6d45cef6ff7cf5ff772b82207f02f845fa...f3c844d266353e0d6faaf90c092eace5afa60e3c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 20:16:58 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 16:16:58 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: JS: Re-add
 optimization for literal strings in genApp (fixes #23479)
Message-ID: <672142ba19a04_3d5b163e22b842824@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
020ad8d6 by Serge S. Gulin at 2024-10-29T16:16:50-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
f75f7ff7 by Cheng Shao at 2024-10-29T16:16:50-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
dd7b0f40 by Cheng Shao at 2024-10-29T16:16:51-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
9d563c49 by Cheng Shao at 2024-10-29T16:16:51-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -


30 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- rts/js/string.js
- + testsuite/tests/ghci/scripts/T25414.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- testsuite/tests/javascript/T24495.hs
- testsuite/tests/javascript/T24495.stdout


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d5e7990ca9637ebee2293b22815fa0c393231baf...9d563c4969598d1630709d67bf3a1f01e645bb18

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d5e7990ca9637ebee2293b22815fa0c393231baf...9d563c4969598d1630709d67bf3a1f01e645bb18
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 20:42:44 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Tue, 29 Oct 2024 16:42:44 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <672148c432dd_3d5b1665467c529e9@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
4eb45adb by Ben Gamari at 2024-10-29T16:42:29-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

 * `version=9.13` while `RELEASE=YES` since this would imply a
   release made from an unstable branch
 * `version=9.13.0` since unstable versions should only have two
   components
 * `version=9.12` since this has the wrong number of version components
   for a stable branch

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,22 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$StableRelease" = "1" -a "$NumVersionComponents" != "3"; then
+        AC_MSG_ERROR([Stable (even) version numbers must have three components])
+    elif test "$StableRelease" = "0" -a "$NumVersionComponents" != "3"; then
+        AC_MSG_ERROR([Unstable (odd) version numbers must have two components])
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        AC_MSG_RESULT([okay stable branch version])
+    else
+        AC_MSG_RESULT([okay unstable branch version])
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4eb45adb764b0095e69c2f5fd0c8cb9262064692

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 21:17:39 2024
From: gitlab at gitlab.haskell.org (Hassan Al-Awwadi (@hassan.awwadi))
Date: Tue, 29 Oct 2024 17:17:39 -0400
Subject: [Git][ghc/ghc][wip/ttg/types/basic] redundent import
Message-ID: <672150f3155b6_3d5b1683ec6c58450@gitlab.mail>



Hassan Al-Awwadi pushed to branch wip/ttg/types/basic at Glasgow Haskell Compiler / GHC


Commits:
f623eede by Hassan Al-Awwadi at 2024-10-29T22:17:17+01:00
redundent import

- - - - -


1 changed file:

- utils/haddock/haddock-api/src/Haddock/Types.hs


Changes:

=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -56,7 +56,6 @@ import qualified GHC.Data.Strict as Strict
 import GHC.Driver.Session (Language)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Core.InstEnv (is_dfun_name)
-import GHC.Types.Fixity (Fixity (..))
 import GHC.Types.Name (stableNameCmp)
 import GHC.Types.Name.Occurrence
 import GHC.Types.Name.Reader (RdrName (..))



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 23:00:44 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Tue, 29 Oct 2024 19:00:44 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/az/epa-last-eptokens
Message-ID: <6721691caf38b_543cc2a06701631e@gitlab.mail>



Alan Zimmerman pushed new branch wip/az/epa-last-eptokens at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/epa-last-eptokens
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Tue Oct 29 23:27:24 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Tue, 29 Oct 2024 19:27:24 -0400
Subject: [Git][ghc/ghc][wip/T20264] More progress
Message-ID: <67216f5c72a60_543cc50b72018536@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
a81b6b90 by Simon Peyton Jones at 2024-10-29T23:27:05+00:00
More progress

- - - - -


4 changed files:

- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Tc/TyCl.hs


Changes:

=====================================
compiler/GHC/Core/Opt/SetLevels.hs
=====================================
@@ -89,12 +89,9 @@ import GHC.Core
 import GHC.Core.Opt.Monad ( FloatOutSwitches(..) )
 import GHC.Core.Utils
 import GHC.Core.Opt.Arity   ( exprBotStrictness_maybe, isOneShotBndr )
-import GHC.Core.TyCo.FVs    ( tyCoVarsOfTypeDSet, scopedSort )
-import GHC.Core.TyCo.Subst  ( substTy, mkTvSubstPrs )
-import GHC.Core.FVs     -- all of it
+import GHC.Core.FVs
 import GHC.Core.Subst
-import GHC.Core.Type    ( Type, tyCoVarsOfType, mightBeUnliftedType, typeHasFixedRuntimeRep )
-import GHC.Core.Multiplicity     ( pattern ManyTy )
+import GHC.Core.Type
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
@@ -1783,10 +1780,9 @@ mkAbsLamTypes abs_vars ty
            , text "res" <+> ppr res ]) res
     -- We can apply the subst at the end there is no shadowing in abs_vars
   where
-    res = substTy subst (mkLamTypes abs_lam_vars ty)
+    res = expandTyVarUnfoldings (mkVarEnv tv_unf_prs) (mkLamTypes abs_lam_vars ty)
     abs_lam_vars   = [ v       | v <- abs_vars, isNothing (tyVarUnfolding_maybe v) ]
     tv_unf_prs = [ (tv,ty) | tv <- abs_vars, Just ty <- [tyVarUnfolding_maybe tv] ]
-    subst = mkTvSubstPrs tv_unf_prs
 
 
 mkAbsVarApps :: Expr LevelledBndr -> AbsVars -> Expr LevelledBndr


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -173,7 +173,7 @@ module GHC.Core.Type (
         anyFreeVarsOfType, anyFreeVarsOfTypes,
         noFreeVarsOfType,
         expandTypeSynonyms, expandSynTyConApp_maybe,
-        typeSize, occCheckExpand,
+        typeSize, occCheckExpand, expandTyVarUnfoldings,
 
         -- ** Closing over kinds
         closeOverKindsDSet, closeOverKindsList,
@@ -292,6 +292,7 @@ import GHC.Utils.Panic
 import GHC.Data.FastString
 
 import GHC.Data.Maybe   ( orElse, isJust, firstJust )
+import Data.Functor.Identity
 
 -- $type_classification
 -- #type_classification#
@@ -506,6 +507,28 @@ on its fast path must also be inlined, linked back to this Note.
 *                                                                      *
 ********************************************************************* -}
 
+expandTyVarUnfoldings :: TyVarEnv Type -> Type -> Type
+-- (expandTyvarUnfoldings tvs ty) replace any occurrences of tvs in ty
+-- with their unfoldings.  There are no substitution or variable-capture
+-- issues: if we have (let @a = ty in body), then at all occurrences of `a`
+-- the free vars of `body` are also in scope, without having been shadowed.
+expandTyVarUnfoldings tvs ty
+  | isEmptyVarEnv tvs = ty
+  | otherwise         = runIdentity (expand ty)
+  where
+    expand :: Type -> Identity Type
+    (expand, _, _, _)
+       = mapTyCo (TyCoMapper { tcm_tyvar = exp_tv, tcm_covar = exp_cv
+                             , tcm_hole = exp_hole, tcm_tycobinder = exp_tcb
+                             , tcm_tycon = pure })
+    exp_tv _ tv = case lookupVarEnv tvs tv of
+                      Just ty -> pure ty
+                      Nothing -> pure (TyVarTy tv)
+    exp_cv _   cv = pure (CoVarCo cv)
+    exp_hole _ cv = pprPanic "expand_tv_unf" (ppr cv)
+    exp_tcb :: () -> TyCoVar -> ForAllTyFlag -> (() -> TyCoVar -> Identity r) -> Identity r
+    exp_tcb _ tcv _ k = k () (updateVarType (runIdentity . expand) tcv)
+
 expandTypeSynonyms :: Type -> Type
 -- ^ Expand out all type synonyms.  Actually, it'd suffice to expand out
 -- just the ones that discard type variables (e.g.  type Funny a = Int)


=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -130,21 +130,27 @@ exprType :: HasDebugCallStack => CoreExpr -> Type
 -- ^ Recover the type of a well-typed Core expression. Fails when
 -- applied to the actual 'GHC.Core.Type' expression as it cannot
 -- really be said to have a type
-exprType (Var var)           = idType var
-exprType (Lit lit)           = literalType lit
-exprType (Coercion co)       = coercionType co
-exprType (Let bind body)
-  | NonRec tv rhs <- bind    -- See Note [Type bindings]
-  , Type ty <- rhs           = substTyWithUnchecked [tv] [ty] (exprType body)
-  | otherwise                = exprType body
-exprType (Case _ _ ty _)     = ty
-exprType (Cast _ co)         = coercionRKind co
-exprType (Tick _ e)          = exprType e
-exprType (Lam binder expr)   = mkLamType binder (exprType expr)
-exprType e@(App _ _)
-  = case collectArgs e of
-        (fun, args) -> applyTypeToArgs (exprType fun) args
-exprType (Type ty) = pprPanic "exprType" (ppr ty)
+exprType e = go emptyVarEnv e
+  where
+      -- When we get to a type, expand locally-bound tyvars, if any
+    expand = expandTyVarUnfoldings
+
+    go tvs (Var var)         = expand tvs $ idType var
+    go tvs (Lit lit)         = expand tvs $ literalType lit
+    go tvs (Coercion co)     = expand tvs $ coercionType co
+    go tvs (Let bind body)
+      | NonRec tv rhs <- bind    -- See Note [Type bindings]
+      , Type ty <- rhs       = go (extendVarEnv tvs tv ty) body
+      | otherwise            = go tvs body
+    go tvs (Case _ _ ty _)   = expand tvs ty
+    go tvs (Cast _ co)       = expand tvs $ coercionRKind co
+    go tvs (Tick _ e)        = go tvs e
+    go tvs (Lam binder expr) = mkLamType (updateVarType (expand tvs) binder)
+                                         (go tvs expr)
+    go tvs e@(App _ _)
+      = case collectArgs e of
+            (fun, args) -> expand tvs $ applyTypeToArgs (exprType fun) args
+    go _ (Type ty) = pprPanic "exprType" (ppr ty)
 
 coreAltType :: CoreAlt -> Type
 -- ^ Returns the type of the alternatives right hand side
@@ -1273,6 +1279,9 @@ and that confuses the code generator (#11155). So best to kill
 it off at source.
 -}
 
+coercionIsTrivial :: Coercion -> Bool
+coercionIsTrivial co = coercionSize co < 10    -- Try this out
+
 {-# INLINE trivial_expr_fold #-}
 trivial_expr_fold :: (Id -> r) -> (Literal -> r) -> r -> r -> CoreExpr -> r
 -- ^ The worker function for Note [exprIsTrivial] and Note [getIdFromTrivialExpr]
@@ -1294,14 +1303,14 @@ trivial_expr_fold k_id k_lit k_triv k_not_triv = go
     -- If you change this function, be sure to change SetLevels.notWorthFloating
     -- as well!
     -- (Or yet better: Come up with a way to share code with this function.)
-    go (Var v)                            = k_id v  -- See Note [Variables are trivial]
-    go (Lit l)    | litIsTrivial l        = k_lit l
-    go (Type _)                           = k_triv
-    go (Coercion _)                       = k_triv
-    go (App f t)  | not (isRuntimeArg t)  = go f
-    go (Lam b e)  | not (isRuntimeVar b)  = go e
-    go (Tick t e) | not (tickishIsCode t) = go e              -- See Note [Tick trivial]
-    go (Cast e _)                         = go e
+    go (Var v)                              = k_id v  -- See Note [Variables are trivial]
+    go (Lit l)    | litIsTrivial l          = k_lit l
+    go (Type _)                             = k_triv
+    go (Coercion co) | coercionIsTrivial co = k_triv
+    go (App f t)     | not (isRuntimeArg t) = go f
+    go (Lam b e)     | not (isRuntimeVar b) = go e
+    go (Tick t e)    | not (tickishIsCode t)= go e              -- See Note [Tick trivial]
+    go (Cast e co)   | coercionIsTrivial co = go e
     go (Case e b _ as)
       | null as
       = go e     -- See Note [Empty case is trivial]


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -3646,11 +3646,10 @@ tcConDecl new_or_data dd_info rep_tycon tc_bndrs res_kind tag_map
              -- we're only doing this to find the right kind variables to
              -- quantify over, and this type is fine for that purpose.
 
-         -- exp_tvbndrs have explicit, user-written binding sites
-         -- the kvs below are those kind variables entirely unmentioned by the user
-         --   and discovered only by generalization
-
        ; kvs <- kindGeneralizeAll skol_info fake_ty
+             -- exp_tvbndrs have explicit, user-written binding sites
+             -- These `kvs` below are those kind variables entirely unmentioned
+             -- by the user and discovered only by generalization
 
        ; let all_skol_tvs = tc_tvs ++ kvs
        ; reportUnsolvedEqualities skol_info all_skol_tvs tclvl wanted
@@ -3661,7 +3660,7 @@ tcConDecl new_or_data dd_info rep_tycon tc_bndrs res_kind tag_map
              -- But that just doesn't seem worth it.
              -- See test dependent/should_fail/T13780a
 
-       -- Zonk to Types
+       -- Zonk to TyvVars and Types, instead of TcTyVars and TcTypes
        ; (tc_bndrs, kvs, exp_tvbndrs, arg_tys, ctxt) <- initZonkEnv NoFlexi $
          runZonkBndrT (zonkTyVarBindersX tc_bndrs   ) $ \ tc_bndrs ->
          runZonkBndrT (zonkTyBndrsX      kvs        ) $ \ kvs ->



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 03:17:39 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 23:17:39 -0400
Subject: [Git][ghc/ghc][master] JS: Re-add optimization for literal strings in
 genApp (fixes #23479)
Message-ID: <6721a553e54c9_33f8b411ad8c830e@gitlab.mail>



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


Commits:
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -


27 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- rts/js/string.js
- testsuite/tests/javascript/Makefile
- + testsuite/tests/javascript/T23479_1.hs
- + testsuite/tests/javascript/T23479_1.stdout
- + testsuite/tests/javascript/T23479_2.hs
- + testsuite/tests/javascript/T23479_2.stdout
- testsuite/tests/javascript/T24495.hs
- testsuite/tests/javascript/T24495.stdout
- testsuite/tests/javascript/all.T


Changes:

=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -522,6 +522,8 @@ basicKnownKeyNames
         , unsafeEqualityTyConName
         , unsafeReflDataConName
         , unsafeCoercePrimName
+
+        , unsafeUnpackJSStringUtf8ShShName
     ]
 
 genericTyConNames :: [Name]
@@ -590,7 +592,8 @@ gHC_INTERNAL_BASE, gHC_INTERNAL_ENUM,
     gHC_INTERNAL_ARROW, gHC_INTERNAL_DESUGAR, gHC_INTERNAL_RANDOM, gHC_INTERNAL_EXTS, gHC_INTERNAL_IS_LIST,
     gHC_INTERNAL_CONTROL_EXCEPTION_BASE, gHC_INTERNAL_TYPEERROR, gHC_INTERNAL_TYPELITS, gHC_INTERNAL_TYPELITS_INTERNAL,
     gHC_INTERNAL_TYPENATS, gHC_INTERNAL_TYPENATS_INTERNAL,
-    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR :: Module
+    gHC_INTERNAL_DATA_COERCE, gHC_INTERNAL_DEBUG_TRACE, gHC_INTERNAL_UNSAFE_COERCE, gHC_INTERNAL_FOREIGN_C_CONSTPTR,
+    gHC_INTERNAL_JS_PRIM, gHC_INTERNAL_WASM_PRIM_TYPES :: Module
 gHC_INTERNAL_BASE                   = mkGhcInternalModule (fsLit "GHC.Internal.Base")
 gHC_INTERNAL_ENUM                   = mkGhcInternalModule (fsLit "GHC.Internal.Enum")
 gHC_INTERNAL_GHCI                   = mkGhcInternalModule (fsLit "GHC.Internal.GHCi")
@@ -633,7 +636,7 @@ gHC_INTERNAL_RANDOM                 = mkGhcInternalModule (fsLit "GHC.Internal.S
 gHC_INTERNAL_EXTS                   = mkGhcInternalModule (fsLit "GHC.Internal.Exts")
 gHC_INTERNAL_IS_LIST                = mkGhcInternalModule (fsLit "GHC.Internal.IsList")
 gHC_INTERNAL_CONTROL_EXCEPTION_BASE = mkGhcInternalModule (fsLit "GHC.Internal.Control.Exception.Base")
-gHC_INTERNAL_EXCEPTION_CONTEXT = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
+gHC_INTERNAL_EXCEPTION_CONTEXT      = mkGhcInternalModule (fsLit "GHC.Internal.Exception.Context")
 gHC_INTERNAL_GENERICS               = mkGhcInternalModule (fsLit "GHC.Internal.Generics")
 gHC_INTERNAL_TYPEERROR              = mkGhcInternalModule (fsLit "GHC.Internal.TypeError")
 gHC_INTERNAL_TYPELITS               = mkGhcInternalModule (fsLit "GHC.Internal.TypeLits")
@@ -644,6 +647,8 @@ gHC_INTERNAL_DATA_COERCE            = mkGhcInternalModule (fsLit "GHC.Internal.D
 gHC_INTERNAL_DEBUG_TRACE            = mkGhcInternalModule (fsLit "GHC.Internal.Debug.Trace")
 gHC_INTERNAL_UNSAFE_COERCE          = mkGhcInternalModule (fsLit "GHC.Internal.Unsafe.Coerce")
 gHC_INTERNAL_FOREIGN_C_CONSTPTR     = mkGhcInternalModule (fsLit "GHC.Internal.Foreign.C.ConstPtr")
+gHC_INTERNAL_JS_PRIM                = mkGhcInternalModule (fsLit "GHC.Internal.JS.Prim")
+gHC_INTERNAL_WASM_PRIM_TYPES        = mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")
 
 gHC_INTERNAL_SRCLOC :: Module
 gHC_INTERNAL_SRCLOC = mkGhcInternalModule (fsLit "GHC.Internal.SrcLoc")
@@ -1676,7 +1681,10 @@ constPtrConName =
     tcQual gHC_INTERNAL_FOREIGN_C_CONSTPTR (fsLit "ConstPtr") constPtrTyConKey
 
 jsvalTyConName :: Name
-jsvalTyConName = tcQual (mkGhcInternalModule (fsLit "GHC.Internal.Wasm.Prim.Types")) (fsLit "JSVal") jsvalTyConKey
+jsvalTyConName = tcQual gHC_INTERNAL_WASM_PRIM_TYPES (fsLit "JSVal") jsvalTyConKey
+
+unsafeUnpackJSStringUtf8ShShName :: Name
+unsafeUnpackJSStringUtf8ShShName = varQual gHC_INTERNAL_JS_PRIM (fsLit "unsafeUnpackJSStringUtf8##") unsafeUnpackJSStringUtf8ShShKey
 
 {-
 ************************************************************************
@@ -2082,6 +2090,7 @@ typeSymbolKindConNameKey, typeCharKindConNameKey,
   , typeNatLogTyFamNameKey
   , typeConsSymbolTyFamNameKey, typeUnconsSymbolTyFamNameKey
   , typeCharToNatTyFamNameKey, typeNatToCharTyFamNameKey
+  , exceptionContextTyConKey, unsafeUnpackJSStringUtf8ShShKey
   :: Unique
 typeSymbolKindConNameKey  = mkPreludeTyConUnique 400
 typeCharKindConNameKey    = mkPreludeTyConUnique 401
@@ -2104,9 +2113,10 @@ constPtrTyConKey = mkPreludeTyConUnique 417
 
 jsvalTyConKey = mkPreludeTyConUnique 418
 
-exceptionContextTyConKey :: Unique
 exceptionContextTyConKey = mkPreludeTyConUnique 420
 
+unsafeUnpackJSStringUtf8ShShKey  = mkPreludeMiscIdUnique 805
+
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -470,6 +470,7 @@ data DumpFlag
    | Opt_D_dump_stg_cg        -- ^ STG (after stg2stg)
    | Opt_D_dump_stg_tags      -- ^ Result of tag inference analysis.
    | Opt_D_dump_stg_final     -- ^ Final STG (before cmm gen)
+   | Opt_D_dump_stg_from_js_sinker -- ^ STG after JS sinker
    | Opt_D_dump_call_arity
    | Opt_D_dump_exitify
    | Opt_D_dump_dmdanal


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1516,6 +1516,8 @@ dynamic_flags_deps = [
         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
   , make_ord_flag defGhcFlag "ddump-stg-tags"
         (setDumpFlag Opt_D_dump_stg_tags)
+  , make_ord_flag defGhcFlag "ddump-stg-from-js-sinker"
+        (setDumpFlag Opt_D_dump_stg_from_js_sinker)
   , make_ord_flag defGhcFlag "ddump-call-arity"
         (setDumpFlag Opt_D_dump_call_arity)
   , make_ord_flag defGhcFlag "ddump-exitify"


=====================================
compiler/GHC/StgToJS/Apply.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE LambdaCase #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE BlockArguments #-}
+{-# LANGUAGE ViewPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -46,11 +47,13 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.Id
 import GHC.Types.Id.Info
 import GHC.Types.CostCentre
 import GHC.Types.RepType (mightBeFunTy)
+import GHC.Types.Literal
 
 import GHC.Stg.Syntax
 
@@ -86,7 +89,6 @@ rtsApply cfg = jBlock
      , moveRegs2
      ]
 
-
 -- | Generate an application of some args to an Id.
 --
 -- The case where args is null is common as it's used to generate the evaluation
@@ -98,6 +100,62 @@ genApp
   -> [StgArg]
   -> G (JStgStat, ExprResult)
 genApp ctx i args
+    -- Test case T23479_2
+    -- See: https://github.com/ghcjs/ghcjs/blob/b7711fbca7c3f43a61f1dba526e6f2a2656ef44c/src/Gen2/Generator.hs#L876
+    -- Comment by Luite Stegeman 
+    -- Special cases for JSString literals.
+    -- We could handle unpackNBytes# here, but that's probably not common
+    -- enough to warrant a special case.
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/#note_503978
+    -- Comment by Jeffrey Young  
+    -- We detect if the Id is unsafeUnpackJSStringUtf8## applied to a string literal,
+    -- if so then we convert the unsafeUnpack to a call to h$decode.
+    | [StgVarArg v] <- args
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    -- See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588
+    -- Comment by Josh Meredith  
+    -- `typex_expr` can throw an error for certain bindings so it's important
+    -- that this condition comes after matching on the function name
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = (,ExprInline) . (|=) top . app hdDecodeUtf8Z <$> varsForId v
+
+    -- Test case T23479_1
+    | [StgLitArg (LitString bs)] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , idName i == unsafeUnpackJSStringUtf8ShShName
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = return . (,ExprInline) $ top |= toJExpr d
+
+    -- Test case T24495 with single occurrence at -02 and third occurrence at -01
+    -- Moved back from removal at https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12308
+    -- See commit hash b36ee57bfbecc628b7f0919e1e59b7066495034f
+    --
+    -- Case: unpackCStringAppend# "some string"# str
+    --
+    -- Generates h$appendToHsStringA(str, "some string"), which has a faster
+    -- decoding loop.
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendIdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
+    | [StgLitArg (LitString bs), x] <- args
+    , Just d <- decodeModifiedUTF8 bs
+    , getUnique i == unpackCStringAppendUtf8IdKey
+    , [top] <- concatMap typex_expr (ctxTarget ctx)
+    = do
+        prof <- csProf <$> getSettings
+        let profArg = if prof then [jCafCCS] else []
+        a <- genArg x
+        return ( top |= app "h$appendToHsString" (toJExpr d : a ++ profArg)
+               , ExprInline
+               )
 
     -- let-no-escape
     | Just n <- ctxLneBindingStackSize ctx i


=====================================
compiler/GHC/StgToJS/CodeGen.hs
=====================================
@@ -11,7 +11,7 @@ where
 
 import GHC.Prelude
 
-import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js))
+import GHC.Driver.Flags (DumpFlag (Opt_D_dump_js, Opt_D_dump_stg_from_js_sinker))
 
 import GHC.JS.Ppr
 import GHC.JS.JStg.Syntax
@@ -21,7 +21,7 @@ import GHC.JS.Transform
 import GHC.JS.Optimizer
 
 import GHC.StgToJS.Arg
-import GHC.StgToJS.Sinker
+import GHC.StgToJS.Sinker.Sinker
 import GHC.StgToJS.Types
 import qualified GHC.StgToJS.Object as Object
 import GHC.StgToJS.Utils
@@ -81,7 +81,8 @@ stgToJS logger config stg_binds0 this_mod spt_entries foreign_stubs cccs output_
     -- TODO: avoid top level lifting in core-2-core when the JS backend is
     -- enabled instead of undoing it here
 
-    -- TODO: add dump pass for optimized STG ast for JS
+  putDumpFileMaybe logger Opt_D_dump_stg_from_js_sinker "STG Optimized JS Sinker:" FormatSTG
+    (pprGenStgTopBindings (StgPprOpts False) stg_binds)
 
   (deps,lus) <- runG config this_mod unfloated_binds $ do
     ifProfilingM $ initCostCentres cccs


=====================================
compiler/GHC/StgToJS/Expr.hs
=====================================
@@ -54,6 +54,7 @@ import GHC.StgToJS.Stack
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
 import GHC.StgToJS.Utils
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
 import GHC.Types.CostCentre
 import GHC.Types.Tickish
@@ -76,7 +77,6 @@ import GHC.Core.Opt.Arity (isOneShotBndr)
 import GHC.Core.Type hiding (typeSize)
 
 import GHC.Utils.Misc
-import GHC.Utils.Encoding
 import GHC.Utils.Monad
 import GHC.Utils.Panic
 import GHC.Utils.Outputable (ppr, renderWithContext, defaultSDocContext)
@@ -581,7 +581,7 @@ genCase ctx bnd e at alts l
   , getUnique i == unpackCStringAppendIdKey
   , [StgVarArg b',x] <- args
   , bnd == b'
-  , d <- utf8DecodeByteString bs
+  , Just d <- decodeModifiedUTF8 bs
   , [top] <- concatMap typex_expr (ctxTarget ctx)
   = do
       prof <- csProf <$> getSettings
@@ -590,6 +590,21 @@ genCase ctx bnd e at alts l
       return ( top |= app "h$appendToHsStringA" (toJExpr d : a ++ profArg)
              , ExprInline
              )
+  | StgLit (LitString bs) <- e
+  , [GenStgAlt DEFAULT _ rhs] <- alts
+  , StgApp i args <- rhs
+  , getUnique i == unpackCStringAppendUtf8IdKey
+  , [StgVarArg b',x] <- args
+  , bnd == b'
+  , Just d <- decodeModifiedUTF8 bs
+  , [top] <- concatMap typex_expr (ctxTarget ctx)
+  = do
+      prof <- csProf <$> getSettings
+      let profArg = if prof then [jCafCCS] else []
+      a <- genArg x
+      return ( top |= app "h$appendToHsString" (toJExpr d : a ++ profArg)
+             , ExprInline
+             )
 
   | isInlineExpr e = do
       bndi <- identsForId bnd


=====================================
compiler/GHC/StgToJS/ExprCtx.hs
=====================================
@@ -86,6 +86,16 @@ data ExprCtx = ExprCtx
 
   }
 
+instance Outputable ExprCtx where
+  ppr g = hang (text "ExprCtx") 2 $ vcat
+            [ hcat [text "ctxTop: ", ppr (ctxTop g)]
+            , hcat [text "ctxTarget:", ppr (ctxTarget g)]
+            , hcat [text "ctxSrcSpan:", ppr (ctxSrcSpan g)]
+            , hcat [text "ctxLneFrameBs:", ppr (ctxLneFrameBs g)]
+            , hcat [text "ctxLneFrameVars:", ppr (ctxLneFrameVars g)]
+            , hcat [text "ctxLneFrameSize:", ppr (ctxLneFrameSize g)]
+            ]
+
 -- | Initialize an expression context in the context of the given top-level
 -- binding Id
 initExprCtx :: Id -> ExprCtx


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -548,6 +548,16 @@ data ModuleCode = ModuleCode
   , mc_frefs    :: ![ForeignJSRef]
   }
 
+instance Outputable ModuleCode where
+  ppr m = hang (text "ModuleCode") 2 $ vcat
+            [ hcat [text "Module: ", ppr (mc_module m)]
+            , hcat [text "JS Code:", pretty True (mc_js_code m)]
+            , hcat [text "JS Exports:", pprHsBytes (mc_exports m)]
+            , hang (text "JS Closures::") 2 (vcat (fmap (text . show) (mc_closures m)))
+            , hang (text "JS Statics::") 2 (vcat (fmap (text . show) (mc_statics m)))
+            , hang (text "JS ForeignRefs::") 2 (vcat (fmap (text . show) (mc_frefs m)))
+            ]
+
 -- | ModuleCode after link with other modules.
 --
 -- It contains less information than ModuleCode because they have been commoned


=====================================
compiler/GHC/StgToJS/Literal.hs
=====================================
@@ -18,8 +18,8 @@ import GHC.StgToJS.Ids
 import GHC.StgToJS.Monad
 import GHC.StgToJS.Symbols
 import GHC.StgToJS.Types
+import GHC.StgToJS.Linker.Utils (decodeModifiedUTF8)
 
-import GHC.Data.FastString
 import GHC.Types.Literal
 import GHC.Types.Basic
 import GHC.Types.RepType
@@ -95,9 +95,10 @@ genLit = \case
 genStaticLit :: Literal -> G [StaticLit]
 genStaticLit = \case
   LitChar c                -> return [ IntLit (fromIntegral $ ord c) ]
-  LitString str
-    | True                 -> return [ StringLit (mkFastStringByteString str), IntLit 0]
-    -- \|  invalid UTF8         -> return [ BinLit str, IntLit 0]
+  LitString str -> case decodeModifiedUTF8 str of
+    Just t                 -> return [ StringLit t, IntLit 0]
+    -- invalid UTF8
+    Nothing                -> return [ BinLit str, IntLit 0]
   LitNullAddr              -> return [ NullLit, IntLit 0 ]
   LitNumber nt v           -> case nt of
     LitNumInt     -> return [ IntLit v ]


=====================================
compiler/GHC/StgToJS/Monad.hs
=====================================
@@ -31,6 +31,7 @@ import GHC.JS.Transform
 import GHC.StgToJS.Types
 
 import GHC.Unit.Module
+import GHC.Utils.Outputable
 import GHC.Stg.Syntax
 
 import GHC.Types.SrcLoc
@@ -159,6 +160,13 @@ data GlobalOcc = GlobalOcc
   , global_count :: !Word
   }
 
+instance Outputable GlobalOcc where
+  ppr g = hang (text "GlobalOcc") 2 $ vcat
+            [ hcat [text "Ident: ", ppr (global_ident g)]
+            , hcat [text "Id:", ppr (global_id g)]
+            , hcat [text "Count:", ppr (global_count g)]
+            ]
+
 -- | Return number of occurrences of every global id used in the given JStgStat.
 -- Sort by increasing occurrence count.
 globalOccs :: JStgStat -> G [GlobalOcc]


=====================================
compiler/GHC/StgToJS/Sinker/Collect.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE LambdaCase #-}
+
+module GHC.StgToJS.Sinker.Collect
+  ( collectArgsTop
+  , collectArgs
+  , selectUsedOnce
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Unique
+
+-- | fold over all id in StgArg used at the top level in an StgRhsCon
+collectArgsTop :: CgStgBinding -> [Id]
+collectArgsTop = \case
+  StgNonRec _b r -> collectArgsTopRhs r
+  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
+  where
+    collectArgsTopRhs :: CgStgRhs -> [Id]
+    collectArgsTopRhs = \case
+      StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
+      StgRhsClosure {}                        -> []
+
+-- | fold over all Id in StgArg in the AST
+collectArgs :: CgStgBinding -> [Id]
+collectArgs = \case
+  StgNonRec _b r -> collectArgsR r
+  StgRec bs      -> concatMap (collectArgsR . snd) bs
+  where
+    collectArgsR :: CgStgRhs -> [Id]
+    collectArgsR = \case
+      StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
+      StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
+
+    collectArgsAlt :: CgStgAlt -> [Id]
+    collectArgsAlt alt = collectArgsE (alt_rhs alt)
+
+    collectArgsE :: CgStgExpr -> [Id]
+    collectArgsE = \case
+      StgApp x args
+        -> x : concatMap collectArgsA args
+      StgConApp _con _mn args _ts
+        -> concatMap collectArgsA args
+      StgOpApp _x args _t
+        -> concatMap collectArgsA args
+      StgCase e _b _a alts
+        -> collectArgsE e ++ concatMap collectArgsAlt alts
+      StgLet _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgLetNoEscape _x b e
+        -> collectArgs b ++ collectArgsE e
+      StgTick _i e
+        -> collectArgsE e
+      StgLit _
+        -> []
+
+collectArgsA :: StgArg -> [Id]
+collectArgsA = \case
+  StgVarArg i -> [i]
+  StgLitArg _ -> []
+
+selectUsedOnce :: (Foldable t, Uniquable a) => t a -> UniqSet a
+selectUsedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
+  where
+    g i t@(once, mult)
+      | i `elementOfUniqSet` mult = t
+      | i `elementOfUniqSet` once
+        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
+      | otherwise = (addOneToUniqSet once i, mult)


=====================================
compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
=====================================
@@ -2,7 +2,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE LambdaCase #-}
 
-module GHC.StgToJS.Sinker (sinkPgm) where
+module GHC.StgToJS.Sinker.Sinker (sinkPgm) where
 
 import GHC.Prelude
 import GHC.Types.Unique.Set
@@ -14,6 +14,8 @@ import GHC.Types.Name
 import GHC.Unit.Module
 import GHC.Types.Literal
 import GHC.Data.Graph.Directed
+import GHC.StgToJS.Sinker.Collect
+import GHC.StgToJS.Sinker.StringsUnfloat
 
 import GHC.Utils.Misc (partitionWith)
 import GHC.StgToJS.Utils
@@ -21,7 +23,7 @@ import GHC.StgToJS.Utils
 import Data.Char
 import Data.List (partition)
 import Data.Maybe
-
+import Data.ByteString (ByteString)
 
 -- | Unfloat some top-level unexported things
 --
@@ -34,27 +36,43 @@ import Data.Maybe
 sinkPgm :: Module
         -> [CgStgTopBinding]
         -> (UniqFM Id CgStgExpr, [CgStgTopBinding])
-sinkPgm m pgm = (sunk, map StgTopLifted pgm'' ++ stringLits)
+sinkPgm m pgm
+  = (sunk, map StgTopLifted pgm''' ++ stringLits)
   where
-    selectLifted (StgTopLifted b) = Left b
-    selectLifted x                = Right x
-    (pgm', stringLits) = partitionWith selectLifted pgm
-    (sunk, pgm'')      = sinkPgm' m pgm'
+    selectLifted :: CgStgTopBinding -> Either CgStgBinding (Id, ByteString)
+    selectLifted (StgTopLifted b)      = Left b
+    selectLifted (StgTopStringLit i b) = Right (i, b)
+
+    (pgm', allStringLits) = partitionWith selectLifted pgm
+    usedOnceIds = selectUsedOnce $ concatMap collectArgs pgm'
+
+    stringLitsUFM = listToUFM $ (\(i, b) -> (idName i, (i, b))) <$> allStringLits
+    (pgm'', _actuallyUnfloatedStringLitNames) =
+      unfloatStringLits
+        (idName `mapUniqSet` usedOnceIds)
+        (snd `mapUFM` stringLitsUFM)
+        pgm'
+
+    stringLits = uncurry StgTopStringLit <$> allStringLits
+
+    (sunk, pgm''') = sinkPgm' m usedOnceIds pgm''
 
 sinkPgm'
   :: Module
        -- ^ the module, since we treat definitions from the current module
        -- differently
+  -> IdSet
+       -- ^ the set of used once ids
   -> [CgStgBinding]
        -- ^ the bindings
   -> (UniqFM Id CgStgExpr, [CgStgBinding])
        -- ^ a map with sunken replacements for nodes, for where the replacement
        -- does not fit in the 'StgBinding' AST and the new bindings
-sinkPgm' m pgm =
-  let usedOnce = collectUsedOnce pgm
+sinkPgm' m usedOnceIds pgm =
+  let usedOnce = collectTopLevelUsedOnce usedOnceIds pgm
       sinkables = listToUFM $
           concatMap alwaysSinkable pgm ++
-          filter ((`elementOfUniqSet` usedOnce) . fst) (concatMap (onceSinkable m) pgm)
+          concatMap (filter ((`elementOfUniqSet` usedOnce) . fst) . onceSinkable m) pgm
       isSunkBind (StgNonRec b _e) | elemUFM b sinkables = True
       isSunkBind _                                      = False
   in (sinkables, filter (not . isSunkBind) $ topSortDecls m pgm)
@@ -95,66 +113,10 @@ onceSinkable _ _ = []
 
 -- | collect all idents used only once in an argument at the top level
 --   and never anywhere else
-collectUsedOnce :: [CgStgBinding] -> IdSet
-collectUsedOnce binds = intersectUniqSets (usedOnce args) (usedOnce top_args)
+collectTopLevelUsedOnce :: IdSet -> [CgStgBinding] -> IdSet
+collectTopLevelUsedOnce usedOnceIds binds = intersectUniqSets usedOnceIds (selectUsedOnce top_args)
   where
     top_args = concatMap collectArgsTop binds
-    args     = concatMap collectArgs    binds
-    usedOnce = fst . foldr g (emptyUniqSet, emptyUniqSet)
-    g i t@(once, mult)
-      | i `elementOfUniqSet` mult = t
-      | i `elementOfUniqSet` once
-        = (delOneFromUniqSet once i, addOneToUniqSet mult i)
-      | otherwise = (addOneToUniqSet once i, mult)
-
--- | fold over all id in StgArg used at the top level in an StgRhsCon
-collectArgsTop :: CgStgBinding -> [Id]
-collectArgsTop = \case
-  StgNonRec _b r -> collectArgsTopRhs r
-  StgRec bs      -> concatMap (collectArgsTopRhs . snd) bs
-
-collectArgsTopRhs :: CgStgRhs -> [Id]
-collectArgsTopRhs = \case
-  StgRhsCon _ccs _dc _mu _ticks args _typ -> concatMap collectArgsA args
-  StgRhsClosure {}                        -> []
-
--- | fold over all Id in StgArg in the AST
-collectArgs :: CgStgBinding -> [Id]
-collectArgs = \case
-  StgNonRec _b r -> collectArgsR r
-  StgRec bs      -> concatMap (collectArgsR . snd) bs
-
-collectArgsR :: CgStgRhs -> [Id]
-collectArgsR = \case
-  StgRhsClosure _x0 _x1 _x2 _x3 e _typ     -> collectArgsE e
-  StgRhsCon _ccs _con _mu _ticks args _typ -> concatMap collectArgsA args
-
-collectArgsAlt :: CgStgAlt -> [Id]
-collectArgsAlt alt = collectArgsE (alt_rhs alt)
-
-collectArgsE :: CgStgExpr -> [Id]
-collectArgsE = \case
-  StgApp x args
-    -> x : concatMap collectArgsA args
-  StgConApp _con _mn args _ts
-    -> concatMap collectArgsA args
-  StgOpApp _x args _t
-    -> concatMap collectArgsA args
-  StgCase e _b _a alts
-    -> collectArgsE e ++ concatMap collectArgsAlt alts
-  StgLet _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgLetNoEscape _x b e
-    -> collectArgs b ++ collectArgsE e
-  StgTick _i e
-    -> collectArgsE e
-  StgLit _
-    -> []
-
-collectArgsA :: StgArg -> [Id]
-collectArgsA = \case
-  StgVarArg i -> [i]
-  StgLitArg _ -> []
 
 isLocal :: Id -> Bool
 isLocal i = isNothing (nameModule_maybe . idName $ i) && not (isExportedId i)


=====================================
compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
=====================================
@@ -0,0 +1,156 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE PatternSynonyms #-}
+
+module GHC.StgToJS.Sinker.StringsUnfloat
+  ( unfloatStringLits
+  )
+  where
+
+import GHC.Prelude
+import GHC.Types.Unique.Set
+import GHC.Types.Unique.FM
+import GHC.Stg.Syntax
+import GHC.Types.Id
+import GHC.Types.Name
+import GHC.Types.Literal
+import GHC.Utils.Misc (partitionWith)
+
+import Data.ByteString qualified as BS
+import Data.ByteString (ByteString)
+import Data.Bifunctor (Bifunctor (..))
+
+-- | We suppose that every string shorter than 80 symbols is safe for sink.
+-- Sinker is working on per module. It means that ALL locally defined strings
+-- in a module shorter 80 symbols will be unfloated back.
+pattern STRING_LIT_MAX_LENGTH :: Int
+pattern STRING_LIT_MAX_LENGTH = 80
+
+unfloatStringLits
+  :: UniqSet Name
+  -> UniqFM Name ByteString
+  -> [CgStgBinding]
+  -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits usedOnceStringLits stringLits =
+  unfloatStringLits' (selectStringLitsForUnfloat usedOnceStringLits stringLits)
+
+-- | We are doing attempts to unfloat string literals back to
+-- the call site. Further special JS optimizations
+-- can generate more performant operations over them.
+unfloatStringLits' :: UniqFM Name ByteString -> [CgStgBinding] -> ([CgStgBinding], UniqSet Name)
+unfloatStringLits' stringLits allBindings = (binderWithoutChanges ++ binderWithUnfloatedStringLit, actuallyUsedStringLitNames)
+  where
+    (binderWithoutChanges, binderWithUnfloatedStringLitPairs) = partitionWith substituteStringLit allBindings
+
+    binderWithUnfloatedStringLit = fst <$> binderWithUnfloatedStringLitPairs
+    actuallyUsedStringLitNames = unionManyUniqSets (snd <$> binderWithUnfloatedStringLitPairs)
+
+    substituteStringLit :: CgStgBinding -> Either CgStgBinding (CgStgBinding, UniqSet Name)
+    substituteStringLit x@(StgRec bnds)
+      | isEmptyUniqSet names = Left x
+      | otherwise = Right (StgRec bnds', names)
+      where
+        (bnds', names) = extractNames id $ do
+          (i, rhs) <- bnds
+          pure $ case processStgRhs rhs of
+            Nothing -> Left (i, rhs)
+            Just (rhs', names) -> Right ((i, rhs'), names)
+    substituteStringLit x@(StgNonRec binder rhs)
+      = maybe (Left x)
+        (\(body', names) -> Right (StgNonRec binder body', names))
+        (processStgRhs rhs)
+
+    processStgRhs :: CgStgRhs -> Maybe (CgStgRhs, UniqSet Name)
+    processStgRhs (StgRhsCon ccs dataCon mu ticks args typ)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgRhsCon ccs dataCon mu ticks unified typ, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgRhs (StgRhsClosure fvs ccs upd bndrs body typ)
+      = (\(body', names) -> (StgRhsClosure fvs ccs upd bndrs body' typ, names)) <$>
+        processStgExpr body
+
+    -- Recursive expressions
+    processStgExpr :: CgStgExpr -> Maybe (CgStgExpr, UniqSet Name)
+    processStgExpr (StgLit _) = Nothing
+    processStgExpr (StgTick _ _) = Nothing
+    processStgExpr (StgLet n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLet n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLet n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLet n b' e', names `unionUniqSets` names')
+    processStgExpr (StgLetNoEscape n b e) =
+      case (substituteStringLit b, processStgExpr e) of
+        (Left _, Nothing) -> Nothing
+        (Right (b', names), Nothing) -> Just (StgLetNoEscape n b' e, names)
+        (Left _, Just (e', names)) -> Just (StgLetNoEscape n b e', names)
+        (Right (b', names), Just (e', names')) -> Just (StgLetNoEscape n b' e', names `unionUniqSets` names')
+    -- We should keep the order: See Note [Case expression invariants]
+    processStgExpr (StgCase e bndr alt_type alts) =
+      case (isEmptyUniqSet names, processStgExpr e) of
+        (True, Nothing) -> Nothing
+        (True, Just (e', names')) -> Just (StgCase e' bndr alt_type alts, names')
+        (False, Nothing) -> Just (StgCase e bndr alt_type unified, names)
+        (False, Just (e', names')) -> Just (StgCase e' bndr alt_type unified, names `unionUniqSets` names')
+      where
+        (unified, names) = extractNames splitAlts alts
+
+        splitAlts :: CgStgAlt -> Either CgStgAlt (CgStgAlt, UniqSet Name)
+        splitAlts alt@(GenStgAlt con bndrs rhs) =
+          case processStgExpr rhs of
+            Nothing -> Left alt
+            Just (alt', names) -> Right (GenStgAlt con bndrs alt', names)
+
+    -- No args
+    processStgExpr (StgApp _ []) = Nothing
+    processStgExpr (StgConApp _ _ [] _) = Nothing
+    processStgExpr (StgOpApp _ [] _) = Nothing
+
+    -- Main targets. Preserving the order of args is important
+    processStgExpr (StgApp fn args@(_:_))
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgApp fn unified, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgConApp dc n args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgConApp dc n unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+    processStgExpr (StgOpApp op args@(_:_) tys)
+      | isEmptyUniqSet names = Nothing
+      | otherwise = Just (StgOpApp op unified tys, names)
+      where
+        (unified, names) = substituteArgWithNames args
+
+    substituteArg :: StgArg -> Either StgArg (StgArg, Name)
+    substituteArg a@(StgLitArg _) = Left a
+    substituteArg a@(StgVarArg i) =
+      let name = idName i
+      in case lookupUFM stringLits name of
+        Nothing -> Left a
+        Just b -> Right (StgLitArg $ LitString b, name)
+
+    substituteArgWithNames = extractNames (second (second unitUniqSet) . substituteArg)
+
+    extractNames :: (a -> Either x (x, UniqSet Name)) -> [a] -> ([x], UniqSet Name)
+    extractNames splitter target =
+      let
+        splitted = splitter <$> target
+        combined = either (, emptyUniqSet) id <$> splitted
+        unified = fst <$> combined
+        names = unionManyUniqSets (snd <$> combined)
+      in (unified, names)
+
+selectStringLitsForUnfloat :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+selectStringLitsForUnfloat usedOnceStringLits stringLits = alwaysUnfloat `plusUFM` usedOnceUnfloat
+  where
+    alwaysUnfloat = alwaysUnfloatStringLits stringLits
+    usedOnceUnfloat = selectUsedOnceStringLits usedOnceStringLits stringLits
+
+    alwaysUnfloatStringLits :: UniqFM Name ByteString -> UniqFM Name ByteString
+    alwaysUnfloatStringLits = filterUFM $ \b -> BS.length b < STRING_LIT_MAX_LENGTH
+
+    selectUsedOnceStringLits :: UniqSet Name -> UniqFM Name ByteString -> UniqFM Name ByteString
+    selectUsedOnceStringLits usedOnceStringLits stringLits =
+      stringLits `intersectUFM` getUniqSet usedOnceStringLits


=====================================
compiler/GHC/StgToJS/Symbols.hs
=====================================
@@ -1215,3 +1215,7 @@ hdStiStr = fsLit "h$sti"
 
 hdStrStr :: FastString
 hdStrStr = fsLit "h$str"
+------------------------------ Pack/Unpack --------------------------------------------
+
+hdDecodeUtf8Z :: FastString
+hdDecodeUtf8Z = fsLit "h$decodeUtf8z"


=====================================
compiler/GHC/StgToJS/Types.hs
=====================================
@@ -284,8 +284,8 @@ instance ToJExpr StaticLit where
   toJExpr (IntLit i)            = toJExpr i
   toJExpr NullLit               = null_
   toJExpr (DoubleLit d)         = toJExpr (unSaneDouble d)
-  toJExpr (StringLit t)         = app hdStrStr [toJExpr t]
-  toJExpr (BinLit b)            = app hdRawStr [toJExpr (map toInteger (BS.unpack b))]
+  toJExpr (StringLit t)         = app hdEncodeModifiedUtf8Str [toJExpr t]
+  toJExpr (BinLit b)            = app hdRawStringDataStr      [toJExpr (map toInteger (BS.unpack b))]
   toJExpr (LabelLit _isFun lbl) = global lbl
 
 -- | A foreign reference to some JS code
@@ -297,6 +297,7 @@ data ForeignJSRef = ForeignJSRef
   , foreignRefArgs     :: ![FastString]
   , foreignRefResult   :: !FastString
   }
+  deriving (Show)
 
 -- | data used to generate one ObjBlock in our object file
 data LinkableUnit = LinkableUnit


=====================================
compiler/GHC/Types/ForeignCall.hs
=====================================
@@ -156,7 +156,7 @@ data CCallConv
   | StdCallConv
   | PrimCallConv
   | JavaScriptCallConv
-  deriving (Eq, Data, Enum)
+  deriving (Show, Eq, Data, Enum)
 
 instance Outputable CCallConv where
   ppr StdCallConv = text "stdcall"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -766,7 +766,9 @@ Library
         GHC.StgToJS.Regs
         GHC.StgToJS.Rts.Types
         GHC.StgToJS.Rts.Rts
-        GHC.StgToJS.Sinker
+        GHC.StgToJS.Sinker.Collect
+        GHC.StgToJS.Sinker.StringsUnfloat
+        GHC.StgToJS.Sinker.Sinker
         GHC.StgToJS.Stack
         GHC.StgToJS.StaticPtr
         GHC.StgToJS.Symbols


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -560,6 +560,11 @@ These flags dump various phases of GHC's STG pipeline.
     Alias for :ghc-flag:`-ddump-stg-from-core`. Deprecated in favor of more explicit
     flags: :ghc-flag:`-ddump-stg-from-core`, :ghc-flag:`-ddump-stg-final`, etc.
 
+.. ghc-flag:: -ddump-stg-from-js-sinker
+    :shortdesc: Show JavaScript sinker output
+    :type: dynamic
+
+    Show the output of JavaScript Sinker pass.
 
 C-\\- representation
 ~~~~~~~~~~~~~~~~~~~~


=====================================
rts/js/string.js
=====================================
@@ -612,6 +612,7 @@ function h$toHsString(str) {
   var i = str.length - 1;
   var r = HS_NIL;
   while(i>=0) {
+    // Used at h$appendToHsString as well
     var cp = str.charCodeAt(i);
     if(cp >= 0xDC00 && cp <= 0xDFFF && i > 0) {
       --i;
@@ -660,6 +661,30 @@ function h$toHsStringA(str) {
     return r;
 }
 
+// unpack utf8 string, append to existing Haskell string
+#ifdef GHCJS_PROF
+function h$appendToHsString(str, appendTo, cc) {
+#else
+function h$appendToHsString(str, appendTo) {
+#endif
+  var i = str.length - 1;
+  // we need to make an updatable thunk here
+  // if we embed the given closure in a CONS cell.
+  // (#24495)
+  var r = i == 0 ? appendTo : MK_UPD_THUNK(appendTo);
+  while(i>=0) {
+    // Copied from h$toHsString
+    var cp = str.charCodeAt(i);
+    if(cp >= 0xDC00 && cp <= 0xDFFF && i > 0) {
+      --i;
+      cp = (cp - 0xDC00) + (str.charCodeAt(i) - 0xD800) * 1024 + 0x10000;
+    }
+    r = MK_CONS_CC(cp, r, cc);
+    --i;
+  }
+  return r;
+}
+
 // convert array with modified UTF-8 encoded text
 #ifdef GHCJS_PROF
 function h$toHsStringMU8(arr, cc) {


=====================================
testsuite/tests/javascript/Makefile
=====================================
@@ -5,5 +5,28 @@ include $(TOP)/mk/test.mk
 T24495:
 	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O1 -dsuppress-uniques -ddump-js -ddump-to-file
 	./T24495
-	# check that the optimization occurred
+	# check that the optimization occurred for -01 3 times (2 for cases + 1 for unfloated lits)
+	grep -c appendToHsStringA T24495.dump-js
+
+	'$(TEST_HC)' $(TEST_HC_OPTS) T24495.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T24495
+	# check that the optimization occurred for -02 1 time (1 for unfloated lits)
 	grep -c appendToHsStringA T24495.dump-js
+
+T23479_1:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_1.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_1
+	# check that the optimization occurred
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_2\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_3\"" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local" T23479_1.dump-js
+	grep -c "h\$$r1 = \"test_val_80_global" T23479_1.dump-js || true
+
+T23479_2:
+	'$(TEST_HC)' $(TEST_HC_OPTS) T23479_2.hs -v0 -O2 -dsuppress-uniques -ddump-js -ddump-to-file
+	./T23479_2
+	grep -c "h\$$r1 = \"test_val_1\"" T23479_2.dump-js
+	grep -c "h\$$r1 = \"test_val_80_local_once" T23479_2.dump-js
+	# check that the optimization occurred
+	grep -c "h\$$r1 = h\$$decodeUtf8z" T23479_2.dump-js


=====================================
testsuite/tests/javascript/T23479_1.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE MagicHash #-}
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+test_val_2 :: String
+test_val_2 = "test_val_2"
+
+test_val_80_global :: String
+test_val_80_global = "test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val"
+
+main :: IO ()
+main = do
+  -- Direct usage
+  js_log1 (JSVal (unsafeUnpackJSStringUtf8## "test_val_1"#))
+  -- Requires string sinker hit for strings shorter 80 symbols
+  js_log1 (toJSString test_val_2)
+  -- Requires rewrite hit "toJSString/literal"
+  js_log1 (toJSString test_val_3)
+  -- Locally defined strings become unfloatted at any length
+  js_log1 (toJSString test_val_80_local)
+  -- Globally defined strings with length >= 80 should not be unfloatted
+  js_log1 (toJSString test_val_80_global)
+  where
+    test_val_3 :: String
+    test_val_3 = "test_val_3"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"


=====================================
testsuite/tests/javascript/T23479_1.stdout
=====================================
@@ -0,0 +1,10 @@
+test_val_1
+test_val_2
+test_val_3
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_80_globaltest_val_80_globaltest_val_80_globaltest_val_80_globaltest_val
+1
+1
+1
+1
+0


=====================================
testsuite/tests/javascript/T23479_2.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.Prim
+import GHC.JS.Prim
+
+foreign import javascript "((x) => { console.log(x); })"
+  js_log1 :: JSVal -> IO ()
+
+main :: IO ()
+main = do
+  -- When long string (>= 80) used once it is unfloatted
+  js_log1 (toJSString test_val_80_local_once)
+
+  -- When long string (>= 80) used more than once no unfloatting happened
+  js_log1 (toJSString test_val_80_local)
+  js_log1 (toJSString (testFn80 "testFn80:"))
+
+  -- Even if short string used more than once it is unfloatted anyway
+  js_log1 (toJSString test_val_1)
+  js_log1 (toJSString (testFn "testFn:"))
+  where
+    test_val_80_local_once :: String
+    test_val_80_local_once = "test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo"
+
+    test_val_80_local :: String
+    test_val_80_local = "test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_"
+
+    testFn80 s = s ++ test_val_80_local
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn80 #-}
+
+    test_val_1 :: String
+    test_val_1 = "test_val_1"
+
+    testFn s = s ++ test_val_1
+    -- We should mark this function as NOINLINE to prevent deeper optimizations for the specific test case
+    {-# NOINLINE testFn #-}


=====================================
testsuite/tests/javascript/T23479_2.stdout
=====================================
@@ -0,0 +1,8 @@
+test_val_80_local_oncetest_val_80_local_oncetest_val_80_local_oncetest_val_80_lo
+test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+testFn80:test_val_80_localtest_val_80_localtest_val_80_localtest_val_80_localtest_val_80_
+test_val_1
+testFn:test_val_1
+1
+1
+1


=====================================
testsuite/tests/javascript/T24495.hs
=====================================
@@ -1,6 +1,6 @@
 {-# LANGUAGE MagicHash #-}
-{-# OPTIONS_GHC -O1 #-}
 -- -O1 required to make "rest" thunk SingleEntry
+-- -O2 shows that it still do one optimization
 
 module Main where
 


=====================================
testsuite/tests/javascript/T24495.stdout
=====================================
@@ -1,2 +1,4 @@
 2 ab bd
-2
+3
+2 ab bd
+1


=====================================
testsuite/tests/javascript/all.T
=====================================
@@ -22,3 +22,6 @@ test('T23346', normal, compile_and_run, [''])
 test('T22455', normal, compile_and_run, ['-ddisable-js-minifier'])
 test('T23565', normal, compile_and_run, [''])
 test('T24495', normal, makefile_test, ['T24495'])
+
+test('T23479_1', normal, makefile_test, ['T23479_1'])
+test('T23479_2', normal, makefile_test, ['T23479_2'])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 03:18:15 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 23:18:15 -0400
Subject: [Git][ghc/ghc][master] compiler: remove unused
 hscDecls/hscDeclsWithLocation
Message-ID: <6721a57746eb8_33f8b412987886115@gitlab.mail>



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


Commits:
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -


1 changed file:

- compiler/GHC/Driver/Main.hs


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -81,7 +81,7 @@ module GHC.Driver.Main
     , hscRnImportDecls
     , hscTcRnLookupRdrName
     , hscStmt, hscParseStmtWithLocation, hscStmtWithLocation, hscParsedStmt
-    , hscDecls, hscParseDeclsWithLocation, hscDeclsWithLocation, hscParsedDecls
+    , hscParseDeclsWithLocation, hscParsedDecls
     , hscParseModuleWithLocation
     , hscTcExpr, TcRnExprMode(..), hscImport, hscKcType
     , hscParseExpr
@@ -2461,12 +2461,6 @@ hscParsedStmt hsc_env stmt = runInteractiveHsc hsc_env $ do
 
   return $ Just (ids, hval, fix_env)
 
--- | Compile a decls
-hscDecls :: HscEnv
-         -> String -- ^ The statement
-         -> IO ([TyThing], InteractiveContext)
-hscDecls hsc_env str = hscDeclsWithLocation hsc_env str "" 1
-
 hscParseModuleWithLocation :: HscEnv -> String -> Int -> String -> IO (HsModule GhcPs)
 hscParseModuleWithLocation hsc_env source line_num str = do
     L _ mod <-
@@ -2479,18 +2473,6 @@ hscParseDeclsWithLocation hsc_env source line_num str = do
   HsModule { hsmodDecls = decls } <- hscParseModuleWithLocation hsc_env source line_num str
   return decls
 
--- | Compile a decls
-hscDeclsWithLocation :: HscEnv
-                     -> String -- ^ The statement
-                     -> String -- ^ The source
-                     -> Int    -- ^ Starting line
-                     -> IO ([TyThing], InteractiveContext)
-hscDeclsWithLocation hsc_env str source linenumber = do
-    L _ (HsModule{ hsmodDecls = decls }) <-
-      runInteractiveHsc hsc_env $
-        hscParseThingWithLocation source linenumber parseModule str
-    hscParsedDecls hsc_env decls
-
 hscParsedDecls :: HscEnv -> [LHsDecl GhcPs] -> IO ([TyThing], InteractiveContext)
 hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
     hsc_env <- getHscEnv



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 03:18:48 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Tue, 29 Oct 2024 23:18:48 -0400
Subject: [Git][ghc/ghc][master] 2 commits: testsuite: add T25414 test case
 marked as broken
Message-ID: <6721a598af290_33f8b45fc88c90636@gitlab.mail>



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


Commits:
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -


4 changed files:

- compiler/GHC/Driver/Main.hs
- compiler/GHC/Linker/Loader.hs
- + testsuite/tests/ghci/scripts/T25414.script
- testsuite/tests/ghci/scripts/all.T


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2507,46 +2507,21 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
     (tidy_cg, mod_details) <- liftIO $ hscTidy hsc_env simpl_mg
 
     let !CgGuts{ cg_module    = this_mod,
-                 cg_binds     = core_binds,
-                 cg_tycons    = tycons,
-                 cg_modBreaks = mod_breaks,
-                 cg_spt_entries = spt_entries
+                 cg_binds     = core_binds
                  } = tidy_cg
 
         !ModDetails { md_insts     = cls_insts
                     , md_fam_insts = fam_insts } = mod_details
             -- Get the *tidied* cls_insts and fam_insts
 
-        data_tycons = filter isDataTyCon tycons
-
-    {- Prepare For Code Generation -}
-    -- Do saturation and convert to A-normal form
-    prepd_binds <- {-# SCC "CorePrep" #-} liftIO $ do
-      cp_cfg <- initCorePrepConfig hsc_env
-      corePrepPgm
-        (hsc_logger hsc_env)
-        cp_cfg
-        (initCorePrepPgmConfig (hsc_dflags hsc_env) (interactiveInScope $ hsc_IC hsc_env))
-        this_mod iNTERACTIVELoc core_binds data_tycons
-
-    (stg_binds_with_deps, _infotable_prov, _caf_ccs__caf_cc_stacks, _stg_cg_info)
-        <- {-# SCC "CoreToStg" #-}
-           liftIO $ myCoreToStg (hsc_logger hsc_env)
-                                (hsc_dflags hsc_env)
-                                (interactiveInScope (hsc_IC hsc_env))
-                                True
-                                this_mod
-                                iNTERACTIVELoc
-                                prepd_binds
-
-    let (stg_binds,_stg_deps) = unzip stg_binds_with_deps
-
-    {- Generate byte code -}
-    cbc <- liftIO $ byteCodeGen hsc_env this_mod
-                                stg_binds data_tycons mod_breaks spt_entries
+    {- Generate byte code & foreign stubs -}
+    linkable <- liftIO $ generateFreshByteCode hsc_env
+      (moduleName this_mod)
+      (mkCgInteractiveGuts tidy_cg)
+      iNTERACTIVELoc
 
     let src_span = srcLocSpan interactiveSrcLoc
-    _ <- liftIO $ loadDecls interp hsc_env src_span cbc
+    _ <- liftIO $ loadDecls interp hsc_env src_span linkable
 
     {- Load static pointer table entries -}
     liftIO $ hscAddSptEntries hsc_env (cg_spt_entries tidy_cg)
@@ -2825,7 +2800,9 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do
                 [] -- spt entries
 
       {- load it -}
-      (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan bcos
+      bco_time <- getCurrentTime
+      (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
+        Linkable bco_time this_mod $ NE.singleton $ BCOs bcos
       {- Get the HValue for the root -}
       return (expectJust "hscCompileCoreExpr'"
          $ lookup (idName binding_id) fv_hvs, mods_needed, units_needed)


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -669,32 +669,40 @@ initLinkDepsOpts hsc_env = opts
 
   ********************************************************************* -}
 
-loadDecls :: Interp -> HscEnv -> SrcSpan -> CompiledByteCode -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
-loadDecls interp hsc_env span cbc at CompiledByteCode{..} = do
+loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
+loadDecls interp hsc_env span linkable = do
     -- Initialise the linker (if it's not been done already)
     initLoaderState interp hsc_env
 
     -- Take lock for the actual work.
     modifyLoaderState interp $ \pls0 -> do
+      -- Link the foreign objects first; BCOs in linkable are ignored here.
+      (pls1, objs_ok) <- loadObjects interp hsc_env pls0 [linkable]
+      when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
+
       -- Link the packages and modules required
-      (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 span needed_mods
+      (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
       if failed ok
         then throwGhcExceptionIO (ProgramError "")
         else do
           -- Link the expression itself
           let le  = linker_env pls
-              le2 = le { itbl_env = plusNameEnv (itbl_env le) bc_itbls
-                       , addr_env = plusNameEnv (addr_env le) bc_strs }
+              le2 = le { itbl_env = foldl' (\acc cbc -> plusNameEnv acc (bc_itbls cbc)) (itbl_env le) cbcs
+                       , addr_env = foldl' (\acc cbc -> plusNameEnv acc (bc_strs cbc)) (addr_env le) cbcs }
 
           -- Link the necessary packages and linkables
-          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 [cbc]
+          new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 cbcs
           nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
           let ce2  = extendClosureEnv (closure_env le2) nms_fhvs
               !pls2 = pls { linker_env = le2 { closure_env = ce2 } }
           return (pls2, (nms_fhvs, links_needed, units_needed))
   where
+    cbcs = linkableBCOs linkable
+
     free_names = uniqDSetToList $
-      foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet bc_bcos
+      foldl'
+        (\acc cbc -> foldl' (\acc' bco -> bcoFreeNames bco `unionUniqDSets` acc') acc (bc_bcos cbc))
+        emptyUniqDSet cbcs
 
     needed_mods :: [Module]
     needed_mods = [ nameModule n | n <- free_names,


=====================================
testsuite/tests/ghci/scripts/T25414.script
=====================================
@@ -0,0 +1,6 @@
+:set -XCApiFFI
+import Foreign
+import Foreign.C
+foreign import capi unsafe "stdlib.h malloc" c_malloc :: CSize -> IO (Ptr ())
+foreign import capi unsafe "stdlib.h free" c_free :: Ptr () -> IO ()
+c_free =<< c_malloc 16


=====================================
testsuite/tests/ghci/scripts/all.T
=====================================
@@ -360,6 +360,7 @@ test('T20455', normal, ghci_script, ['T20455.script'])
 test('shadow-bindings', normal, ghci_script, ['shadow-bindings.script'])
 test('T925', normal, ghci_script, ['T925.script'])
 test('T7388', normal, ghci_script, ['T7388.script'])
+test('T25414', normal, ghci_script, ['T25414.script'])
 test('T20627', normal, ghci_script, ['T20627.script'])
 test('T20473a', normal, ghci_script, ['T20473a.script'])
 test('T20473b', normal, ghci_script, ['T20473b.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3496ef6c6f4cdb8bbef8b0e9dfa61219c32a575...e70009bc5b388ed02db12ee7a99bca0e4c283c87

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3496ef6c6f4cdb8bbef8b0e9dfa61219c32a575...e70009bc5b388ed02db12ee7a99bca0e4c283c87
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 11:37:49 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 30 Oct 2024 07:37:49 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/9.12-alpha2
Message-ID: <67221a8d7edcb_3894e814c710499ac@gitlab.mail>



Zubin pushed new branch wip/9.12-alpha2 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9.12-alpha2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 11:46:45 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 30 Oct 2024 07:46:45 -0400
Subject: [Git][ghc/ghc][wip/9.12-testsuite-fixes] 116 commits: users-guide:
 Document GHCi :where command
Message-ID: <67221ca5336e6_3894e8320b2c517df@gitlab.mail>



Zubin pushed to branch wip/9.12-testsuite-fixes at Glasgow Haskell Compiler / GHC


Commits:
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -
980a295a by Zubin Duggal at 2024-10-30T11:46:38+00:00
testsuite: normalise some versions in callstacks

(cherry picked from commit f230e29f30d0c1c566d4dd251807fcab76a2710e)

- - - - -
823d57d3 by Zubin Duggal at 2024-10-30T11:46:38+00:00
testsuite: use -fhide-source-paths to normalise some backpack tests

(cherry picked from commit b19de476bc5ce5c7792e8af1354b94a4286a1a13)

- - - - -
a6680ff3 by Zubin Duggal at 2024-10-30T11:46:38+00:00
testsuite/haddock: strip version identifiers and unit hashes from html tests

(cherry picked from commit fbf0889eadc410d43dd5c1657e320634b6738fa5)

- - - - -
492fd139 by Zubin Duggal at 2024-10-30T11:46:38+00:00
haddock: oneshot tests can drop files if they share modtimes. Stop this by
including the filename in the key.

Ideally we would use `ghc -M` output to do a proper toposort

Partially addresses #25372

(cherry picked from commit e78c7ef96e395f1ef41f04790aebecd0409b92b9)

- - - - -
88b17928 by Zubin Duggal at 2024-10-30T11:46:38+00:00
testsuite: fix normalisation of T9930fail so that it doesn't get tripped up by ghc executable (ARGV[0]) differences

(cherry picked from commit a79a587e025d42d34bb30e115fc5c7cab6c1e030)

- - - - -
c4ce90c8 by Zubin Duggal at 2024-10-30T11:46:38+00:00
testsuite: normalise windows file seperators

(cherry picked from commit f858875e03b9609656b542aaaaff85ad0a83878a)

- - - - -


24 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72db6625d1067ddba918f2247cc34f18b120bda7...c4ce90c81e85830269cfa4840b071e2198e8095d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72db6625d1067ddba918f2247cc34f18b120bda7...c4ce90c81e85830269cfa4840b071e2198e8095d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 12:00:30 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 30 Oct 2024 08:00:30 -0400
Subject: [Git][ghc/ghc][wip/9.12-alpha2] 2 commits: Bump binary submodule to
 0.8.9.2
Message-ID: <67221fde9c665_1685f711f2881124b@gitlab.mail>



Zubin pushed to branch wip/9.12-alpha2 at Glasgow Haskell Compiler / GHC


Commits:
2f2beee4 by Zubin Duggal at 2024-10-30T17:23:30+05:30
Bump binary submodule to 0.8.9.2

(cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20)

- - - - -
aa417868 by Ben Gamari at 2024-10-30T17:26:54+05:30
Bump process submodule to v1.6.25.0

(cherry picked from commit 18f532f3ed021fff9529f50da2006b8a8d8b1df7)

- - - - -


6 changed files:

- libraries/binary
- libraries/process
- testsuite/tests/process/process004.hs
- testsuite/tests/process/process004.stdout
- testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
- testsuite/tests/process/process004.stdout-mingw32


Changes:

=====================================
libraries/binary
=====================================
@@ -1 +1 @@
-Subproject commit b30971d569e934cd54d08c45c7e906cfe8af3709
+Subproject commit 2a712db14912dddccf3e2207815e30b9f3049514


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit 8364eaa2c83f7918be41cf3bd520e4ede1b07c35
+Subproject commit 9c3bfc214c72bbd0c8a30a1c41465deed0feaf47


=====================================
testsuite/tests/process/process004.hs
=====================================
@@ -4,8 +4,13 @@ import System.IO.Error
 import System.Process
 
 main :: IO ()
-main = do test1 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
-          test2 `catchIOError` \e -> putStrLn ("Exc: " ++ show e)
+main = do
+  -- N.B. Only show the error type since the exact error text
+  -- may depend upon precise system call which @process@ decided
+  -- to use.
+  let printError e = putStrLn ("Exc: " ++ show (ioeGetErrorType e))
+  test1 `catchIOError` printError
+  test2 `catchIOError` printError
 
 test1 :: IO ()
 test1 = do


=====================================
testsuite/tests/process/process004.stdout
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: chdir: invalid argument (Bad file descriptor)
-Exc: true: runProcess: chdir: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-javascript-unknown-ghcjs
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: does not exist (No such file or directory)
-Exc: true: runProcess: does not exist (No such file or directory)
+Exc: does not exist
+Exc: does not exist


=====================================
testsuite/tests/process/process004.stdout-mingw32
=====================================
@@ -1,2 +1,2 @@
-Exc: true: runInteractiveProcess: invalid argument (Invalid argument)
-Exc: true: runProcess: invalid argument (Invalid argument)
+Exc: invalid argument
+Exc: invalid argument



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/755928ba2f8dab6271680b06c9ba43e93408231f...aa417868fa6b6d47497709c671679104cbd55251

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/755928ba2f8dab6271680b06c9ba43e93408231f...aa417868fa6b6d47497709c671679104cbd55251
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 12:24:18 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 30 Oct 2024 08:24:18 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/25431
Message-ID: <67222572974db_1685f753fa84149c0@gitlab.mail>



Zubin pushed new branch wip/25431 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/25431
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 12:27:48 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Wed, 30 Oct 2024 08:27:48 -0400
Subject: [Git][ghc/ghc][wip/9.12-alpha2] testsuite: normalise execvp vs exec
 differences in process tests
Message-ID: <6722264453738_1685f74e41e818656@gitlab.mail>



Zubin pushed to branch wip/9.12-alpha2 at Glasgow Haskell Compiler / GHC


Commits:
728a0bf1 by Zubin Duggal at 2024-10-30T17:57:11+05:30
testsuite: normalise execvp vs exec differences in process tests

Fixes #25431

(cherry picked from commit a23d8e73166725b699af88a36e97c63b2a0ede25)

- - - - -


1 changed file:

- testsuite/tests/process/all.T


Changes:

=====================================
testsuite/tests/process/all.T
=====================================
@@ -1,6 +1,6 @@
 # some platforms use spawnp instead of exec in some cases, resulting
 # in spurious error output changes.
-normalise_exec = normalise_fun(lambda s: s.replace('posix_spawnp', 'exec'))
+normalise_exec = normalise_fun(lambda s: s.replace('posix_spawnp', 'exec').replace('execvp','exec'))
 
 test('process001', [req_process], compile_and_run, [''])
 test('process002', [fragile_for(16547, concurrent_ways), req_process], compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/728a0bf10026e8629c16e9f5ce9ebfe73628a8a6

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 12:51:48 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 30 Oct 2024 08:51:48 -0400
Subject: [Git][ghc/ghc][wip/T24359] 297 commits: RTS linker: add support for
 hidden symbols (#25191)
Message-ID: <67222be46d891_1685f78c81d81897b@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC


Commits:
9ca15506 by doyougnu at 2024-09-10T10:46:38-04:00
RTS linker: add support for hidden symbols (#25191)

Add linker support for hidden symbols. We basically treat them as weak
symbols.

Patch upstreamed from haskell.nix

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3b2dc826 by Sven Tennie at 2024-09-10T10:47:14-04:00
Fix C warnings (#25237)

GCC 14 treats the fixed warnings as errors by default. I.e. we're
gaining GCC 14 compatibility with these fixes.

- - - - -
05715994 by Sylvain Henry at 2024-09-10T10:47:55-04:00
JS: fix codegen of static string data

Before this patch, when string literals are made trivial, we would
generate `h$("foo")` instead of `h$str("foo")`. This was
introduced by mistake in 6bd850e887b82c5a28bdacf5870d3dc2fc0f5091.

- - - - -
949ebced by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Re-organise cross-OS compatibility layer

- - - - -
84ac9a99 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Remove CPP for obsolete GHC and Cabal versions

- - - - -
370d1599 by Hécate Kleidukos at 2024-09-10T19:19:40-04:00
haddock: Move the changelog file to the 'extra-doc-files' section in the cabal file

- - - - -
cfbff65a by Simon Peyton Jones at 2024-09-10T19:20:16-04:00
Add ZonkAny and document it

This MR fixed #24817 by adding ZonkAny, which takes a Nat
argument.

See Note [Any types] in GHC.Builtin.Types, especially
wrinkle (Any4).

- - - - -
0167e472 by Matthew Pickering at 2024-09-11T02:41:42-04:00
hadrian: Make sure ffi headers are built before using a compiler

When we are using ffi adjustors then we rely on `ffi.h` and
`ffitarget.h` files during code generation when compiling stubs.

Therefore we need to add this dependency to the build system (which this
patch does).

Reproducer, configure with `--enable-libffi-adjustors` and then build
"_build/stage1/libraries/ghc-prim/build/GHC/Types.p_o".

Observe that this fails before this patch and works afterwards.

Fixes #24864

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>

- - - - -
0f696958 by Rodrigo Mesquita at 2024-09-11T02:42:18-04:00
base: Deprecate BCO primops exports from GHC.Exts

See https://github.com/haskell/core-libraries-committee/issues/212.

These reexports will be removed in GHC 9.14.

- - - - -
cf0e7729 by Alan Zimmerman at 2024-09-11T02:42:54-04:00
EPA: Remove Anchor = EpaLocation synonym

This just causes confusion.

- - - - -
8e462f4d by Andrew Lelechenko at 2024-09-11T22:20:37-04:00
Bump submodule deepseq to 1.5.1.0

- - - - -
aa4500ae by Sebastian Graf at 2024-09-11T22:21:13-04:00
User's guide: Fix the "no-backtracking" example of -XOrPatterns (#25250)

Fixes #25250.

- - - - -
1c479c01 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add Native Code Generator (NCG)

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
51b678e1 by Sven Tennie at 2024-09-12T10:39:38+00:00
Adjust test timings for slower computers

Increase the delays a bit to be able to run these tests on slower
computers.

The reference was a Lichee Pi 4a RISCV64 machine.

- - - - -
a0e41741 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add RTS linker

This architecture wasn't supported before.

Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d365b1d4 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Ignore divbyzero test

The architecture's behaviour differs from the test's expectations. See
comment in code why this is okay.

- - - - -
abf3d699 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Enable MulMayOflo_full test

It works and thus can be tested.

- - - - -
38c7ea8c by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: LibffiAdjustor: Ensure code caches are flushed

RISCV64 needs a specific code flushing sequence (involving fence.i) when
new code is created/loaded.

- - - - -
7edc6965 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add additional linker symbols for builtins

We're relying on some GCC/Clang builtins. These need to be visible to
the linker (and not be stripped away.)

- - - - -
92ad3d42 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Add GHCi support

As we got a RTS linker for this architecture now, we can enable GHCi for
it.

- - - - -
a145f701 by Sven Tennie at 2024-09-12T10:39:38+00:00
RISCV64: Set codeowners of the NCG

- - - - -
8e6d58cf by Sven Tennie at 2024-09-12T10:39:38+00:00
Add test for C calling convention

Ensure that parameters and return values are correctly processed. A
dedicated test (like this) helps to get the subtleties of calling
conventions easily right.

The test is failing for WASM32 and marked as fragile to not forget to
investigate this (#25249).

- - - - -
fff55592 by Torsten Schmits at 2024-09-12T21:50:34-04:00
finder: Add `IsBootInterface` to finder cache keys

- - - - -
cdf530df by Alan Zimmerman at 2024-09-12T21:51:10-04:00
EPA: Sync ghc-exactprint to GHC

- - - - -
1374349b by Sebastian Graf at 2024-09-13T07:52:11-04:00
DmdAnal: Fast path for `multDmdType` (#25196)

This is in order to counter a regression exposed by SpecConstr.

Fixes #25196.

- - - - -
80769bc9 by Andrew Lelechenko at 2024-09-13T07:52:47-04:00
Bump submodule array to 0.5.8.0

- - - - -
49ac3fb8 by Sylvain Henry at 2024-09-16T10:33:01-04:00
Linker: add support for extra built-in symbols (#25155)

See added Note [Extra RTS symbols] and new user guide entry.

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
3939a8bf by Samuel Thibault at 2024-09-16T10:33:44-04:00
GNU/Hurd: Add getExecutablePath support

GNU/Hurd exposes it as /proc/self/exe just like on Linux.

- - - - -
d3b19851 by Sylvain Henry at 2024-09-17T11:03:28-04:00
RTS: expose closure_sizeW_ (#25252)

C code using the closure_sizeW macro can't be linked with the RTS linker
without this patch. It fails with:

  ghc-9.11.20240911: Failed to lookup symbol: closure_sizeW_

Fix #25252

Co-authored-by: Hamish Mackenzie <Hamish.K.Mackenzie at gmail.com>
Co-authored-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
137bf74d by Sebastian Graf at 2024-09-17T11:04:05-04:00
HsExpr: Inline `HsWrap` into `WrapExpr`

This nice refactoring was suggested by Simon during review:
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13261#note_583374

Fixes #25264.

- - - - -
7fd9e5e2 by Sebastian Graf at 2024-09-17T11:04:05-04:00
Pmc: Improve Desugaring of overloaded list patterns (#25257)

This actually makes things simpler.

Fixes #25257.

- - - - -
e4169ba9 by Ben Gamari at 2024-09-18T07:55:28-04:00
configure: Correctly report when subsections-via-symbols is disabled

As noted in #24962, currently subsections-via-symbols is disabled on
AArch64/Darwin due to alleged breakage. However, `configure` reports to
the user that it is enabled. Fix this.

- - - - -
9d20a787 by Mario Blažević at 2024-09-18T07:56:08-04:00
Modified the default export implementation to match the amended spec

- - - - -
35eb4f42 by Sylvain Henry at 2024-09-18T07:57:00-04:00
FFI: don't ppr Id/Var symbols with debug info (#25255)

Even if `-dpp-debug` is enabled we should still generate valid C code.
So we disable debug info printing when rendering with Code style.

- - - - -
9e96dad8 by Sebastian Graf at 2024-09-21T17:47:59-04:00
Demand: Combine examples into Note (#25107)

Just a leftover from !13060.

Fixes #25107.

- - - - -
21aaa34b by sheaf at 2024-09-21T17:48:36-04:00
Use x86_64-unknown-windows-gnu target for LLVM on Windows

- - - - -
992a7624 by sheaf at 2024-09-21T17:48:36-04:00
LLVM: use -relocation-model=pic on Windows

This is necessary to avoid the segfaults reported in #22487.

Fixes #22487

- - - - -
c50d29be by Ryan Hendrickson at 2024-09-21T17:49:15-04:00
compiler: Use type abstractions when deriving

For deriving newtype and deriving via, in order to bring type variables
needed for the coercions into scope, GHC generates type signatures for
derived class methods. As a simplification, drop the type signatures and
instead use type abstractions to bring method type variables into scope.

- - - - -
f04fd0ae by Zubin Duggal at 2024-09-21T17:49:51-04:00
driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them

- - - - -
620becd7 by Andreas Klebinger at 2024-09-21T17:50:27-04:00
Allow unknown fd device types for setNonBlockingMode.

This allows fds with a unknown device type to have blocking mode
set. This happens for example for fds from the inotify subsystem.

Fixes #25199.

- - - - -
c76e25b3 by Hécate Kleidukos at 2024-09-21T17:51:07-04:00
Use Hackage version of Cabal 3.14.0.0 for Hadrian.
We remove the vendored Cabal submodule.

Also update the bootstrap plans

Fixes #25086

- - - - -
6c83fd7f by Zubin Duggal at 2024-09-21T17:51:07-04:00
ci: Ensure we source ci.sh in any jobs that run commands outside of ci.sh

ci.sh sets up the toolchain environment, including paths for the cabal directory, the
toolchain binaries etc. If we run any commands outside of ci.sh, unless we
source ci.sh we will use the wrong values for these environment variables.

In particular, I ran into an issue where the cabal invocation `hadrian/ghci` was
using an old index state despite `ci.sh setup` updating and setting the correct
index state. This is because `ci.sh` sets the `CABAL_DIR` to a different place, which
is where the index was downloaded to, but we were using the default cabal directory
outside ci.sh

The solution is to source the correct environment `ci.sh` using `. ci.sh setup`

- - - - -
9586998d by Sven Tennie at 2024-09-21T17:51:43-04:00
ghc-toolchain: Set -fuse-ld even for ld.bfd

This reflects the behaviour of the autoconf scripts.

- - - - -
d7016e0d by Sylvain Henry at 2024-09-21T17:52:24-04:00
Parser: be more careful when lexing extended literals (#25258)

Previously we would lex invalid prefixes like "8#Int3" as [8#Int, 3].

A side-effect of this patch is that we now allow negative unsigned
extended literals. They trigger an overflow warning later anyway.

- - - - -
ca67d7cb by Zubin Duggal at 2024-09-22T02:34:06-04:00
rts: Ensure we dump new Cost Centres added by freshly loaded objects to the eventlog.

To do this, we keep track of the ID of the last cost centre we dumped in DUMPED_CC_ID,
and call dumpCostCentresToEventLog from refreshProfilingCCSs, which will dump all the new
cost centres up to the one we already dumped in DUMPED_CC_ID.

Fixes #24148

- - - - -
c0df5aa9 by Alan Zimmerman at 2024-09-22T02:34:42-04:00
EPA: Replace AnnsModule am_main with EpTokens

Working towards removing `AddEpAnn`

- - - - -
2a551cd5 by Matthew Pickering at 2024-09-24T16:33:50+05:30
ci: Run abi-test on test-abi label

- - - - -
ab4039ac by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
testsuite: Add a test for object determinism

Extends the abi_test with an object determinism check
Also includes a standalone test to be run by developers manually when
debugging issues with determinism.

- - - - -
d62c18d8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Sampling uniques in the CG

To achieve object determinism, the passes processing Cmm and the rest of
the code generation pipeline musn't create new uniques which are
non-deterministic.

This commit changes occurrences of non-deterministic unique sampling
within these code generation passes by a deterministic unique sampling
strategy by propagating and threading through a deterministic
incrementing counter in them. The threading is done implicitly with
`UniqDSM` and `UniqDSMT`.

Secondly, the `DUniqSupply` used to run a `UniqDSM` must be threaded
through all passes to guarantee uniques in different passes are unique
amongst them altogether. Specifically, the same `DUniqSupply` must be
threaded through the CG Streaming pipeline, starting with Driver.Main
calling `StgToCmm.codeGen`, `cmmPipeline`, `cmmToRawCmm`, and
`codeOutput` in sequence.

To thread resources through the `Stream` abstraction, we use the `UniqDSMT`
transformer on top of `IO` as the Monad underlying the Stream. `UniqDSMT` will
thread the `DUniqSupply` through every pass applied to the `Stream`, for every
element. We use @type CgStream = Stream (UniqDSMT IO)@ for the Stream used in
code generation which that carries through the deterministic unique supply.

See Note [Deterministic Uniques in the CG]

- - - - -
3bbe4af4 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Cmm unique renaming pass

To achieve object determinism, we need to prevent the non-deterministic
uniques from leaking into the object code. We can do this by
deterministically renaming the non-external uniques in the Cmm groups
that are yielded right after StgToCmm.

The key to deterministic renaming is observing that the order of
declarations, instructions, and data in the Cmm groups are already
deterministic (modulo other determinism bugs), regardless of the
uniques. We traverse the Cmm AST in this deterministic order and
rename the uniques, incrementally, in the order they are found, thus
making them deterministic. This renaming is guarded by
-fobject-determinism which is disabled by default for now.

This is one of the key passes for object determinism. Read about the
overview of object determinism and a more detailed explanation of this
pass in:
* Note [Object determinism]
* Note [Renaming uniques deterministically]

Significantly closes the gap to #12935

- - - - -
8357ed50 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: DCmmGroup vs CmmGroup

Part of our strategy in producing deterministic objects, namely,
renaming all Cmm uniques in order, depend on the object code produced
having a deterministic order (say, A_closure always comes before
B_closure).

However, the use of LabelMaps in the Cmm representation invalidated this
requirement because the LabelMaps elements would already be in a
non-deterministic order (due to the original uniques), and the renaming
in sequence wouldn't work because of that non-deterministic order.

Therefore, we now start off with lists in CmmGroup (which preserve the
original order), and convert them into LabelMaps (for performance in the
code generator) after the uniques of the list elements have been
renamed.

See Note [DCmmGroup vs CmmGroup or: Deterministic Info Tables] and #12935.

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
0e675fb8 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: Don't print unique in pprFullName

This unique was leaking as part of the profiling description in info
tables when profiling was enabled, despite not providing information
relevant to the profile.

- - - - -
340f58b0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: UDFM for distinct-constructor-tables

In order to produce deterministic objects when compiling with
-distinct-constructor-tables, we also have to update the data
constructor map to be backed by a deterministic unique map (UDFM) rather
than a non-deterministic one (UniqMap).

- - - - -
282f37a0 by Rodrigo Mesquita at 2024-09-24T16:33:50+05:30
determinism: InfoTableMap uniques in generateCgIPEStub

Fixes object determinism when using -finfo-table-map

Make sure to also deterministically rename the IPE map (as per Note
[Renaming uniques deterministically]), and to use a deterministic unique
supply when creating new labels for the IPE information to guarantee
deterministic objects when IPE information is requested.

Note that the Cmm group produced in generateCgIPEStub must /not/ be
renamed because renaming uniques is not idempotent, and the references
to the previously renamed code in the IPE Cmm group would be renamed
twice and become invalid references to non-existent symbols.

We do need to det-rename the InfoTableMap that is created in the
conversion from Core to Stg. This is not a problem since that map won't
refer any already renamed names (since it was created before the
renaming).

- - - - -
7b37afc9 by Zubin Duggal at 2024-09-24T16:33:50+05:30
ci: Allow abi-test to fail.

We are not fully deterministic yet, see #12935 for work that remains to be done.

- - - - -
a63ee33a by Simon Peyton Jones at 2024-09-25T17:08:24-04:00
Add Given injectivity for built-in type families

Ticket #24845 asks (reasonably enough) that if we have
   [G] a+b ~ 0
then we also know
   [G] a ~ 0, b ~ 0
and similar injectivity-like facts for other built-in type
families.  The status quo was that we never generate evidence for
injectivity among Givens -- but it is quite reasonnable to do so.
All we need is to have /evidence/ for the new constraints

This MR implements that goal.  I also took the opportunity to
* Address #24978: refactoring UnivCo
* Fix #25248, which was a consequences of the previous formulation of UnivCo

As a result this MR touches a lot of code.  The big things are:

* Coercion constructor UnivCo now takes a [Coercion] as argument to
  express the coercions on which the UnivCo depends. A nice consequence
  is that UnivCoProvenance now has no free variables, simpler in a number
  of places.

* Coercion constructors AxiomInstCo and AxiomRuleCo are combined into
  AxiomCo.  The new AxiomCo, carries a (slightly oddly named)
  CoAxiomRule, which itself is a sum type of the various forms of
  built-in axiom.  See Note [CoAxiomRule] in GHC.Core.Coercion.Axiom

  A merit of this is that we can separate the case of open and closed
  type families, and eliminate the redundant `BranchIndex` in the former
  case.

* Much better representation for data BuiltInSynFamily, which means we
  no longer need to enumerate built-in axioms as well as built-in tycons.

* There is a massive refactor in GHC.Builtin.Types.Literals, which contains all
  the built-in axioms for type-level operations (arithmetic, append, cons etc).

  A big change is that instead of redundantly having (a) a hand-written
  matcher, and (b) a template-based "proves" function, which were hard to
  keep in sync, the two are derive from one set of human-supplied info.
  See GHC.Builtin.Types.Literals.mkRewriteAxiom, and friends.

* Significant changes in GHC.Tc.Solver.Equality to account for the new
  opportunity for Given/Given equalities.

Smaller things

* Improve pretty-printing to avoid parens around atomic coercions.

* Do proper eqType in findMatchingIrreds, not `eqTypeNoKindCheck`.
  Looks like a bug, Richard agrees.

* coercionLKind and coercionRKind are hot functions.  I refactored the
  implementation (which I had to change anyway) to increase sharing.
  See Note [coercionKind performance] in GHC.Core.Coercion

* I wrote a new Note [Finding orphan names] in GHC.Core.FVs about orphan
  names

* I improved the `is_concrete` flag in GHC.Core.Type.buildSynTyCon, to avoid
  calling tyConsOfType.  I forget exactly why I did this, but it's definitely
  better now.

* I moved some code from GHC.Tc.Types.Constraint into GHC.Tc.Types.CtLocEnv
  and I renamed the module GHC.Tc.Types.CtLocEnv to GHC.Tc.Types.CtLoc

- - - - -
dd8ef342 by Ryan Scott at 2024-09-25T17:09:01-04:00
Resolve ambiguous method-bound type variables in vanilla defaults and GND

When defining an instance of a class with a "vanilla" default, such as in the
following example (from #14266):

```hs
class A t where
  f :: forall x m. Monoid x => t m -> m
  f = <blah>

instance A []
```

We have to reckon with the fact that the type of `x` (bound by the type
signature for the `f` method) is ambiguous. If we don't deal with the ambiguity
somehow, then when we generate the following code:

```hs
instance A [] where
  f = $dmf @[] -- NB: the type of `x` is still ambiguous
```

Then the generated code will not typecheck. (Issue #25148 is a more recent
example of the same problem.)

To fix this, we bind the type variables from the method's original type
signature using `TypeAbstractions` and instantiate `$dmf` with them using
`TypeApplications`:

```hs
instance A [] where
  f @x @m = $dmf @[] @x @m -- `x` is no longer ambiguous
```

Note that we only do this for vanilla defaults and not for generic defaults
(i.e., defaults using `DefaultSignatures`). For the full details, see `Note
[Default methods in instances] (Wrinkle: Ambiguous types from vanilla method
type signatures)`.

The same problem arose in the code generated by `GeneralizedNewtypeDeriving`,
as we also fix it here using the same technique. This time, we can take
advantage of the fact that `GeneralizedNewtypeDeriving`-generated code
_already_ brings method-bound type variables into scope via `TypeAbstractions`
(after !13190), so it is very straightforward to visibly apply the type
variables on the right-hand sides of equations. See `Note [GND and ambiguity]`.

Fixes #14266. Fixes #25148.

- - - - -
0a4da5d2 by ARATA Mizuki at 2024-09-25T17:09:41-04:00
Document primitive string literals and desugaring of string literals

Fixes #17474 and #17974

Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -
ad0731ad by Zubin Duggal at 2024-09-25T17:10:18-04:00
rts: Fix segfault when using non-moving GC with profiling

`nonMovingCollect()` swaps out the `static_flag` value used as a
sentinel for `gct->scavenged_static_objects`, but the subsequent call
`resetStaticObjectForProfiling()` sees the old value of `static_flag` used as
the sentinel and segfaults. So we must call `resetStaticObjectForProfiling()`
before calling `nonMovingCollect()` as otherwise it looks for the incorrect
sentinel value

Fixes #25232 and #23958

Also teach the testsuite driver about nonmoving profiling ways
and stop disabling metric collection when nonmoving GC is enabled.

- - - - -
e7a26d7a by Sylvain Henry at 2024-09-25T17:11:00-04:00
Fix interaction between fork and kqueue (#24672)

A kqueue file descriptor isn't inherited by a child created with fork.
As such we mustn't try to close this file descriptor as we would close a
random one, e.g. the one used by timerfd.

Fix #24672

- - - - -
6863503c by Simon Peyton Jones at 2024-09-25T17:11:37-04:00
Improve GHC.Tc.Solver.defaultEquality

This MR improves GHC.Tc.Solver.defaultEquality to solve #25251.

The main change is to use checkTyEqRhs to check the equality, so
that we do promotion properly.

But within that we needed a small enhancement to LC_Promote.  See
Note [Defaulting equalites] (DE4) and (DE5)

The tricky case is (alas) hard to trigger, so I have not added a
regression test.

- - - - -
97a6c6c3 by Sylvain Henry at 2024-09-25T17:12:18-04:00
JS: fix h$withCStringOnHeap helper (#25288)

strlen returns the length of the string without the \0 terminating byte,
hence CString weren't properly allocated on the heap (ending \0 byte was
missing).

- - - - -
5f7c20bc by Ben Gamari at 2024-09-26T04:14:05-04:00
base: Propagate `error` CallStack to thrown exception

Previously `errorCallWithCallStackException` failed to propagate its
`CallStack` argument, which represents the call-chain of the preceding
`error` call, to the exception that it returned. Consequently, the
call-stack of `error` calls were quite useless.

Unfortunately, this is the second time that I have fixed this but it
seems the first must have been lost in rebasing.

Fixes a bug in the implementation of CLC proposal 164
<https://github.com/haskell/core-libraries-committee/issues/164>

Fixes #24807.

- - - - -
c20d5186 by Matthew Pickering at 2024-09-26T04:14:42-04:00
driver: Fix -working-dir for foreign files

-working-dir definitely needs more serious testing, there are some easy
ways to test this.

* Modify Cabal to call ghc using -working-dir rather than changing
  directory.
* Modify the testsuite to run ghc using `-working-dir` rather than
  running GHC with cwd = temporary directory.

However this will have to wait until after 9.12.

Fixes #25150

- - - - -
88eaa7ac by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: reuse predError, succError, toEnumError

Reuse predError, succError, and toEnumError when deriving Enum instances
to avoid generating different error strings per instance. E.g. before
this patch for every instance for a type FOO we would generate a string:

  "pred{FOO}: tried to take `pred' of first tag in enumeration"#

- - - - -
e9fa1163 by Sylvain Henry at 2024-09-26T04:15:24-04:00
Enum deriving: generate better code (#16364)

Generate better code for Enum.toEnum: check both the lower and the upper
bounds at once with an unsigned comparison.

Initially I've used a type ascription with a call to 'fromIntegral',
hence the slight refactoring of nlAscribe. Using 'fromIntegral' was
problematic (too low in the module hierarchy) so 'enumIntToWord' was
introduced instead.

Combined with the previous commit, T21839c ghc/alloc decrease by 5%

Metric Decrease:
    T21839c

- - - - -
383af074 by Sylvain Henry at 2024-09-26T04:16:06-04:00
Core: add absorb rules for binary or/and (#16351)

Rules:
  x or (x and y) ==> x
  x and (x or y) ==> x

- - - - -
783c8b29 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Don't compile `asBox` with -fprof-late

The `asBox` function is intended to store exactly the closure which the
user passes to it. Placing a cost centre on asBox introduces a thunk,
which violates this expectation and can change the result of using asBox
when profiling is enabled.

See #25212 for more details and ample opportunity to discuss if this is
a bug or not.

- - - - -
0967dcc7 by Matthew Pickering at 2024-09-26T12:07:44-04:00
Fix normalisation of .prof files

Fix 1: If a cost centre contained CAF then the normalisation was
corrupted, now only check if CAF is at the start of a line.

Fix 2: "no location info" contain a space, which messed up the next
normalisation logic which assumed that columns didn't have spaced in.

- - - - -
9eda1cb9 by Matthew Pickering at 2024-09-26T12:07:44-04:00
testsuite: Fix normalisation of prof_files removing newlines

These normalisation steps were collapsing lines together, which made
subsequent normalisation steps fail.

```
foo x y z
CAF x y z
qux x y z
```

was getting normalised to

```
foo x y z qux x y z
```

which means that subsequent line based filters would not work correctly.

- - - - -
2b25f9e2 by Matthew Pickering at 2024-09-26T12:07:44-04:00
packaging: Enable late-ccs for release flavour

This enables late cost centres when building profiled libraries and
subsequently greatly improves the resolution of cost centre stacks when
profiling.

This patch also introduces the `grep_prof` test modifier which is used
to apply a further filter to the .prof file before they are compared.

Fixes #21732

-------------------------
Metric Increase:
    libdir
-------------------------

- - - - -
bb030d0d by Brandon Chinn at 2024-09-26T12:08:21-04:00
Replace manual string lexing (#25158)

Metric Increase:
    MultilineStringsPerf

This commit replaces the manual string lexing logic with native Alex
lexing syntax. This aligns the lexer much closer to the Haskell Report,
making it easier to see how the implementation and spec relate. This
slightly increases memory usage when compiling multiline strings because
we now have two distinct phases: lexing the multiline string with Alex
and post-processing the string afterwards. Before, these were done at
the same time, but separating them allows us to push as much logic into
normal Alex lexing as possible.

Since multiline strings are a new feature, this regression shouldn't be
too noticeable. We can optimize this over time.

- - - - -
16742987 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Revert !4655: Stop 'import "base" Prelude' removing implicit Prelude import

This behaviour is problematic for the principle reason that `import
Prelude` may not refer to the `base` package, and in which case
importing an entirely unrelated module causing your implicit prelude to
leave the scope is extremely surprising. See the added test for this
example. Discussion on #17045.

The secondary reason for reverting this patch is that "base" can't be a
wired in package any more (see #24903), so we have to remove special
logic which singles out base from the compiler.

The rule for implicit shadowing is now simply:

* If you write import Prelude (..) then you don't get an implicit prelude import
* If you write import "foobar" Prelude (..) for all pkgs foobar,
  you get an implicit import of prelude.

If you want to write a package import of Prelude, then you can enable
`NoImplicitPrelude` for the module in question to recover the behaviour
of ghc-9.2-9.10.

Fixes #17045

- - - - -
57c50f41 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Rename COMPILING_BASE_PACKAGE to COMPILING_GHC_INTERNAL_PACKAGE

The COMPILING_BASE_PACKAGE macro is concerned with issues defining
symbols and using symbols in the same compilation unit. However, these
symbols now exist in ghc-internal rather than base, so we should rename
the macro accordingly.

The code is guards is likely never used as we never produce windows DLLs
but it is simpler to just perform the renaming for now.

These days there is little doubt that this macro defined in this ad-hoc
manner would be permitted to exist, but these days are not those days.

Fixes #25221

- - - - -
70764243 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Preload ghc-internal rather than base

This occurence of baseUnitId was missed when moving the bulk of internal
definitions into `ghc-internal`.

We need to remove this preloading of `base` now because `base` should
not be wired in.

Towards #24903

- - - - -
12915609 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Remove Data.List compat warning

There is currently a warning implemented in -Wcompat which warns you
when importing Data.List in a non-qualified manner.

```
A.hs:3:8: warning: [-Wcompat-unqualified-imports]
    To ensure compatibility with future core libraries changes
    imports to Data.List should be
    either qualified or have an explicit import list.
  |
3 | import Data.List
  |        ^^^^^^^^^
Ok, one module loaded.
```

GHC ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/17244
CLC discussion: https://groups.google.com/g/haskell-core-libraries/c/q3zHLmzBa5E

This warning was implemented as part of the migration to making
Data.List monomorphic again (and to be used like Data.Set, Data.Map
etc). That doesn't seem like it happened, and I imagine that the current
CLC would require a new proposal anyway in order to do that now. It's
not clear in any case what "future core libraries changes" we are
waiting to happen before this warning can be removed.

Given the first phase of the proposal has lasted 5 years it doesn't seem
that anyone is motivated to carry the proposal to completion. It does
seem a bit unnecessary to include a warning in the compiler about
"future changes to the module" when there's no timeline or volunteer to
implement these changes.

The removal of this warning was discussed again at:
https://github.com/haskell/core-libraries-committee/issues/269

During the discussion there was no new enthusiasm to move onto the next
stages of the proposal so we are removing the warning to unblock the
reinstallable "base" project (#24903)

Fixes #24904

- - - - -
d4e4d498 by Matthew Pickering at 2024-09-26T12:08:57-04:00
Move Control.Monad.Zip into ghc-internal

mzip is wired in and therefore needs to be in ghc-internal.

Fixes #25222

Towards #24903

- - - - -
d3dacdfb by Matthew Pickering at 2024-09-26T12:08:57-04:00
Unwire the base package

This patch just removes all the functions related to wiring-in the base
package and the `-this-unit-id=base` flag from the cabal file.

After this commit "base" becomes just like any other package and the
door is opened to moving base into an external repo and releasing base
on a separate schedule to the rest of ghc.

Closes #24903

- - - - -
1b39363b by Patrick at 2024-09-27T06:10:19-04:00
Add entity information to HieFile #24544

Enhanced HieFile to capture entity information for identifiers, enabling better support for language tools and protocols. See issue #24544 for more details.

Work have been done:
* Introduction of new data type `EntityInfo` in `GHC.Iface.Ext.Types`.
* Add extra field `hie_entity_infos :: NameEntityInfo` to `HieFile`
  to store the mapping from entity name to corresponding entity infos
  in `GHC.Iface.Ext.Types`.
* Compute `EntityInfo` for each entity name in the HieAst from `TyThing,
  Id, OccName` when generating the `HieFile` in `GHC.Iface.Ext.Ast`.
* Add test T24544 to test the generation of `EntityInfo`.

- - - - -
4f3618d8 by sheaf at 2024-09-27T06:10:57-04:00
The X86 SIMD patch.

This commit adds support for 128 bit wide SIMD vectors and vector
operations to GHC's X86 native code generator.

Main changes:

  - Introduction of vector formats (`GHC.CmmToAsm.Format`)
  - Introduction of 128-bit virtual register (`GHC.Platform.Reg`),
    and removal of unused Float virtual register.
  - Refactor of `GHC.Platform.Reg.Class.RegClass`: it now only contains
    two classes, `RcInteger` (for general purpose registers) and `RcFloatOrVector`
    (for registers that can be used for scalar floating point values as well
    as vectors).
  - Modify `GHC.CmmToAsm.X86.Instr.regUsageOfInstr` to keep track
    of which format each register is used at, so that the register
    allocator can know if it needs to spill the entire vector register
    or just the lower 64 bits.
  - Modify spill/load/reg-2-reg code to account for vector registers
    (`GHC.CmmToAsm.X86.Instr.{mkSpillInstr, mkLoadInstr, mkRegRegMoveInstr, takeRegRegMoveInstr}`).
  - Modify the register allocator code (`GHC.CmmToAsm.Reg.*`) to propagate
    the format we are storing in any given register, for instance changing
    `Reg` to `RegFormat` or `GlobalReg` to `GlobalRegUse`.
  - Add logic to lower vector `MachOp`s to X86 assembly
    (see `GHC.CmmToAsm.X86.CodeGen`)
  - Minor cleanups to genprimopcode, to remove the llvm_only attribute
    which is no longer applicable.

Tests for this feature are provided in the "testsuite/tests/simd" directory.

Fixes #7741

Keeping track of register formats adds a small memory overhead to the
register allocator (in particular, regUsageOfInstr now allocates more
to keep track of the `Format` each register is used at). This explains
the following metric increases.

-------------------------
Metric Increase:
    T12707
    T13035
    T13379
    T3294
    T4801
    T5321FD
    T5321Fun
    T783
-------------------------

- - - - -
10e431ef by sheaf at 2024-09-27T06:10:57-04:00
Use xmm registers in genapply

This commit updates genapply to use xmm, ymm and zmm registers, for
stg_ap_v16/stg_ap_v32/stg_ap_v64, respectively.

It also updates the Cmm lexer and parser to produce Cmm vectors rather
than 128/256/512 bit wide scalars for V16/V32/V64, removing bits128,
bits256 and bits512 in favour of vectors.

The Cmm Lint check is weakened for vectors, as (in practice, e.g. on X86)
it is okay to use a single vector register to hold multiple different
types of data, and we don't know just from seeing e.g. "XMM1" how to
interpret the 128 bits of data within.

Fixes #25062

- - - - -
8238fb2d by sheaf at 2024-09-27T06:10:57-04:00
Add vector fused multiply-add operations

This commit adds fused multiply add operations such as `fmaddDoubleX2#`.
These are handled both in the X86 NCG and the LLVM backends.

- - - - -
2cb7b748 by sheaf at 2024-09-27T06:10:57-04:00
Add vector shuffle primops

This adds vector shuffle primops, such as

```
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#
```

which shuffle the components of the input two vectors into the output vector.

NB: the indices must be compile time literals, to match the X86 SHUFPD
instruction immediate and the LLVM shufflevector instruction.

These are handled in the X86 NCG and the LLVM backend.

Tested in simd009.

- - - - -
0d2428d6 by sheaf at 2024-09-27T06:10:57-04:00
Add Broadcast MachOps

This adds proper MachOps for broadcast instructions, allowing us to
produce better code for broadcasting a value than simply packing that
value (doing many vector insertions in a row).

These are lowered in the X86 NCG and LLVM backends. In the LLVM backend,
it uses the previously introduced shuffle instructions.

- - - - -
e6c19a41 by sheaf at 2024-09-27T06:10:57-04:00
Fix treatment of signed zero in vector negation

This commit fixes the handling of signed zero in floating-point vector
negation.

A slight hack was introduced to work around the fact that Cmm doesn't
currently have a notion of signed floating point literals
(see get_float_broadcast_value_reg). This can be removed once CmmFloat
can express the value -0.0.

The simd006 test has been updated to use a stricter notion of equality
of floating-point values, which ensure the validity of this change.

- - - - -
f496ff7f by sheaf at 2024-09-27T06:10:57-04:00
Add min/max primops

This commit adds min/max primops, such as

  minDouble# :: Double# -> Double# -> Double#
  minFloatX4# :: FloatX4# -> FloatX4# -> FloatX4#
  minWord16X8# :: Word16X8# -> Word16X8# -> Word16X8#

These are supported in:
  - the X86, AArch64 and PowerPC NCGs,
  - the LLVM backend,
  - the WebAssembly and JavaScript backends.

Fixes #25120

- - - - -
5dd2a423 by sheaf at 2024-09-27T06:10:57-04:00
Add test for C calls & SIMD vectors

- - - - -
f824e1ee by sheaf at 2024-09-27T06:10:58-04:00
Add test for #25169

- - - - -
d54db7f3 by sheaf at 2024-09-27T06:10:58-04:00
Fix #25169 using Plan A from the ticket

We now compile certain low-level Cmm functions in the RTS multiple
times, with different levels of vector support. We then dispatch
at runtime in the RTS, based on what instructions are supported.

See Note [realArgRegsCover] in GHC.Cmm.CallConv.

Fixes #25169

-------------------------
Metric Increase:
    T10421
    T12425
    T18730
    T1969
    T9198
-------------------------

- - - - -
d5f8778a by sheaf at 2024-09-27T06:10:58-04:00
Fix C calls with SIMD vectors

This commit fixes the code generation for C calls, to take into account
the calling convention.

This is particularly tricky on Windows, where all vectors are expected
to be passed by reference. See Note [The Windows X64 C calling convention]
in GHC.CmmToAsm.X86.CodeGen.

- - - - -
f64bd564 by sheaf at 2024-09-27T06:10:58-04:00
X86 CodeGen: refactor getRegister CmmLit

This refactors the code dealing with loading literals into registers,
removing duplication and putting all the code in a single place.
It also changes which XOR instruction is used to place a zero value
into a register, so that we use VPXOR for a 128-bit integer vector
when AVX is supported.

- - - - -
ab12de6b by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall: promote arg before calling evalArgs

The job of evalArgs is to ensure each argument is put into a temporary
register, so that it can then be loaded directly into one of the
argument registers for the C call, without the generated code clobbering
any other register used for argument passing.

However, if we promote arguments after calling evalArgs, there is the
possibility that the code used for the promotion will clobber a register,
defeating the work of evalArgs.
To avoid this, we first promote arguments, and only then call evalArgs.

- - - - -
8fd12429 by sheaf at 2024-09-27T06:10:58-04:00
X86 genCCall64: simplify loadArg code

This commit simplifies the argument loading code by making the
assumption that it is safe to directly load the argument into register,
because doing so will not clobber any previous assignments.

This assumption is borne from the use of 'evalArgs', which evaluates
any arguments which might necessitate non-trivial code generation into
separate temporary registers.

- - - - -
12504a9f by sheaf at 2024-09-27T06:10:58-04:00
LLVM: propagate GlobalRegUse information

This commit ensures we keep track of how any particular global register
is being used in the LLVM backend. This informs the LLVM type
annotations, and avoids type mismatches of the following form:

  argument is not of expected type '<2 x double>'
    call ccc <2 x double> (<2 x double>)
      (<4 x i32> arg)

- - - - -
2bb1e8df by Cheng Shao at 2024-09-27T06:11:35-04:00
Link bytecode from interface-stored core bindings in oneshot mode

!13042

Part of #T25090

If the flag `-fprefer-byte-code` is given when compiling a module
containing TH, GHC will use Core bindings stored in interfaces to
compile and link bytecode for splices.

This was only implemented for `--make` mode initially, so this commit
adds the same mechanism to oneshot mode (`-c`).

When an interface is loaded into the EPS in `loadInterface` that has
dehydrated Core bindings, an entry is added to the new field
`eps_iface_bytecode`, containing an IO action that produces a bytecode
`Linkable`, lazily processing the `mi_extra_decls` by calling
`loadIfaceByteCode`.

When Template Haskell dependencies are resolved in `getLinkDeps`, this
action is looked up after loading a module's interface.
If it exists, the action is evaluated and the bytecode is added to the
set of `Linkable`s used for execution of the splice; otherwise it falls
back on the traditional object file.

Metric Decrease:
    MultiLayerModules
    T13701

- - - - -
7cb7172e by Matthew Pickering at 2024-09-27T06:12:12-04:00
ci: Fix variable inheritence for ghcup-metadata testing job

Downstream in ghcup-ci we use the CONFIGURE_ARGS variable to determine
how to setup all the different jobs.

On the downstream trigger this was being inherited from the default
setting in .gitlab.yml file.

Therefore this led to job failures as the necessary CONFIGURE_ARGS were
not being passed to the configure script when installing the bindist.

See docs:

* https://docs.gitlab.com/ee/ci/yaml/#inherit
* https://docs.gitlab.com/ee/ci/yaml/#triggerforward

1. inherit:variables:fals
  - This stops the global variables being inherited into the job and
    hence forwarded onto the downstream job.

2. trigger:forward:*
  - yaml_variables: true (default) pass yaml variables to downstream,
    this is important to pass the upstream pipeline id to downstream.
  - pipeline_variables: false (default) but don't pass pipeline
    variables (normal environment variables).

Fixes #25294

- - - - -
9ffd6163 by Leo at 2024-09-27T16:26:01+05:30
Fix typo in Prelude doc for (>>=)

Fix a minor typo ("equivialent" instead of "equivalent") in the documentation for (>>=) in the prelude.

- - - - -
5745dbd3 by Vladislav Zavialov at 2024-09-27T16:26:52+05:30
Wildcard binders in type declarations (#23501)

Add support for wildcard binders in type declarations:

	type Const a b = a   -- BEFORE: the `b` had to be named
	                     --         even if unused on the RHS

	type Const a _ = a   -- AFTER: the compiler accepts
	                     --        a wildcard binder `_`

The new feature is part of GHC Proposal #425 "Invisible binders
in type declarations", and more specifically its amendment #641.

Just like a named binder, a wildcard binder `_` may be:

	* plain:      _
	* kinded:    (_ :: k -> Type)
	* invisible, plain:  @_
	* invisible, kinded: @(_ :: k -> Type)

Those new forms of binders are allowed to occur on the LHSs of
data, newtype, type, class, and type/data family declarations:

	data D _ = ...
	newtype N _ = ...
	type T _ = ...
	class C _ where ...
	type family F _
	data family DF _

(Test case: testsuite/tests/typecheck/should_compile/T23501a.hs)

However, we choose to reject them in forall telescopes and
type family result variable binders (the latter being part
of the TypeFamilyDependencies extension):

	type family Fd a = _    -- disallowed  (WildcardBndrInTyFamResultVar)
	fn :: forall _. Int     -- disallowed  (WildcardBndrInForallTelescope)

(Test case: testsuite/tests/rename/should_fail/T23501_fail.hs)

See the new Notes:
	* Note [Type variable binders]
	* Note [Wildcard binders in disallowed contexts]

To accommodate the new forms of binders, HsTyVarBndr was changed
as follows (demonstrated without x-fields for clarity)

	-- BEFORE (ignoring x-fields and locations)
	data HsTyVarBndr flag
	  = UserTyVar   flag Name
	  | KindedTyVar flag Name HsKind

	-- AFTER (ignoring x-fields and locations)
	data HsTyVarBndr flag = HsTvb flag HsBndrVar HsBndrKind
	data HsBndrVar  = HsBndrVar Name | HsBndrWildCard
	data HsBndrKind = HsBndrNoKind | HsBndrKind LHsKind

The rest of the patch is downstream from this change.

To avoid a breaking change to the TH AST, we generate fresh
names to replace wildcard binders instead of adding a dedicated
representation for them (as discussed in #641).

And to put a cherry on top of the cake, we now allow wildcards in
kind-polymorphic type variable binders in constructor patterns,
see Note [Type patterns: binders and unifiers] and the tyPatToBndr
function in GHC.Tc.Gen.HsType; example:

	fn (MkT @(_ :: forall k. k -> Type) _ _) = ...

(Test case: testsuite/tests/typecheck/should_compile/T23501b.hs)

- - - - -
ff2bdca2 by Matthew Pickering at 2024-09-27T16:27:08+05:30
ci: Push perf notes from wasm jobs

It was observed in #25299 that we were failing to push performance
numbers from the wasm jobs.

In future we might want to remove this ad-hoc check but for now it's
easier to add another special case.

Towards #25299

- - - - -
4c76f75c by Zubin Duggal at 2024-09-27T16:44:00+05:30
Bump GHC version to 9.12

- - - - -
e4ac1b0d by Zubin Duggal at 2024-09-27T19:12:24+05:30
Bump GHC version to 9.13

- - - - -
da20cac1 by Andreas Klebinger at 2024-10-02T22:18:48-04:00
SpecConstr: Introduce a separate argument limit for forced specs.

We used to put no limit at all on specializations forced via the SPEC
argument. This isn't always reasonable so we introduce a very high limit
that applies to forced specializations, a flag to control it, and we now
emit a warning if we fail a specialization because we exceed the
warning.

Fixes #25197

- - - - -
39497eed by Andreas Klebinger at 2024-10-02T22:19:24-04:00
ghc-experimental: Expose primops and ghc extensions via GHC.PrimOps

This will be the new place for functions that would have gone into
GHC.Exts in the past but are not stable enough to do so now.

Addresses #25242

- - - - -
e9dc2690 by Sylvain Henry at 2024-10-02T22:20:06-04:00
RTS: cleanup timerfd file descriptors after a fork (#25280)

When we init a timerfd-based ticker, we should be careful to cleanup the
old file descriptors (e.g. after a fork).

- - - - -
64e876bc by Rodrigo Mesquita at 2024-10-02T22:20:43-04:00
determinism: Deterministic MonadGetUnique LlvmM

Update LlvmM to thread a unique deterministic supply (using UniqDSMT),
and use it in the MonadGetUnique instance.

This makes uniques sampled from LlvmM deterministic, which guarantees
object determinism with -fllvm.

Fixes #25274

- - - - -
36bbb167 by Matthew Pickering at 2024-10-02T22:21:18-04:00
Bump LLVM upper bound to allow LLVM 19

Also bumps the ci-images commit so that the deb12 images uses LLVM 19
for testing.

-------------------------
Metric Decrease:
    size_hello_artifact_gzip
    size_hello_unicode_gzip
-------------------------

Fixes #25295

- - - - -
0029ca91 by Matthew Pickering at 2024-10-02T22:21:54-04:00
configure: Allow happy-2.0.2

happy-2.0.2 can be used to compile GHC.

happy-2.0 and 2.0.1 have bugs which make it unsuitable to use.

The version bound is now == 1.20.* || >= 2.0.2 && < 2.1

Fixes #25276

- - - - -
92976985 by ARATA Mizuki at 2024-10-02T22:22:35-04:00
Use bundled llc/opt on Windows (#22438)

- - - - -
af59749a by Matthew Pickering at 2024-10-02T22:23:11-04:00
Fix registerArch for riscv64

The register allocator doesn't support vector registers on riscv64,
therefore advertise as NoVectors.

Fixes #25314

- - - - -
a49e66fc by Matthew Pickering at 2024-10-02T22:23:11-04:00
riscv: Avoid using csrr instruction to test for vector registers

The csrr instruction isn't allowed in qemu user-mode, and raises an
illegal instruction error when it is encountered.

Therefore for now, we just hard-code that there is no support for vector
registers since the rest of the compiler doesn't support vector
registers for riscv.

Fixes #25312

- - - - -
115a30e9 by Andreas Klebinger at 2024-10-02T22:23:11-04:00
Add support for fp min/max to riscv

Fixes #25313

- - - - -
f28b5992 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite/perf: Report better error message on malformed note

Previously a malformed perf note resulted in very poor errors.
Here we slight improve this situation.

- - - - -
51377508 by Ben Gamari at 2024-10-02T22:23:47-04:00
testsuite: Handle division-by-zero more gracefully

Previously we would fail with an ZeroDivisionError.

Fixes #25321

- - - - -
50490075 by Matthew Pickering at 2024-10-03T05:55:13-04:00
ci: Add nightly & release ubuntu-22.04 jobs

This adds build of bindists on ubuntu-22.04 on nightly and release
pipelines.

We also update ghcup-metadata to provide ubuntu-22.04 bindists on
ubuntu-22.04.

Fixes #25317

- - - - -
9cf1cef5 by Zubin Duggal at 2024-10-03T05:55:49-04:00
haddock: Bump binary interface version to 46.

This allows haddock to give good error messages when being used on mismatched interface files.

We bump to 46 since GHC 9.12 uses version 45: https://gitlab.haskell.org/ghc/ghc/-/commit/362afd632032ee8f174690c3ffe0015076b83ce6

This should have been done in e4ac1b0d281b85a0144d1ef6f84a1df00e236052 but was overlooked.

- - - - -
2293c0b7 by Andreas Klebinger at 2024-10-03T05:56:25-04:00
Change versionig of ghc-experimental to follow ghc versions.

Just like ghc-internal it will now use the @ProjectVersionForLib@ macro for versioning.
This means for ghc=9.10.1, ghc-experimental's version will be 9.1001.0 and so on.

This fixes #25289

- - - - -
876d6e0e by Ben Gamari at 2024-10-04T15:07:53+01:00
base: Add `HasCallStack` constraint to `ioError`

As proposed in core-libraries-committee#275.

- - - - -
9bfd9fd0 by Matthew Pickering at 2024-10-04T15:08:03+01:00
Fix toException method for ExceptionWithContext

Fixes #25235

- - - - -
ac004028 by Matthew Pickering at 2024-10-04T15:09:07+01:00
Exception rethrowing

Basic changes:

* Change `catch` function to propagate exceptions using the
  WhileHandling mechanism.
* Introduce `catchNoPropagate`, which does the same as before, but
  passes an exception which can be rethrown.
* Introduce `rethrowIO` combinator, which rethrows an exception with a
  context and doesn't add a new backtrace.
* Introduce `tryWithContext` for a variant of `try` which can rethrow
  the exception with it's original context.
* onException is modified to rethrow the original error rather than
  creating a new callstack.
* Functions which rethrow in GHC.Internal.IO.Handle.FD,
  GHC.Internal.IO.Handle.Internals, GHC.Internal.IO.Handle.Text, and
  GHC.Internal.System.IO.Error are modified to not add a new callstack.

Implements CLC proposal#202 <https://github.com/haskell/core-libraries-committee/issues/202>

- - - - -
bcb293f2 by Cheng Shao at 2024-10-04T17:59:28-04:00
testsuite: remove accidentally checked in debug print logic

- - - - -
68e2da5a by Rodrigo Mesquita at 2024-10-05T10:36:15-04:00
Deprecation for WarnCompatUnqualifiedImports

Fixes #25330

- - - - -
4327f0e8 by Andrew Lelechenko at 2024-10-05T10:36:52-04:00
Restrict Data.List.NonEmpty.unzip to NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)

Implementing the final phase of CLC proposal https://github.com/haskell/core-libraries-committee/issues/86

- - - - -
ceca9efb by Cheng Shao at 2024-10-06T02:18:31+00:00
driver: fix runWorkerLimit on wasm

This commit fixes link-time unresolved symbol errors for sem_open etc
on wasm, by making runWorkerLimit always behave single-threaded. This
avoids introducing the jobserver logic into the final wasm module and
thus avoids referencing the posix semaphore symbols.

- - - - -
135fd1ac by Torsten Schmits at 2024-10-06T02:18:31+00:00
Parallelize getRootSummary computations in dep analysis downsweep

This reuses the upsweep step's infrastructure to process batches of
modules in parallel.

I benchmarked this by running `ghc -M` on two sets of 10,000 modules;
one with a linear dependency chain and the other with a binary tree.
Comparing different values for the number of modules per thread
suggested an optimum at `length targets `div` (n_cap * 2)`, with results
similar to this one (6 cores, 12 threads):

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      1.775 s ±  0.026 s    [User: 1.377 s, System: 0.399 s]
  Range (min … max):    1.757 s …  1.793 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):     876.2 ms ±  20.9 ms    [User: 1833.2 ms, System: 518.6 ms]
  Range (min … max):   856.2 ms … 898.0 ms    3 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):     793.5 ms ±  23.2 ms    [User: 2318.9 ms, System: 718.6 ms]
  Range (min … max):   771.9 ms … 818.0 ms    3 runs
```

Results don't differ much when the batch size is reduced to a quarter
of that, but there's significant thread scheduling overhead for a size
of 1:

```
Benchmark 1: linear 1 jobs
  Time (mean ± σ):      2.611 s ±  0.029 s    [User: 2.851 s, System: 0.783 s]
  Range (min … max):    2.591 s …  2.632 s    2 runs

Benchmark 2: linear 6 jobs
  Time (mean ± σ):      1.189 s ±  0.007 s    [User: 2.707 s, System: 1.103 s]
  Range (min … max):    1.184 s …  1.194 s    2 runs

Benchmark 3: linear 12 jobs
  Time (mean ± σ):      1.097 s ±  0.006 s    [User: 2.938 s, System: 1.300 s]
  Range (min … max):    1.093 s …  1.101 s    2 runs
```

Larger batches also slightly worsen performance.

- - - - -
535a2117 by Daniel Díaz at 2024-10-06T09:51:46-04:00
Clarify the meaning of "exactly once" in LinearTypes

Solves documentaion issue #25084.

- - - - -
92f8939a by Krzysztof Gogolewski at 2024-10-06T09:52:22-04:00
Only allow (a => b) :: Constraint rather than CONSTRAINT rep

Fixes #25243

- - - - -
4a2f0f13 by Alan Zimmerman at 2024-10-07T05:16:54-04:00
EPA: Remove unused hsCaseAnnsRest

We never populate it, so remove it.

- - - - -
5099057b by John Paul Adrian Glaubitz at 2024-10-07T05:17:40-04:00
rts: Fix invocation of __ieee_set_fp_control() on alpha-linux

Fixes the following error when building GHC on alpha-linux:

rts/posix/Signals.c: In function ‘initDefaultHandlers’:

rts/posix/Signals.c:709:5: error:
     error: implicit declaration of function ‘ieee_set_fp_control’ [-Wimplicit-function-declaration]
      709 |     ieee_set_fp_control(0);
          |     ^~~~~~~~~~~~~~~~~~~
    |
709 |     ieee_set_fp_control(0);
    |

- - - - -
c9590ba0 by Teo Camarasu at 2024-10-07T05:18:17-04:00
Add changelog entries for !12479

- - - - -
bf9c9566 by Matthew Pickering at 2024-10-07T13:19:30-04:00
javascript: Read fields of ObjectBlock lazily

When linking a module with a large dependency footprint too much of the
object files were forced during linking. This lead to a large amount of
memory taken up by thunks which would never be forced

On the PartialDownsweep test this halves the memory required (from 25G
to 13G).

Towards #25324

-------------------------
Metric Increase:
    size_hello_obj
-------------------------

- - - - -
571329df by Matthew Pickering at 2024-10-07T13:20:06-04:00
ci: Run the i386 validation job when i386 label is set

This is helpful when making changes to base and must update the
javascript and i386 base exports files.

- - - - -
e68f9aaf by Matthew Pickering at 2024-10-07T13:20:42-04:00
Rewrite partitionByWorkerSize to avoid pattern match checker bug

With `-g3` the pattern match checker would warn about these incomplete
patterns. This affects the debug_info builds on CI.

```
    Pattern match(es) are non-exhaustive
    In an equation for ‘go’:
        Patterns of type ‘[a]’, ‘[a]’, ‘[SpecFailWarning]’ not matched:
            (_:_) _ _
     |
2514 |         go [] small warnings = (small, warnings)
     |         ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^...
```

Workaround for #25338

- - - - -
d915dc8b by Arnaud Spiwack at 2024-10-07T19:23:00-04:00
Remove the wrapper/coercion-passing logic for submultiplicity checks

Instead, we use a dedicated DelayedError, which is emitted
systematically on submultiplicity checks, but is suppressed if we can
indeed solve the submultiplicity constraint with a reflexivity
coercion.

This way, we don't have to return anything from `tcSubMult`, which now
looks like a regular constraint check, the rest is implementation
detail. This removes all of the strange boilerplate that I'd been
struggling with under the previous implementation. Even if
submultiplicity checks are not properly constraints, this way it's
contained entirely within a `WantedConstraint`. Much more pleasant.

Closes #25128.

- - - - -
1d226116 by Sven Tennie at 2024-10-07T19:23:37-04:00
AArch64: Implement switch/jump tables (#19912)

This improves the performance of Cmm switch statements (compared to a
chain of if statements.)

- - - - -
3fe621dd by Mario Blažević at 2024-10-07T19:24:18-04:00
Fixes #25256, missing parens inside TH-printed pattern type signature

- - - - -
ea4b4391 by ARATA Mizuki at 2024-10-07T19:24:59-04:00
Better documentation for floatRange function

Closes #16479

- - - - -
ff09205c by Andreas Klebinger at 2024-10-07T19:25:35-04:00
Adjust progress message for hadrian to include cwd.

Fixes #25335

- - - - -
5fd320da by Sven Tennie at 2024-10-07T19:26:12-04:00
CCallConv test: Align argument types

The C calling convention / standard requires that arguments and their
values are of the same type.

- - - - -
c6e5fd3d by Cheng Shao at 2024-10-07T19:26:47-04:00
hadrian: remove unused ghciWithDebugger field from flavour config

This patch removes the ghciWithDebugger field from flavour config
since it's actually not used anywhere.

- - - - -
9c9c790d by sheaf at 2024-10-07T19:27:23-04:00
user's guide: update docs for X86 CPU flags

This commit updates the section of the user's guide pertaining to
X86 feature flags with the following changes:

  - the NCG backend now supports SIMD, so remove all text
    that says the contrary,
  - the LLVM backend does not "automatically detect" features,
    so remove any text that makes that claim.

- - - - -
a1ecc826 by Sven Tennie at 2024-10-08T13:36:03-04:00
ci: RISCV64 cross-compile testing

This adds a validation job which tests that we can build a riscv64 cross
compiler and build a simple program using it. We do not currently run
the whole testsuite.

Towards #25254

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
d5c2577f by Arnaud Spiwack at 2024-10-08T13:36:44-04:00
Remove unused accumulators in partition_errors

- - - - -
55609880 by Andrzej Rybczak at 2024-10-09T16:41:46-04:00
Fix typo in the @since annotation of annotateIO

- - - - -
ef481813 by Alan Zimmerman at 2024-10-09T16:42:23-04:00
EPA: Remove [AddEpAnn] from (most of) HsExpr

EPA: introduce EpAnnLam for lambda annotationsi, and remove `glAA`
from `Parser.y`, it is the same as `glR`

EPA: Remove unused annotation from XOpApp

EPA: Use EpToken for XNPat and XNegApp

EPA: specific anns for XExplicitTuple / XTuplePat / sumPatParens.

EPA: Use specific annotation for MultiIf

EPA: Move annotations into FunRhs

EPA: Remove [AddEpAnn] from SigPat and ExprWithTySig

EPA: Remove [AddEpAnn] from ArithSeq

EPA: Remove [AddEpAnn] from HsProc

EPA: Remove [AddEpAnn] from HsStatic

EPA: Remove [AddEpAnn] from BindStmt

EPA: Remove [AddEpAnn] from TransStmt

EPA: Remove [AddEpAnn] from HsTypedSplice

EPA: Remove [AddEpAnn] from HsUntypedSpliceExpr

- - - - -
69960230 by Fabian Thorand at 2024-10-10T19:03:59+00:00
Handle exceptions from IO manager backend

If an IO manager backend throws, it will not actually have registered
the file descriptor. However, at that point, the IO manager state was
already updated to assume the file descriptor is being tracked, leading
to errors and an eventual deadlock down the line as documented in the
issue #21969.

The fix for this is to undo the IO manager state change in case the
backend throws (just as we already do when the backend signals that the
file type is not supported). The exception then bubbles up to user code.

That way we make sure that
1. the bookkeeping state of the IO manager is consistent with the
   actions taken by the backend, even in the presence of unexpected
   failures, and
2. the error is not silent and visible to user code, making failures
   easier to debug.

- - - - -
1587cccf by Hassan Al-Awwadi at 2024-10-11T03:52:36-04:00
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

- - - - -
2338a971 by Cheng Shao at 2024-10-11T03:53:13-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM

This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.

Fixes #25011

Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com>

- - - - -
78ad81ec by Cristiano Moraes at 2024-10-11T03:53:55-04:00
configure: Find C++ probing when GCC version is the latest but G++ is old #23118
- - - - -
083703a1 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Consider Wanteds with rewriters as insoluble

This MR fixes #25325

See GHC.Tc.Types.Constraint, Note [Insoluble Wanteds], especially (IW2)

There is a small change in the error message for T14172, but it looks
entirely acceptable to me.

- - - - -
0dfaeb66 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Wibbles

- - - - -
09d24d82 by Simon Peyton Jones at 2024-10-11T03:54:32-04:00
Spelling errors

- - - - -
694489ed by sheaf at 2024-10-11T03:55:14-04:00
LLVM: use sse4.2 instead of sse42

LLVM expects the former instead of the latter since version 3.4.

Fixes #25019

- - - - -
06ae8507 by sheaf at 2024-10-11T03:55:14-04:00
LLVM: make SSE4.2 imply +popcnt

For consistency with the NCG as well as with Clang and GCC, we make
the SSE4.2 feature flag imply +popcnt when using the LLVM backend.

Fixes #25353

- - - - -
3fe843c7 by Cheng Shao at 2024-10-11T03:55:50-04:00
Drop obsolete libffi Makefile

This patch drops obsolete libffi Makefile from the tree, given it's
completely unused since removal of make build system in !7094.

- - - - -
df70405c by Ben Gamari at 2024-10-11T03:56:26-04:00
ghc-internal: Fix incomplete matches on IOError

As noted in #25362, these incomplete matches were previously not being
warned about. They were easily addressed by use of
`GHC.Internal.Event.Windows.withException`.

Closes #25362.

- - - - -
8584504b by Matthew Pickering at 2024-10-11T03:57:02-04:00
compiler: Fix orientation of GHC.Hs.Doc boot file

We should be free to import things from Language.Haskell.Syntax in GHC
modules. Therefore the the boot file for the loop between ImpExp and
GHC.Hs.Doc was in the wrong place.

Issue #21592

- - - - -
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -
18f532f3 by Ben Gamari at 2024-10-11T23:43:53-04:00
Bump process submodule to v1.6.25.0

- - - - -
a9a3badf by Hassan Al-Awwadi at 2024-10-11T23:44:29-04:00
Move HsInteger and HsRat to an extension constructor

These constructors were only used during the TC stage,
or during template haskell. It seemed clear that it was
independent of the source syntax represented in L.H.S,
and thus we removed it according to #21592.

- - - - -
4dd30cba by Artem Pelenitsyn at 2024-10-11T23:45:09-04:00
Docs: Linear types: link Strict Patterns subsection

Also, fix a bug in RST with missing newline before a listing.

Co-authored-by: Arnaud Spiwack <arnaud at spiwack.net>

- - - - -
adca5f2b by Ben Gamari at 2024-10-11T23:45:45-04:00
users guide: Address remaining TODOs in eventlog format docs

Closes #25296.

- - - - -
9291c125 by Sylvain Henry at 2024-10-11T23:46:26-04:00
Fix z-encoding of tuples (#25364)

Tuples with prefix/suffix strings weren't always properly encoded with
their shortcut notations. Fix this.

- - - - -
c08b68bc by Sven Tennie at 2024-10-11T23:47:01-04:00
Delete constants that can be deduced

There are macros in MachRegs.h to figure those out.

- - - - -
8b402da2 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: Handle broken symlinks properly when creating source dist directories

If we have a broken symlink in the repository, don't try to `need` the symlink
or the target of the symlink. Attempting to do so has `shake` attempt to read the
target to compute its hash, which fails because the target doesn't exist.

- - - - -
16f97667 by Zubin Duggal at 2024-10-12T20:36:57+00:00
hadrian: exclude cabal.project.symlink.broken from source archives

Cabal 3.14 introduced a broken symlink in its testsuite. Unfortunately,
this broke our source distribution as we use use `tar --dereference` to avoid
issues with symlink compatibility on windows, and `tar --dereference` chokes
when it encounters any broken symlinks.

We can't get rid of `--dereference` because symlinks are generally broken on
windows, so the only option is to exclude this file from source archives.

see also https://github.com/haskell/cabal/issues/10442

- - - - -
f1a2c9fc by Zubin Duggal at 2024-10-12T20:36:57+00:00
Bump Cabal submodule to 3.14

Metric Decrease:
    MultiLayerModulesTH_OneShot
Metric Increase:
    haddock.Cabal

- - - - -
745dd590 by Ben Gamari at 2024-10-14T09:13:12-04:00
users-guide: Document GHCi :where command

Resolve #24509.

- - - - -
e9cc4699 by Alan Zimmerman at 2024-10-14T09:13:48-04:00
EPA: Remove [AddEpAnn] from IE, Pat and some Tys

EPA: Remove [AddEpAnn] from LazyPat

EPA: Remove [AddEpAnn] from RecordCon/RecordUpd/ConPat

EPA: Remove [AddEpAnn] from HsFieldBind

EPA: Remove [AddEpAnn] from PatSynBind

EPA: Remove [AddEpAnn] from IPBind

EPA: Remove [AddEpAnn] from FixSig

EPA: Remove [AddEpAnn] from activation rules

EPA: Remove [AddEpann] from SpecInstSig

EPA: Remove [AddEpAnn] from MinimalSig

EPA: Remove [AddEpAnn] from SCCFunSig

EPA: Remove [AddEpAnn] from CompleteMatchSig

EPA: Remove [AddEpAnn] from AnnSig, as used in PatSynSig, ClassOpSig, TypeSig

EPA: Remove [AddEpAnn] from IEThingAbs

EPA: Remove [AddEpAnn] from IEThingAll / IEThingWith

EPA: Remove [AddEpAnn] from IEModuleContents

EPA: Remove [AddEpAnn] from HsOpTy

EPA: Remove [AddEpAnn] for various binders

EPA: Remove [AddEpAnn] for HsIParamTy

- - - - -
81a570bf by Sebastian Graf at 2024-10-14T22:15:31-04:00
Desugaring, plus -Wincomplete-record-selectors

This commit does several related things:

* Major refactor of the handling of applications in the desugarer.
  Now all applications are handled in `dsApp`, `ds_app` and related
  functions.  This dramatically simplifies the code and removes
  complicated cruft that had accumulated.  Hooray.

  Fixes #25281.

* Improve the handling of -Wincomplete-record-selectors.

  We now incorporate the result type of unsaturated record selector
  applications as well as consider long-distance information in
  getField applications.

  Plus, the implmentation now builds the improved `dsApp` stuff
  above, so it is much easier to understand.

  Plus, incorporates improved error message wording suggested
  by Adam Gundry in !12685.

  Fixes #24824, #24891

  See the long Note [Detecting incomplete record selectors]

* Add -Wincomplete-record-selectors to -Wall, as specified in
  GHC Proposal 516.

  To do this, I also had to add -Wno-incomplete-record-selectors
  to the build flags for Cabal in GHC's CI.  See
  hadrian/src/Settings/Warnings.hs.  We can remove this when
  Cabal is updated so that it doesn't trigger the warning:
  https://github.com/haskell/cabal/issues/10402

2.6% decrease in compile time allocation in RecordUpPerf

Metric Decrease:
    RecordUpdPerf

- - - - -
ae7bc08e by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Elmininate incomplete record selectors

This patch is a pure refactor of GHC's source code, to avoid the use
of partial record selectors.  It was provoked by adding
-Wincomplete-record-selectors to -Wall (as the GHC Proposal specified),
which in turn showed up lots of places where GHC was using incomplete
record selectors.

This patch does mostly-simple refactoring to make it clear to the pattern
match checker that there is in fact no partiality.

There is one externally-visible change: I changed the data type HoleFit
to split out the two cases

  data HoleFit = TcHoleFit  TcHoleFit | RawHoleFit SDoc
  data TcHoleFit = HoleFit { ...lots of fields }

There are large swathes of code that just deal with `TcHoleFit`, and
having it as a separate data types makes it apparent that `RawHoleFit`
can't occur.

This makes it much better -- but the change is visible in the
HolePlugin interface.  I decided that there are so few clients of this
API that it's worth the change.

I moved several functions from Language.Haskell.Syntax to GHC.Hs.
Reason, when instantiated at (GhcPass _), the extension data construtcor
is guaranteed unused, and that justifies omitted patterns in these
functions.  By putting them in GHC.Hs.X I can specialise the type for
(GhcPass _) and thereby make the function total.

An interesting side-light is that there were a few local function
definitions without a type signature, like this one in GHC.Parser.Header
     convImport (L _ i) = (ideclPkgQual i, reLoc $ ideclName i)
This is fully closed, and so is generalised; but that generalises
it to any old pass, not (GhcPass _), so GHC rightly complains about the
use of the selector `ideclPkgQual`.  I added a type signature to `i`, thus
     convImport (L _ (i::ImportDecl GhcPs))
         = (ideclPkgQual i, reLoc $ ideclName i)
which specialised the function enough to make the record selector complete.
Quite a surprising consequence of local let-generalisation!

- - - - -
6a067226 by Simon Peyton Jones at 2024-10-14T22:15:31-04:00
Add -Werror=-Wno-error=incomplete-record-selectors to hadrian-multi

In the main MR, -Wall now includes -Wincomplete-record-selectors.
However `hadrian-multi` has many, many warnings about incomplete
record selectors, so this patch stops those warnings being treated
as errors.  (See discussion on !13308.)

A better fix would be to remove the use of incomplete record
selectors, since each of them represents a potential crash.

- - - - -
edeafc14 by Ben Gamari at 2024-10-14T22:16:08-04:00
users-guide: Document field coalescence

- - - - -
55b83587 by ARATA Mizuki at 2024-10-14T22:16:49-04:00
LLVM backend: Use correct rounding for Float literals

Fixes #22033

- - - - -
e59fe5c6 by Hassan Al-Awwadi at 2024-10-15T08:25:33+00:00
Changed import from Ghc.  module to L.H.S module

Progresses #21592

For some reason we still imported GHC.Types.Fixity when the definitino of Fixity and LexicalFixity have already been moved to Language.Haskell.Syntax.Basic. This fixes that for

- - - - -
ab1767d5 by Simon Peyton Jones at 2024-10-15T23:45:04-04:00
Add a release-notes entry for -Wincomplete-record-selectors

- - - - -
6f0a62db by ur4t at 2024-10-16T15:33:43+00:00
GHCi: fix improper location of ghci_history file

Fixes #24266

- - - - -
5f67db48 by Alan Zimmerman at 2024-10-17T05:18:43-04:00
EPA: Remove [AddEpAnn] commit 3

EPA: Remove [AddEpAnn] from HsDocTy

EPA: Remove [AddEpAnn] from HsBangTy

EPA: Remove [AddEpAnn] from HsExplicitListTy

EPA: Remove [AddEpAnn] from HsExplicitTupleTy

EPA: Remove [AddEpAnn] from HsTypedBracket

EPA: Remove [AddEpAnn] from HsUntypedBracket

EPA: Remove [AddEpAnn] from PatBuilderOpApp

EPA: break out 'EpToken "|"' from ClassDecl anns

EPA: Remove [AddEpAnn] from ClassDecl

EPA: Remove [AddEpAnn] from SynDecl

- - - - -
fbbbd010 by Daan Rijks at 2024-10-17T05:19:19-04:00
Expand the haddocks for Control.Category

- - - - -
076c1a10 by Andrew Lelechenko at 2024-10-17T05:19:19-04:00
documentation: more examples for Control.Category

- - - - -
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -
4486d9ae by Simon Peyton Jones at 2024-10-30T10:12:46+00:00
Just a start on specialising expressions

Addresses #24359.  Just a start, does not compile.

- - - - -
ea08e617 by Simon Peyton Jones at 2024-10-30T10:12:46+00:00
More progress

(Still does not compile.)

- - - - -
59cc9263 by Simon Peyton Jones at 2024-10-30T10:38:39+00:00
More progress

- - - - -
2f5e00e9 by Simon Peyton Jones at 2024-10-30T10:38:39+00:00
Wibble

- - - - -
cf021b23 by Simon Peyton Jones at 2024-10-30T10:40:50+00:00
More progress

- - - - -
8fcebf95 by Simon Peyton Jones at 2024-10-30T10:40:50+00:00
More progress

- - - - -
069fb55f by Simon Peyton Jones at 2024-10-30T10:40:50+00:00
Finally runnable!

- - - - -
eecf1364 by Simon Peyton Jones at 2024-10-30T10:40:50+00:00
Progress

- - - - -
db3528fb by Simon Peyton Jones at 2024-10-30T10:40:50+00:00
Working I think

- - - - -
d58e7834 by Andrei Borzenkov at 2024-10-30T10:52:04+00:00
Fix derivations conflict in parser, disambiguate them in post-process

- - - - -
6bdf2a4d by Alan Zimmerman at 2024-10-30T12:14:01+00:00
Fix exact printing for RuleBndrs

This puts the exact print annotations inside a TTG extension point in
RuleBndrs.

It also adds an exact print case for SpecSigE

- - - - -
0011109a by Simon Peyton Jones at 2024-10-30T12:14:01+00:00
Wibble imports

- - - - -
0455c062 by Simon Peyton Jones at 2024-10-30T12:14:01+00:00
Typo in comments

- - - - -
d2767b8a by Simon Peyton Jones at 2024-10-30T12:14:01+00:00
Wibbles

- - - - -
19583461 by Simon Peyton Jones at 2024-10-30T12:14:53+00:00
Go via new route for simple SPECIALISE pragmas

- - - - -
248afd5b by Simon Peyton Jones at 2024-10-30T12:15:30+00:00
Further work

- - - - -
d164ea11 by Simon Peyton Jones at 2024-10-30T12:15:30+00:00
Wibble

- - - - -
7fcd3cee by Simon Peyton Jones at 2024-10-30T12:15:30+00:00
Fix build

- - - - -


15 changed files:

- .ghcid
- .gitignore
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitmodules
- CODEOWNERS
- cabal.project-reinstall
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c412451fcf9960df43ecd24b1c8a384a77a1ac31...7fcd3cee500621733a70a26a50801686a0f60989

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c412451fcf9960df43ecd24b1c8a384a77a1ac31...7fcd3cee500621733a70a26a50801686a0f60989
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 13:20:57 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Wed, 30 Oct 2024 09:20:57 -0400
Subject: [Git][ghc/ghc][wip/andreask/selectors] ghc-heap: Fix incomplete
 selector warnings.
Message-ID: <672232b96ad66_1685f7b96978232dc@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC


Commits:
6219ec60 by Andreas Klebinger at 2024-10-30T14:01:43+01:00
ghc-heap: Fix incomplete selector warnings.

Use utility functions instead of selectors to read partial attributes.

Part of fixing #25380.

- - - - -


4 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -128,6 +128,11 @@ isFullyEvaluatedTerm NewtypeWrap{wrapped_term=t} = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm RefWrap{wrapped_term=t}     = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm _                  = False
 
+-- | Gives an error if the term doesn't have subterms
+expectSubTerms :: Term -> [Term]
+expectSubTerms (Term { subTerms = subTerms} ) = subTerms
+expectSubTerms _                              = panic "expectSubTerms"
+
 instance Outputable (Term) where
  ppr t | Just doc <- cPprTerm cPprTermBase t = doc
        | otherwise = panic "Outputable Term instance"
@@ -332,8 +337,8 @@ cPprTermBase :: forall m. Monad m => CustomTermPrinter m
 cPprTermBase y =
   [ ifTerm (isTupleTy.ty) (\_p -> liftM (parens . hcat . punctuate comma)
                                       . mapM (y (-1))
-                                      . subTerms)
-  , ifTerm (\t -> isTyCon listTyCon (ty t) && subTerms t `lengthIs` 2)
+                                      . expectSubTerms)
+  , ifTerm (\t -> isTyCon listTyCon (ty t) && expectSubTerms t `lengthIs` 2)
            ppr_list
   , ifTerm' (isTyCon intTyCon     . ty) ppr_int
   , ifTerm' (isTyCon charTyCon    . ty) ppr_char
@@ -768,7 +773,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
     traceTR (text "Gave up reconstructing a term after" <>
                   int max_depth <> text " steps")
     clos <- trIO $ GHCi.getClosure interp a
-    return (Suspension (tipe (info clos)) my_ty a Nothing)
+    return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
   go !max_depth my_ty old_ty a = do
     let monomorphic = not(isTyVarTy my_ty)
     -- This ^^^ is a convention. The ancestor tests for
@@ -864,7 +869,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
       _ -> do
          traceTR (text "Unknown closure:" <+>
                   text (show (fmap (const ()) clos)))
-         return (Suspension (tipe (info clos)) my_ty a Nothing)
+         return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
 
   -- insert NewtypeWraps around newtypes
   expandNewtypes = foldTerm idTermFold { fTerm = worker } where
@@ -918,7 +923,7 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
 
     go_rep ptr_i arr_i ty rep
       | isGcPtrRep rep = do
-          t <- recurse ty $ (ptrArgs clos)!!ptr_i
+          t <- recurse ty $ (getClosurePtrArgs clos)!!ptr_i
           return (ptr_i + 1, arr_i, t)
       | otherwise = do
           -- This is a bit involved since we allow packing multiple fields


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -44,6 +44,11 @@ Cmm
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+* The functions `getClosureInfoTbl_maybe`, and `getClosureInfoTbl`,
+ `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow
+  reading of the relevant Closure attributes without reliance on incomplete
+  selectors.
+
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -29,6 +29,10 @@ module GHC.Exts.Heap (
     , WhyBlocked(..)
     , TsoFlags(..)
     , HasHeapRep(getClosureData)
+    , getClosureInfoTbl
+    , getClosureInfoTbl_maybe
+    , getClosurePtrArgs
+    , getClosurePtrArgs_maybe
     , getClosureDataFromHeapRep
     , getClosureDataFromHeapRepPrim
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -8,12 +8,18 @@
 {-# LANGUAGE DeriveTraversable #-}
 -- Late cost centres introduce a thunk in the asBox function, which leads to
 -- an additional wrapper being added to any value placed inside a box.
+-- This can be removed once our boot compiler is no longer affected by #25212
 {-# OPTIONS_GHC -fno-prof-late  #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Exts.Heap.Closures (
     -- * Closures
       Closure
     , GenClosure(..)
+    , getClosureInfoTbl
+    , getClosureInfoTbl_maybe
+    , getClosurePtrArgs
+    , getClosurePtrArgs_maybe
     , PrimType(..)
     , WhatNext(..)
     , WhyBlocked(..)
@@ -67,6 +73,7 @@ import Data.Word
 import GHC.Exts
 import GHC.Generics
 import Numeric
+import GHC.Stack (HasCallStack)
 
 ------------------------------------------------------------------------
 -- Boxes
@@ -382,6 +389,104 @@ data GenClosure b
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
 
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosureInfoTbl_maybe #-} -- Ensure we can get rid of the just box
+getClosureInfoTbl_maybe closure = case closure of
+  ConstrClosure{info} ->Just info
+  FunClosure{info} ->Just info
+  ThunkClosure{info} ->Just info
+  SelectorClosure{info} ->Just info
+  PAPClosure{info} ->Just info
+  APClosure{info} ->Just info
+  APStackClosure{info} ->Just info
+  IndClosure{info} ->Just info
+  BCOClosure{info} ->Just info
+  BlackholeClosure{info} ->Just info
+  ArrWordsClosure{info} ->Just info
+  MutArrClosure{info} ->Just info
+  SmallMutArrClosure{info} ->Just info
+  MVarClosure{info} ->Just info
+  IOPortClosure{info} ->Just info
+  MutVarClosure{info} ->Just info
+  BlockingQueueClosure{info} ->Just info
+  WeakClosure{info} ->Just info
+  TSOClosure{info} ->Just info
+  StackClosure{info} ->Just info
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{info} -> Just info
+  UnsupportedClosure {info} -> Just info
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
+getClosureInfoTbl closure = case getClosureInfoTbl_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosureInfoTbl - Closure without info table"
+
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosurePtrArgs_maybe :: GenClosure b -> Maybe [b]
+{-# INLINE getClosurePtrArgs_maybe #-} -- Ensure we can get rid of the just box
+getClosurePtrArgs_maybe closure = case closure of
+  ConstrClosure{ptrArgs} -> Just ptrArgs
+  FunClosure{ptrArgs} -> Just ptrArgs
+  ThunkClosure{ptrArgs} -> Just ptrArgs
+  SelectorClosure{} -> Nothing
+  PAPClosure{} -> Nothing
+  APClosure{} -> Nothing
+  APStackClosure{} -> Nothing
+  IndClosure{} -> Nothing
+  BCOClosure{} -> Nothing
+  BlackholeClosure{} -> Nothing
+  ArrWordsClosure{} -> Nothing
+  MutArrClosure{} -> Nothing
+  SmallMutArrClosure{} -> Nothing
+  MVarClosure{} -> Nothing
+  IOPortClosure{} -> Nothing
+  MutVarClosure{} -> Nothing
+  BlockingQueueClosure{} -> Nothing
+  WeakClosure{} -> Nothing
+  TSOClosure{} -> Nothing
+  StackClosure{} -> Nothing
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{} -> Nothing
+  UnsupportedClosure{} -> Nothing
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosurePtrArgs :: HasCallStack => GenClosure b -> [b]
+getClosurePtrArgs closure = case getClosurePtrArgs_maybe closure of
+  Just ptrs -> ptrs
+  Nothing -> error "getClosurePtrArgs - Closure without ptrArgs table"
+
 type StgStackClosure = GenStgStackClosure Box
 
 -- | A decoded @StgStack@ with `StackFrame`s



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6219ec604380d9da79b0928207b8119b823c21e6

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 13:22:46 2024
From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK))
Date: Wed, 30 Oct 2024 09:22:46 -0400
Subject: [Git][ghc/ghc][wip/andreask/selectors] ghc-heap: Fix incomplete
 selector warnings.
Message-ID: <672233262cf1_1685f7b3fd4423698@gitlab.mail>



Andreas Klebinger pushed to branch wip/andreask/selectors at Glasgow Haskell Compiler / GHC


Commits:
5f447f40 by Andreas Klebinger at 2024-10-30T14:03:33+01:00
ghc-heap: Fix incomplete selector warnings.

Use utility functions instead of selectors to read partial attributes.

Part of fixing #25380.

- - - - -


4 changed files:

- compiler/GHC/Runtime/Heap/Inspect.hs
- docs/users_guide/9.14.1-notes.rst
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs


Changes:

=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -128,6 +128,11 @@ isFullyEvaluatedTerm NewtypeWrap{wrapped_term=t} = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm RefWrap{wrapped_term=t}     = isFullyEvaluatedTerm t
 isFullyEvaluatedTerm _                  = False
 
+-- | Gives an error if the term doesn't have subterms
+expectSubTerms :: Term -> [Term]
+expectSubTerms (Term { subTerms = subTerms} ) = subTerms
+expectSubTerms _                              = panic "expectSubTerms"
+
 instance Outputable (Term) where
  ppr t | Just doc <- cPprTerm cPprTermBase t = doc
        | otherwise = panic "Outputable Term instance"
@@ -332,8 +337,8 @@ cPprTermBase :: forall m. Monad m => CustomTermPrinter m
 cPprTermBase y =
   [ ifTerm (isTupleTy.ty) (\_p -> liftM (parens . hcat . punctuate comma)
                                       . mapM (y (-1))
-                                      . subTerms)
-  , ifTerm (\t -> isTyCon listTyCon (ty t) && subTerms t `lengthIs` 2)
+                                      . expectSubTerms)
+  , ifTerm (\t -> isTyCon listTyCon (ty t) && expectSubTerms t `lengthIs` 2)
            ppr_list
   , ifTerm' (isTyCon intTyCon     . ty) ppr_int
   , ifTerm' (isTyCon charTyCon    . ty) ppr_char
@@ -768,7 +773,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
     traceTR (text "Gave up reconstructing a term after" <>
                   int max_depth <> text " steps")
     clos <- trIO $ GHCi.getClosure interp a
-    return (Suspension (tipe (info clos)) my_ty a Nothing)
+    return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
   go !max_depth my_ty old_ty a = do
     let monomorphic = not(isTyVarTy my_ty)
     -- This ^^^ is a convention. The ancestor tests for
@@ -864,7 +869,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do
       _ -> do
          traceTR (text "Unknown closure:" <+>
                   text (show (fmap (const ()) clos)))
-         return (Suspension (tipe (info clos)) my_ty a Nothing)
+         return (Suspension (tipe (getClosureInfoTbl clos)) my_ty a Nothing)
 
   -- insert NewtypeWraps around newtypes
   expandNewtypes = foldTerm idTermFold { fTerm = worker } where
@@ -918,7 +923,7 @@ extractSubTerms recurse clos = liftM thdOf3 . go 0 0
 
     go_rep ptr_i arr_i ty rep
       | isGcPtrRep rep = do
-          t <- recurse ty $ (ptrArgs clos)!!ptr_i
+          t <- recurse ty $ (getClosurePtrArgs clos)!!ptr_i
           return (ptr_i + 1, arr_i, t)
       | otherwise = do
           -- This is a bit involved since we allow packing multiple fields


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -44,6 +44,11 @@ Cmm
 ``ghc-heap`` library
 ~~~~~~~~~~~~~~~~~~~~
 
+* The functions `getClosureInfoTbl_maybe`, `getClosureInfoTbl`,
+ `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow
+  reading of the relevant Closure attributes without reliance on incomplete
+  selectors.
+
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -29,6 +29,10 @@ module GHC.Exts.Heap (
     , WhyBlocked(..)
     , TsoFlags(..)
     , HasHeapRep(getClosureData)
+    , getClosureInfoTbl
+    , getClosureInfoTbl_maybe
+    , getClosurePtrArgs
+    , getClosurePtrArgs_maybe
     , getClosureDataFromHeapRep
     , getClosureDataFromHeapRepPrim
 


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -8,12 +8,18 @@
 {-# LANGUAGE DeriveTraversable #-}
 -- Late cost centres introduce a thunk in the asBox function, which leads to
 -- an additional wrapper being added to any value placed inside a box.
+-- This can be removed once our boot compiler is no longer affected by #25212
 {-# OPTIONS_GHC -fno-prof-late  #-}
+{-# LANGUAGE NamedFieldPuns #-}
 
 module GHC.Exts.Heap.Closures (
     -- * Closures
       Closure
     , GenClosure(..)
+    , getClosureInfoTbl
+    , getClosureInfoTbl_maybe
+    , getClosurePtrArgs
+    , getClosurePtrArgs_maybe
     , PrimType(..)
     , WhatNext(..)
     , WhyBlocked(..)
@@ -67,6 +73,7 @@ import Data.Word
 import GHC.Exts
 import GHC.Generics
 import Numeric
+import GHC.Stack (HasCallStack)
 
 ------------------------------------------------------------------------
 -- Boxes
@@ -382,6 +389,104 @@ data GenClosure b
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
 
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosureInfoTbl_maybe :: GenClosure b -> Maybe StgInfoTable
+{-# INLINE getClosureInfoTbl_maybe #-} -- Ensure we can get rid of the just box
+getClosureInfoTbl_maybe closure = case closure of
+  ConstrClosure{info} ->Just info
+  FunClosure{info} ->Just info
+  ThunkClosure{info} ->Just info
+  SelectorClosure{info} ->Just info
+  PAPClosure{info} ->Just info
+  APClosure{info} ->Just info
+  APStackClosure{info} ->Just info
+  IndClosure{info} ->Just info
+  BCOClosure{info} ->Just info
+  BlackholeClosure{info} ->Just info
+  ArrWordsClosure{info} ->Just info
+  MutArrClosure{info} ->Just info
+  SmallMutArrClosure{info} ->Just info
+  MVarClosure{info} ->Just info
+  IOPortClosure{info} ->Just info
+  MutVarClosure{info} ->Just info
+  BlockingQueueClosure{info} ->Just info
+  WeakClosure{info} ->Just info
+  TSOClosure{info} ->Just info
+  StackClosure{info} ->Just info
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{info} -> Just info
+  UnsupportedClosure {info} -> Just info
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosureInfoTbl :: HasCallStack => GenClosure b -> StgInfoTable
+getClosureInfoTbl closure = case getClosureInfoTbl_maybe closure of
+  Just info -> info
+  Nothing -> error "getClosureInfoTbl - Closure without info table"
+
+-- | Get the info table for a heap closure, or Nothing for a prim value
+--
+-- @since 9.14.1
+getClosurePtrArgs_maybe :: GenClosure b -> Maybe [b]
+{-# INLINE getClosurePtrArgs_maybe #-} -- Ensure we can get rid of the just box
+getClosurePtrArgs_maybe closure = case closure of
+  ConstrClosure{ptrArgs} -> Just ptrArgs
+  FunClosure{ptrArgs} -> Just ptrArgs
+  ThunkClosure{ptrArgs} -> Just ptrArgs
+  SelectorClosure{} -> Nothing
+  PAPClosure{} -> Nothing
+  APClosure{} -> Nothing
+  APStackClosure{} -> Nothing
+  IndClosure{} -> Nothing
+  BCOClosure{} -> Nothing
+  BlackholeClosure{} -> Nothing
+  ArrWordsClosure{} -> Nothing
+  MutArrClosure{} -> Nothing
+  SmallMutArrClosure{} -> Nothing
+  MVarClosure{} -> Nothing
+  IOPortClosure{} -> Nothing
+  MutVarClosure{} -> Nothing
+  BlockingQueueClosure{} -> Nothing
+  WeakClosure{} -> Nothing
+  TSOClosure{} -> Nothing
+  StackClosure{} -> Nothing
+
+  IntClosure{} -> Nothing
+  WordClosure{} -> Nothing
+  Int64Closure{} -> Nothing
+  Word64Closure{} -> Nothing
+  AddrClosure{} -> Nothing
+  FloatClosure{} -> Nothing
+  DoubleClosure{} -> Nothing
+
+  OtherClosure{} -> Nothing
+  UnsupportedClosure{} -> Nothing
+
+  UnknownTypeWordSizedPrimitive{} -> Nothing
+
+-- | Partial version of getClosureInfoTbl_maybe for when we know we deal with a
+-- heap closure.
+--
+-- @since 9.14.1
+getClosurePtrArgs :: HasCallStack => GenClosure b -> [b]
+getClosurePtrArgs closure = case getClosurePtrArgs_maybe closure of
+  Just ptrs -> ptrs
+  Nothing -> error "getClosurePtrArgs - Closure without ptrArgs field"
+
 type StgStackClosure = GenStgStackClosure Box
 
 -- | A decoded @StgStack@ with `StackFrame`s



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f447f401c117c5bfc1a0f12dfe5e2ce911ac036

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 13:24:21 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 30 Oct 2024 09:24:21 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: JS: Re-add
 optimization for literal strings in genApp (fixes #23479)
Message-ID: <67223385a6ae2_1685f7b091542403a@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -
106c61e7 by Andreas Klebinger at 2024-10-30T09:24:15-04:00
Add since tag for -fwrite-if-compression in user guide.

Partial fix for #25395

- - - - -
93e73b22 by Alan Zimmerman at 2024-10-30T09:24:15-04:00
EPA: Remove some unused functions

- - - - -
c157d202 by Alan Zimmerman at 2024-10-30T09:24:15-04:00
EPA: use explicit vertical bar token for ExplicitSum / SumPat

- - - - -


30 changed files:

- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/StgToJS/Apply.hs
- compiler/GHC/StgToJS/CodeGen.hs
- compiler/GHC/StgToJS/Expr.hs
- compiler/GHC/StgToJS/ExprCtx.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Literal.hs
- compiler/GHC/StgToJS/Monad.hs
- + compiler/GHC/StgToJS/Sinker/Collect.hs
- compiler/GHC/StgToJS/Sinker.hs → compiler/GHC/StgToJS/Sinker/Sinker.hs
- + compiler/GHC/StgToJS/Sinker/StringsUnfloat.hs
- compiler/GHC/StgToJS/Symbols.hs
- compiler/GHC/StgToJS/Types.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- docs/users_guide/using-optimisation.rst
- rts/js/string.js
- + testsuite/tests/ghci/scripts/T25414.script
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/javascript/Makefile


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d563c4969598d1630709d67bf3a1f01e645bb18...c157d202c9814455c67a7b1407575e66daeb8989

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d563c4969598d1630709d67bf3a1f01e645bb18...c157d202c9814455c67a7b1407575e66daeb8989
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 14:55:32 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 30 Oct 2024 10:55:32 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T24382
Message-ID: <672248e42bca6_2eb5c0456a1495746@gitlab.mail>



Ben Gamari pushed new branch wip/T24382 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24382
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 15:00:41 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 30 Oct 2024 11:00:41 -0400
Subject: [Git][ghc/ghc][wip/T25390] configure: Check version number validity
Message-ID: <67224a1920c73_2eb5c0399db01013cf@gitlab.mail>



Ben Gamari pushed to branch wip/T25390 at Glasgow Haskell Compiler / GHC


Commits:
2985af36 by Ben Gamari at 2024-10-30T11:00:29-04:00
configure: Check version number validity

Here we verify the previously informal invariant that stable release
version numbers must have three components, preventing costly failed
releases.

Specifically, the check fails in the following scenarios:

 * `version=9.13` while `RELEASE=YES` since this would imply a
   release made from an unstable branch
 * `version=9.13.0` since unstable versions should only have two
   components
 * `version=9.12` since this has the wrong number of version components
   for a stable branch

Fixes #25390.

- - - - -


1 changed file:

- m4/fp_setup_project_version.m4


Changes:

=====================================
m4/fp_setup_project_version.m4
=====================================
@@ -2,6 +2,9 @@
 # ---------------------
 AC_DEFUN([FP_SETUP_PROJECT_VERSION],
 [
+    # number of version number components
+    NumVersionComponents="$(( $(echo "$PACKAGE_VERSION" | tr -cd . | wc -c) + 1 ))"
+
     if test "$RELEASE" = "NO"; then
         AC_MSG_CHECKING([for GHC version date])
         if test -f VERSION_DATE; then
@@ -62,6 +65,22 @@ AC_DEFUN([FP_SETUP_PROJECT_VERSION],
     VERSION_MINOR=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\1'/`
     ProjectPatchLevel=`echo $VERSION_TMP | sed 's/^\(@<:@^.@:>@*\)\(\.\{0,1\}\(.*\)\)$/\3'/`
 
+    # Verify that the version number has three components if a release version
+    # (that is, even minor version number).
+    AC_MSG_CHECKING([package version validity])
+    StableRelease="$(( ($VERSION_MINOR & 1) == 0))"
+    if test "$StableRelease" = "1" -a "$NumVersionComponents" != "3"; then
+        AC_MSG_ERROR([Stable (even) version numbers must have three components])
+    elif test "$StableRelease" = "0" -a "$NumVersionComponents" != "2"; then
+        AC_MSG_ERROR([Unstable (odd) version numbers must have two components])
+    elif test "$RELEASE" = "YES" -a "$StableRelease" = "0"; then
+        AC_MSG_ERROR([RELEASE=YES despite having an unstable odd minor version number])
+    elif test "$StableRelease" = "1"; then
+        AC_MSG_RESULT([okay stable branch version])
+    else
+        AC_MSG_RESULT([okay unstable branch version])
+    fi
+
     # Calculate project version as an integer, using 2 digits for minor version
     case $VERSION_MINOR in
       ?) ProjectVersionInt=${VERSION_MAJOR}0${VERSION_MINOR} ;;



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2985af3605ad7aeb527b35da23ba79f12c4979eb

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 15:18:30 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Wed, 30 Oct 2024 11:18:30 -0400
Subject: [Git][ghc/ghc][wip/T25374] rts/Disassembler: Fix encoding of BRK_FUN
 instruction
Message-ID: <67224e46e4476_2eb5c06ef6681145fc@gitlab.mail>



Ben Gamari pushed to branch wip/T25374 at Glasgow Haskell Compiler / GHC


Commits:
04794089 by Ben Gamari at 2024-10-30T11:18:25-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -


5 changed files:

- rts/Disassembler.c
- + testsuite/tests/codeGen/should_run/T25374/T25374.hs
- + testsuite/tests/codeGen/should_run/T25374/T25374.script
- + testsuite/tests/codeGen/should_run/T25374/T25374A.hs
- + testsuite/tests/codeGen/should_run/T25374/all.T


Changes:

=====================================
rts/Disassembler.c
=====================================
@@ -67,12 +67,12 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }
          debugBelch("\n");
-         pc += 4;
+         pc += 6;
          break;
       case bci_SWIZZLE: {
          W_     stkoff = BCO_GET_LARGE_ARG;


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.hs
=====================================
@@ -0,0 +1,8 @@
+import T25374A
+
+fieldsSam :: NP xs -> NP xs -> Bool
+fieldsSam UNil UNil = True
+
+x :: Bool
+x = fieldsSam UNil UNil
+


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.script
=====================================
@@ -0,0 +1,2 @@
+:load T25374
+x


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374A.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+module T25374A where
+
+import GHC.Exts
+
+type NP :: [UnliftedType] -> UnliftedType
+data NP xs where
+  UNil :: NP '[]
+  (::*) :: x -> NP xs -> NP (x ': xs)
+


=====================================
testsuite/tests/codeGen/should_run/T25374/all.T
=====================================
@@ -0,0 +1,3 @@
+# This shouldn't crash the disassembler
+test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, unless(debug_rts(), skip)], ghci_script, [''])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/047940890aab231626a5cc23db7e70f46badd4a5

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 15:48:09 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Wed, 30 Oct 2024 11:48:09 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/T18462
Message-ID: <672255394a2e7_2eb5c08c16bc117133@gitlab.mail>



Sjoerd Visscher pushed new branch wip/T18462 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18462
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 17:08:08 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Wed, 30 Oct 2024 13:08:08 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/rm-use-report-prelude
Message-ID: <672267f820ce1_2eb5c0d4b40812832@gitlab.mail>



Cheng Shao pushed new branch wip/rm-use-report-prelude at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rm-use-report-prelude
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 17:50:21 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 30 Oct 2024 13:50:21 -0400
Subject: [Git][ghc/ghc][wip/T20264] 51 commits: linker: add
 --optimistic-linking flag
Message-ID: <672271dd73a76_2eb5c0102889c1447d6@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -
282366e3 by Joseph Fourment at 2024-10-30T08:23:51+00:00
compiler: introduce type variable unfoldings

The plan for #20264 is to introduce let-bound types to have observable sharing in types.
To avoid the need to carry an environment when dealing with occurrences of these type variables,
we embed the types they're bound to (if any) in a `tv_unfolding :: Maybe Type` attribute.
This way, one can look through let-bound type variables using `coreView` and friends.
In particular, definitional equality looks through unfoldings.

- - - - -
773d2c8d by Joseph Fourment at 2024-10-30T08:23:51+00:00
simple-opt: don't inline type-lets

- - - - -
40f49737 by Joseph Fourment at 2024-10-30T08:23:51+00:00
specialise: fix type-lets in DFun unfoldings

During specialisation, a dictionary being specialised gets a new unfolding by turning
`DFun \ bndrs      -> MkD @<T1> ... @<Tm> <op1> ... <opn>` into
`DFun \ spec_bndrs -> MkD @((\ bndrs -> TYPE: <T1>) spec_args) ... ((\ bndrs -> <opn>) spec_args)`
which in turns gets beta-reduced into
`DFun \ spec_bndrs -> MkD (let { bndrs = spec_args } in TYPE: <T1>) ... (let { bndrs = spec_args } in <opn>)`.
Previously, such let binders would immediately be substituted into the type so it didn't cause any issue,
but now we want to avoid inlining.
Arguments of the form `let { bndrs = spec_args } in TYPE: <T1>` are not considered as type arguments since they're
not of the canonical form `TYPE: something`.
This commit restores the previous behavior of substituting the specialised type arguments.
Alternatively, we could attach some floated type bindings to `DFun`s.

- - - - -
7395d89f by Joseph Fourment at 2024-10-30T08:23:51+00:00
occur-anal: implement occurence analysis for type variables

In order to find out let-bound type variables that are used only once, in the hope of inlining them,
we need to track type variables as well in the occurrence analiser. Just like Id's, we attach an
`OccInfo` to each (immutable) type variable, and we walk into types and coercions to accurately gather
occurrences.

- - - - -
33f03e56 by Joseph Fourment at 2024-10-30T08:23:51+00:00
simplifier: don't inline type-lets

Keep propagating type-lets further down the pipeline, in the simplifier.
We also update CallArity, CprAnal, DmdAnal, WorkWrap, and Specialise to ignore type-lets.

- - - - -
a32b89e6 by Joseph Fourment at 2024-10-30T08:23:51+00:00
prep: make type-lets pass through CorePrep

As a first attempt, ignore type-lets in CorePrep to avoid crashes.
However, this is not enough: CorePrep also does some let-floating.
If we don't float type-lets along with value-level let-bindings,
the latter can float out of the scope of a type variable in use.

- - - - -
79e83544 by Joseph Fourment at 2024-10-30T08:23:51+00:00
simple-opt: fix simple_type_bind

Also:
- Inline small types using a new typeIsSmallEnoughToInline predicate
- Inline single-occurrence variables

- - - - -
1ea9351b by Joseph Fourment at 2024-10-30T08:23:51+00:00
simple-opt: make beta-reduction use simple_bind_type

- - - - -
5ab48664 by Joseph Fourment at 2024-10-30T08:23:52+00:00
iface: add IfaceTypeLetBndr to represent non-top-level type-let binders

IfaceLetBndr isn't fit to represent type-let binders, as it includes a
bunch of vacuous flags for Ids only.
Instead of putting squares in circles, I added a new constructor for type binders.

The downside is that it breaks existing iface files, so since we can't bootstrap
yet so we have to bootstrap a cherry-picked branch and then checkout again to build
with --freeze1.

To avoid similar issues in the future, IfaceTyVarInfoItem serialises with a tag
despite there being only one constructor for now.

- - - - -
7046ed68 by Joseph Fourment at 2024-10-30T08:23:52+00:00
dmd-anal: prefix unused variable with _ to avoid warning

- - - - -
eb4447e1 by Joseph Fourment at 2024-10-30T08:23:52+00:00
type: inline unfoldView in sORTKind_maybe

- - - - -
c925a398 by Joseph Fourment at 2024-10-30T08:23:52+00:00
tidy: deal with type-lets

- - - - -
026747e0 by Joseph Fourment at 2024-10-30T08:23:52+00:00
notes: add Note [Type and coercion lets]

- - - - -
222a1377 by Joseph Fourment at 2024-10-30T08:23:52+00:00
notes: update Note [Comparing nullary type synonyms] to account for type variables

While updating backlinks, I noticed the optimisation for type variables
could be performed in more places.

- - - - -
38bce420 by Joseph Fourment at 2024-10-30T08:23:52+00:00
simplifier: inline single-occurring type-lets

- - - - -
1fe5f0c1 by Joseph Fourment at 2024-10-30T08:23:52+00:00
cleanup: remove NOINLINE on tyVarOccInfo

- - - - -
a7c4079c by Simon Peyton Jones at 2024-10-30T08:23:52+00:00
Wibbles

- - - - -
f7af1667 by Simon Peyton Jones at 2024-10-30T08:23:52+00:00
Wibbles

- - - - -
08295693 by Simon Peyton Jones at 2024-10-30T08:23:52+00:00
Progress

- - - - -
6b9950ce by Simon Peyton Jones at 2024-10-30T08:23:52+00:00
Progress

- - - - -
8be412c6 by Simon Peyton Jones at 2024-10-30T08:24:32+00:00
More progress

- - - - -
3fad6cd0 by Simon Peyton Jones at 2024-10-30T17:49:50+00:00
Progress

...doesn't compile though

- - - - -


30 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CallArity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/FloatIn.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Monad.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a81b6b9024cc3f8c436c78c12d6976d36cc34a00...3fad6cd08131bc7b05bd9f3b9a1c9a0cc212fc8d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a81b6b9024cc3f8c436c78c12d6976d36cc34a00...3fad6cd08131bc7b05bd9f3b9a1c9a0cc212fc8d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 18:26:26 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 30 Oct 2024 14:26:26 -0400
Subject: [Git][ghc/ghc][wip/az/epa-last-eptokens] EPA: Bring in last EpToken
 usages
Message-ID: <67227a525f4b0_ce24817dab8449be@gitlab.mail>



Alan Zimmerman pushed to branch wip/az/epa-last-eptokens at Glasgow Haskell Compiler / GHC


Commits:
8b183191 by Alan Zimmerman at 2024-10-30T18:26:07+00:00
EPA: Bring in last EpToken usages

For import declarations, NameAnnCommas and NPlusKPat.

And remove anchor, it is the same as epaLocationRealSrcSpan.

- - - - -


19 changed files:

- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- testsuite/tests/simplCore/should_compile/T23864.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Types.hs
- utils/check-exact/Utils.hs
- utils/check-ppr/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs


Changes:

=====================================
compiler/GHC/Hs/ImpExp.hs
=====================================
@@ -194,9 +194,9 @@ instance (OutputableBndrId p
 -}
 
 type instance XIEName    (GhcPass _) = NoExtField
-type instance XIEDefault (GhcPass _) = EpaLocation
-type instance XIEPattern (GhcPass _) = EpaLocation
-type instance XIEType    (GhcPass _) = EpaLocation
+type instance XIEDefault (GhcPass _) = EpToken "default"
+type instance XIEPattern (GhcPass _) = EpToken "pattern"
+type instance XIEType    (GhcPass _) = EpToken "type"
 type instance XXIEWrappedName (GhcPass _) = DataConCantHappen
 
 type instance Anno (IEWrappedName (GhcPass _)) = SrcSpanAnnA


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -158,7 +158,7 @@ type instance XNPat GhcPs = EpToken "-"
 type instance XNPat GhcRn = EpToken "-"
 type instance XNPat GhcTc = Type
 
-type instance XNPlusKPat GhcPs = EpaLocation -- Of the "+"
+type instance XNPlusKPat GhcPs = EpToken "+"
 type instance XNPlusKPat GhcRn = NoExtField
 type instance XNPlusKPat GhcTc = Type
 


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -340,7 +340,7 @@ mkHsCompAnns   :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs
 
 mkNPat      :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpToken "-"
             -> Pat GhcPs
-mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpaLocation
+mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpToken "+"
             -> Pat GhcPs
 
 -- NB: The following functions all use noSyntaxExpr: the generated expressions


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1040,9 +1040,9 @@ export  :: { LIE GhcPs }
                                                           ; locImpExp <- return (sL span (IEModuleContents ($1, (epTok $2)) $3))
                                                           ; return $ reLoc $ locImpExp } }
         | maybe_warning_pragma 'pattern' qcon            { let span = (maybe comb2 comb3 $1) $2 $>
-                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (glR $2) $3)) Nothing }
+                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (epTok $2) $3)) Nothing }
         | maybe_warning_pragma 'default' qtycon          {% do { let { span = (maybe comb2 comb3 $1) $2 $> }
-                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (glR $2) $3)) Nothing))
+                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (epTok $2) $3)) Nothing))
                                                           ; return $ reLoc $ locImpExp } }
 
 
@@ -1076,7 +1076,7 @@ qcname_ext_w_wildcard :: { LocatedA ImpExpQcSpec }
 qcname_ext :: { LocatedA ImpExpQcSpec }
         :  qcname                   { sL1a $1 (ImpExpQcName $1) }
         |  'type' oqtycon           {% do { n <- mkTypeImpExp $2
-                                          ; return $ sLLa $1 $> (ImpExpQcType (glR $1) n) }}
+                                          ; return $ sLLa $1 $> (ImpExpQcType (epTok $1) n) }}
 
 qcname  :: { LocatedN RdrName }  -- Variable or type constructor
         :  qvar                 { $1 } -- Things which look like functions
@@ -1209,7 +1209,7 @@ importlist1 :: { OrdList (LIE GhcPs) }
 import  :: { OrdList (LIE GhcPs) }
         : qcname_ext export_subspec {% fmap (unitOL . reLoc . (sLL $1 $>)) $ mkModuleImpExp Nothing (fst $ unLoc $2) $1 (snd $ unLoc $2) }
         | 'module' modid            {% fmap (unitOL . reLoc) $ return (sLL $1 $> (IEModuleContents (Nothing, (epTok $1)) $2)) }
-        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (glR $1) $2)) Nothing }
+        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (epTok $1) $2)) Nothing }
 
 -----------------------------------------------------------------------------
 -- Fixity Declarations
@@ -3776,10 +3776,10 @@ qcon_list : qcon                  { [$1] }
 -- See Note [ExplicitTuple] in GHC.Hs.Expr
 sysdcon_nolist :: { LocatedN DataCon }  -- Wired in data constructors
         : '(' commas ')'        {% amsr (sLL $1 $> $ tupleDataCon Boxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
         | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '(#' commas '#)'      {% amsr (sLL $1 $> $ tupleDataCon Unboxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
 
 syscon :: { LocatedN RdrName }
         : sysdcon               {  L (getLoc $1) $ nameRdrName (dataConName (unLoc $1)) }
@@ -3820,9 +3820,9 @@ gtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, including unit t
 ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit tuples
         : oqtycon               { $1 }
         | '(' commas ')'        {% do { n <- mkTupleSyntaxTycon Boxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' commas '#)'      {% do { n <- mkTupleSyntaxTycon Unboxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
                                        (NameAnnBars (epTok $1, epTok $3) (fst $2) []) } }


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -23,7 +23,6 @@ module GHC.Parser.Annotation (
   DeltaPos(..), deltaPos, getDeltaLine,
 
   EpAnn(..),
-  anchor,
   spanAsAnchor, realSpanAsAnchor,
   noSpanAnchor,
   NoAnn(..),
@@ -350,7 +349,7 @@ instance Outputable a => Outputable (GenLocated TokenLocation a) where
 -- | Used in the parser only, extract the 'RealSrcSpan' from an
 -- 'EpaLocation'. The parser will never insert a 'DeltaPos', so the
 -- partial function is safe.
-epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
+epaLocationRealSrcSpan :: EpaLocation' a -> RealSrcSpan
 epaLocationRealSrcSpan (EpaSpan (RealSrcSpan r _)) = r
 epaLocationRealSrcSpan _ = panic "epaLocationRealSrcSpan"
 
@@ -401,9 +400,6 @@ data EpAnn ann
         deriving (Data, Eq, Functor)
 -- See Note [XRec and Anno in the AST]
 
-anchor :: (EpaLocation' a) -> RealSrcSpan
-anchor (EpaSpan (RealSrcSpan r _)) = r
-anchor _ = panic "anchor"
 
 spanAsAnchor :: SrcSpan -> (EpaLocation' a)
 spanAsAnchor ss  = EpaSpan ss
@@ -602,7 +598,7 @@ data NameAnn
   -- | Used for @(,,,)@, or @(#,,,#)@
   | NameAnnCommas {
       nann_adornment :: NameAdornment,
-      nann_commas    :: [EpaLocation],
+      nann_commas    :: [EpToken ","],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(# | | #)@
@@ -641,10 +637,10 @@ data NameAnn
 -- such as parens or backquotes. This data type identifies what
 -- particular pair are being used.
 data NameAdornment
-  = NameParens     (EpToken "(")  (EpToken ")") -- ^ '(' ')'
-  | NameParensHash (EpToken "(#") (EpToken "#)")-- ^ '(#' '#)'
-  | NameBackquotes (EpToken "`")  (EpToken "`")-- ^ '`'
-  | NameSquare     (EpToken "[")  (EpToken "]")-- ^ '[' ']'
+  = NameParens     (EpToken "(")  (EpToken ")")
+  | NameParensHash (EpToken "(#") (EpToken "#)")
+  | NameBackquotes (EpToken "`")  (EpToken "`")
+  | NameSquare     (EpToken "[")  (EpToken "]")
   | NameNoAdornment
   deriving (Eq, Data)
 


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -3672,8 +3672,8 @@ allocateComments
   -> ([LEpaComment], [LEpaComment])
 allocateComments ss comment_q =
   let
-    (before,rest)  = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
-    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
+    (before,rest)  = break (\(L l _) -> isRealSubspanOf (epaLocationRealSrcSpan l) ss) comment_q
+    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (epaLocationRealSrcSpan l) ss)) rest
     comment_q' = before ++ after
     newAnns = middle
   in
@@ -3691,14 +3691,14 @@ splitPriorComments ss prior_comments =
     -- And the token preceding the comment is on a different line
     cmp :: RealSrcSpan -> LEpaComment -> Bool
     cmp later (L l c)
-         = srcSpanStartLine later - srcSpanEndLine (anchor l) == 1
-          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (anchor l)
+         = srcSpanStartLine later - srcSpanEndLine (epaLocationRealSrcSpan l) == 1
+          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (epaLocationRealSrcSpan l)
 
     go :: [LEpaComment] -> RealSrcSpan -> [LEpaComment]
        -> ([LEpaComment], [LEpaComment])
     go decl_comments _ [] = ([],decl_comments)
     go decl_comments r (c@(L l _):cs) = if cmp r c
-                              then go (c:decl_comments) (anchor l) cs
+                              then go (c:decl_comments) (epaLocationRealSrcSpan l) cs
                               else (reverse (c:cs), decl_comments)
   in
     go [] ss prior_comments
@@ -3710,7 +3710,7 @@ allocatePriorComments
   -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
 allocatePriorComments ss comment_q mheader_comments =
   let
-    cmp (L l _) = anchor l <= ss
+    cmp (L l _) = epaLocationRealSrcSpan l <= ss
     (newAnns,after) = partition cmp comment_q
     comment_q'= after
     (prior_comments, decl_comments) = splitPriorComments ss newAnns


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1312,7 +1312,7 @@ checkAPat loc e0 = do
            _
                      | nPlusKPatterns && (plus == plus_RDR)
                      -> return (mkNPlusKPat (L nloc n) (L (l2l lloc) lit)
-                                (entry l))
+                                (EpTok $ entry l))
 
    -- Improve error messages for the @-operator when the user meant an @-pattern
    PatBuilderOpApp _ op _ _ | opIsAt (unLoc op) -> do
@@ -3158,7 +3158,7 @@ data ImpExpSubSpec = ImpExpAbs
                    | ImpExpAllWith [LocatedA ImpExpQcSpec]
 
 data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName)
-                  | ImpExpQcType EpaLocation (LocatedN RdrName)
+                  | ImpExpQcType (EpToken "type") (LocatedN RdrName)
                   | ImpExpQcWildcard (EpToken "..") (EpToken ",")
 
 mkModuleImpExp :: Maybe (LWarningTxt GhcPs) -> (EpToken "(", EpToken ")") -> LocatedA ImpExpQcSpec


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -2107,13 +2107,13 @@ printMinimalImports hsc_src imports_w_usage
 
 to_ie_post_rn_var :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn_var (L l n)
-  | isDataOcc $ occName n = L l (IEPattern (entry l)   (L (l2l l) n))
+  | isDataOcc $ occName n = L l (IEPattern noAnn      (L (l2l l) n))
   | otherwise             = L l (IEName    noExtField (L (l2l l) n))
 
 
 to_ie_post_rn :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn (L l n)
-  | isTcOcc occ && isSymOcc occ = L l (IEType (entry l)   (L (l2l l) n))
+  | isTcOcc occ && isSymOcc occ = L l (IEType noAnn      (L (l2l l) n))
   | otherwise                   = L l (IEName noExtField (L (l2l l) n))
   where occ = occName n
 


=====================================
testsuite/tests/simplCore/should_compile/T23864.hs
=====================================
@@ -49,7 +49,7 @@ insertCommentsByPos ::
   -> (EpAnnComments -> [LEpaComment] -> EpAnnComments)
   -> EpAnn a
   -> WithComments (EpAnn a)
-insertCommentsByPos cond = insertComments (cond . anchor . getLoc)
+insertCommentsByPos cond = insertComments (cond . epaLocationRealSrcSpan . getLoc)
 
 insertComments ::
      (LEpaComment -> Bool)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -570,7 +570,7 @@ splitAfterTrailingAnns tas cs = (before, after)
         (s:_) -> (b,a)
           where
             s_pos = ss2pos s
-            (b,a) = break (\(L ll _) -> (ss2pos $ anchor ll) > s_pos)
+            (b,a) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > s_pos)
                           cs
 
 -- ---------------------------------------------------------------------
@@ -731,12 +731,6 @@ printStringAtNC el str = do
   el' <- printStringAtAAC NoCaptureComments (noCommentsToEpaLocation el) str
   return (epaToNoCommentsLocation el')
 
-printStringAtAAL :: (Monad m, Monoid w)
-  => a -> Lens a EpaLocation -> String -> EP w m a
-printStringAtAAL an l str = do
-  r <- printStringAtAAC CaptureComments (view l an) str
-  return (set l r an)
-
 printStringAtAAC :: (Monad m, Monoid w)
   => CaptureComments -> EpaLocation -> String -> EP w m EpaLocation
 printStringAtAAC capture (EpaSpan (RealSrcSpan r _)) s = printStringAtRsC capture r s
@@ -1020,10 +1014,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lid :: Lens a a
-lid k parent = fmap (\new -> new)
-                    (k parent)
-
 lfst :: Lens (a,b) a
 lfst k parent = fmap (\new -> (new, snd parent))
                      (k (fst parent))
@@ -4186,7 +4176,7 @@ instance ExactPrint (LocatedN RdrName) where
             _ -> error "ExactPrint (LocatedN RdrName)"
         NameAnnCommas a commas t -> do
           a0 <- markNameAdornmentO a
-          commas' <- forM commas (\loc -> printStringAtAAC NoCaptureComments loc ",")
+          commas' <- forM commas markEpToken
           a1 <- markNameAdornmentC a0
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
@@ -4247,7 +4237,7 @@ printUnicode :: (Monad m, Monoid w) => EpaLocation -> RdrName -> EP w m EpaLocat
 printUnicode anc n = do
   let str = case (showPprUnsafe n) of
             -- TODO: unicode support?
-              "forall" -> if spanLength (anchor anc) == 1 then "∀" else "forall"
+              "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall"
               s -> s
   loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str
   case loc of
@@ -4617,15 +4607,15 @@ instance ExactPrint (IEWrappedName GhcPs) where
     n' <- markAnnotated n
     return (IEName x n')
   exact (IEDefault r n) = do
-    r' <- printStringAtAA r "default"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEDefault r' n')
   exact (IEPattern r n) = do
-    r' <- printStringAtAA r "pattern"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEPattern r' n')
   exact (IEType r n) = do
-    r' <- printStringAtAA r "type"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEType r' n')
 
@@ -4715,7 +4705,7 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (NPlusKPat an n k lit2 a b) = do
     n' <- markAnnotated n
-    an' <- printStringAtAAL an lid "+"
+    an' <- markEpToken an
     k' <- markAnnotated k
     return (NPlusKPat an' n' k' lit2 a b)
 


=====================================
utils/check-exact/Parsers.hs
=====================================
@@ -289,7 +289,8 @@ fixModuleTrailingComments (GHC.L l p) = GHC.L l p'
             let
               pc = GHC.priorComments cs
               fc = GHC.getFollowingComments cs
-              bf (GHC.L anc _) = GHC.anchor anc > ss
+              bf (GHC.L anc _) = GHC.epaLocationRealSrcSpan anc > ss
+
               (prior,f) = break bf fc
               cs'' = GHC.EpaCommentsBalanced (pc <> prior) f
             in cs''
@@ -310,7 +311,7 @@ fixModuleHeaderComments (GHC.L l p) = GHC.L l p'
         -- Move any comments on the decl that occur prior to the location
         pc = GHC.priorComments csd
         fc = GHC.getFollowingComments csd
-        bf (GHC.L anch _) = GHC.anchor anch > r
+        bf (GHC.L anch _) = GHC.epaLocationRealSrcSpan anch > r
         (move,keep) = break bf pc
         csd' = GHC.EpaCommentsBalanced keep fc
 


=====================================
utils/check-exact/Transform.hs
=====================================
@@ -211,7 +211,7 @@ captureTypeSigSpacing (L l (SigD x (TypeSig (AnnSig (EpUniTok dca u) mp md) ns (
     -- we want DPs for the distance from the end of the ns to the
     -- AnnDColon, and to the start of the ty
     rd = case last ns of
-      L (EpAnn anc' _ _) _ -> anchor anc'
+      L (EpAnn anc' _ _) _ -> epaLocationRealSrcSpan anc'
     dca' = case dca of
           EpaSpan ss@(RealSrcSpan r _) -> (EpaDelta ss (ss2delta (ss2posEnd rd) r) [])
           _                            -> dca
@@ -298,7 +298,7 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp
                 col = deltaColumn delta
                 edp' = if line == 0 then SameLine col
                                     else DifferentLine line col
-                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ anchor $ getLoc lc), r))
+                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r))
 
 
 -- ---------------------------------------------------------------------
@@ -552,12 +552,12 @@ trailingCommentsDeltas _ [] = []
 trailingCommentsDeltas r (la@(L (EpaDelta _ dp _) _):las)
   = (getDeltaLine dp, la): trailingCommentsDeltas r las
 trailingCommentsDeltas r (la@(L l _):las)
-  = deltaComment r la : trailingCommentsDeltas (anchor l) las
+  = deltaComment r la : trailingCommentsDeltas (epaLocationRealSrcSpan l) las
   where
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2posEnd rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 priorCommentsDeltas :: RealSrcSpan -> [LEpaComment]
                     -> [(Int, LEpaComment)]
@@ -565,14 +565,14 @@ priorCommentsDeltas r cs = go r (sortEpaComments cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 
 -- ---------------------------------------------------------------------
@@ -664,14 +664,14 @@ addCommentOrigDeltasAnn (EpAnn e a cs) = EpAnn e a (addCommentOrigDeltas cs)
 -- TODO: this is replicating functionality in ExactPrint. Sort out the
 -- import loop`
 anchorFromLocatedA :: LocatedA a -> RealSrcSpan
-anchorFromLocatedA (L (EpAnn anc _ _) _) = anchor anc
+anchorFromLocatedA (L (EpAnn anc _ _) _) = epaLocationRealSrcSpan anc
 
 -- | Get the full span of interest for comments from a LocatedA.
 -- This extends up to the last TrailingAnn
 fullSpanFromLocatedA :: LocatedA a -> RealSrcSpan
 fullSpanFromLocatedA (L (EpAnn anc (AnnListItem tas)  _) _) = rr
   where
-    r = anchor anc
+    r = epaLocationRealSrcSpan anc
     trailing_loc ta = case ta_location ta of
         EpaSpan (RealSrcSpan s _) -> [s]
         _ -> []
@@ -695,7 +695,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb)))
           (csp,csf) = case anc1 of
             EpaComments cs -> ([],cs)
             EpaCommentsBalanced p f -> (p,f)
-          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (anchor anc) csf)
+          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (epaLocationRealSrcSpan anc) csf)
           move = map snd move'
           stay = map snd stay'
           cs1 = epaCommentsBalanced csp stay


=====================================
utils/check-exact/Types.hs
=====================================
@@ -8,8 +8,7 @@
 {-# LANGUAGE TypeSynonymInstances #-}
 {-# LANGUAGE ViewPatterns         #-}
 
-module Types
-  where
+module Types where
 
 import GHC hiding (EpaComment)
 import GHC.Utils.Outputable hiding ( (<>) )
@@ -41,7 +40,7 @@ instance Ord Comment where
   -- When we have CPP injected comments with a fake filename, or LINE
   -- pragma, the file name changes, so we need to compare the
   -- locations only, with out the filename.
-  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ anchor ss1) (ss2pos $ anchor ss2)
+  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan ss1) (ss2pos $ epaLocationRealSrcSpan ss2)
     where
       ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss)
 


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -268,7 +268,7 @@ workInComments ocs new = cs'
                                         (sortEpaComments $ fc ++ cs_after)
              where
                (cs_before,cs_after)
-                   = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) )
+                   = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) )
                            new
 
 insertTopLevelCppComments ::  HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment])
@@ -292,7 +292,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an1,cs0a) = case lo of
         EpExplicitBraces (EpTok (EpaSpan (RealSrcSpan s _))) _close ->
             let
-                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0
+                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0
                 cs' = workInComments (comments an0) stay
             in (an0 { comments = cs' }, cs0a')
         _ -> (an0,cs0)
@@ -300,7 +300,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an2, cs0b) = case am_decls $ anns an1 of
         (AddSemiAnn (EpTok (EpaSpan (RealSrcSpan s _))):_) -> (an1 {comments = cs'}, cs0b')
           where
-            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0a
+            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0a
             cs' = workInComments (comments an1) stay
         _ -> (an1,cs0a)
 
@@ -314,7 +314,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
                            (csh', cs0b') = case annListBracketsLocs $ al_brackets $ anns l of
                                (EpaSpan (RealSrcSpan s _),_) ->(h, n)
                                  where
-                                   (h,n) = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+                                   (h,n) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        cs0b
 
                                _ -> ([], cs0b)
@@ -361,7 +361,7 @@ splitOnWhere w (EpTok (EpaSpan (RealSrcSpan s _))) csIn = (hc, fc)
   where
     splitFunc Before anc_pos c_pos = c_pos < anc_pos
     splitFunc After  anc_pos c_pos = anc_pos < c_pos
-    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ anchor ll) (ss2pos s)) csIn
+    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ epaLocationRealSrcSpan ll) (ss2pos s)) csIn
 splitOnWhere _ _ csIn = (csIn,[])
 
 balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment])
@@ -372,7 +372,7 @@ balanceFirstLocatedAComments ((L (EpAnn anc an csd) a):ds) = (L (EpAnn anc an cs
         EpaSpan (RealSrcSpan s _) -> (csd', hc)
                `debug` ("balanceFirstLocatedAComments: (csd,csd',attached,header)=" ++ showAst (csd,csd',attached,header))
           where
-            (priors, inners) =  break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+            (priors, inners) =  break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        (priorComments csd)
             pcds = priorCommentsDeltas' s priors
             (attached, header) = break (\(d,_c) -> d /= 1) pcds
@@ -388,14 +388,14 @@ priorCommentsDeltas' r cs = go r (reverse cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 allocatePriorComments
   :: Pos
@@ -403,7 +403,7 @@ allocatePriorComments
   -> ([LEpaComment], [LEpaComment])
 allocatePriorComments ss_loc comment_q =
   let
-    cmp (L l _) = ss2pos (anchor l) <= ss_loc
+    cmp (L l _) = ss2pos (epaLocationRealSrcSpan l) <= ss_loc
     (newAnns,after) = partition cmp comment_q
   in
     (after, newAnns)
@@ -420,7 +420,7 @@ insertRemainingCppComments (L l p) cs = L l p'
             EpTok (EpaSpan (RealSrcSpan s _)) -> ss2pos s
             _ -> (1,1)
         _ -> (1,1)
-    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ anchor ll) > end_loc ) cs
+    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > end_loc ) cs
 
     addTrailingComments end_loc' cur new = epaCommentsBalanced pc' fc'
       where
@@ -431,8 +431,8 @@ insertRemainingCppComments (L l p) cs = L l p'
             (L ac _:_) -> (sortEpaComments $ pc ++ cs_before, sortEpaComments $ fc ++ cs_after)
               where
                (cs_before,cs_after)
-                   = if (ss2pos $ anchor ac) > end_loc'
-                       then break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) ) new
+                   = if (ss2pos $ epaLocationRealSrcSpan ac) > end_loc'
+                       then break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) ) new
                        else (new_before, new_after)
 
 -- ---------------------------------------------------------------------
@@ -513,7 +513,7 @@ normaliseCommentText (x:xs) = x:normaliseCommentText xs
 
 -- |Must compare without span filenames, for CPP injected comments with fake filename
 cmpComments :: Comment -> Comment -> Ordering
-cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- |Sort, comparing without span filenames, for CPP injected comments with fake filename
 sortComments :: [Comment] -> [Comment]
@@ -523,7 +523,7 @@ sortComments cs = sortBy cmpComments cs
 sortEpaComments :: [LEpaComment] -> [LEpaComment]
 sortEpaComments cs = sortBy cmp cs
   where
-    cmp (L l1 _) (L l2 _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- | Makes a comment which originates from a specific keyword.
 mkKWComment :: String -> NoCommentsLocation -> Comment
@@ -532,7 +532,7 @@ mkKWComment kw (EpaSpan (UnhelpfulSpan _))   = Comment kw (EpaDelta noSrcSpan (S
 mkKWComment kw (EpaDelta ss dp cs)           = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw)
 
 sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a]
-sortAnchorLocated = sortBy (compare `on` (anchor . getLoc))
+sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc))
 
 -- | Calculates the distance from the start of a string to the end of
 -- a string.


=====================================
utils/check-ppr/Main.hs
=====================================
@@ -97,7 +97,7 @@ getPragmas (L _ (HsModule { hsmodExt = XModulePs { hsmodAnn = anns' } })) = prag
     tokComment (L _ (EpaComment (EpaLineComment  s) _)) = s
     tokComment _ = ""
 
-    cmp (L l1 _) (L l2 _) = compare (anchor l1) (anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (epaLocationRealSrcSpan l1) (epaLocationRealSrcSpan l2)
     comments' = map tokComment $ sortBy cmp $ priorComments $ epAnnComments anns'
     pragmas = filter (\c -> isPrefixOf "{-#" c ) comments'
     pragmaStr = intercalate "\n" pragmas


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
=====================================
@@ -41,7 +41,7 @@ import qualified Data.Map.Strict as Map
 import Data.Maybe
 import Data.Ord (comparing)
 import qualified Data.Set as Set hiding (Set)
-import GHC hiding (LexicalFixity (..), NoLink, anchor, moduleInfo)
+import GHC hiding (LexicalFixity (..), NoLink, moduleInfo)
 import GHC.Types.Name
 import GHC.Unit.State
 import System.Directory


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
=====================================
@@ -24,7 +24,7 @@ module Haddock.Backends.Xhtml.DocMarkup
 
 import Data.List (intersperse)
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name
 import Text.XHtml hiding (name, p, quote)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
=====================================
@@ -54,7 +54,7 @@ module Haddock.Backends.Xhtml.Layout
 
 import qualified Data.Map as Map
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name (nameOccName)
 import Text.XHtml hiding (name, quote, title)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
=====================================
@@ -31,7 +31,7 @@ module Haddock.Backends.Xhtml.Names
   ) where
 
 import Data.List (stripPrefix)
-import GHC hiding (LexicalFixity (..), anchor)
+import GHC hiding (LexicalFixity (..))
 import GHC.Data.FastString (unpackFS)
 import GHC.Types.Name
 import GHC.Types.Name.Reader



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b183191be1bf2488a6924758de025c131f9458f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 20:27:48 2024
From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz))
Date: Wed, 30 Oct 2024 16:27:48 -0400
Subject: [Git][ghc/ghc][wip/T24359] Fix PostProcess/Parser/Exact print
 annotations
Message-ID: <672296c42cccb_399db7124b488139f@gitlab.mail>



Alan Zimmerman pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC


Commits:
71a23964 by Alan Zimmerman at 2024-10-30T20:26:51+00:00
Fix PostProcess/Parser/Exact print annotations

It compiles, is now stuck on something related to the main work.

- - - - -


4 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs


Changes:

=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -745,7 +745,7 @@ data AnnSpecSig
   = AnnSpecSig {
       ass_open   :: EpaLocation,
       ass_close  :: EpToken "#-}",
-      ass_dcolon :: TokDcolon,
+      ass_dcolon :: Maybe TokDcolon,
       ass_act    :: ActivationAnn
     } deriving Data
 
@@ -1021,10 +1021,10 @@ pprMinimalSig (L _ bf) = ppr (fmap unLoc bf)
 
 data HsRuleBndrsAnn
   = HsRuleBndrsAnn
-       { ra_tyanns :: Maybe (AddEpAnn, AddEpAnn)
+       { rb_tyanns :: Maybe (TokForall, EpToken ".")
                  -- ^ The locations of 'forall' and '.' for forall'd type vars
                  -- Using AddEpAnn to capture possible unicode variants
-       , ra_tmanns :: Maybe (AddEpAnn, AddEpAnn)
+       , rb_tmanns :: Maybe (TokForall, EpToken ".")
                  -- ^ The locations of 'forall' and '.' for forall'd term vars
                  -- Using AddEpAnn to capture possible unicode variants
        } deriving (Data, Eq)
@@ -1033,10 +1033,10 @@ instance NoAnn HsRuleBndrsAnn where
   noAnn = HsRuleBndrsAnn Nothing Nothing
 
 
-type instance XCRuleBndr    (GhcPass _) = [AddEpAnn]
+type instance XCRuleBndr    (GhcPass _) = AnnTyVarBndr
 type instance XCRuleBndrs   (GhcPass _) = HsRuleBndrsAnn
 type instance XXRuleBndrs   (GhcPass _) = DataConCantHappen
-type instance XRuleBndrSig  (GhcPass _) = [AddEpAnn]
+type instance XRuleBndrSig  (GhcPass _) = AnnTyVarBndr
 type instance XXRuleBndr    (GhcPass _) = DataConCantHappen
 
 instance (OutputableBndrId p) => Outputable (RuleBndrs (GhcPass p)) where


=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -67,6 +67,7 @@ module GHC.Hs.Decls (
   XViaStrategyPs(..),
   -- ** @RULE@ declarations
   LRuleDecls,RuleDecls(..),RuleDecl(..),LRuleDecl,HsRuleRn(..),
+  HsRuleAnn(..),
   RuleBndr(..),LRuleBndr,
   collectRuleBndrSigTys,
   flattenRuleDecls, pprFullRuleName,
@@ -1314,13 +1315,24 @@ type instance XCRuleDecls    GhcTc = SourceText
 
 type instance XXRuleDecls    (GhcPass _) = DataConCantHappen
 
-type instance XHsRule       GhcPs = ([AddEpAnn], SourceText)
+type instance XHsRule       GhcPs = ((ActivationAnn, EpToken "="), SourceText)
 type instance XHsRule       GhcRn = (HsRuleRn, SourceText)
 type instance XHsRule       GhcTc = (HsRuleRn, SourceText)
 
 data HsRuleRn = HsRuleRn NameSet NameSet -- Free-vars from the LHS and RHS
   deriving Data
 
+data HsRuleAnn
+  = HsRuleAnn
+       { ra_tyanns :: Maybe (TokForall, EpToken ".")
+       , ra_tmanns :: Maybe (TokForall, EpToken ".")
+       , ra_equal  :: EpToken "="
+       , ra_rest :: ActivationAnn
+       } deriving (Data, Eq)
+
+instance NoAnn HsRuleAnn where
+  noAnn = HsRuleAnn Nothing Nothing noAnn noAnn
+
 type instance XXRuleDecl    (GhcPass _) = DataConCantHappen
 
 flattenRuleDecls :: [LRuleDecls (GhcPass p)] -> [LRuleDecl (GhcPass p)]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1926,7 +1926,7 @@ rule    :: { LRuleDecl GhcPs }
          {%runPV (unECP $4) >>= \ $4 ->
            runPV (unECP $6) >>= \ $6 ->
            amsA' (sLL $1 $> $ HsRule
-                                   { rd_ext =(((fst $3) (epTok $5) (fst $2)), getSTRINGs $1)
+                                   { rd_ext =((fst $2, epTok $5), getSTRINGs $1)
                                    , rd_name = L (noAnnSrcSpan $ gl $1) (getSTRING $1)
                                    , rd_act = snd $2 `orElse` AlwaysActive
                                    , rd_bndrs = ruleBndrsOrDef $3
@@ -1970,12 +1970,12 @@ rule_foralls :: { Maybe (RuleBndrs GhcPs) }
               {% hintExplicitForall $1
                  >> checkRuleTyVarBndrNames $2
                  >> let ann = HsRuleBndrsAnn
-                                (Just (mu AnnForall $1,mj AnnDot $3))
-                                (Just (mu AnnForall $4,mj AnnDot $6))
+                                (Just (epUniTok $1,epTok $3))
+                                (Just (epUniTok $4,epTok $6))
                      in return (Just (mkRuleBndrs ann  (Just $2) $5)) }
 
         | 'forall' rule_vars '.'
-           { Just (mkRuleBndrs (HsRuleBndrsAnn Nothing (Just (mu AnnForall $1,mj AnnDot $3)))
+           { Just (mkRuleBndrs (HsRuleBndrsAnn Nothing (Just (epUniTok $1,epTok $3)))
                                Nothing $2) }
 
         -- See Note [%shift: rule_foralls -> {- empty -}]
@@ -2770,11 +2770,11 @@ sigdecl :: { LHsDecl GhcPs }
                 let inl_prag = mkInlinePragma (getSPEC_PRAGs $1)
                                             (NoUserInlinePrag, FunLike)
                                             (snd $2)
-                spec <- mkSpecSig $1 inl_prag (fst $2) $3 $4 $5 $6
+                spec <- mkSpecSig inl_prag (AnnSpecSig (glR $1) (epTok $6) Nothing (fst $2)) $3 $4 $5
                 amsA' $ sLL $1 $> $ SigD noExtField spec }
 
         | '{-# SPECIALISE_INLINE' activation qvar '::' sigtypes1 '#-}'
-             {% amsA' (sLL $1 $> $ SigD noExtField (SpecSig (AnnSpecSig (glR $1) (epTok $6) (epUniTok $4) (fst $2)) $3 (fromOL $5)
+             {% amsA' (sLL $1 $> $ SigD noExtField (SpecSig (AnnSpecSig (glR $1) (epTok $6) (Just $ epUniTok $4) (fst $2)) $3 (fromOL $5)
                                (mkInlinePragma (getSPEC_INLINE_PRAGs $1)
                                                (getSPEC_INLINE $1) (snd $2)))) }
 
@@ -2785,8 +2785,8 @@ sigdecl :: { LHsDecl GhcPs }
         | '{-# MINIMAL' name_boolformula_opt '#-}'
             {% amsA' (sLL $1 $> $ SigD noExtField (MinimalSig ((glR $1,epTok $3), (getMINIMAL_PRAGs $1)) $2)) }
 
-sigtypes_maybe :: { Maybe (Located Token, OrdList (LHsSigType GhcPs)) }
-        : '::' sigtypes1         { Just ($1, $2) }
+sigtypes_maybe :: { Maybe (TokDcolon, OrdList (LHsSigType GhcPs)) }
+        : '::' sigtypes1         { Just (epUniTok $1, $2) }
         | {- empty -}            { Nothing }
 
 activation :: { (ActivationAnn,Maybe Activation) }


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1015,7 +1015,7 @@ ruleBndrsOrDef Nothing      = mkRuleBndrs noAnn Nothing []
 mkRuleBndrs :: HsRuleBndrsAnn -> Maybe [LRuleTyTmVar] -> [LRuleTyTmVar] -> RuleBndrs GhcPs
 mkRuleBndrs ann tvbs tmbs
   = RuleBndrs { rb_ext = ann
-              , rb_tyvs = fmap (setLHsTyVarBndrNameSpace tvName . cvt_tv) tvbs
+              , rb_tyvs = fmap (fmap (setLHsTyVarBndrNameSpace tvName . cvt_tv)) tvbs
               , rb_tmvs = fmap (fmap cvt_tm) tmbs }
   where
     -- cvt_tm turns RuleTyTmVars into RuleBnrs - this is straightforward
@@ -1039,32 +1039,30 @@ checkRuleTyVarBndrNames bndrs
                           PsErrParseErrorOnInput occ
     check _ = panic "checkRuleTyVarBndrNames"
 
-mkSpecSig :: Located Token
-          -> InlinePragma
-          -> [AddEpAnn]
+mkSpecSig :: InlinePragma
+          -> AnnSpecSig
           -> Maybe (RuleBndrs GhcPs)
           -> LHsExpr GhcPs
-          -> Maybe (Located Token, OrdList (LHsSigType GhcPs))
-          -> Located Token
+          -> Maybe (TokDcolon, OrdList (LHsSigType GhcPs))
           -> P (Sig GhcPs)
-mkSpecSig prag_start inl_prag activation_anns m_rule_binds expr m_sigtypes_ascr prag_end
+mkSpecSig inl_prag activation_anns m_rule_binds expr m_sigtypes_ascr
   = case m_sigtypes_ascr of
       Nothing
         -- New form, no trailing type signature, e.g {-# SPECIALISE f @Int #-}
         -> pure $
-           SpecSigE (start_ann:end_ann:activation_anns)
+           SpecSigE activation_anns
                     (ruleBndrsOrDef m_rule_binds) expr inl_prag
 
-      Just (dcolon, sigtype_ol)
+      Just (colon_ann, sigtype_ol)
 
         -- Singleton, e.g.  {-# SPECIALISE f :: ty #-}
         -- Use the SpecSigE route
         | [sigtype] <- sigtype_list
         -> pure $
-           SpecSigE (start_ann:end_ann:activation_anns)
+           SpecSigE activation_anns
                     (ruleBndrsOrDef m_rule_binds)
                     (L (getLoc expr)  -- ToDo: not really the right location for (e::ty)
-                       (ExprWithTySig [colon_ann] expr (mkHsWildCardBndrs sigtype)))
+                       (ExprWithTySig colon_ann expr (mkHsWildCardBndrs sigtype)))
                     inl_prag
 
         -- So we must have the old form  {# SPECIALISE f :: ty1, ty2, ty3 #-}
@@ -1072,26 +1070,18 @@ mkSpecSig prag_start inl_prag activation_anns m_rule_binds expr m_sigtypes_ascr
         | Nothing <- m_rule_binds
         , L _ (HsVar _ var) <- expr
         -> pure $
-           SpecSig (start_ann:colon_ann:end_ann:activation_anns)
+           SpecSig activation_anns
                    var sigtype_list inl_prag
 
         | otherwise -> ps_err PsErrSpecExprMultipleTypeAscription
 
         where
           sigtype_list = fromOL sigtype_ol
-          colon_ann = AddEpAnn (toUnicodeAnn AnnDcolon dcolon) (gl dcolon)
 
   where
-    gl        = srcSpan2e . getLoc
-    start_ann = AddEpAnn AnnOpen (gl prag_start)
-    end_ann   = AddEpAnn AnnClose (gl prag_end)
-
-    toUnicodeAnn !a (L _ (ITdcolon UnicodeSyntax)) = unicodeAnn a
-    toUnicodeAnn a _ = a
-
     ps_err = addFatalError
            . mkPlainErrorMsgEnvelope
-              (getLoc prag_start `combineSrcSpans` getLoc prag_end)
+              (getHasLoc (ass_open activation_anns) `combineSrcSpans` getHasLoc (ass_close activation_anns))
 
 checkRecordSyntax :: (MonadP m, Outputable a) => LocatedA a -> m (LocatedA a)
 checkRecordSyntax lr@(L loc r)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71a2396406fcc6fb4bdf198847eded9a94a55c72

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 21:03:10 2024
From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack))
Date: Wed, 30 Oct 2024 17:03:10 -0400
Subject: [Git][ghc/ghc] Pushed new branch wip/fix-T25062_V64
Message-ID: <67229f0e87d2f_399db7294f7884745@gitlab.mail>



Cheng Shao pushed new branch wip/fix-T25062_V64 at Glasgow Haskell Compiler / GHC

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-T25062_V64
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:14:49 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 30 Oct 2024 19:14:49 -0400
Subject: [Git][ghc/ghc][master] Add since tag for -fwrite-if-compression in
 user guide.
Message-ID: <6722bde9df924_1abb2211afa875522@gitlab.mail>



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


Commits:
1d7cd7fe by Andreas Klebinger at 2024-10-30T19:14:28-04:00
Add since tag for -fwrite-if-compression in user guide.

Partial fix for #25395

- - - - -


1 changed file:

- docs/users_guide/using-optimisation.rst


Changes:

=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1851,6 +1851,8 @@ as such you shouldn't need to set any of them explicitly. A flag
 
     :default: 2
 
+    :since: 9.12.1
+
     This flag defines the level of compression of interface files when writing to disk.
     The higher the flag, the more we deduplicate the interface file, at the cost of a higher compilation time.
     Deduplication (when applied to :ghc-flag:`--make` mode and :ghc-flag:`--interactive` mode) decreases the size of interface files as well as reducing



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d7cd7feac0878087c1210ece4974490ba3e5b85

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:15:43 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 30 Oct 2024 19:15:43 -0400
Subject: [Git][ghc/ghc][master] 2 commits: EPA: Remove some unused functions
Message-ID: <6722be1f1387c_1abb22395c74786f6@gitlab.mail>



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


Commits:
b349fd1b by Alan Zimmerman at 2024-10-30T19:15:04-04:00
EPA: Remove some unused functions

- - - - -
f859d61c by Alan Zimmerman at 2024-10-30T19:15:04-04:00
EPA: use explicit vertical bar token for ExplicitSum / SumPat

- - - - -


6 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Types.hs
- utils/check-exact/ExactPrint.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -419,8 +419,8 @@ arrowToHsExpr = expandHsArrow (HsVar noExtField)
 data AnnExplicitSum
   = AnnExplicitSum {
       aesOpen       :: EpaLocation,
-      aesBarsBefore :: [EpaLocation],
-      aesBarsAfter  :: [EpaLocation],
+      aesBarsBefore :: [EpToken "|"],
+      aesBarsAfter  :: [EpToken "|"],
       aesClose      :: EpaLocation
       } deriving Data
 


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -273,8 +273,8 @@ discarded inside tcMatchPats, where we know if visible pattern retained or erase
 
 data EpAnnSumPat = EpAnnSumPat
       { sumPatParens      :: (EpaLocation, EpaLocation)
-      , sumPatVbarsBefore :: [EpaLocation]
-      , sumPatVbarsAfter  :: [EpaLocation]
+      , sumPatVbarsBefore :: [EpToken "|"]
+      , sumPatVbarsAfter  :: [EpToken "|"]
       } deriving Data
 
 instance NoAnn EpAnnSumPat where


=====================================
compiler/GHC/Parser.y
=====================================
@@ -3280,13 +3280,11 @@ tup_exprs :: { forall b. DisambECP b => PV (SumOrTuple b) }
                       ; return (Tuple (cos ++ $2)) } }
 
            | texp bars   { unECP $1 >>= \ $1 -> return $
-                            (Sum 1  (snd $2 + 1) $1 [] (map srcSpan2e $ fst $2)) }
+                            (Sum 1  (snd $2 + 1) $1 [] (fst $2)) }
 
            | bars texp bars0
                 { unECP $2 >>= \ $2 -> return $
-                  (Sum (snd $1 + 1) (snd $1 + snd $3 + 1) $2
-                    (map srcSpan2e $ fst $1)
-                    (map srcSpan2e $ fst $3)) }
+                  (Sum (snd $1 + 1) (snd $1 + snd $3 + 1) $2 (fst $1) (fst $3)) }
 
 -- Always starts with commas; always follows an expr
 commas_tup_tail :: { forall b. DisambECP b => PV (SrcSpan,[Either (EpAnn Bool) (LocatedA b)]) }
@@ -3827,7 +3825,7 @@ ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit
                                       ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
-                                       (NameAnnBars (epTok $1, epTok $3) (map srcSpan2e (fst $2)) []) } }
+                                       (NameAnnBars (epTok $1, epTok $3) (fst $2) []) } }
         | '(' '->' ')'          {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
                                        (NameAnnRArrow  (Just $ epTok $1) (epUniTok $2) (Just $ epTok $3) []) }
 
@@ -4160,13 +4158,13 @@ commas :: { ([SrcSpan],Int) }   -- One or more commas
         : commas ','             { ((fst $1)++[gl $2],snd $1 + 1) }
         | ','                    { ([gl $1],1) }
 
-bars0 :: { ([SrcSpan],Int) }     -- Zero or more bars
+bars0 :: { ([EpToken "|"],Int) }     -- Zero or more bars
         : bars                   { $1 }
         |                        { ([], 0) }
 
-bars :: { ([SrcSpan],Int) }     -- One or more bars
-        : bars '|'               { ((fst $1)++[gl $2],snd $1 + 1) }
-        | '|'                    { ([gl $1],1) }
+bars :: { ([EpToken "|"],Int) }     -- One or more bars
+        : bars '|'               { ((fst $1)++[epTok $2],snd $1 + 1) }
+        | '|'                    { ([epTok $1],1) }
 
 {
 happyError :: P a


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -66,7 +66,6 @@ module GHC.Parser.Annotation (
   srcSpan2e, realSrcSpan,
 
   -- ** Building up annotations
-  reAnnL, reAnnC,
   addAnnsA, widenSpanL, widenSpanT, widenAnchorT, widenAnchorS,
   widenLocatedAnL,
   listLocation,
@@ -94,7 +93,6 @@ module GHC.Parser.Annotation (
   noComments, comment, addCommentsToEpAnn, setCommentsEpAnn,
   transferAnnsA, transferAnnsOnlyA, transferCommentsOnlyA,
   transferPriorCommentsA, transferFollowingA,
-  commentsOnlyA, removeCommentsA,
 
   placeholderRealSpan,
   ) where
@@ -610,7 +608,7 @@ data NameAnn
   -- | Used for @(# | | #)@
   | NameAnnBars {
       nann_parensh   :: (EpToken "(#", EpToken "#)"),
-      nann_bars      :: [EpaLocation],
+      nann_bars      :: [EpToken "|"],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @()@, @(##)@, @[]@
@@ -929,12 +927,6 @@ srcSpan2e :: SrcSpan -> EpaLocation
 srcSpan2e ss@(RealSrcSpan _ _) = EpaSpan ss
 srcSpan2e span = EpaSpan (RealSrcSpan (realSrcSpan span) Strict.Nothing)
 
-reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a
-reAnnC anns cs (L l a) = L (EpAnn (spanAsAnchor l) anns cs) a
-
-reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (EpAnn ann) e
-reAnnL anns cs (L l a) = L (EpAnn (spanAsAnchor l) anns cs) a
-
 getLocAnn :: Located a  -> SrcSpanAnnA
 getLocAnn (L l _) = noAnnSrcSpan l
 
@@ -1094,16 +1086,6 @@ transferPriorCommentsA (EpAnn a1 an1 cs1) (EpAnn a2 an2 cs2)
     cs1' = setFollowingComments emptyComments fc
     cs2' = setPriorComments cs2 (priorComments cs2 <> pc)
 
-
--- | Remove the exact print annotations payload, leaving only the
--- anchor and comments.
-commentsOnlyA :: NoAnn ann => EpAnn ann -> EpAnn ann
-commentsOnlyA (EpAnn a _ cs) = EpAnn a noAnn cs
-
--- | Remove the comments, leaving the exact print annotations payload
-removeCommentsA :: EpAnn ann -> EpAnn ann
-removeCommentsA (EpAnn a an _) = EpAnn a an emptyComments
-
 -- ---------------------------------------------------------------------
 -- Semigroup instances, to allow easy combination of annotation elements
 -- ---------------------------------------------------------------------


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -27,7 +27,7 @@ import GHC.Parser.Annotation
 import Language.Haskell.Syntax
 
 data SumOrTuple b
-  = Sum ConTag Arity (LocatedA b) [EpaLocation] [EpaLocation]
+  = Sum ConTag Arity (LocatedA b) [EpToken "|"] [EpToken "|"]
   -- ^ Last two are the locations of the '|' before and after the payload
   | Tuple [Either (EpAnn Bool) (LocatedA b)]
 


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -1036,8 +1036,8 @@ lsnd k parent = fmap (\new -> (fst parent, new))
 -- data AnnExplicitSum
 --   = AnnExplicitSum {
 --       aesOpen       :: EpaLocation,
---       aesBarsBefore :: [EpaLocation],
---       aesBarsAfter  :: [EpaLocation],
+--       aesBarsBefore :: [EpToken "|"],
+--       aesBarsAfter  :: [EpToken "|"],
 --       aesClose      :: EpaLocation
 --       } deriving Data
 
@@ -1045,11 +1045,11 @@ laesOpen :: Lens AnnExplicitSum EpaLocation
 laesOpen k parent = fmap (\new -> parent { aesOpen = new })
                          (k (aesOpen parent))
 
-laesBarsBefore :: Lens AnnExplicitSum [EpaLocation]
+laesBarsBefore :: Lens AnnExplicitSum [EpToken "|"]
 laesBarsBefore k parent = fmap (\new -> parent { aesBarsBefore = new })
                                (k (aesBarsBefore parent))
 
-laesBarsAfter :: Lens AnnExplicitSum [EpaLocation]
+laesBarsAfter :: Lens AnnExplicitSum [EpToken "|"]
 laesBarsAfter k parent = fmap (\new -> parent { aesBarsAfter = new })
                                (k (aesBarsAfter parent))
 
@@ -1215,19 +1215,19 @@ lga_sep k parent = fmap (\new -> parent { ga_sep = new })
 -- ---------------------------------------------------------------------
 -- data EpAnnSumPat = EpAnnSumPat
 --       { sumPatParens      :: (EpaLocation, EpaLocation)
---       , sumPatVbarsBefore :: [EpaLocation]
---       , sumPatVbarsAfter  :: [EpaLocation]
+--       , sumPatVbarsBefore :: [EpToken "|"]
+--       , sumPatVbarsAfter  :: [EpToken "|"]
 --       } deriving Data
 
 lsumPatParens :: Lens EpAnnSumPat (EpaLocation, EpaLocation)
 lsumPatParens k parent = fmap (\new -> parent { sumPatParens = new })
                               (k (sumPatParens parent))
 
-lsumPatVbarsBefore :: Lens EpAnnSumPat [EpaLocation]
+lsumPatVbarsBefore :: Lens EpAnnSumPat [EpToken "|"]
 lsumPatVbarsBefore k parent = fmap (\new -> parent { sumPatVbarsBefore = new })
                               (k (sumPatVbarsBefore parent))
 
-lsumPatVbarsAfter :: Lens EpAnnSumPat [EpaLocation]
+lsumPatVbarsAfter :: Lens EpAnnSumPat [EpToken "|"]
 lsumPatVbarsAfter k parent = fmap (\new -> parent { sumPatVbarsAfter = new })
                               (k (sumPatVbarsAfter parent))
 
@@ -2985,9 +2985,9 @@ instance ExactPrint (HsExpr GhcPs) where
 
   exact (ExplicitSum an alt arity expr) = do
     an0 <- markLensFun an laesOpen (\loc -> printStringAtAA loc "(#")
-    an1 <- markLensFun an0 laesBarsBefore (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an1 <- markLensFun an0 laesBarsBefore (\locs -> mapM markEpToken locs)
     expr' <- markAnnotated expr
-    an2 <- markLensFun an1 laesBarsAfter (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an2 <- markLensFun an1 laesBarsAfter (\locs -> mapM markEpToken locs)
     an3 <- markLensFun an2 laesClose (\loc -> printStringAtAA loc "#)")
     return (ExplicitSum an3 alt arity expr')
 
@@ -4191,7 +4191,7 @@ instance ExactPrint (LocatedN RdrName) where
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
           o' <- markEpToken o
-          bars' <- forM bars (\loc -> printStringAtAAC NoCaptureComments loc "|")
+          bars' <- mapM markEpToken bars
           c' <- markEpToken c
           return (NameAnnBars (o',c') bars' t)
         NameAnnOnly a t -> do
@@ -4684,9 +4684,9 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (SumPat an pat alt arity) = do
     an0 <- markLensFun an (lsumPatParens . lfst) (\loc -> printStringAtAA loc "(#")
-    an1 <- markLensFun an0 lsumPatVbarsBefore (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an1 <- markLensFun an0 lsumPatVbarsBefore (\locs -> mapM markEpToken locs)
     pat' <- markAnnotated pat
-    an2 <- markLensFun an1 lsumPatVbarsAfter (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an2 <- markLensFun an1 lsumPatVbarsAfter (\locs -> mapM markEpToken locs)
     an3 <- markLensFun an2 (lsumPatParens . lsnd)  (\loc -> printStringAtAA loc "#)")
     return (SumPat an3 pat' alt arity)
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d7cd7feac0878087c1210ece4974490ba3e5b85...f859d61c4832b16ae3b4dd14aad5cb41b0051de3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d7cd7feac0878087c1210ece4974490ba3e5b85...f859d61c4832b16ae3b4dd14aad5cb41b0051de3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:24:30 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 30 Oct 2024 19:24:30 -0400
Subject: [Git][ghc/ghc][wip/T20264] Mostly working now
Message-ID: <6722c02e381cf_1abb2211afe47902@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
69f83064 by Simon Peyton Jones at 2024-10-30T23:24:08+00:00
Mostly working now

- - - - -


2 changed files:

- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Opt/SpecConstr.hs


Changes:

=====================================
compiler/GHC/Core/FVs.hs
=====================================
@@ -672,20 +672,20 @@ freeVarsBind (NonRec binder rhs) body_fvs
   = ( AnnNonRec binder rhs2
     , freeVarsOf rhs2 `unionFVs` body_fvs2 )
     where
-      rhs2      = freeVarsRhs rhs
+      rhs2      = freeVarsRhs (binder, rhs)
       body_fvs2 = binder `delBinderFV` body_fvs
 
 freeVarsBind (Rec binds) body_fvs
   = ( AnnRec (binders `zip` rhss2)
     , delBindersFV binders all_fvs )
   where
-    (binders, rhss) = unzip binds
-    rhss2           = map freeVarsRhs rhss
-    all_fvs         = foldr (unionFVs . freeVarsOf) body_fvs rhss2
+    binders = map fst binds
+    rhss2   = map freeVarsRhs binds
+    all_fvs = foldr (unionFVs . freeVarsOf) body_fvs rhss2
             -- The "delBinderFV" happens after adding the idSpecVars,
             -- since the latter may add some of the binders as fvs
 
-freeVarsRhs :: Var -> CoreExpr -> CoreExprWithFVs
+freeVarsRhs :: (Var, CoreExpr) -> CoreExprWithFVs
 -- Decorate the RHS with its free vars,
 -- PLUS the free vars of:
 --    - rules
@@ -693,7 +693,7 @@ freeVarsRhs :: Var -> CoreExpr -> CoreExprWithFVs
 --    - type
 -- The free vars of the type matters because of type-lets;
 -- they may be free in the RHS itself
-freeVarsRhs bndr rhs
+freeVarsRhs (bndr, rhs)
   = (rhs_fvs `unionFVs` extra_fvs, rhs')
   where
     (rhs_fvs, rhs') = freeVars rhs


=====================================
compiler/GHC/Core/Opt/SpecConstr.hs
=====================================
@@ -55,6 +55,7 @@ import GHC.Unit.Module.ModGuts
 import GHC.Types.Error (MessageClass(..), Severity(..), DiagnosticReason(WarningWithoutFlag), ResolvedDiagnosticReason (..))
 import GHC.Types.Literal ( litIsLifted )
 import GHC.Types.Id
+import GHC.Types.Var     ( setTyVarUnfolding )
 import GHC.Types.Id.Info ( IdDetails(..) )
 import GHC.Types.Id.Make ( voidArgId, voidPrimId )
 import GHC.Types.Var.Env
@@ -1411,9 +1412,14 @@ scBind :: TopLevelFlag -> ScEnv -> InBind
        -> (ScEnv -> UniqSM (ScUsage, a, [SpecFailWarning]))   -- Specialise the scope of the binding
        -> UniqSM (ScUsage, [OutBind], a, [SpecFailWarning])
 scBind top_lvl env (NonRec bndr rhs) do_body
-  | isTyVar bndr         -- Type-lets may be created by doBeta
-  = do { (final_usage, body', warnings) <- do_body (extendScSubst env bndr rhs)
-       ; return (final_usage, [], body', warnings) }
+  | Type rhs_ty <- rhs
+  = assertPpr (isTyVar bndr) (ppr bndr) $
+    do { let (body_env, bndr') = extendBndr env bndr
+             !(MkSolo rhs_ty') = scSubstTy env rhs_ty
+             bndr'' = setTyVarUnfolding bndr' rhs_ty'
+             body_env' = extendScSubst body_env bndr (Type (mkTyVarTy bndr''))
+       ; (final_usage, body', warnings) <- do_body body_env'
+       ; return (final_usage, [NonRec bndr'' (Type rhs_ty')], body', warnings) }
 
   | not (isTopLevel top_lvl)  -- Nested non-recursive value binding
     -- See Note [Specialising local let bindings]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69f830646817c8292ccb8d2c473ac66b24dd266f

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:24:58 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 30 Oct 2024 19:24:58 -0400
Subject: [Git][ghc/ghc][wip/T24359] More small fixes
Message-ID: <6722c04a7a406_1abb224b8d2c79693@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC


Commits:
9e47814d by Simon Peyton Jones at 2024-10-30T23:24:42+00:00
More small fixes

- - - - -


3 changed files:

- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver.hs


Changes:

=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -820,7 +820,7 @@ dsSpec mb_poly_rhs (SpecPrag poly_id spec_co spec_inl)
                --         \spec_bndrs. [] spec_args
                -- perhaps with the body of the lambda wrapped in some WpLets
                -- E.g. /\a \(d:Eq a). let d2 = $df d in [] (Maybe a) d2
-  = dsHsWrapperForRuleLHS spec_app $ \core_app ->
+  = dsHsWrapper spec_app $ \core_app ->
     finishSpecPrag mb_poly_rhs
                    spec_bndrs (core_app (Var poly_id))
                    spec_bndrs (\_ poly_rhs -> core_app poly_rhs)


=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -36,7 +36,9 @@ import {-# SOURCE #-} GHC.Tc.Gen.Expr  ( tcInferRho, tcCheckMonoExpr )
 
 import GHC.Tc.Errors.Types ( FixedRuntimeRepProvenance(..), TcRnMessage(..) )
 import GHC.Tc.Gen.HsType
-import GHC.Tc.Solver
+import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX
+                    , growThetaTyVars )
+import GHC.Tc.Solver.Solve( solveWanteds )
 import GHC.Tc.Solver.Monad( runTcS )
 import GHC.Tc.Validity ( checkValidType )
 


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -1851,8 +1851,7 @@ decideQuantifiedTyVars skol_info name_taus psigs candidates
            , text "candidates =" <+> ppr candidates
            , text "dvs =" <+> ppr dvs
            , text "tau_tys =" <+> ppr tau_tys
-           , text "seed_tys =" <+> ppr seed_tys
-           , text "seed_tcvs =" <+> ppr (tyCoVarsOfTypes seed_tys)
+           , text "seed_tvs =" <+> ppr seed_tvs
            , text "grown_tcvs =" <+> ppr grown_tcvs
            , text "dvs =" <+> ppr dvs_plus])
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e47814d6def642b6aef6ad272d3ee92fb9b4e0e

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:46:54 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Wed, 30 Oct 2024 19:46:54 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Add since
 tag for -fwrite-if-compression in user guide.
Message-ID: <6722c56dea3c7_1abb227b14ac823ad@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
1d7cd7fe by Andreas Klebinger at 2024-10-30T19:14:28-04:00
Add since tag for -fwrite-if-compression in user guide.

Partial fix for #25395

- - - - -
b349fd1b by Alan Zimmerman at 2024-10-30T19:15:04-04:00
EPA: Remove some unused functions

- - - - -
f859d61c by Alan Zimmerman at 2024-10-30T19:15:04-04:00
EPA: use explicit vertical bar token for ExplicitSum / SumPat

- - - - -
afd077fd by Ben Gamari at 2024-10-30T19:46:23-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -
a6891547 by Alan Zimmerman at 2024-10-30T19:46:24-04:00
EPA: Bring in last EpToken usages

For import declarations, NameAnnCommas and NPlusKPat.

And remove anchor, it is the same as epaLocationRealSrcSpan.

- - - - -
b6a270c2 by sheaf at 2024-10-30T19:46:31-04:00
Assert that ctEvCoercion is called on an equality

Calling 'ctEvCoercion' on non-equality constraints is always incorrect.
We add an assertion to this function to detect such cases; for example
a type-checking plugin might erroneously do this.

- - - - -


28 changed files:

- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Types/Constraint.hs
- docs/users_guide/using-optimisation.rst
- rts/Disassembler.c
- + testsuite/tests/codeGen/should_run/T25374/T25374.hs
- + testsuite/tests/codeGen/should_run/T25374/T25374.script
- + testsuite/tests/codeGen/should_run/T25374/T25374A.hs
- + testsuite/tests/codeGen/should_run/T25374/all.T
- testsuite/tests/simplCore/should_compile/T23864.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Types.hs
- utils/check-exact/Utils.hs
- utils/check-ppr/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs


Changes:

=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -419,8 +419,8 @@ arrowToHsExpr = expandHsArrow (HsVar noExtField)
 data AnnExplicitSum
   = AnnExplicitSum {
       aesOpen       :: EpaLocation,
-      aesBarsBefore :: [EpaLocation],
-      aesBarsAfter  :: [EpaLocation],
+      aesBarsBefore :: [EpToken "|"],
+      aesBarsAfter  :: [EpToken "|"],
       aesClose      :: EpaLocation
       } deriving Data
 


=====================================
compiler/GHC/Hs/ImpExp.hs
=====================================
@@ -194,9 +194,9 @@ instance (OutputableBndrId p
 -}
 
 type instance XIEName    (GhcPass _) = NoExtField
-type instance XIEDefault (GhcPass _) = EpaLocation
-type instance XIEPattern (GhcPass _) = EpaLocation
-type instance XIEType    (GhcPass _) = EpaLocation
+type instance XIEDefault (GhcPass _) = EpToken "default"
+type instance XIEPattern (GhcPass _) = EpToken "pattern"
+type instance XIEType    (GhcPass _) = EpToken "type"
 type instance XXIEWrappedName (GhcPass _) = DataConCantHappen
 
 type instance Anno (IEWrappedName (GhcPass _)) = SrcSpanAnnA


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -158,7 +158,7 @@ type instance XNPat GhcPs = EpToken "-"
 type instance XNPat GhcRn = EpToken "-"
 type instance XNPat GhcTc = Type
 
-type instance XNPlusKPat GhcPs = EpaLocation -- Of the "+"
+type instance XNPlusKPat GhcPs = EpToken "+"
 type instance XNPlusKPat GhcRn = NoExtField
 type instance XNPlusKPat GhcTc = Type
 
@@ -273,8 +273,8 @@ discarded inside tcMatchPats, where we know if visible pattern retained or erase
 
 data EpAnnSumPat = EpAnnSumPat
       { sumPatParens      :: (EpaLocation, EpaLocation)
-      , sumPatVbarsBefore :: [EpaLocation]
-      , sumPatVbarsAfter  :: [EpaLocation]
+      , sumPatVbarsBefore :: [EpToken "|"]
+      , sumPatVbarsAfter  :: [EpToken "|"]
       } deriving Data
 
 instance NoAnn EpAnnSumPat where


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -340,7 +340,7 @@ mkHsCompAnns   :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs
 
 mkNPat      :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpToken "-"
             -> Pat GhcPs
-mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpaLocation
+mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpToken "+"
             -> Pat GhcPs
 
 -- NB: The following functions all use noSyntaxExpr: the generated expressions


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1040,9 +1040,9 @@ export  :: { LIE GhcPs }
                                                           ; locImpExp <- return (sL span (IEModuleContents ($1, (epTok $2)) $3))
                                                           ; return $ reLoc $ locImpExp } }
         | maybe_warning_pragma 'pattern' qcon            { let span = (maybe comb2 comb3 $1) $2 $>
-                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (glR $2) $3)) Nothing }
+                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (epTok $2) $3)) Nothing }
         | maybe_warning_pragma 'default' qtycon          {% do { let { span = (maybe comb2 comb3 $1) $2 $> }
-                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (glR $2) $3)) Nothing))
+                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (epTok $2) $3)) Nothing))
                                                           ; return $ reLoc $ locImpExp } }
 
 
@@ -1076,7 +1076,7 @@ qcname_ext_w_wildcard :: { LocatedA ImpExpQcSpec }
 qcname_ext :: { LocatedA ImpExpQcSpec }
         :  qcname                   { sL1a $1 (ImpExpQcName $1) }
         |  'type' oqtycon           {% do { n <- mkTypeImpExp $2
-                                          ; return $ sLLa $1 $> (ImpExpQcType (glR $1) n) }}
+                                          ; return $ sLLa $1 $> (ImpExpQcType (epTok $1) n) }}
 
 qcname  :: { LocatedN RdrName }  -- Variable or type constructor
         :  qvar                 { $1 } -- Things which look like functions
@@ -1209,7 +1209,7 @@ importlist1 :: { OrdList (LIE GhcPs) }
 import  :: { OrdList (LIE GhcPs) }
         : qcname_ext export_subspec {% fmap (unitOL . reLoc . (sLL $1 $>)) $ mkModuleImpExp Nothing (fst $ unLoc $2) $1 (snd $ unLoc $2) }
         | 'module' modid            {% fmap (unitOL . reLoc) $ return (sLL $1 $> (IEModuleContents (Nothing, (epTok $1)) $2)) }
-        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (glR $1) $2)) Nothing }
+        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (epTok $1) $2)) Nothing }
 
 -----------------------------------------------------------------------------
 -- Fixity Declarations
@@ -3280,13 +3280,11 @@ tup_exprs :: { forall b. DisambECP b => PV (SumOrTuple b) }
                       ; return (Tuple (cos ++ $2)) } }
 
            | texp bars   { unECP $1 >>= \ $1 -> return $
-                            (Sum 1  (snd $2 + 1) $1 [] (map srcSpan2e $ fst $2)) }
+                            (Sum 1  (snd $2 + 1) $1 [] (fst $2)) }
 
            | bars texp bars0
                 { unECP $2 >>= \ $2 -> return $
-                  (Sum (snd $1 + 1) (snd $1 + snd $3 + 1) $2
-                    (map srcSpan2e $ fst $1)
-                    (map srcSpan2e $ fst $3)) }
+                  (Sum (snd $1 + 1) (snd $1 + snd $3 + 1) $2 (fst $1) (fst $3)) }
 
 -- Always starts with commas; always follows an expr
 commas_tup_tail :: { forall b. DisambECP b => PV (SrcSpan,[Either (EpAnn Bool) (LocatedA b)]) }
@@ -3778,10 +3776,10 @@ qcon_list : qcon                  { [$1] }
 -- See Note [ExplicitTuple] in GHC.Hs.Expr
 sysdcon_nolist :: { LocatedN DataCon }  -- Wired in data constructors
         : '(' commas ')'        {% amsr (sLL $1 $> $ tupleDataCon Boxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
         | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '(#' commas '#)'      {% amsr (sLL $1 $> $ tupleDataCon Unboxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
 
 syscon :: { LocatedN RdrName }
         : sysdcon               {  L (getLoc $1) $ nameRdrName (dataConName (unLoc $1)) }
@@ -3822,12 +3820,12 @@ gtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, including unit t
 ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit tuples
         : oqtycon               { $1 }
         | '(' commas ')'        {% do { n <- mkTupleSyntaxTycon Boxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' commas '#)'      {% do { n <- mkTupleSyntaxTycon Unboxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
-                                       (NameAnnBars (epTok $1, epTok $3) (map srcSpan2e (fst $2)) []) } }
+                                       (NameAnnBars (epTok $1, epTok $3) (fst $2) []) } }
         | '(' '->' ')'          {% amsr (sLL $1 $> $ getRdrName unrestrictedFunTyCon)
                                        (NameAnnRArrow  (Just $ epTok $1) (epUniTok $2) (Just $ epTok $3) []) }
 
@@ -4160,13 +4158,13 @@ commas :: { ([SrcSpan],Int) }   -- One or more commas
         : commas ','             { ((fst $1)++[gl $2],snd $1 + 1) }
         | ','                    { ([gl $1],1) }
 
-bars0 :: { ([SrcSpan],Int) }     -- Zero or more bars
+bars0 :: { ([EpToken "|"],Int) }     -- Zero or more bars
         : bars                   { $1 }
         |                        { ([], 0) }
 
-bars :: { ([SrcSpan],Int) }     -- One or more bars
-        : bars '|'               { ((fst $1)++[gl $2],snd $1 + 1) }
-        | '|'                    { ([gl $1],1) }
+bars :: { ([EpToken "|"],Int) }     -- One or more bars
+        : bars '|'               { ((fst $1)++[epTok $2],snd $1 + 1) }
+        | '|'                    { ([epTok $1],1) }
 
 {
 happyError :: P a


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -23,7 +23,6 @@ module GHC.Parser.Annotation (
   DeltaPos(..), deltaPos, getDeltaLine,
 
   EpAnn(..),
-  anchor,
   spanAsAnchor, realSpanAsAnchor,
   noSpanAnchor,
   NoAnn(..),
@@ -66,7 +65,6 @@ module GHC.Parser.Annotation (
   srcSpan2e, realSrcSpan,
 
   -- ** Building up annotations
-  reAnnL, reAnnC,
   addAnnsA, widenSpanL, widenSpanT, widenAnchorT, widenAnchorS,
   widenLocatedAnL,
   listLocation,
@@ -94,7 +92,6 @@ module GHC.Parser.Annotation (
   noComments, comment, addCommentsToEpAnn, setCommentsEpAnn,
   transferAnnsA, transferAnnsOnlyA, transferCommentsOnlyA,
   transferPriorCommentsA, transferFollowingA,
-  commentsOnlyA, removeCommentsA,
 
   placeholderRealSpan,
   ) where
@@ -352,7 +349,7 @@ instance Outputable a => Outputable (GenLocated TokenLocation a) where
 -- | Used in the parser only, extract the 'RealSrcSpan' from an
 -- 'EpaLocation'. The parser will never insert a 'DeltaPos', so the
 -- partial function is safe.
-epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
+epaLocationRealSrcSpan :: EpaLocation' a -> RealSrcSpan
 epaLocationRealSrcSpan (EpaSpan (RealSrcSpan r _)) = r
 epaLocationRealSrcSpan _ = panic "epaLocationRealSrcSpan"
 
@@ -403,9 +400,6 @@ data EpAnn ann
         deriving (Data, Eq, Functor)
 -- See Note [XRec and Anno in the AST]
 
-anchor :: (EpaLocation' a) -> RealSrcSpan
-anchor (EpaSpan (RealSrcSpan r _)) = r
-anchor _ = panic "anchor"
 
 spanAsAnchor :: SrcSpan -> (EpaLocation' a)
 spanAsAnchor ss  = EpaSpan ss
@@ -604,13 +598,13 @@ data NameAnn
   -- | Used for @(,,,)@, or @(#,,,#)@
   | NameAnnCommas {
       nann_adornment :: NameAdornment,
-      nann_commas    :: [EpaLocation],
+      nann_commas    :: [EpToken ","],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(# | | #)@
   | NameAnnBars {
       nann_parensh   :: (EpToken "(#", EpToken "#)"),
-      nann_bars      :: [EpaLocation],
+      nann_bars      :: [EpToken "|"],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @()@, @(##)@, @[]@
@@ -643,10 +637,10 @@ data NameAnn
 -- such as parens or backquotes. This data type identifies what
 -- particular pair are being used.
 data NameAdornment
-  = NameParens     (EpToken "(")  (EpToken ")") -- ^ '(' ')'
-  | NameParensHash (EpToken "(#") (EpToken "#)")-- ^ '(#' '#)'
-  | NameBackquotes (EpToken "`")  (EpToken "`")-- ^ '`'
-  | NameSquare     (EpToken "[")  (EpToken "]")-- ^ '[' ']'
+  = NameParens     (EpToken "(")  (EpToken ")")
+  | NameParensHash (EpToken "(#") (EpToken "#)")
+  | NameBackquotes (EpToken "`")  (EpToken "`")
+  | NameSquare     (EpToken "[")  (EpToken "]")
   | NameNoAdornment
   deriving (Eq, Data)
 
@@ -929,12 +923,6 @@ srcSpan2e :: SrcSpan -> EpaLocation
 srcSpan2e ss@(RealSrcSpan _ _) = EpaSpan ss
 srcSpan2e span = EpaSpan (RealSrcSpan (realSrcSpan span) Strict.Nothing)
 
-reAnnC :: AnnContext -> EpAnnComments -> Located a -> LocatedC a
-reAnnC anns cs (L l a) = L (EpAnn (spanAsAnchor l) anns cs) a
-
-reAnnL :: ann -> EpAnnComments -> Located e -> GenLocated (EpAnn ann) e
-reAnnL anns cs (L l a) = L (EpAnn (spanAsAnchor l) anns cs) a
-
 getLocAnn :: Located a  -> SrcSpanAnnA
 getLocAnn (L l _) = noAnnSrcSpan l
 
@@ -1094,16 +1082,6 @@ transferPriorCommentsA (EpAnn a1 an1 cs1) (EpAnn a2 an2 cs2)
     cs1' = setFollowingComments emptyComments fc
     cs2' = setPriorComments cs2 (priorComments cs2 <> pc)
 
-
--- | Remove the exact print annotations payload, leaving only the
--- anchor and comments.
-commentsOnlyA :: NoAnn ann => EpAnn ann -> EpAnn ann
-commentsOnlyA (EpAnn a _ cs) = EpAnn a noAnn cs
-
--- | Remove the comments, leaving the exact print annotations payload
-removeCommentsA :: EpAnn ann -> EpAnn ann
-removeCommentsA (EpAnn a an _) = EpAnn a an emptyComments
-
 -- ---------------------------------------------------------------------
 -- Semigroup instances, to allow easy combination of annotation elements
 -- ---------------------------------------------------------------------


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -3672,8 +3672,8 @@ allocateComments
   -> ([LEpaComment], [LEpaComment])
 allocateComments ss comment_q =
   let
-    (before,rest)  = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
-    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
+    (before,rest)  = break (\(L l _) -> isRealSubspanOf (epaLocationRealSrcSpan l) ss) comment_q
+    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (epaLocationRealSrcSpan l) ss)) rest
     comment_q' = before ++ after
     newAnns = middle
   in
@@ -3691,14 +3691,14 @@ splitPriorComments ss prior_comments =
     -- And the token preceding the comment is on a different line
     cmp :: RealSrcSpan -> LEpaComment -> Bool
     cmp later (L l c)
-         = srcSpanStartLine later - srcSpanEndLine (anchor l) == 1
-          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (anchor l)
+         = srcSpanStartLine later - srcSpanEndLine (epaLocationRealSrcSpan l) == 1
+          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (epaLocationRealSrcSpan l)
 
     go :: [LEpaComment] -> RealSrcSpan -> [LEpaComment]
        -> ([LEpaComment], [LEpaComment])
     go decl_comments _ [] = ([],decl_comments)
     go decl_comments r (c@(L l _):cs) = if cmp r c
-                              then go (c:decl_comments) (anchor l) cs
+                              then go (c:decl_comments) (epaLocationRealSrcSpan l) cs
                               else (reverse (c:cs), decl_comments)
   in
     go [] ss prior_comments
@@ -3710,7 +3710,7 @@ allocatePriorComments
   -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
 allocatePriorComments ss comment_q mheader_comments =
   let
-    cmp (L l _) = anchor l <= ss
+    cmp (L l _) = epaLocationRealSrcSpan l <= ss
     (newAnns,after) = partition cmp comment_q
     comment_q'= after
     (prior_comments, decl_comments) = splitPriorComments ss newAnns


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1312,7 +1312,7 @@ checkAPat loc e0 = do
            _
                      | nPlusKPatterns && (plus == plus_RDR)
                      -> return (mkNPlusKPat (L nloc n) (L (l2l lloc) lit)
-                                (entry l))
+                                (EpTok $ entry l))
 
    -- Improve error messages for the @-operator when the user meant an @-pattern
    PatBuilderOpApp _ op _ _ | opIsAt (unLoc op) -> do
@@ -3158,7 +3158,7 @@ data ImpExpSubSpec = ImpExpAbs
                    | ImpExpAllWith [LocatedA ImpExpQcSpec]
 
 data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName)
-                  | ImpExpQcType EpaLocation (LocatedN RdrName)
+                  | ImpExpQcType (EpToken "type") (LocatedN RdrName)
                   | ImpExpQcWildcard (EpToken "..") (EpToken ",")
 
 mkModuleImpExp :: Maybe (LWarningTxt GhcPs) -> (EpToken "(", EpToken ")") -> LocatedA ImpExpQcSpec


=====================================
compiler/GHC/Parser/Types.hs
=====================================
@@ -27,7 +27,7 @@ import GHC.Parser.Annotation
 import Language.Haskell.Syntax
 
 data SumOrTuple b
-  = Sum ConTag Arity (LocatedA b) [EpaLocation] [EpaLocation]
+  = Sum ConTag Arity (LocatedA b) [EpToken "|"] [EpToken "|"]
   -- ^ Last two are the locations of the '|' before and after the payload
   | Tuple [Either (EpAnn Bool) (LocatedA b)]
 


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -2107,13 +2107,13 @@ printMinimalImports hsc_src imports_w_usage
 
 to_ie_post_rn_var :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn_var (L l n)
-  | isDataOcc $ occName n = L l (IEPattern (entry l)   (L (l2l l) n))
+  | isDataOcc $ occName n = L l (IEPattern noAnn      (L (l2l l) n))
   | otherwise             = L l (IEName    noExtField (L (l2l l) n))
 
 
 to_ie_post_rn :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn (L l n)
-  | isTcOcc occ && isSymOcc occ = L l (IEType (entry l)   (L (l2l l) n))
+  | isTcOcc occ && isSymOcc occ = L l (IEType noAnn      (L (l2l l) n))
   | otherwise                   = L l (IEName noExtField (L (l2l l) n))
   where occ = occName n
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -2306,8 +2306,10 @@ ctEvExpr ev@(CtWanted { ctev_dest = HoleDest _ })
 ctEvExpr ev = evId (ctEvEvId ev)
 
 ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion
-ctEvCoercion (CtGiven { ctev_evar = ev_id })
-  = mkCoVarCo ev_id
+ctEvCoercion _given@(CtGiven { ctev_evar = ev_id })
+  = assertPpr (isCoVar ev_id)
+    (text "ctEvCoercion used on non-equality Given constraint:" <+> ppr _given)
+  $ mkCoVarCo ev_id
 ctEvCoercion (CtWanted { ctev_dest = dest })
   | HoleDest hole <- dest
   = -- ctEvCoercion is only called on type equalities


=====================================
docs/users_guide/using-optimisation.rst
=====================================
@@ -1851,6 +1851,8 @@ as such you shouldn't need to set any of them explicitly. A flag
 
     :default: 2
 
+    :since: 9.12.1
+
     This flag defines the level of compression of interface files when writing to disk.
     The higher the flag, the more we deduplicate the interface file, at the cost of a higher compilation time.
     Deduplication (when applied to :ghc-flag:`--make` mode and :ghc-flag:`--interactive` mode) decreases the size of interface files as well as reducing


=====================================
rts/Disassembler.c
=====================================
@@ -67,12 +67,12 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }
          debugBelch("\n");
-         pc += 4;
+         pc += 6;
          break;
       case bci_SWIZZLE: {
          W_     stkoff = BCO_GET_LARGE_ARG;


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.hs
=====================================
@@ -0,0 +1,8 @@
+import T25374A
+
+fieldsSam :: NP xs -> NP xs -> Bool
+fieldsSam UNil UNil = True
+
+x :: Bool
+x = fieldsSam UNil UNil
+


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.script
=====================================
@@ -0,0 +1,2 @@
+:load T25374
+x


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374A.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+module T25374A where
+
+import GHC.Exts
+
+type NP :: [UnliftedType] -> UnliftedType
+data NP xs where
+  UNil :: NP '[]
+  (::*) :: x -> NP xs -> NP (x ': xs)
+


=====================================
testsuite/tests/codeGen/should_run/T25374/all.T
=====================================
@@ -0,0 +1,3 @@
+# This shouldn't crash the disassembler
+test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, unless(debug_rts(), skip)], ghci_script, [''])
+


=====================================
testsuite/tests/simplCore/should_compile/T23864.hs
=====================================
@@ -49,7 +49,7 @@ insertCommentsByPos ::
   -> (EpAnnComments -> [LEpaComment] -> EpAnnComments)
   -> EpAnn a
   -> WithComments (EpAnn a)
-insertCommentsByPos cond = insertComments (cond . anchor . getLoc)
+insertCommentsByPos cond = insertComments (cond . epaLocationRealSrcSpan . getLoc)
 
 insertComments ::
      (LEpaComment -> Bool)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -570,7 +570,7 @@ splitAfterTrailingAnns tas cs = (before, after)
         (s:_) -> (b,a)
           where
             s_pos = ss2pos s
-            (b,a) = break (\(L ll _) -> (ss2pos $ anchor ll) > s_pos)
+            (b,a) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > s_pos)
                           cs
 
 -- ---------------------------------------------------------------------
@@ -731,12 +731,6 @@ printStringAtNC el str = do
   el' <- printStringAtAAC NoCaptureComments (noCommentsToEpaLocation el) str
   return (epaToNoCommentsLocation el')
 
-printStringAtAAL :: (Monad m, Monoid w)
-  => a -> Lens a EpaLocation -> String -> EP w m a
-printStringAtAAL an l str = do
-  r <- printStringAtAAC CaptureComments (view l an) str
-  return (set l r an)
-
 printStringAtAAC :: (Monad m, Monoid w)
   => CaptureComments -> EpaLocation -> String -> EP w m EpaLocation
 printStringAtAAC capture (EpaSpan (RealSrcSpan r _)) s = printStringAtRsC capture r s
@@ -1020,10 +1014,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lid :: Lens a a
-lid k parent = fmap (\new -> new)
-                    (k parent)
-
 lfst :: Lens (a,b) a
 lfst k parent = fmap (\new -> (new, snd parent))
                      (k (fst parent))
@@ -1036,8 +1026,8 @@ lsnd k parent = fmap (\new -> (fst parent, new))
 -- data AnnExplicitSum
 --   = AnnExplicitSum {
 --       aesOpen       :: EpaLocation,
---       aesBarsBefore :: [EpaLocation],
---       aesBarsAfter  :: [EpaLocation],
+--       aesBarsBefore :: [EpToken "|"],
+--       aesBarsAfter  :: [EpToken "|"],
 --       aesClose      :: EpaLocation
 --       } deriving Data
 
@@ -1045,11 +1035,11 @@ laesOpen :: Lens AnnExplicitSum EpaLocation
 laesOpen k parent = fmap (\new -> parent { aesOpen = new })
                          (k (aesOpen parent))
 
-laesBarsBefore :: Lens AnnExplicitSum [EpaLocation]
+laesBarsBefore :: Lens AnnExplicitSum [EpToken "|"]
 laesBarsBefore k parent = fmap (\new -> parent { aesBarsBefore = new })
                                (k (aesBarsBefore parent))
 
-laesBarsAfter :: Lens AnnExplicitSum [EpaLocation]
+laesBarsAfter :: Lens AnnExplicitSum [EpToken "|"]
 laesBarsAfter k parent = fmap (\new -> parent { aesBarsAfter = new })
                                (k (aesBarsAfter parent))
 
@@ -1215,19 +1205,19 @@ lga_sep k parent = fmap (\new -> parent { ga_sep = new })
 -- ---------------------------------------------------------------------
 -- data EpAnnSumPat = EpAnnSumPat
 --       { sumPatParens      :: (EpaLocation, EpaLocation)
---       , sumPatVbarsBefore :: [EpaLocation]
---       , sumPatVbarsAfter  :: [EpaLocation]
+--       , sumPatVbarsBefore :: [EpToken "|"]
+--       , sumPatVbarsAfter  :: [EpToken "|"]
 --       } deriving Data
 
 lsumPatParens :: Lens EpAnnSumPat (EpaLocation, EpaLocation)
 lsumPatParens k parent = fmap (\new -> parent { sumPatParens = new })
                               (k (sumPatParens parent))
 
-lsumPatVbarsBefore :: Lens EpAnnSumPat [EpaLocation]
+lsumPatVbarsBefore :: Lens EpAnnSumPat [EpToken "|"]
 lsumPatVbarsBefore k parent = fmap (\new -> parent { sumPatVbarsBefore = new })
                               (k (sumPatVbarsBefore parent))
 
-lsumPatVbarsAfter :: Lens EpAnnSumPat [EpaLocation]
+lsumPatVbarsAfter :: Lens EpAnnSumPat [EpToken "|"]
 lsumPatVbarsAfter k parent = fmap (\new -> parent { sumPatVbarsAfter = new })
                               (k (sumPatVbarsAfter parent))
 
@@ -2985,9 +2975,9 @@ instance ExactPrint (HsExpr GhcPs) where
 
   exact (ExplicitSum an alt arity expr) = do
     an0 <- markLensFun an laesOpen (\loc -> printStringAtAA loc "(#")
-    an1 <- markLensFun an0 laesBarsBefore (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an1 <- markLensFun an0 laesBarsBefore (\locs -> mapM markEpToken locs)
     expr' <- markAnnotated expr
-    an2 <- markLensFun an1 laesBarsAfter (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an2 <- markLensFun an1 laesBarsAfter (\locs -> mapM markEpToken locs)
     an3 <- markLensFun an2 laesClose (\loc -> printStringAtAA loc "#)")
     return (ExplicitSum an3 alt arity expr')
 
@@ -4186,12 +4176,12 @@ instance ExactPrint (LocatedN RdrName) where
             _ -> error "ExactPrint (LocatedN RdrName)"
         NameAnnCommas a commas t -> do
           a0 <- markNameAdornmentO a
-          commas' <- forM commas (\loc -> printStringAtAAC NoCaptureComments loc ",")
+          commas' <- forM commas markEpToken
           a1 <- markNameAdornmentC a0
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
           o' <- markEpToken o
-          bars' <- forM bars (\loc -> printStringAtAAC NoCaptureComments loc "|")
+          bars' <- mapM markEpToken bars
           c' <- markEpToken c
           return (NameAnnBars (o',c') bars' t)
         NameAnnOnly a t -> do
@@ -4247,7 +4237,7 @@ printUnicode :: (Monad m, Monoid w) => EpaLocation -> RdrName -> EP w m EpaLocat
 printUnicode anc n = do
   let str = case (showPprUnsafe n) of
             -- TODO: unicode support?
-              "forall" -> if spanLength (anchor anc) == 1 then "∀" else "forall"
+              "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall"
               s -> s
   loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str
   case loc of
@@ -4617,15 +4607,15 @@ instance ExactPrint (IEWrappedName GhcPs) where
     n' <- markAnnotated n
     return (IEName x n')
   exact (IEDefault r n) = do
-    r' <- printStringAtAA r "default"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEDefault r' n')
   exact (IEPattern r n) = do
-    r' <- printStringAtAA r "pattern"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEPattern r' n')
   exact (IEType r n) = do
-    r' <- printStringAtAA r "type"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEType r' n')
 
@@ -4684,9 +4674,9 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (SumPat an pat alt arity) = do
     an0 <- markLensFun an (lsumPatParens . lfst) (\loc -> printStringAtAA loc "(#")
-    an1 <- markLensFun an0 lsumPatVbarsBefore (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an1 <- markLensFun an0 lsumPatVbarsBefore (\locs -> mapM markEpToken locs)
     pat' <- markAnnotated pat
-    an2 <- markLensFun an1 lsumPatVbarsAfter (\locs -> mapM (\l -> printStringAtAA l "|") locs)
+    an2 <- markLensFun an1 lsumPatVbarsAfter (\locs -> mapM markEpToken locs)
     an3 <- markLensFun an2 (lsumPatParens . lsnd)  (\loc -> printStringAtAA loc "#)")
     return (SumPat an3 pat' alt arity)
 
@@ -4715,7 +4705,7 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (NPlusKPat an n k lit2 a b) = do
     n' <- markAnnotated n
-    an' <- printStringAtAAL an lid "+"
+    an' <- markEpToken an
     k' <- markAnnotated k
     return (NPlusKPat an' n' k' lit2 a b)
 


=====================================
utils/check-exact/Parsers.hs
=====================================
@@ -289,7 +289,8 @@ fixModuleTrailingComments (GHC.L l p) = GHC.L l p'
             let
               pc = GHC.priorComments cs
               fc = GHC.getFollowingComments cs
-              bf (GHC.L anc _) = GHC.anchor anc > ss
+              bf (GHC.L anc _) = GHC.epaLocationRealSrcSpan anc > ss
+
               (prior,f) = break bf fc
               cs'' = GHC.EpaCommentsBalanced (pc <> prior) f
             in cs''
@@ -310,7 +311,7 @@ fixModuleHeaderComments (GHC.L l p) = GHC.L l p'
         -- Move any comments on the decl that occur prior to the location
         pc = GHC.priorComments csd
         fc = GHC.getFollowingComments csd
-        bf (GHC.L anch _) = GHC.anchor anch > r
+        bf (GHC.L anch _) = GHC.epaLocationRealSrcSpan anch > r
         (move,keep) = break bf pc
         csd' = GHC.EpaCommentsBalanced keep fc
 


=====================================
utils/check-exact/Transform.hs
=====================================
@@ -211,7 +211,7 @@ captureTypeSigSpacing (L l (SigD x (TypeSig (AnnSig (EpUniTok dca u) mp md) ns (
     -- we want DPs for the distance from the end of the ns to the
     -- AnnDColon, and to the start of the ty
     rd = case last ns of
-      L (EpAnn anc' _ _) _ -> anchor anc'
+      L (EpAnn anc' _ _) _ -> epaLocationRealSrcSpan anc'
     dca' = case dca of
           EpaSpan ss@(RealSrcSpan r _) -> (EpaDelta ss (ss2delta (ss2posEnd rd) r) [])
           _                            -> dca
@@ -298,7 +298,7 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp
                 col = deltaColumn delta
                 edp' = if line == 0 then SameLine col
                                     else DifferentLine line col
-                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ anchor $ getLoc lc), r))
+                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r))
 
 
 -- ---------------------------------------------------------------------
@@ -552,12 +552,12 @@ trailingCommentsDeltas _ [] = []
 trailingCommentsDeltas r (la@(L (EpaDelta _ dp _) _):las)
   = (getDeltaLine dp, la): trailingCommentsDeltas r las
 trailingCommentsDeltas r (la@(L l _):las)
-  = deltaComment r la : trailingCommentsDeltas (anchor l) las
+  = deltaComment r la : trailingCommentsDeltas (epaLocationRealSrcSpan l) las
   where
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2posEnd rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 priorCommentsDeltas :: RealSrcSpan -> [LEpaComment]
                     -> [(Int, LEpaComment)]
@@ -565,14 +565,14 @@ priorCommentsDeltas r cs = go r (sortEpaComments cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 
 -- ---------------------------------------------------------------------
@@ -664,14 +664,14 @@ addCommentOrigDeltasAnn (EpAnn e a cs) = EpAnn e a (addCommentOrigDeltas cs)
 -- TODO: this is replicating functionality in ExactPrint. Sort out the
 -- import loop`
 anchorFromLocatedA :: LocatedA a -> RealSrcSpan
-anchorFromLocatedA (L (EpAnn anc _ _) _) = anchor anc
+anchorFromLocatedA (L (EpAnn anc _ _) _) = epaLocationRealSrcSpan anc
 
 -- | Get the full span of interest for comments from a LocatedA.
 -- This extends up to the last TrailingAnn
 fullSpanFromLocatedA :: LocatedA a -> RealSrcSpan
 fullSpanFromLocatedA (L (EpAnn anc (AnnListItem tas)  _) _) = rr
   where
-    r = anchor anc
+    r = epaLocationRealSrcSpan anc
     trailing_loc ta = case ta_location ta of
         EpaSpan (RealSrcSpan s _) -> [s]
         _ -> []
@@ -695,7 +695,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb)))
           (csp,csf) = case anc1 of
             EpaComments cs -> ([],cs)
             EpaCommentsBalanced p f -> (p,f)
-          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (anchor anc) csf)
+          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (epaLocationRealSrcSpan anc) csf)
           move = map snd move'
           stay = map snd stay'
           cs1 = epaCommentsBalanced csp stay


=====================================
utils/check-exact/Types.hs
=====================================
@@ -8,8 +8,7 @@
 {-# LANGUAGE TypeSynonymInstances #-}
 {-# LANGUAGE ViewPatterns         #-}
 
-module Types
-  where
+module Types where
 
 import GHC hiding (EpaComment)
 import GHC.Utils.Outputable hiding ( (<>) )
@@ -41,7 +40,7 @@ instance Ord Comment where
   -- When we have CPP injected comments with a fake filename, or LINE
   -- pragma, the file name changes, so we need to compare the
   -- locations only, with out the filename.
-  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ anchor ss1) (ss2pos $ anchor ss2)
+  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan ss1) (ss2pos $ epaLocationRealSrcSpan ss2)
     where
       ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss)
 


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -268,7 +268,7 @@ workInComments ocs new = cs'
                                         (sortEpaComments $ fc ++ cs_after)
              where
                (cs_before,cs_after)
-                   = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) )
+                   = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) )
                            new
 
 insertTopLevelCppComments ::  HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment])
@@ -292,7 +292,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an1,cs0a) = case lo of
         EpExplicitBraces (EpTok (EpaSpan (RealSrcSpan s _))) _close ->
             let
-                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0
+                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0
                 cs' = workInComments (comments an0) stay
             in (an0 { comments = cs' }, cs0a')
         _ -> (an0,cs0)
@@ -300,7 +300,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an2, cs0b) = case am_decls $ anns an1 of
         (AddSemiAnn (EpTok (EpaSpan (RealSrcSpan s _))):_) -> (an1 {comments = cs'}, cs0b')
           where
-            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0a
+            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0a
             cs' = workInComments (comments an1) stay
         _ -> (an1,cs0a)
 
@@ -314,7 +314,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
                            (csh', cs0b') = case annListBracketsLocs $ al_brackets $ anns l of
                                (EpaSpan (RealSrcSpan s _),_) ->(h, n)
                                  where
-                                   (h,n) = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+                                   (h,n) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        cs0b
 
                                _ -> ([], cs0b)
@@ -361,7 +361,7 @@ splitOnWhere w (EpTok (EpaSpan (RealSrcSpan s _))) csIn = (hc, fc)
   where
     splitFunc Before anc_pos c_pos = c_pos < anc_pos
     splitFunc After  anc_pos c_pos = anc_pos < c_pos
-    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ anchor ll) (ss2pos s)) csIn
+    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ epaLocationRealSrcSpan ll) (ss2pos s)) csIn
 splitOnWhere _ _ csIn = (csIn,[])
 
 balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment])
@@ -372,7 +372,7 @@ balanceFirstLocatedAComments ((L (EpAnn anc an csd) a):ds) = (L (EpAnn anc an cs
         EpaSpan (RealSrcSpan s _) -> (csd', hc)
                `debug` ("balanceFirstLocatedAComments: (csd,csd',attached,header)=" ++ showAst (csd,csd',attached,header))
           where
-            (priors, inners) =  break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+            (priors, inners) =  break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        (priorComments csd)
             pcds = priorCommentsDeltas' s priors
             (attached, header) = break (\(d,_c) -> d /= 1) pcds
@@ -388,14 +388,14 @@ priorCommentsDeltas' r cs = go r (reverse cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 allocatePriorComments
   :: Pos
@@ -403,7 +403,7 @@ allocatePriorComments
   -> ([LEpaComment], [LEpaComment])
 allocatePriorComments ss_loc comment_q =
   let
-    cmp (L l _) = ss2pos (anchor l) <= ss_loc
+    cmp (L l _) = ss2pos (epaLocationRealSrcSpan l) <= ss_loc
     (newAnns,after) = partition cmp comment_q
   in
     (after, newAnns)
@@ -420,7 +420,7 @@ insertRemainingCppComments (L l p) cs = L l p'
             EpTok (EpaSpan (RealSrcSpan s _)) -> ss2pos s
             _ -> (1,1)
         _ -> (1,1)
-    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ anchor ll) > end_loc ) cs
+    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > end_loc ) cs
 
     addTrailingComments end_loc' cur new = epaCommentsBalanced pc' fc'
       where
@@ -431,8 +431,8 @@ insertRemainingCppComments (L l p) cs = L l p'
             (L ac _:_) -> (sortEpaComments $ pc ++ cs_before, sortEpaComments $ fc ++ cs_after)
               where
                (cs_before,cs_after)
-                   = if (ss2pos $ anchor ac) > end_loc'
-                       then break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) ) new
+                   = if (ss2pos $ epaLocationRealSrcSpan ac) > end_loc'
+                       then break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) ) new
                        else (new_before, new_after)
 
 -- ---------------------------------------------------------------------
@@ -513,7 +513,7 @@ normaliseCommentText (x:xs) = x:normaliseCommentText xs
 
 -- |Must compare without span filenames, for CPP injected comments with fake filename
 cmpComments :: Comment -> Comment -> Ordering
-cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- |Sort, comparing without span filenames, for CPP injected comments with fake filename
 sortComments :: [Comment] -> [Comment]
@@ -523,7 +523,7 @@ sortComments cs = sortBy cmpComments cs
 sortEpaComments :: [LEpaComment] -> [LEpaComment]
 sortEpaComments cs = sortBy cmp cs
   where
-    cmp (L l1 _) (L l2 _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- | Makes a comment which originates from a specific keyword.
 mkKWComment :: String -> NoCommentsLocation -> Comment
@@ -532,7 +532,7 @@ mkKWComment kw (EpaSpan (UnhelpfulSpan _))   = Comment kw (EpaDelta noSrcSpan (S
 mkKWComment kw (EpaDelta ss dp cs)           = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw)
 
 sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a]
-sortAnchorLocated = sortBy (compare `on` (anchor . getLoc))
+sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc))
 
 -- | Calculates the distance from the start of a string to the end of
 -- a string.


=====================================
utils/check-ppr/Main.hs
=====================================
@@ -97,7 +97,7 @@ getPragmas (L _ (HsModule { hsmodExt = XModulePs { hsmodAnn = anns' } })) = prag
     tokComment (L _ (EpaComment (EpaLineComment  s) _)) = s
     tokComment _ = ""
 
-    cmp (L l1 _) (L l2 _) = compare (anchor l1) (anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (epaLocationRealSrcSpan l1) (epaLocationRealSrcSpan l2)
     comments' = map tokComment $ sortBy cmp $ priorComments $ epAnnComments anns'
     pragmas = filter (\c -> isPrefixOf "{-#" c ) comments'
     pragmaStr = intercalate "\n" pragmas


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
=====================================
@@ -41,7 +41,7 @@ import qualified Data.Map.Strict as Map
 import Data.Maybe
 import Data.Ord (comparing)
 import qualified Data.Set as Set hiding (Set)
-import GHC hiding (LexicalFixity (..), NoLink, anchor, moduleInfo)
+import GHC hiding (LexicalFixity (..), NoLink, moduleInfo)
 import GHC.Types.Name
 import GHC.Unit.State
 import System.Directory


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
=====================================
@@ -24,7 +24,7 @@ module Haddock.Backends.Xhtml.DocMarkup
 
 import Data.List (intersperse)
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name
 import Text.XHtml hiding (name, p, quote)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
=====================================
@@ -54,7 +54,7 @@ module Haddock.Backends.Xhtml.Layout
 
 import qualified Data.Map as Map
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name (nameOccName)
 import Text.XHtml hiding (name, quote, title)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
=====================================
@@ -31,7 +31,7 @@ module Haddock.Backends.Xhtml.Names
   ) where
 
 import Data.List (stripPrefix)
-import GHC hiding (LexicalFixity (..), anchor)
+import GHC hiding (LexicalFixity (..))
 import GHC.Data.FastString (unpackFS)
 import GHC.Types.Name
 import GHC.Types.Name.Reader



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c157d202c9814455c67a7b1407575e66daeb8989...b6a270c21e877c552ebcd8b77f7f2f630884fafe

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c157d202c9814455c67a7b1407575e66daeb8989...b6a270c21e877c552ebcd8b77f7f2f630884fafe
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Wed Oct 30 23:47:05 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Wed, 30 Oct 2024 19:47:05 -0400
Subject: [Git][ghc/ghc][wip/T20264] Aggressively create type-lets
Message-ID: <6722c5797dfad_1abb227a1f2085458@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
b43a2e3c by Simon Peyton Jones at 2024-10-30T23:46:18+00:00
Aggressively create type-lets

- - - - -


2 changed files:

- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -1804,7 +1804,9 @@ simpl_lam :: HasDebugCallStack
 -- Type beta-reduction
 simpl_lam env bndr body (ApplyToTy { sc_arg_ty = arg_ty, sc_cont = cont })
   = do { tick (BetaReduction bndr)
-       ; simplLam (extendTvSubst env bndr arg_ty) body cont }
+       ; (floats1, env1)  <- completeTyVarBindX env bndr arg_ty
+       ; (floats2, expr') <- simplLam env1 body cont
+       ; return (floats1 `addFloats` floats2, expr') } 
 
 -- Coercion beta-reduction
 simpl_lam env bndr body (ApplyToVal { sc_arg = Coercion arg_co, sc_env = arg_se
@@ -1905,10 +1907,9 @@ simplNonRecE :: HasDebugCallStack
 simplNonRecE env from_what bndr (rhs, rhs_se) body cont
   | Type ty <- rhs
   = assert (isTyVar bndr) $
-    do { (env1, bndr1) <- simplNonRecBndr env bndr
-       ; ty'           <- simplType env ty
-       ; let (floats1, env2) = mkTyVarFloatBind env1 bndr bndr1 ty'
-       ; (floats2, expr') <- simplNonRecBody env2 from_what body cont
+    do { ty'              <- simplType (rhs_se `setInScopeFromE` env) ty
+       ; (floats1, env1)  <- completeTyVarBindX env bndr ty'
+       ; (floats2, expr') <- simplNonRecBody env1 from_what body cont
        ; return (floats1 `addFloats` floats2, expr') }
 
   | assert (isId bndr && not (isJoinId bndr) ) $
@@ -1936,6 +1937,13 @@ simplNonRecE env from_what bndr (rhs, rhs_se) body cont
        -- (FromBeta Lifted) or FromLet: look at the demand info
        _ -> seCaseCase env && isStrUsedDmd (idDemandInfo bndr)
 
+completeTyVarBindX :: SimplEnv -> InTyVar -> OutType -> SimplM (SimplFloats, SimplEnv)
+completeTyVarBindX env tv rhs_ty
+  | postInlineTypeUnconditionally rhs_ty
+  = return (emptyFloats env, extendTvSubst env tv rhs_ty)
+  | otherwise
+  = do { (env1, tv1) <- simplNonRecBndr env tv
+       ; return (mkTyVarFloatBind env1 tv tv1 rhs_ty) }
 
 ------------------
 simplRecE :: SimplEnv


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -13,6 +13,7 @@ module GHC.Core.Opt.Simplify.Utils (
 
         -- Inlining,
         preInlineUnconditionally, postInlineUnconditionally,
+        postInlineTypeUnconditionally,
         activeRule,
         getUnfoldingInRuleMatch,
         updModeForStableUnfoldings, updModeForRules,
@@ -1455,7 +1456,8 @@ the former.
 -}
 
 preInlineUnconditionally
-    :: SimplEnv -> TopLevelFlag -> InId
+    :: SimplEnv -> TopLevelFlag
+    -> InVar                -- Works for TyVar, CoVar, and Id
     -> InExpr -> StaticEnv  -- These two go together
     -> Maybe SimplEnv       -- Returned env has extended substitution
 -- Precondition: rhs satisfies the let-can-float invariant
@@ -1601,6 +1603,9 @@ may seem surprising; for instance, the LHS of rules. See Note [Simplifying
 rules] for details.
 -}
 
+postInlineTypeUnconditionally :: Type -> Bool
+postInlineTypeUnconditionally _ = False
+
 postInlineUnconditionally
     :: SimplEnv -> BindContext
     -> InId -> OutId    -- The binder (*not* a CoVar), including its unfolding



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 07:47:50 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 31 Oct 2024 03:47:50 -0400
Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits:
 rts/Disassembler: Fix encoding of BRK_FUN instruction
Message-ID: <672336263ef02_c15f491f4b054669@gitlab.mail>



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
f88d3235 by Ben Gamari at 2024-10-31T03:47:26-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -
e8c71487 by Alan Zimmerman at 2024-10-31T03:47:27-04:00
EPA: Bring in last EpToken usages

For import declarations, NameAnnCommas and NPlusKPat.

And remove anchor, it is the same as epaLocationRealSrcSpan.

- - - - -
de769a1f by sheaf at 2024-10-31T03:47:30-04:00
Assert that ctEvCoercion is called on an equality

Calling 'ctEvCoercion' on non-equality constraints is always incorrect.
We add an assertion to this function to detect such cases; for example
a type-checking plugin might erroneously do this.

- - - - -


25 changed files:

- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Types/Constraint.hs
- rts/Disassembler.c
- + testsuite/tests/codeGen/should_run/T25374/T25374.hs
- + testsuite/tests/codeGen/should_run/T25374/T25374.script
- + testsuite/tests/codeGen/should_run/T25374/T25374A.hs
- + testsuite/tests/codeGen/should_run/T25374/all.T
- testsuite/tests/simplCore/should_compile/T23864.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Types.hs
- utils/check-exact/Utils.hs
- utils/check-ppr/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs


Changes:

=====================================
compiler/GHC/Hs/ImpExp.hs
=====================================
@@ -194,9 +194,9 @@ instance (OutputableBndrId p
 -}
 
 type instance XIEName    (GhcPass _) = NoExtField
-type instance XIEDefault (GhcPass _) = EpaLocation
-type instance XIEPattern (GhcPass _) = EpaLocation
-type instance XIEType    (GhcPass _) = EpaLocation
+type instance XIEDefault (GhcPass _) = EpToken "default"
+type instance XIEPattern (GhcPass _) = EpToken "pattern"
+type instance XIEType    (GhcPass _) = EpToken "type"
 type instance XXIEWrappedName (GhcPass _) = DataConCantHappen
 
 type instance Anno (IEWrappedName (GhcPass _)) = SrcSpanAnnA


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -158,7 +158,7 @@ type instance XNPat GhcPs = EpToken "-"
 type instance XNPat GhcRn = EpToken "-"
 type instance XNPat GhcTc = Type
 
-type instance XNPlusKPat GhcPs = EpaLocation -- Of the "+"
+type instance XNPlusKPat GhcPs = EpToken "+"
 type instance XNPlusKPat GhcRn = NoExtField
 type instance XNPlusKPat GhcTc = Type
 


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -340,7 +340,7 @@ mkHsCompAnns   :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs
 
 mkNPat      :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpToken "-"
             -> Pat GhcPs
-mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpaLocation
+mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpToken "+"
             -> Pat GhcPs
 
 -- NB: The following functions all use noSyntaxExpr: the generated expressions


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1040,9 +1040,9 @@ export  :: { LIE GhcPs }
                                                           ; locImpExp <- return (sL span (IEModuleContents ($1, (epTok $2)) $3))
                                                           ; return $ reLoc $ locImpExp } }
         | maybe_warning_pragma 'pattern' qcon            { let span = (maybe comb2 comb3 $1) $2 $>
-                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (glR $2) $3)) Nothing }
+                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (epTok $2) $3)) Nothing }
         | maybe_warning_pragma 'default' qtycon          {% do { let { span = (maybe comb2 comb3 $1) $2 $> }
-                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (glR $2) $3)) Nothing))
+                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (epTok $2) $3)) Nothing))
                                                           ; return $ reLoc $ locImpExp } }
 
 
@@ -1076,7 +1076,7 @@ qcname_ext_w_wildcard :: { LocatedA ImpExpQcSpec }
 qcname_ext :: { LocatedA ImpExpQcSpec }
         :  qcname                   { sL1a $1 (ImpExpQcName $1) }
         |  'type' oqtycon           {% do { n <- mkTypeImpExp $2
-                                          ; return $ sLLa $1 $> (ImpExpQcType (glR $1) n) }}
+                                          ; return $ sLLa $1 $> (ImpExpQcType (epTok $1) n) }}
 
 qcname  :: { LocatedN RdrName }  -- Variable or type constructor
         :  qvar                 { $1 } -- Things which look like functions
@@ -1209,7 +1209,7 @@ importlist1 :: { OrdList (LIE GhcPs) }
 import  :: { OrdList (LIE GhcPs) }
         : qcname_ext export_subspec {% fmap (unitOL . reLoc . (sLL $1 $>)) $ mkModuleImpExp Nothing (fst $ unLoc $2) $1 (snd $ unLoc $2) }
         | 'module' modid            {% fmap (unitOL . reLoc) $ return (sLL $1 $> (IEModuleContents (Nothing, (epTok $1)) $2)) }
-        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (glR $1) $2)) Nothing }
+        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (epTok $1) $2)) Nothing }
 
 -----------------------------------------------------------------------------
 -- Fixity Declarations
@@ -3776,10 +3776,10 @@ qcon_list : qcon                  { [$1] }
 -- See Note [ExplicitTuple] in GHC.Hs.Expr
 sysdcon_nolist :: { LocatedN DataCon }  -- Wired in data constructors
         : '(' commas ')'        {% amsr (sLL $1 $> $ tupleDataCon Boxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
         | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '(#' commas '#)'      {% amsr (sLL $1 $> $ tupleDataCon Unboxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
 
 syscon :: { LocatedN RdrName }
         : sysdcon               {  L (getLoc $1) $ nameRdrName (dataConName (unLoc $1)) }
@@ -3820,9 +3820,9 @@ gtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, including unit t
 ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit tuples
         : oqtycon               { $1 }
         | '(' commas ')'        {% do { n <- mkTupleSyntaxTycon Boxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' commas '#)'      {% do { n <- mkTupleSyntaxTycon Unboxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
                                        (NameAnnBars (epTok $1, epTok $3) (fst $2) []) } }


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -23,7 +23,6 @@ module GHC.Parser.Annotation (
   DeltaPos(..), deltaPos, getDeltaLine,
 
   EpAnn(..),
-  anchor,
   spanAsAnchor, realSpanAsAnchor,
   noSpanAnchor,
   NoAnn(..),
@@ -350,7 +349,7 @@ instance Outputable a => Outputable (GenLocated TokenLocation a) where
 -- | Used in the parser only, extract the 'RealSrcSpan' from an
 -- 'EpaLocation'. The parser will never insert a 'DeltaPos', so the
 -- partial function is safe.
-epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
+epaLocationRealSrcSpan :: EpaLocation' a -> RealSrcSpan
 epaLocationRealSrcSpan (EpaSpan (RealSrcSpan r _)) = r
 epaLocationRealSrcSpan _ = panic "epaLocationRealSrcSpan"
 
@@ -401,9 +400,6 @@ data EpAnn ann
         deriving (Data, Eq, Functor)
 -- See Note [XRec and Anno in the AST]
 
-anchor :: (EpaLocation' a) -> RealSrcSpan
-anchor (EpaSpan (RealSrcSpan r _)) = r
-anchor _ = panic "anchor"
 
 spanAsAnchor :: SrcSpan -> (EpaLocation' a)
 spanAsAnchor ss  = EpaSpan ss
@@ -602,7 +598,7 @@ data NameAnn
   -- | Used for @(,,,)@, or @(#,,,#)@
   | NameAnnCommas {
       nann_adornment :: NameAdornment,
-      nann_commas    :: [EpaLocation],
+      nann_commas    :: [EpToken ","],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(# | | #)@
@@ -641,10 +637,10 @@ data NameAnn
 -- such as parens or backquotes. This data type identifies what
 -- particular pair are being used.
 data NameAdornment
-  = NameParens     (EpToken "(")  (EpToken ")") -- ^ '(' ')'
-  | NameParensHash (EpToken "(#") (EpToken "#)")-- ^ '(#' '#)'
-  | NameBackquotes (EpToken "`")  (EpToken "`")-- ^ '`'
-  | NameSquare     (EpToken "[")  (EpToken "]")-- ^ '[' ']'
+  = NameParens     (EpToken "(")  (EpToken ")")
+  | NameParensHash (EpToken "(#") (EpToken "#)")
+  | NameBackquotes (EpToken "`")  (EpToken "`")
+  | NameSquare     (EpToken "[")  (EpToken "]")
   | NameNoAdornment
   deriving (Eq, Data)
 


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -3672,8 +3672,8 @@ allocateComments
   -> ([LEpaComment], [LEpaComment])
 allocateComments ss comment_q =
   let
-    (before,rest)  = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
-    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
+    (before,rest)  = break (\(L l _) -> isRealSubspanOf (epaLocationRealSrcSpan l) ss) comment_q
+    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (epaLocationRealSrcSpan l) ss)) rest
     comment_q' = before ++ after
     newAnns = middle
   in
@@ -3691,14 +3691,14 @@ splitPriorComments ss prior_comments =
     -- And the token preceding the comment is on a different line
     cmp :: RealSrcSpan -> LEpaComment -> Bool
     cmp later (L l c)
-         = srcSpanStartLine later - srcSpanEndLine (anchor l) == 1
-          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (anchor l)
+         = srcSpanStartLine later - srcSpanEndLine (epaLocationRealSrcSpan l) == 1
+          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (epaLocationRealSrcSpan l)
 
     go :: [LEpaComment] -> RealSrcSpan -> [LEpaComment]
        -> ([LEpaComment], [LEpaComment])
     go decl_comments _ [] = ([],decl_comments)
     go decl_comments r (c@(L l _):cs) = if cmp r c
-                              then go (c:decl_comments) (anchor l) cs
+                              then go (c:decl_comments) (epaLocationRealSrcSpan l) cs
                               else (reverse (c:cs), decl_comments)
   in
     go [] ss prior_comments
@@ -3710,7 +3710,7 @@ allocatePriorComments
   -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
 allocatePriorComments ss comment_q mheader_comments =
   let
-    cmp (L l _) = anchor l <= ss
+    cmp (L l _) = epaLocationRealSrcSpan l <= ss
     (newAnns,after) = partition cmp comment_q
     comment_q'= after
     (prior_comments, decl_comments) = splitPriorComments ss newAnns


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1312,7 +1312,7 @@ checkAPat loc e0 = do
            _
                      | nPlusKPatterns && (plus == plus_RDR)
                      -> return (mkNPlusKPat (L nloc n) (L (l2l lloc) lit)
-                                (entry l))
+                                (EpTok $ entry l))
 
    -- Improve error messages for the @-operator when the user meant an @-pattern
    PatBuilderOpApp _ op _ _ | opIsAt (unLoc op) -> do
@@ -3158,7 +3158,7 @@ data ImpExpSubSpec = ImpExpAbs
                    | ImpExpAllWith [LocatedA ImpExpQcSpec]
 
 data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName)
-                  | ImpExpQcType EpaLocation (LocatedN RdrName)
+                  | ImpExpQcType (EpToken "type") (LocatedN RdrName)
                   | ImpExpQcWildcard (EpToken "..") (EpToken ",")
 
 mkModuleImpExp :: Maybe (LWarningTxt GhcPs) -> (EpToken "(", EpToken ")") -> LocatedA ImpExpQcSpec


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -2107,13 +2107,13 @@ printMinimalImports hsc_src imports_w_usage
 
 to_ie_post_rn_var :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn_var (L l n)
-  | isDataOcc $ occName n = L l (IEPattern (entry l)   (L (l2l l) n))
+  | isDataOcc $ occName n = L l (IEPattern noAnn      (L (l2l l) n))
   | otherwise             = L l (IEName    noExtField (L (l2l l) n))
 
 
 to_ie_post_rn :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn (L l n)
-  | isTcOcc occ && isSymOcc occ = L l (IEType (entry l)   (L (l2l l) n))
+  | isTcOcc occ && isSymOcc occ = L l (IEType noAnn      (L (l2l l) n))
   | otherwise                   = L l (IEName noExtField (L (l2l l) n))
   where occ = occName n
 


=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -2306,8 +2306,10 @@ ctEvExpr ev@(CtWanted { ctev_dest = HoleDest _ })
 ctEvExpr ev = evId (ctEvEvId ev)
 
 ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion
-ctEvCoercion (CtGiven { ctev_evar = ev_id })
-  = mkCoVarCo ev_id
+ctEvCoercion _given@(CtGiven { ctev_evar = ev_id })
+  = assertPpr (isCoVar ev_id)
+    (text "ctEvCoercion used on non-equality Given constraint:" <+> ppr _given)
+  $ mkCoVarCo ev_id
 ctEvCoercion (CtWanted { ctev_dest = dest })
   | HoleDest hole <- dest
   = -- ctEvCoercion is only called on type equalities


=====================================
rts/Disassembler.c
=====================================
@@ -67,12 +67,12 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }
          debugBelch("\n");
-         pc += 4;
+         pc += 6;
          break;
       case bci_SWIZZLE: {
          W_     stkoff = BCO_GET_LARGE_ARG;


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.hs
=====================================
@@ -0,0 +1,8 @@
+import T25374A
+
+fieldsSam :: NP xs -> NP xs -> Bool
+fieldsSam UNil UNil = True
+
+x :: Bool
+x = fieldsSam UNil UNil
+


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.script
=====================================
@@ -0,0 +1,2 @@
+:load T25374
+x


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374A.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+module T25374A where
+
+import GHC.Exts
+
+type NP :: [UnliftedType] -> UnliftedType
+data NP xs where
+  UNil :: NP '[]
+  (::*) :: x -> NP xs -> NP (x ': xs)
+


=====================================
testsuite/tests/codeGen/should_run/T25374/all.T
=====================================
@@ -0,0 +1,3 @@
+# This shouldn't crash the disassembler
+test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, unless(debug_rts(), skip)], ghci_script, [''])
+


=====================================
testsuite/tests/simplCore/should_compile/T23864.hs
=====================================
@@ -49,7 +49,7 @@ insertCommentsByPos ::
   -> (EpAnnComments -> [LEpaComment] -> EpAnnComments)
   -> EpAnn a
   -> WithComments (EpAnn a)
-insertCommentsByPos cond = insertComments (cond . anchor . getLoc)
+insertCommentsByPos cond = insertComments (cond . epaLocationRealSrcSpan . getLoc)
 
 insertComments ::
      (LEpaComment -> Bool)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -570,7 +570,7 @@ splitAfterTrailingAnns tas cs = (before, after)
         (s:_) -> (b,a)
           where
             s_pos = ss2pos s
-            (b,a) = break (\(L ll _) -> (ss2pos $ anchor ll) > s_pos)
+            (b,a) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > s_pos)
                           cs
 
 -- ---------------------------------------------------------------------
@@ -731,12 +731,6 @@ printStringAtNC el str = do
   el' <- printStringAtAAC NoCaptureComments (noCommentsToEpaLocation el) str
   return (epaToNoCommentsLocation el')
 
-printStringAtAAL :: (Monad m, Monoid w)
-  => a -> Lens a EpaLocation -> String -> EP w m a
-printStringAtAAL an l str = do
-  r <- printStringAtAAC CaptureComments (view l an) str
-  return (set l r an)
-
 printStringAtAAC :: (Monad m, Monoid w)
   => CaptureComments -> EpaLocation -> String -> EP w m EpaLocation
 printStringAtAAC capture (EpaSpan (RealSrcSpan r _)) s = printStringAtRsC capture r s
@@ -1020,10 +1014,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lid :: Lens a a
-lid k parent = fmap (\new -> new)
-                    (k parent)
-
 lfst :: Lens (a,b) a
 lfst k parent = fmap (\new -> (new, snd parent))
                      (k (fst parent))
@@ -4186,7 +4176,7 @@ instance ExactPrint (LocatedN RdrName) where
             _ -> error "ExactPrint (LocatedN RdrName)"
         NameAnnCommas a commas t -> do
           a0 <- markNameAdornmentO a
-          commas' <- forM commas (\loc -> printStringAtAAC NoCaptureComments loc ",")
+          commas' <- forM commas markEpToken
           a1 <- markNameAdornmentC a0
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
@@ -4247,7 +4237,7 @@ printUnicode :: (Monad m, Monoid w) => EpaLocation -> RdrName -> EP w m EpaLocat
 printUnicode anc n = do
   let str = case (showPprUnsafe n) of
             -- TODO: unicode support?
-              "forall" -> if spanLength (anchor anc) == 1 then "∀" else "forall"
+              "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall"
               s -> s
   loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str
   case loc of
@@ -4617,15 +4607,15 @@ instance ExactPrint (IEWrappedName GhcPs) where
     n' <- markAnnotated n
     return (IEName x n')
   exact (IEDefault r n) = do
-    r' <- printStringAtAA r "default"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEDefault r' n')
   exact (IEPattern r n) = do
-    r' <- printStringAtAA r "pattern"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEPattern r' n')
   exact (IEType r n) = do
-    r' <- printStringAtAA r "type"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEType r' n')
 
@@ -4715,7 +4705,7 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (NPlusKPat an n k lit2 a b) = do
     n' <- markAnnotated n
-    an' <- printStringAtAAL an lid "+"
+    an' <- markEpToken an
     k' <- markAnnotated k
     return (NPlusKPat an' n' k' lit2 a b)
 


=====================================
utils/check-exact/Parsers.hs
=====================================
@@ -289,7 +289,8 @@ fixModuleTrailingComments (GHC.L l p) = GHC.L l p'
             let
               pc = GHC.priorComments cs
               fc = GHC.getFollowingComments cs
-              bf (GHC.L anc _) = GHC.anchor anc > ss
+              bf (GHC.L anc _) = GHC.epaLocationRealSrcSpan anc > ss
+
               (prior,f) = break bf fc
               cs'' = GHC.EpaCommentsBalanced (pc <> prior) f
             in cs''
@@ -310,7 +311,7 @@ fixModuleHeaderComments (GHC.L l p) = GHC.L l p'
         -- Move any comments on the decl that occur prior to the location
         pc = GHC.priorComments csd
         fc = GHC.getFollowingComments csd
-        bf (GHC.L anch _) = GHC.anchor anch > r
+        bf (GHC.L anch _) = GHC.epaLocationRealSrcSpan anch > r
         (move,keep) = break bf pc
         csd' = GHC.EpaCommentsBalanced keep fc
 


=====================================
utils/check-exact/Transform.hs
=====================================
@@ -211,7 +211,7 @@ captureTypeSigSpacing (L l (SigD x (TypeSig (AnnSig (EpUniTok dca u) mp md) ns (
     -- we want DPs for the distance from the end of the ns to the
     -- AnnDColon, and to the start of the ty
     rd = case last ns of
-      L (EpAnn anc' _ _) _ -> anchor anc'
+      L (EpAnn anc' _ _) _ -> epaLocationRealSrcSpan anc'
     dca' = case dca of
           EpaSpan ss@(RealSrcSpan r _) -> (EpaDelta ss (ss2delta (ss2posEnd rd) r) [])
           _                            -> dca
@@ -298,7 +298,7 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp
                 col = deltaColumn delta
                 edp' = if line == 0 then SameLine col
                                     else DifferentLine line col
-                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ anchor $ getLoc lc), r))
+                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r))
 
 
 -- ---------------------------------------------------------------------
@@ -552,12 +552,12 @@ trailingCommentsDeltas _ [] = []
 trailingCommentsDeltas r (la@(L (EpaDelta _ dp _) _):las)
   = (getDeltaLine dp, la): trailingCommentsDeltas r las
 trailingCommentsDeltas r (la@(L l _):las)
-  = deltaComment r la : trailingCommentsDeltas (anchor l) las
+  = deltaComment r la : trailingCommentsDeltas (epaLocationRealSrcSpan l) las
   where
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2posEnd rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 priorCommentsDeltas :: RealSrcSpan -> [LEpaComment]
                     -> [(Int, LEpaComment)]
@@ -565,14 +565,14 @@ priorCommentsDeltas r cs = go r (sortEpaComments cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 
 -- ---------------------------------------------------------------------
@@ -664,14 +664,14 @@ addCommentOrigDeltasAnn (EpAnn e a cs) = EpAnn e a (addCommentOrigDeltas cs)
 -- TODO: this is replicating functionality in ExactPrint. Sort out the
 -- import loop`
 anchorFromLocatedA :: LocatedA a -> RealSrcSpan
-anchorFromLocatedA (L (EpAnn anc _ _) _) = anchor anc
+anchorFromLocatedA (L (EpAnn anc _ _) _) = epaLocationRealSrcSpan anc
 
 -- | Get the full span of interest for comments from a LocatedA.
 -- This extends up to the last TrailingAnn
 fullSpanFromLocatedA :: LocatedA a -> RealSrcSpan
 fullSpanFromLocatedA (L (EpAnn anc (AnnListItem tas)  _) _) = rr
   where
-    r = anchor anc
+    r = epaLocationRealSrcSpan anc
     trailing_loc ta = case ta_location ta of
         EpaSpan (RealSrcSpan s _) -> [s]
         _ -> []
@@ -695,7 +695,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb)))
           (csp,csf) = case anc1 of
             EpaComments cs -> ([],cs)
             EpaCommentsBalanced p f -> (p,f)
-          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (anchor anc) csf)
+          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (epaLocationRealSrcSpan anc) csf)
           move = map snd move'
           stay = map snd stay'
           cs1 = epaCommentsBalanced csp stay


=====================================
utils/check-exact/Types.hs
=====================================
@@ -8,8 +8,7 @@
 {-# LANGUAGE TypeSynonymInstances #-}
 {-# LANGUAGE ViewPatterns         #-}
 
-module Types
-  where
+module Types where
 
 import GHC hiding (EpaComment)
 import GHC.Utils.Outputable hiding ( (<>) )
@@ -41,7 +40,7 @@ instance Ord Comment where
   -- When we have CPP injected comments with a fake filename, or LINE
   -- pragma, the file name changes, so we need to compare the
   -- locations only, with out the filename.
-  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ anchor ss1) (ss2pos $ anchor ss2)
+  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan ss1) (ss2pos $ epaLocationRealSrcSpan ss2)
     where
       ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss)
 


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -268,7 +268,7 @@ workInComments ocs new = cs'
                                         (sortEpaComments $ fc ++ cs_after)
              where
                (cs_before,cs_after)
-                   = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) )
+                   = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) )
                            new
 
 insertTopLevelCppComments ::  HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment])
@@ -292,7 +292,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an1,cs0a) = case lo of
         EpExplicitBraces (EpTok (EpaSpan (RealSrcSpan s _))) _close ->
             let
-                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0
+                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0
                 cs' = workInComments (comments an0) stay
             in (an0 { comments = cs' }, cs0a')
         _ -> (an0,cs0)
@@ -300,7 +300,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an2, cs0b) = case am_decls $ anns an1 of
         (AddSemiAnn (EpTok (EpaSpan (RealSrcSpan s _))):_) -> (an1 {comments = cs'}, cs0b')
           where
-            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0a
+            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0a
             cs' = workInComments (comments an1) stay
         _ -> (an1,cs0a)
 
@@ -314,7 +314,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
                            (csh', cs0b') = case annListBracketsLocs $ al_brackets $ anns l of
                                (EpaSpan (RealSrcSpan s _),_) ->(h, n)
                                  where
-                                   (h,n) = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+                                   (h,n) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        cs0b
 
                                _ -> ([], cs0b)
@@ -361,7 +361,7 @@ splitOnWhere w (EpTok (EpaSpan (RealSrcSpan s _))) csIn = (hc, fc)
   where
     splitFunc Before anc_pos c_pos = c_pos < anc_pos
     splitFunc After  anc_pos c_pos = anc_pos < c_pos
-    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ anchor ll) (ss2pos s)) csIn
+    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ epaLocationRealSrcSpan ll) (ss2pos s)) csIn
 splitOnWhere _ _ csIn = (csIn,[])
 
 balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment])
@@ -372,7 +372,7 @@ balanceFirstLocatedAComments ((L (EpAnn anc an csd) a):ds) = (L (EpAnn anc an cs
         EpaSpan (RealSrcSpan s _) -> (csd', hc)
                `debug` ("balanceFirstLocatedAComments: (csd,csd',attached,header)=" ++ showAst (csd,csd',attached,header))
           where
-            (priors, inners) =  break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+            (priors, inners) =  break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        (priorComments csd)
             pcds = priorCommentsDeltas' s priors
             (attached, header) = break (\(d,_c) -> d /= 1) pcds
@@ -388,14 +388,14 @@ priorCommentsDeltas' r cs = go r (reverse cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 allocatePriorComments
   :: Pos
@@ -403,7 +403,7 @@ allocatePriorComments
   -> ([LEpaComment], [LEpaComment])
 allocatePriorComments ss_loc comment_q =
   let
-    cmp (L l _) = ss2pos (anchor l) <= ss_loc
+    cmp (L l _) = ss2pos (epaLocationRealSrcSpan l) <= ss_loc
     (newAnns,after) = partition cmp comment_q
   in
     (after, newAnns)
@@ -420,7 +420,7 @@ insertRemainingCppComments (L l p) cs = L l p'
             EpTok (EpaSpan (RealSrcSpan s _)) -> ss2pos s
             _ -> (1,1)
         _ -> (1,1)
-    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ anchor ll) > end_loc ) cs
+    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > end_loc ) cs
 
     addTrailingComments end_loc' cur new = epaCommentsBalanced pc' fc'
       where
@@ -431,8 +431,8 @@ insertRemainingCppComments (L l p) cs = L l p'
             (L ac _:_) -> (sortEpaComments $ pc ++ cs_before, sortEpaComments $ fc ++ cs_after)
               where
                (cs_before,cs_after)
-                   = if (ss2pos $ anchor ac) > end_loc'
-                       then break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) ) new
+                   = if (ss2pos $ epaLocationRealSrcSpan ac) > end_loc'
+                       then break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) ) new
                        else (new_before, new_after)
 
 -- ---------------------------------------------------------------------
@@ -513,7 +513,7 @@ normaliseCommentText (x:xs) = x:normaliseCommentText xs
 
 -- |Must compare without span filenames, for CPP injected comments with fake filename
 cmpComments :: Comment -> Comment -> Ordering
-cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- |Sort, comparing without span filenames, for CPP injected comments with fake filename
 sortComments :: [Comment] -> [Comment]
@@ -523,7 +523,7 @@ sortComments cs = sortBy cmpComments cs
 sortEpaComments :: [LEpaComment] -> [LEpaComment]
 sortEpaComments cs = sortBy cmp cs
   where
-    cmp (L l1 _) (L l2 _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- | Makes a comment which originates from a specific keyword.
 mkKWComment :: String -> NoCommentsLocation -> Comment
@@ -532,7 +532,7 @@ mkKWComment kw (EpaSpan (UnhelpfulSpan _))   = Comment kw (EpaDelta noSrcSpan (S
 mkKWComment kw (EpaDelta ss dp cs)           = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw)
 
 sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a]
-sortAnchorLocated = sortBy (compare `on` (anchor . getLoc))
+sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc))
 
 -- | Calculates the distance from the start of a string to the end of
 -- a string.


=====================================
utils/check-ppr/Main.hs
=====================================
@@ -97,7 +97,7 @@ getPragmas (L _ (HsModule { hsmodExt = XModulePs { hsmodAnn = anns' } })) = prag
     tokComment (L _ (EpaComment (EpaLineComment  s) _)) = s
     tokComment _ = ""
 
-    cmp (L l1 _) (L l2 _) = compare (anchor l1) (anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (epaLocationRealSrcSpan l1) (epaLocationRealSrcSpan l2)
     comments' = map tokComment $ sortBy cmp $ priorComments $ epAnnComments anns'
     pragmas = filter (\c -> isPrefixOf "{-#" c ) comments'
     pragmaStr = intercalate "\n" pragmas


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
=====================================
@@ -41,7 +41,7 @@ import qualified Data.Map.Strict as Map
 import Data.Maybe
 import Data.Ord (comparing)
 import qualified Data.Set as Set hiding (Set)
-import GHC hiding (LexicalFixity (..), NoLink, anchor, moduleInfo)
+import GHC hiding (LexicalFixity (..), NoLink, moduleInfo)
 import GHC.Types.Name
 import GHC.Unit.State
 import System.Directory


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
=====================================
@@ -24,7 +24,7 @@ module Haddock.Backends.Xhtml.DocMarkup
 
 import Data.List (intersperse)
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name
 import Text.XHtml hiding (name, p, quote)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
=====================================
@@ -54,7 +54,7 @@ module Haddock.Backends.Xhtml.Layout
 
 import qualified Data.Map as Map
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name (nameOccName)
 import Text.XHtml hiding (name, quote, title)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
=====================================
@@ -31,7 +31,7 @@ module Haddock.Backends.Xhtml.Names
   ) where
 
 import Data.List (stripPrefix)
-import GHC hiding (LexicalFixity (..), anchor)
+import GHC hiding (LexicalFixity (..))
 import GHC.Data.FastString (unpackFS)
 import GHC.Types.Name
 import GHC.Types.Name.Reader



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6a270c21e877c552ebcd8b77f7f2f630884fafe...de769a1f4c04b304c2e97447f47595dc4f8bdbc2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6a270c21e877c552ebcd8b77f7f2f630884fafe...de769a1f4c04b304c2e97447f47595dc4f8bdbc2
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 11:43:43 2024
From: gitlab at gitlab.haskell.org (Zubin (@wz1000))
Date: Thu, 31 Oct 2024 07:43:43 -0400
Subject: [Git][ghc/ghc][wip/9.12-alpha2] 8 commits: Put RdrName in the foExt
 field of FieldOcc
Message-ID: <67236d6f2efca_2965bd86a1143635a@gitlab.mail>



Zubin pushed to branch wip/9.12-alpha2 at Glasgow Haskell Compiler / GHC


Commits:
d5390862 by Hassan Al-Awwadi at 2024-10-31T17:13:29+05:30
Put RdrName in the foExt field of FieldOcc

The main purpose of this commit is to rip RdrName out of FieldOcc, in
accordance with #21592, and as a side note it has simplified the method
we use to deal with ambiguity somewhat.

To do the first, we make FieldOccs store (LIdP p) instead of always
storing Located RdrName, and moved the readername to the extension
points where necessary.

For the second, well, we just turn an ambiguous RdrName into a unbound
Name through mkUnboundName. Later during disambiguateRecordBinds of the
type checking phase, we will try and do type-directed disambiguation based
on the rdrName field (for now), so this hack works out fine.

See Note [Ambiguous FieldOcc in record updates] for more details.

There are two additional minor changes in this commit:
*  The HsRecSel constructor of HsExpr has been moved to the extension
constuctors, since its really GHC specific.
*  HsProjection no longer has a Located DotFieldOcc as a field, but just a
regular DotFieldOcc, since DotFieldOcc already wraps a located
FieldLabelString

co-authored by: @Jade       <Jade512 at proton.me>
                @alt-romes  <rodrigo.m.mesquita at gmail.com>

(cherry picked from commit 1587cccfe7c3c1db3ccc48437b47ccb6ae215701)

- - - - -
c580b505 by Cheng Shao at 2024-10-31T17:13:29+05:30
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

(cherry picked from commit e70009bc5b388ed02db12ee7a99bca0e4c283c87)

- - - - -
7202e2ac by Andrew Lelechenko at 2024-10-31T17:13:29+05:30
hadrian: allow -Wunused-imports for text package

(cherry picked from commit 90746a591919fc51a0ec9dec58d8f1c8397040e3)

- - - - -
4595620a by Andrew Lelechenko at 2024-10-31T17:13:29+05:30
Bump text submodule to 2.1.2

(cherry picked from commit 853050c386ff8634b950204edf4c7f8d973f9a89)

- - - - -
ccd4f869 by Zubin Duggal at 2024-10-31T17:13:29+05:30
configure: Set release version to 9.12.0 instead of 9.12.

This means our alphas will be properly named.

- - - - -
ec2f40b4 by Zubin Duggal at 2024-10-31T17:13:29+05:30
Bump binary submodule to 0.8.9.2

(cherry picked from commit 7199869a52ab45e8856658248bf807954d58cc20)

- - - - -
d2a10e25 by Ben Gamari at 2024-10-31T17:13:29+05:30
Bump process submodule to v1.6.25.0

(cherry picked from commit 18f532f3ed021fff9529f50da2006b8a8d8b1df7)

- - - - -
c0eb35df by Zubin Duggal at 2024-10-31T17:13:29+05:30
testsuite: normalise execvp vs exec differences in process tests

Fixes #25431

(cherry picked from commit a23d8e73166725b699af88a36e97c63b2a0ede25)

- - - - -


30 changed files:

- compiler/GHC/Driver/Main.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Expr.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/728a0bf10026e8629c16e9f5ce9ebfe73628a8a6...c0eb35df4663386e11820c80d6637c61ac75a21e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/728a0bf10026e8629c16e9f5ce9ebfe73628a8a6...c0eb35df4663386e11820c80d6637c61ac75a21e
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 12:38:07 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 31 Oct 2024 08:38:07 -0400
Subject: [Git][ghc/ghc][master] rts/Disassembler: Fix encoding of BRK_FUN
 instruction
Message-ID: <67237a2fcc3e6_2965bdbba008460db@gitlab.mail>



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


Commits:
721ac00d by Ben Gamari at 2024-10-31T08:37:38-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -


5 changed files:

- rts/Disassembler.c
- + testsuite/tests/codeGen/should_run/T25374/T25374.hs
- + testsuite/tests/codeGen/should_run/T25374/T25374.script
- + testsuite/tests/codeGen/should_run/T25374/T25374A.hs
- + testsuite/tests/codeGen/should_run/T25374/all.T


Changes:

=====================================
rts/Disassembler.c
=====================================
@@ -67,12 +67,12 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }
          debugBelch("\n");
-         pc += 4;
+         pc += 6;
          break;
       case bci_SWIZZLE: {
          W_     stkoff = BCO_GET_LARGE_ARG;


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.hs
=====================================
@@ -0,0 +1,8 @@
+import T25374A
+
+fieldsSam :: NP xs -> NP xs -> Bool
+fieldsSam UNil UNil = True
+
+x :: Bool
+x = fieldsSam UNil UNil
+


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374.script
=====================================
@@ -0,0 +1,2 @@
+:load T25374
+x


=====================================
testsuite/tests/codeGen/should_run/T25374/T25374A.hs
=====================================
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+
+module T25374A where
+
+import GHC.Exts
+
+type NP :: [UnliftedType] -> UnliftedType
+data NP xs where
+  UNil :: NP '[]
+  (::*) :: x -> NP xs -> NP (x ': xs)
+


=====================================
testsuite/tests/codeGen/should_run/T25374/all.T
=====================================
@@ -0,0 +1,3 @@
+# This shouldn't crash the disassembler
+test('T25374', [extra_hc_opts('+RTS -Di -RTS'), ignore_stderr, unless(debug_rts(), skip)], ghci_script, [''])
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/721ac00d63216e5e6512baba09b6ebb3cc456ebf

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 12:38:46 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 31 Oct 2024 08:38:46 -0400
Subject: [Git][ghc/ghc][master] EPA: Bring in last EpToken usages
Message-ID: <67237a56a09a9_2965bdb72ec44954b@gitlab.mail>



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


Commits:
0bc94360 by Alan Zimmerman at 2024-10-31T08:38:15-04:00
EPA: Bring in last EpToken usages

For import declarations, NameAnnCommas and NPlusKPat.

And remove anchor, it is the same as epaLocationRealSrcSpan.

- - - - -


19 changed files:

- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Names.hs
- testsuite/tests/simplCore/should_compile/T23864.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Transform.hs
- utils/check-exact/Types.hs
- utils/check-exact/Utils.hs
- utils/check-ppr/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs


Changes:

=====================================
compiler/GHC/Hs/ImpExp.hs
=====================================
@@ -194,9 +194,9 @@ instance (OutputableBndrId p
 -}
 
 type instance XIEName    (GhcPass _) = NoExtField
-type instance XIEDefault (GhcPass _) = EpaLocation
-type instance XIEPattern (GhcPass _) = EpaLocation
-type instance XIEType    (GhcPass _) = EpaLocation
+type instance XIEDefault (GhcPass _) = EpToken "default"
+type instance XIEPattern (GhcPass _) = EpToken "pattern"
+type instance XIEType    (GhcPass _) = EpToken "type"
 type instance XXIEWrappedName (GhcPass _) = DataConCantHappen
 
 type instance Anno (IEWrappedName (GhcPass _)) = SrcSpanAnnA


=====================================
compiler/GHC/Hs/Pat.hs
=====================================
@@ -158,7 +158,7 @@ type instance XNPat GhcPs = EpToken "-"
 type instance XNPat GhcRn = EpToken "-"
 type instance XNPat GhcTc = Type
 
-type instance XNPlusKPat GhcPs = EpaLocation -- Of the "+"
+type instance XNPlusKPat GhcPs = EpToken "+"
 type instance XNPlusKPat GhcRn = NoExtField
 type instance XNPlusKPat GhcTc = Type
 


=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -340,7 +340,7 @@ mkHsCompAnns   :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs
 
 mkNPat      :: LocatedAn NoEpAnns (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> EpToken "-"
             -> Pat GhcPs
-mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpaLocation
+mkNPlusKPat :: LocatedN RdrName -> LocatedAn NoEpAnns (HsOverLit GhcPs) -> EpToken "+"
             -> Pat GhcPs
 
 -- NB: The following functions all use noSyntaxExpr: the generated expressions


=====================================
compiler/GHC/Parser.y
=====================================
@@ -1040,9 +1040,9 @@ export  :: { LIE GhcPs }
                                                           ; locImpExp <- return (sL span (IEModuleContents ($1, (epTok $2)) $3))
                                                           ; return $ reLoc $ locImpExp } }
         | maybe_warning_pragma 'pattern' qcon            { let span = (maybe comb2 comb3 $1) $2 $>
-                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (glR $2) $3)) Nothing }
+                                                           in reLoc $ sL span $ IEVar $1 (sLLa $2 $> (IEPattern (epTok $2) $3)) Nothing }
         | maybe_warning_pragma 'default' qtycon          {% do { let { span = (maybe comb2 comb3 $1) $2 $> }
-                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (glR $2) $3)) Nothing))
+                                                          ; locImpExp <- return (sL span (IEThingAbs $1 (sLLa $2 $> (IEDefault (epTok $2) $3)) Nothing))
                                                           ; return $ reLoc $ locImpExp } }
 
 
@@ -1076,7 +1076,7 @@ qcname_ext_w_wildcard :: { LocatedA ImpExpQcSpec }
 qcname_ext :: { LocatedA ImpExpQcSpec }
         :  qcname                   { sL1a $1 (ImpExpQcName $1) }
         |  'type' oqtycon           {% do { n <- mkTypeImpExp $2
-                                          ; return $ sLLa $1 $> (ImpExpQcType (glR $1) n) }}
+                                          ; return $ sLLa $1 $> (ImpExpQcType (epTok $1) n) }}
 
 qcname  :: { LocatedN RdrName }  -- Variable or type constructor
         :  qvar                 { $1 } -- Things which look like functions
@@ -1209,7 +1209,7 @@ importlist1 :: { OrdList (LIE GhcPs) }
 import  :: { OrdList (LIE GhcPs) }
         : qcname_ext export_subspec {% fmap (unitOL . reLoc . (sLL $1 $>)) $ mkModuleImpExp Nothing (fst $ unLoc $2) $1 (snd $ unLoc $2) }
         | 'module' modid            {% fmap (unitOL . reLoc) $ return (sLL $1 $> (IEModuleContents (Nothing, (epTok $1)) $2)) }
-        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (glR $1) $2)) Nothing }
+        | 'pattern' qcon            { unitOL $ reLoc $ sLL $1 $> $ IEVar Nothing (sLLa $1 $> (IEPattern (epTok $1) $2)) Nothing }
 
 -----------------------------------------------------------------------------
 -- Fixity Declarations
@@ -3776,10 +3776,10 @@ qcon_list : qcon                  { [$1] }
 -- See Note [ExplicitTuple] in GHC.Hs.Expr
 sysdcon_nolist :: { LocatedN DataCon }  -- Wired in data constructors
         : '(' commas ')'        {% amsr (sLL $1 $> $ tupleDataCon Boxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
         | '(#' '#)'             {% amsr (sLL $1 $> $ unboxedUnitDataCon) (NameAnnOnly (NameParensHash (epTok $1) (epTok $2)) []) }
         | '(#' commas '#)'      {% amsr (sLL $1 $> $ tupleDataCon Unboxed (snd $2 + 1))
-                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }
+                                       (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }
 
 syscon :: { LocatedN RdrName }
         : sysdcon               {  L (getLoc $1) $ nameRdrName (dataConName (unLoc $1)) }
@@ -3820,9 +3820,9 @@ gtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, including unit t
 ntgtycon :: { LocatedN RdrName }  -- A "general" qualified tycon, excluding unit tuples
         : oqtycon               { $1 }
         | '(' commas ')'        {% do { n <- mkTupleSyntaxTycon Boxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParens (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' commas '#)'      {% do { n <- mkTupleSyntaxTycon Unboxed (snd $2 + 1)
-                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map srcSpan2e (fst $2)) []) }}
+                                      ; amsr (sLL $1 $> n) (NameAnnCommas (NameParensHash (epTok $1) (epTok $3)) (map (EpTok . srcSpan2e) (fst $2)) []) }}
         | '(#' bars '#)'        {% do { requireLTPuns PEP_SumSyntaxType $1 $>
                                       ; amsr (sLL $1 $> $ (getRdrName (sumTyCon (snd $2 + 1))))
                                        (NameAnnBars (epTok $1, epTok $3) (fst $2) []) } }


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -23,7 +23,6 @@ module GHC.Parser.Annotation (
   DeltaPos(..), deltaPos, getDeltaLine,
 
   EpAnn(..),
-  anchor,
   spanAsAnchor, realSpanAsAnchor,
   noSpanAnchor,
   NoAnn(..),
@@ -350,7 +349,7 @@ instance Outputable a => Outputable (GenLocated TokenLocation a) where
 -- | Used in the parser only, extract the 'RealSrcSpan' from an
 -- 'EpaLocation'. The parser will never insert a 'DeltaPos', so the
 -- partial function is safe.
-epaLocationRealSrcSpan :: EpaLocation -> RealSrcSpan
+epaLocationRealSrcSpan :: EpaLocation' a -> RealSrcSpan
 epaLocationRealSrcSpan (EpaSpan (RealSrcSpan r _)) = r
 epaLocationRealSrcSpan _ = panic "epaLocationRealSrcSpan"
 
@@ -401,9 +400,6 @@ data EpAnn ann
         deriving (Data, Eq, Functor)
 -- See Note [XRec and Anno in the AST]
 
-anchor :: (EpaLocation' a) -> RealSrcSpan
-anchor (EpaSpan (RealSrcSpan r _)) = r
-anchor _ = panic "anchor"
 
 spanAsAnchor :: SrcSpan -> (EpaLocation' a)
 spanAsAnchor ss  = EpaSpan ss
@@ -602,7 +598,7 @@ data NameAnn
   -- | Used for @(,,,)@, or @(#,,,#)@
   | NameAnnCommas {
       nann_adornment :: NameAdornment,
-      nann_commas    :: [EpaLocation],
+      nann_commas    :: [EpToken ","],
       nann_trailing  :: [TrailingAnn]
       }
   -- | Used for @(# | | #)@
@@ -641,10 +637,10 @@ data NameAnn
 -- such as parens or backquotes. This data type identifies what
 -- particular pair are being used.
 data NameAdornment
-  = NameParens     (EpToken "(")  (EpToken ")") -- ^ '(' ')'
-  | NameParensHash (EpToken "(#") (EpToken "#)")-- ^ '(#' '#)'
-  | NameBackquotes (EpToken "`")  (EpToken "`")-- ^ '`'
-  | NameSquare     (EpToken "[")  (EpToken "]")-- ^ '[' ']'
+  = NameParens     (EpToken "(")  (EpToken ")")
+  | NameParensHash (EpToken "(#") (EpToken "#)")
+  | NameBackquotes (EpToken "`")  (EpToken "`")
+  | NameSquare     (EpToken "[")  (EpToken "]")
   | NameNoAdornment
   deriving (Eq, Data)
 


=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -3672,8 +3672,8 @@ allocateComments
   -> ([LEpaComment], [LEpaComment])
 allocateComments ss comment_q =
   let
-    (before,rest)  = break (\(L l _) -> isRealSubspanOf (anchor l) ss) comment_q
-    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (anchor l) ss)) rest
+    (before,rest)  = break (\(L l _) -> isRealSubspanOf (epaLocationRealSrcSpan l) ss) comment_q
+    (middle,after) = break (\(L l _) -> not (isRealSubspanOf (epaLocationRealSrcSpan l) ss)) rest
     comment_q' = before ++ after
     newAnns = middle
   in
@@ -3691,14 +3691,14 @@ splitPriorComments ss prior_comments =
     -- And the token preceding the comment is on a different line
     cmp :: RealSrcSpan -> LEpaComment -> Bool
     cmp later (L l c)
-         = srcSpanStartLine later - srcSpanEndLine (anchor l) == 1
-          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (anchor l)
+         = srcSpanStartLine later - srcSpanEndLine (epaLocationRealSrcSpan l) == 1
+          && srcSpanEndLine (ac_prior_tok c) /= srcSpanStartLine (epaLocationRealSrcSpan l)
 
     go :: [LEpaComment] -> RealSrcSpan -> [LEpaComment]
        -> ([LEpaComment], [LEpaComment])
     go decl_comments _ [] = ([],decl_comments)
     go decl_comments r (c@(L l _):cs) = if cmp r c
-                              then go (c:decl_comments) (anchor l) cs
+                              then go (c:decl_comments) (epaLocationRealSrcSpan l) cs
                               else (reverse (c:cs), decl_comments)
   in
     go [] ss prior_comments
@@ -3710,7 +3710,7 @@ allocatePriorComments
   -> (Strict.Maybe [LEpaComment], [LEpaComment], [LEpaComment])
 allocatePriorComments ss comment_q mheader_comments =
   let
-    cmp (L l _) = anchor l <= ss
+    cmp (L l _) = epaLocationRealSrcSpan l <= ss
     (newAnns,after) = partition cmp comment_q
     comment_q'= after
     (prior_comments, decl_comments) = splitPriorComments ss newAnns


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1312,7 +1312,7 @@ checkAPat loc e0 = do
            _
                      | nPlusKPatterns && (plus == plus_RDR)
                      -> return (mkNPlusKPat (L nloc n) (L (l2l lloc) lit)
-                                (entry l))
+                                (EpTok $ entry l))
 
    -- Improve error messages for the @-operator when the user meant an @-pattern
    PatBuilderOpApp _ op _ _ | opIsAt (unLoc op) -> do
@@ -3158,7 +3158,7 @@ data ImpExpSubSpec = ImpExpAbs
                    | ImpExpAllWith [LocatedA ImpExpQcSpec]
 
 data ImpExpQcSpec = ImpExpQcName (LocatedN RdrName)
-                  | ImpExpQcType EpaLocation (LocatedN RdrName)
+                  | ImpExpQcType (EpToken "type") (LocatedN RdrName)
                   | ImpExpQcWildcard (EpToken "..") (EpToken ",")
 
 mkModuleImpExp :: Maybe (LWarningTxt GhcPs) -> (EpToken "(", EpToken ")") -> LocatedA ImpExpQcSpec


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -2107,13 +2107,13 @@ printMinimalImports hsc_src imports_w_usage
 
 to_ie_post_rn_var :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn_var (L l n)
-  | isDataOcc $ occName n = L l (IEPattern (entry l)   (L (l2l l) n))
+  | isDataOcc $ occName n = L l (IEPattern noAnn      (L (l2l l) n))
   | otherwise             = L l (IEName    noExtField (L (l2l l) n))
 
 
 to_ie_post_rn :: LocatedA (IdP GhcRn) -> LIEWrappedName GhcRn
 to_ie_post_rn (L l n)
-  | isTcOcc occ && isSymOcc occ = L l (IEType (entry l)   (L (l2l l) n))
+  | isTcOcc occ && isSymOcc occ = L l (IEType noAnn      (L (l2l l) n))
   | otherwise                   = L l (IEName noExtField (L (l2l l) n))
   where occ = occName n
 


=====================================
testsuite/tests/simplCore/should_compile/T23864.hs
=====================================
@@ -49,7 +49,7 @@ insertCommentsByPos ::
   -> (EpAnnComments -> [LEpaComment] -> EpAnnComments)
   -> EpAnn a
   -> WithComments (EpAnn a)
-insertCommentsByPos cond = insertComments (cond . anchor . getLoc)
+insertCommentsByPos cond = insertComments (cond . epaLocationRealSrcSpan . getLoc)
 
 insertComments ::
      (LEpaComment -> Bool)


=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -570,7 +570,7 @@ splitAfterTrailingAnns tas cs = (before, after)
         (s:_) -> (b,a)
           where
             s_pos = ss2pos s
-            (b,a) = break (\(L ll _) -> (ss2pos $ anchor ll) > s_pos)
+            (b,a) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > s_pos)
                           cs
 
 -- ---------------------------------------------------------------------
@@ -731,12 +731,6 @@ printStringAtNC el str = do
   el' <- printStringAtAAC NoCaptureComments (noCommentsToEpaLocation el) str
   return (epaToNoCommentsLocation el')
 
-printStringAtAAL :: (Monad m, Monoid w)
-  => a -> Lens a EpaLocation -> String -> EP w m a
-printStringAtAAL an l str = do
-  r <- printStringAtAAC CaptureComments (view l an) str
-  return (set l r an)
-
 printStringAtAAC :: (Monad m, Monoid w)
   => CaptureComments -> EpaLocation -> String -> EP w m EpaLocation
 printStringAtAAC capture (EpaSpan (RealSrcSpan r _)) s = printStringAtRsC capture r s
@@ -1020,10 +1014,6 @@ lal_rest k parent = fmap (\new -> parent { al_rest = new })
 
 -- -------------------------------------
 
-lid :: Lens a a
-lid k parent = fmap (\new -> new)
-                    (k parent)
-
 lfst :: Lens (a,b) a
 lfst k parent = fmap (\new -> (new, snd parent))
                      (k (fst parent))
@@ -4186,7 +4176,7 @@ instance ExactPrint (LocatedN RdrName) where
             _ -> error "ExactPrint (LocatedN RdrName)"
         NameAnnCommas a commas t -> do
           a0 <- markNameAdornmentO a
-          commas' <- forM commas (\loc -> printStringAtAAC NoCaptureComments loc ",")
+          commas' <- forM commas markEpToken
           a1 <- markNameAdornmentC a0
           return (NameAnnCommas a1 commas' t)
         NameAnnBars (o,c) bars t -> do
@@ -4247,7 +4237,7 @@ printUnicode :: (Monad m, Monoid w) => EpaLocation -> RdrName -> EP w m EpaLocat
 printUnicode anc n = do
   let str = case (showPprUnsafe n) of
             -- TODO: unicode support?
-              "forall" -> if spanLength (anchor anc) == 1 then "∀" else "forall"
+              "forall" -> if spanLength (epaLocationRealSrcSpan anc) == 1 then "∀" else "forall"
               s -> s
   loc <- printStringAtAAC NoCaptureComments (EpaDelta noSrcSpan (SameLine 0) []) str
   case loc of
@@ -4617,15 +4607,15 @@ instance ExactPrint (IEWrappedName GhcPs) where
     n' <- markAnnotated n
     return (IEName x n')
   exact (IEDefault r n) = do
-    r' <- printStringAtAA r "default"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEDefault r' n')
   exact (IEPattern r n) = do
-    r' <- printStringAtAA r "pattern"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEPattern r' n')
   exact (IEType r n) = do
-    r' <- printStringAtAA r "type"
+    r' <- markEpToken r
     n' <- markAnnotated n
     return (IEType r' n')
 
@@ -4715,7 +4705,7 @@ instance ExactPrint (Pat GhcPs) where
 
   exact (NPlusKPat an n k lit2 a b) = do
     n' <- markAnnotated n
-    an' <- printStringAtAAL an lid "+"
+    an' <- markEpToken an
     k' <- markAnnotated k
     return (NPlusKPat an' n' k' lit2 a b)
 


=====================================
utils/check-exact/Parsers.hs
=====================================
@@ -289,7 +289,8 @@ fixModuleTrailingComments (GHC.L l p) = GHC.L l p'
             let
               pc = GHC.priorComments cs
               fc = GHC.getFollowingComments cs
-              bf (GHC.L anc _) = GHC.anchor anc > ss
+              bf (GHC.L anc _) = GHC.epaLocationRealSrcSpan anc > ss
+
               (prior,f) = break bf fc
               cs'' = GHC.EpaCommentsBalanced (pc <> prior) f
             in cs''
@@ -310,7 +311,7 @@ fixModuleHeaderComments (GHC.L l p) = GHC.L l p'
         -- Move any comments on the decl that occur prior to the location
         pc = GHC.priorComments csd
         fc = GHC.getFollowingComments csd
-        bf (GHC.L anch _) = GHC.anchor anch > r
+        bf (GHC.L anch _) = GHC.epaLocationRealSrcSpan anch > r
         (move,keep) = break bf pc
         csd' = GHC.EpaCommentsBalanced keep fc
 


=====================================
utils/check-exact/Transform.hs
=====================================
@@ -211,7 +211,7 @@ captureTypeSigSpacing (L l (SigD x (TypeSig (AnnSig (EpUniTok dca u) mp md) ns (
     -- we want DPs for the distance from the end of the ns to the
     -- AnnDColon, and to the start of the ty
     rd = case last ns of
-      L (EpAnn anc' _ _) _ -> anchor anc'
+      L (EpAnn anc' _ _) _ -> epaLocationRealSrcSpan anc'
     dca' = case dca of
           EpaSpan ss@(RealSrcSpan r _) -> (EpaDelta ss (ss2delta (ss2posEnd rd) r) [])
           _                            -> dca
@@ -298,7 +298,7 @@ setEntryDP (L (EpAnn (EpaSpan ss@(RealSrcSpan r _)) an cs) a) dp
                 col = deltaColumn delta
                 edp' = if line == 0 then SameLine col
                                     else DifferentLine line col
-                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ anchor $ getLoc lc), r))
+                edp = edp' `debug` ("setEntryDP :" ++ showGhc (edp', (ss2pos $ epaLocationRealSrcSpan $ getLoc lc), r))
 
 
 -- ---------------------------------------------------------------------
@@ -552,12 +552,12 @@ trailingCommentsDeltas _ [] = []
 trailingCommentsDeltas r (la@(L (EpaDelta _ dp _) _):las)
   = (getDeltaLine dp, la): trailingCommentsDeltas r las
 trailingCommentsDeltas r (la@(L l _):las)
-  = deltaComment r la : trailingCommentsDeltas (anchor l) las
+  = deltaComment r la : trailingCommentsDeltas (epaLocationRealSrcSpan l) las
   where
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2posEnd rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 priorCommentsDeltas :: RealSrcSpan -> [LEpaComment]
                     -> [(Int, LEpaComment)]
@@ -565,14 +565,14 @@ priorCommentsDeltas r cs = go r (sortEpaComments cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 
 -- ---------------------------------------------------------------------
@@ -664,14 +664,14 @@ addCommentOrigDeltasAnn (EpAnn e a cs) = EpAnn e a (addCommentOrigDeltas cs)
 -- TODO: this is replicating functionality in ExactPrint. Sort out the
 -- import loop`
 anchorFromLocatedA :: LocatedA a -> RealSrcSpan
-anchorFromLocatedA (L (EpAnn anc _ _) _) = anchor anc
+anchorFromLocatedA (L (EpAnn anc _ _) _) = epaLocationRealSrcSpan anc
 
 -- | Get the full span of interest for comments from a LocatedA.
 -- This extends up to the last TrailingAnn
 fullSpanFromLocatedA :: LocatedA a -> RealSrcSpan
 fullSpanFromLocatedA (L (EpAnn anc (AnnListItem tas)  _) _) = rr
   where
-    r = anchor anc
+    r = epaLocationRealSrcSpan anc
     trailing_loc ta = case ta_location ta of
         EpaSpan (RealSrcSpan s _) -> [s]
         _ -> []
@@ -695,7 +695,7 @@ balanceSameLineComments (L la (Match anm mctxt pats (GRHSs x grhss lb)))
           (csp,csf) = case anc1 of
             EpaComments cs -> ([],cs)
             EpaCommentsBalanced p f -> (p,f)
-          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (anchor anc) csf)
+          (move',stay') = break (simpleBreak 0) (trailingCommentsDeltas (epaLocationRealSrcSpan anc) csf)
           move = map snd move'
           stay = map snd stay'
           cs1 = epaCommentsBalanced csp stay


=====================================
utils/check-exact/Types.hs
=====================================
@@ -8,8 +8,7 @@
 {-# LANGUAGE TypeSynonymInstances #-}
 {-# LANGUAGE ViewPatterns         #-}
 
-module Types
-  where
+module Types where
 
 import GHC hiding (EpaComment)
 import GHC.Utils.Outputable hiding ( (<>) )
@@ -41,7 +40,7 @@ instance Ord Comment where
   -- When we have CPP injected comments with a fake filename, or LINE
   -- pragma, the file name changes, so we need to compare the
   -- locations only, with out the filename.
-  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ anchor ss1) (ss2pos $ anchor ss2)
+  compare (Comment _ ss1 _ _) (Comment _ ss2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan ss1) (ss2pos $ epaLocationRealSrcSpan ss2)
     where
       ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss)
 


=====================================
utils/check-exact/Utils.hs
=====================================
@@ -268,7 +268,7 @@ workInComments ocs new = cs'
                                         (sortEpaComments $ fc ++ cs_after)
              where
                (cs_before,cs_after)
-                   = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) )
+                   = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) )
                            new
 
 insertTopLevelCppComments ::  HsModule GhcPs -> [LEpaComment] -> (HsModule GhcPs, [LEpaComment])
@@ -292,7 +292,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an1,cs0a) = case lo of
         EpExplicitBraces (EpTok (EpaSpan (RealSrcSpan s _))) _close ->
             let
-                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0
+                (stay,cs0a') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0
                 cs' = workInComments (comments an0) stay
             in (an0 { comments = cs' }, cs0a')
         _ -> (an0,cs0)
@@ -300,7 +300,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
     (an2, cs0b) = case am_decls $ anns an1 of
         (AddSemiAnn (EpTok (EpaSpan (RealSrcSpan s _))):_) -> (an1 {comments = cs'}, cs0b')
           where
-            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ s)) cs0a
+            (stay,cs0b') = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ s)) cs0a
             cs' = workInComments (comments an1) stay
         _ -> (an1,cs0a)
 
@@ -314,7 +314,7 @@ insertTopLevelCppComments (HsModule (XModulePs an lo mdeprec mbDoc) mmn mexports
                            (csh', cs0b') = case annListBracketsLocs $ al_brackets $ anns l of
                                (EpaSpan (RealSrcSpan s _),_) ->(h, n)
                                  where
-                                   (h,n) = break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+                                   (h,n) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        cs0b
 
                                _ -> ([], cs0b)
@@ -361,7 +361,7 @@ splitOnWhere w (EpTok (EpaSpan (RealSrcSpan s _))) csIn = (hc, fc)
   where
     splitFunc Before anc_pos c_pos = c_pos < anc_pos
     splitFunc After  anc_pos c_pos = anc_pos < c_pos
-    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ anchor ll) (ss2pos s)) csIn
+    (hc,fc) = break (\(L ll _) ->  splitFunc w (ss2pos $ epaLocationRealSrcSpan ll) (ss2pos s)) csIn
 splitOnWhere _ _ csIn = (csIn,[])
 
 balanceFirstLocatedAComments :: [LocatedA a] -> ([LocatedA a], [LEpaComment])
@@ -372,7 +372,7 @@ balanceFirstLocatedAComments ((L (EpAnn anc an csd) a):ds) = (L (EpAnn anc an cs
         EpaSpan (RealSrcSpan s _) -> (csd', hc)
                `debug` ("balanceFirstLocatedAComments: (csd,csd',attached,header)=" ++ showAst (csd,csd',attached,header))
           where
-            (priors, inners) =  break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos s) )
+            (priors, inners) =  break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos s) )
                                        (priorComments csd)
             pcds = priorCommentsDeltas' s priors
             (attached, header) = break (\(d,_c) -> d /= 1) pcds
@@ -388,14 +388,14 @@ priorCommentsDeltas' r cs = go r (reverse cs)
   where
     go :: RealSrcSpan -> [LEpaComment] -> [(Int, LEpaComment)]
     go _   [] = []
-    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (anchor l) las
-    go rs' (la@(L l _):las) = deltaComment rs' la : go (anchor l) las
+    go _   (la@(L l@(EpaDelta _ dp _) _):las) = (getDeltaLine dp, la) : go (epaLocationRealSrcSpan l) las
+    go rs' (la@(L l _):las) = deltaComment rs' la : go (epaLocationRealSrcSpan l) las
 
     deltaComment :: RealSrcSpan -> LEpaComment -> (Int, LEpaComment)
     deltaComment rs' (L loc c) = (abs(ll - al), L loc c)
       where
         (al,_) = ss2pos rs'
-        (ll,_) = ss2pos (anchor loc)
+        (ll,_) = ss2pos (epaLocationRealSrcSpan loc)
 
 allocatePriorComments
   :: Pos
@@ -403,7 +403,7 @@ allocatePriorComments
   -> ([LEpaComment], [LEpaComment])
 allocatePriorComments ss_loc comment_q =
   let
-    cmp (L l _) = ss2pos (anchor l) <= ss_loc
+    cmp (L l _) = ss2pos (epaLocationRealSrcSpan l) <= ss_loc
     (newAnns,after) = partition cmp comment_q
   in
     (after, newAnns)
@@ -420,7 +420,7 @@ insertRemainingCppComments (L l p) cs = L l p'
             EpTok (EpaSpan (RealSrcSpan s _)) -> ss2pos s
             _ -> (1,1)
         _ -> (1,1)
-    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ anchor ll) > end_loc ) cs
+    (new_before, new_after) = break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > end_loc ) cs
 
     addTrailingComments end_loc' cur new = epaCommentsBalanced pc' fc'
       where
@@ -431,8 +431,8 @@ insertRemainingCppComments (L l p) cs = L l p'
             (L ac _:_) -> (sortEpaComments $ pc ++ cs_before, sortEpaComments $ fc ++ cs_after)
               where
                (cs_before,cs_after)
-                   = if (ss2pos $ anchor ac) > end_loc'
-                       then break (\(L ll _) -> (ss2pos $ anchor ll) > (ss2pos $ anchor ac) ) new
+                   = if (ss2pos $ epaLocationRealSrcSpan ac) > end_loc'
+                       then break (\(L ll _) -> (ss2pos $ epaLocationRealSrcSpan ll) > (ss2pos $ epaLocationRealSrcSpan ac) ) new
                        else (new_before, new_after)
 
 -- ---------------------------------------------------------------------
@@ -513,7 +513,7 @@ normaliseCommentText (x:xs) = x:normaliseCommentText xs
 
 -- |Must compare without span filenames, for CPP injected comments with fake filename
 cmpComments :: Comment -> Comment -> Ordering
-cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+cmpComments (Comment _ l1 _ _) (Comment _ l2 _ _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- |Sort, comparing without span filenames, for CPP injected comments with fake filename
 sortComments :: [Comment] -> [Comment]
@@ -523,7 +523,7 @@ sortComments cs = sortBy cmpComments cs
 sortEpaComments :: [LEpaComment] -> [LEpaComment]
 sortEpaComments cs = sortBy cmp cs
   where
-    cmp (L l1 _) (L l2 _) = compare (ss2pos $ anchor l1) (ss2pos $ anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (ss2pos $ epaLocationRealSrcSpan l1) (ss2pos $ epaLocationRealSrcSpan l2)
 
 -- | Makes a comment which originates from a specific keyword.
 mkKWComment :: String -> NoCommentsLocation -> Comment
@@ -532,7 +532,7 @@ mkKWComment kw (EpaSpan (UnhelpfulSpan _))   = Comment kw (EpaDelta noSrcSpan (S
 mkKWComment kw (EpaDelta ss dp cs)           = Comment kw (EpaDelta ss dp cs) placeholderRealSpan (Just kw)
 
 sortAnchorLocated :: [GenLocated EpaLocation a] -> [GenLocated EpaLocation a]
-sortAnchorLocated = sortBy (compare `on` (anchor . getLoc))
+sortAnchorLocated = sortBy (compare `on` (epaLocationRealSrcSpan . getLoc))
 
 -- | Calculates the distance from the start of a string to the end of
 -- a string.


=====================================
utils/check-ppr/Main.hs
=====================================
@@ -97,7 +97,7 @@ getPragmas (L _ (HsModule { hsmodExt = XModulePs { hsmodAnn = anns' } })) = prag
     tokComment (L _ (EpaComment (EpaLineComment  s) _)) = s
     tokComment _ = ""
 
-    cmp (L l1 _) (L l2 _) = compare (anchor l1) (anchor l2)
+    cmp (L l1 _) (L l2 _) = compare (epaLocationRealSrcSpan l1) (epaLocationRealSrcSpan l2)
     comments' = map tokComment $ sortBy cmp $ priorComments $ epAnnComments anns'
     pragmas = filter (\c -> isPrefixOf "{-#" c ) comments'
     pragmaStr = intercalate "\n" pragmas


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs
=====================================
@@ -41,7 +41,7 @@ import qualified Data.Map.Strict as Map
 import Data.Maybe
 import Data.Ord (comparing)
 import qualified Data.Set as Set hiding (Set)
-import GHC hiding (LexicalFixity (..), NoLink, anchor, moduleInfo)
+import GHC hiding (LexicalFixity (..), NoLink, moduleInfo)
 import GHC.Types.Name
 import GHC.Unit.State
 import System.Directory


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
=====================================
@@ -24,7 +24,7 @@ module Haddock.Backends.Xhtml.DocMarkup
 
 import Data.List (intersperse)
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name
 import Text.XHtml hiding (name, p, quote)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
=====================================
@@ -54,7 +54,7 @@ module Haddock.Backends.Xhtml.Layout
 
 import qualified Data.Map as Map
 import Data.Maybe (fromMaybe)
-import GHC hiding (anchor)
+import GHC
 import GHC.Types.Name (nameOccName)
 import Text.XHtml hiding (name, quote, title)
 


=====================================
utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
=====================================
@@ -31,7 +31,7 @@ module Haddock.Backends.Xhtml.Names
   ) where
 
 import Data.List (stripPrefix)
-import GHC hiding (LexicalFixity (..), anchor)
+import GHC hiding (LexicalFixity (..))
 import GHC.Data.FastString (unpackFS)
 import GHC.Types.Name
 import GHC.Types.Name.Reader



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bc94360908011167284ee4c283c343350cbba78

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 12:39:46 2024
From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot))
Date: Thu, 31 Oct 2024 08:39:46 -0400
Subject: [Git][ghc/ghc][master] Assert that ctEvCoercion is called on an
 equality
Message-ID: <67237a92cdb5f_2965bdbbba48526e7@gitlab.mail>



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


Commits:
0b11cdc0 by sheaf at 2024-10-31T08:38:55-04:00
Assert that ctEvCoercion is called on an equality

Calling 'ctEvCoercion' on non-equality constraints is always incorrect.
We add an assertion to this function to detect such cases; for example
a type-checking plugin might erroneously do this.

- - - - -


1 changed file:

- compiler/GHC/Tc/Types/Constraint.hs


Changes:

=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -2306,8 +2306,10 @@ ctEvExpr ev@(CtWanted { ctev_dest = HoleDest _ })
 ctEvExpr ev = evId (ctEvEvId ev)
 
 ctEvCoercion :: HasDebugCallStack => CtEvidence -> TcCoercion
-ctEvCoercion (CtGiven { ctev_evar = ev_id })
-  = mkCoVarCo ev_id
+ctEvCoercion _given@(CtGiven { ctev_evar = ev_id })
+  = assertPpr (isCoVar ev_id)
+    (text "ctEvCoercion used on non-equality Given constraint:" <+> ppr _given)
+  $ mkCoVarCo ev_id
 ctEvCoercion (CtWanted { ctev_dest = dest })
   | HoleDest hole <- dest
   = -- ctEvCoercion is only called on type equalities



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b11cdc022ce33d089db95b2b2e7c1f4bb326d37

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 13:59:31 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 31 Oct 2024 09:59:31 -0400
Subject: [Git][ghc/ghc][wip/T18462] 98 commits: ghci: mitigate host/target
 word size mismatch in BCOByteArray serialization
Message-ID: <67238d4396bc0_158247323cdc11212c@gitlab.mail>



Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC


Commits:
90891962 by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: mitigate host/target word size mismatch in BCOByteArray serialization

This patch mitigates a severe host/target word size mismatch issue in
BCOByteArray serialization logic introduced since !12142, see added
note for detailed explanation.

- - - - -
839ac52e by Cheng Shao at 2024-10-17T16:41:18+00:00
ghci: use plain malloc for mkConInfoTable on non-TNTC platforms

This patch avoids using mmap() to allocate executable memory for
mkConInfoTable on platforms without tables-next-to-code, see added
comment for explanation.

- - - - -
a998f69d by Cheng Shao at 2024-10-17T16:41:18+00:00
ghc-internal: add missing CPPs for wasm

This patch adds some missing CPP guards to ghc-internal, given those
functions are non existent on wasm and would cause linking issues.

- - - - -
71a471e7 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: rename prelude.js to prelude.mjs

This commit renames prelude.js to prelude.mjs for wasm backend rts
jsbits, and slightly adjusts the jsbits contents. This is for
preparing the implementation of dyld.mjs that contains wasm dynamic
linker logic, which needs to import prelude.mjs as a proper ESM
module.

- - - - -
33d9db17 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: add __wrapped_freeJSVal

This commit wraps imported freeJSVal in a __wrapped_freeJSVal C
function for wasm backend RTS. In general, wasm imports are only
supposed to be directly called by C; they shouldn't be used as
function pointers, which confuses wasm-ld at link-time when generating
shared libraries.

- - - - -
0d0a16a8 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: correct stale link in comment

- - - - -
90a35c41 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: drop interpretBCO support from non-dyn ways on wasm

This commit drops interpretBCO support from non dynamic rts ways on
wasm. The bytecode interpreter is only useful when the RTS linker also
works, and on wasm it only works for dynamic ways anyway. An
additional benefit of dropping interpretBCO is reduction in code size
of linked wasm modules, especially since interpretBCO references
ffi_call which is an auto-generated large function in libffi-wasm and
unused by most user applications.

- - - - -
98a32ec5 by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: don't build predefined GloblRegs for wasm PIC mode

This commit wraps the predefined GlobalRegs in Wasm.S under a CPP
guard to prevent building for PIC mode. When building dynamic ways of
RTS, the wasm globals that represent STG GlobalRegs will be created
and supplied by dyld.mjs. The current wasm dylink convention doesn't
properly support exporting relocatable wasm globals at all, any wasm
global exported by a .so is assumed to be a GOT.mem entry.

- - - - -
bef94bde by Cheng Shao at 2024-10-17T16:41:18+00:00
rts: fix conflicting StgRun definitions on wasm

This commit fixes conflicting StgRun definition when building dynamic
ways of RTS for wasm in unregisterised mode.

- - - - -
a6a82cdb by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: use targetSupportsRPaths predicate

This commit changes the hostSupportsRPaths predicate to
targetSupportsRPaths and use that to decide whether to pass
RPATH-related link-time options. It's not applied to stage0, we should
just use the default link-time options of stageBoot ghc.

- - - - -
f232c872 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: disable internal-interpreter of ghc library when cross compiling

This commit disable the internal-interpreter flag of ghc library when
cross compiling, only external interpreter works in such cases.

- - - - -
577c1819 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: enable internal-interpreter for ghc-bin stage0

This commit enables internal-interpreter flag for ghc-bin even when
compiling stage0, as long as target supports ghci. It enables ghci
functionality for cross targets that support ghci, since cross ghc-bin
is really stage0.

- - - - -
c247f2ee by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: fix CFLAGS for gmp shared objs on wasm

This commit adds -fvisibility=default to CFLAGS of gmp when building
for wasm. This is required to generate the ghc-bignum shared library
without linking errors. Clang defaults to -fvisibility=hidden for wasm
targets, which will cause issues when a symbol is expected to be
exported in a shared library but without explicit visibility attribute
annotation.

- - - - -
775410fd by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: re-enable PIC for gmp on wasm

This commit re-enables --with-pic=yes configuration option of gmp when
building for wasm, given we're about to include support for shared
libraries, TH and ghci.

- - - - -
b45080a3 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian: add the host_fully_static flavour transformer

This commit adds the host_fully_static flavour transformer to hadrian,
which ensures stage0 is fully statically linked while still permitting
stage1 libdir to contain shared libraries. This is intended to be used
by the wasm backend to build portable linux bindists that contain wasm
shared libraries.

- - - - -
5043507c by Cheng Shao at 2024-10-17T16:41:18+00:00
ci: update wasm jobs configuration

This commit bumps ci-image revision to use updated wasm toolchain, and
use host_fully_static instead of fully_static for wasm jobs so to
ensure wasm shared libraries can be properly built.

- - - - -
2956a3f7 by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/testsuite: implement config.cross logic

This commit implements the config.cross field in the testsuite driver.
It comes from the "cross compiling" ghc info field for both
in-tree/out-of-tree GHC, and is an accurate predicate of whether we're
cross-compiling or not (compared to the precense of target emulator),
and is useful to implement predicates to assert the precense of
internal interpreter (only available on non-cross GHC) for tests that
do require it (e.g. plugins).

- - - - -
8c74a0ed by Cheng Shao at 2024-10-17T16:41:18+00:00
hadrian/compiler: implement targetRTSLinkerOnlySupportsSharedLibs

This patch implements the targetRTSLinkerOnlySupportsSharedLibs
predicate in hadrian. Its definition in hadrian is the single source
of truth, and the information propagates to ghc settings file, ghc
driver and testsuite driver. It is used in various places to ensure
dynamic dependency is selected when the target RTS linker only
supports loading dynamic code.

- - - - -
b4c3c340 by Cheng Shao at 2024-10-17T16:41:18+00:00
testsuite: don't use host cpu features when testing cross ghc

This patch disables CPU feature detection logic when testing cross
GHC, since those features don't make sense for the target anyway.

- - - - -
3c21b696 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: implement & use req_plugins predicate

This commit implements req_plugins predicate to indicate that the test
requires plugin functionality. Currently this means cross GHC is
disabled since internal-interpreter doesn't work in cross GHC yet.

- - - - -
93b8af80 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: make use of config.interp_force_dyn

This commit takes config.interp_force_dyn into consideration when
setting up TH/ghci way flags.

- - - - -
94673d41 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T17572 timeout

- - - - -
2b5efc2d by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: bump T22744 pre_cmd timeout

- - - - -
45102e2a by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip terminfo_so for cross ghc

- - - - -
05e40406 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: fix shared library size tests for cross ghc

This commit fixes shared library size tests (e.g. array_so in
testsuite/tests/perf/size/all.T) when testing cross ghc. Previously,
if shared library file extension of host and target differs, those
tests will fail with framework errors due to not finding the right
files.

- - - - -
fa68f833 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip ghc api tests that attempt to spawn processes inside wasm

This commit skips a few ghc api tests on wasm, since they would
attempt to spawn processes inside wasm, which is not supported at all.

- - - - -
1241c04e by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: skip T22840 due to broken -dtag-inference-checks on wasm

- - - - -
78c8b900 by Cheng Shao at 2024-10-17T16:41:19+00:00
testsuite: ensure $(ghciWayFlags) can be overridden

This commit revises boilerplate.mk in testsuite as well as a few other
places, to ensure the tests that do make use of $(ghciWayFlags) can
receive the right $(ghciWayFlags) from testsuite driver config.

- - - - -
47989ecc by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip rdynamic on wasm

- - - - -
fefb4ea1 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: skip T2615 on wasm

This commit marks T2615 as skip on wasm, given LD_* environment
variables aren't supported on wasm anyway.

- - - - -
77c79762 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: mark MultiLayerModulesTH_Make/MultiLayerModulesTH_OneShot as fragile on wasm

- - - - -
69bb4745 by Cheng Shao at 2024-10-17T16:41:24+00:00
testsuite: fix T16180 on wasm

This commit fixes T16180 on wasm once TH support is flipped on. The
fix is simply adding right asm code for wasm.

- - - - -
621c753d by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: fix -fexternal-interpreter flag for JS backend

Previously, -fexternal-interpreter is broken for JS backend, since GHC
would attempt to launch a non-existent ghc-iserv* executable. This
commit fixes it by adjusting pattern matching order in
setTopSessionDynFlags.

- - - - -
80aa8983 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: use interpreterDynamic predicate in preloadLib

This commit use the interpreterDynamic predicate in preloadLib to
decide if we should do dynLoadObjs instead of loadObj. Previously we
used hostIsDynamic which was only written with non-cross internal
interpreter in mind.

The testsuite is also adjusted to remove hard-wired -fPIC flag for
cbits (doesn't work in i386 RTS linker in vanilla way, #25260) and
properly pass ghc_th_way_flags to ghc.

- - - - -
74411461 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix Cmm dynamic CLabels for wasm

This commit fixes the handling of dynamic CLabels for the wasm
backend. Just do the simplest handling: preserve the original CLabel,
both unreg/NCG backends can handle them properly without issue.

- - - - -
f6abaf13 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary compile-time flags for wasm PIC mode

This commit adds necessary compile-time flags when compiling for wasm
PIC mode, see added comment for detailed explanation.

- - - - -
9745fcfb by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: add necessary link-time flags for wasm shared libs

This commit adds necessary link-time flags for wasm shared libs, see
added comments for detailed explanation.

- - - - -
649aae00 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: enforce -fno-use-rpaths for wasm

This commit ensures the GHC driver never passes any RPATH-related
link-time flags on wasm, which is not supported at all.

- - - - -
47baa904 by Cheng Shao at 2024-10-17T16:41:24+00:00
driver: ensure static archives are picked when linking static .wasm modules

This commit ensures static archives are picked when linking .wasm
modules which are supposed to be fully static, even when ghc may be
invoked with -dynamic, see added comment for explanation.

- - - - -
fc3a5591 by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix dynamic_too_enable for targets that require dynamic libraries

This commit fixes dynamic_too_enable for targets whose RTS linker can
only load dynamic code.

- - - - -
94ef949e by Cheng Shao at 2024-10-17T16:41:24+00:00
compiler: fix checkNonStdWay for targets that require dynamic libraries

This commit fixes checkNonStdWay to ensure that for targets whose RTS
linker can only load dynamic code, the dynamic way of object is
selected.

- - - - -
88e99248 by Cheng Shao at 2024-10-17T16:41:24+00:00
ghc-bin: enforce dynamic way when the target requires so

This commit makes ghc-bin use dynamic way when it is doing interactive
stuff on certain targets whose RTS linker can only handle dynamic
code.

- - - - -
549582ef by Cheng Shao at 2024-10-17T16:41:24+00:00
hadrian/ghci: add wasm dyld

This commit adds the wasm dynamic linker implementation, as well as
ghci logic to call it and hadrian logic to install it to the correct
location. See the top-level note in utils/jsffi/dyld.mjs for more
details.

- - - - -
b562e3a6 by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: fix getGccSearchDirectory for wasm target

This commit fixes getGccSearchDirectory logic for wasm target, ensures
the correct search directory containing libc.so etc can be found by
GHC. getGccSearchDirectory is also exported so it can be used
elsewhere to obtain the wasi-sdk libdir and pass to the dyld script.

- - - - -
2d6107dc by Cheng Shao at 2024-10-17T16:41:29+00:00
driver: add wasm backend iserv logic

This commit adds wasm backend iserv logic to the driver, see added
comments for explanation.

- - - - -
61f5baa5 by Cheng Shao at 2024-10-17T16:41:29+00:00
compiler: add PIC support to wasm backend NCG

This commit adds support for generating PIC to the wasm backend NCG.

- - - - -
652e7239 by Cheng Shao at 2024-10-17T16:41:29+00:00
hadrian/compiler: flip on support for shared libs & ghci for wasm

This commit flips on the support for shared libs and ghci for the wasm
target, given all required support logic has been added in previous
commits.

- - - - -
74a1f681 by Cheng Shao at 2024-10-17T16:41:29+00:00
testsuite: flip on support for shared libs, TH & ghci for wasm

This commit flips on support for shared libs, TH & ghci for wasm in
the testsuite, given support has been landed in previous commits.

- - - - -
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"

This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.

- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter

This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:

```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```

Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)

The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.

- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule

The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.

- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal

- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins

- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target

Fixes #23117. Fixes #23281. Fixes #23490.

This required:
 * Updating the bit-rotted compiler/Setup.hs and its setup-depends
 * Listing a few recently-added libraries and utilities
   in cabal.project-reinstall
 * Setting allow-boot-library-installs to 'True' since Cabal
   now considers the 'ghc' package itself a boot library for
   the purposes of this flag

Additionally, the allow-newer block in cabal.project-reinstall
was removed.  This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base.  However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)

Why does setup-depends solving insist on an old version of Cabal? See:
  https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410

The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide.  But this is left
for future work.

- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"

This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.

- - - - -
a04959b8 by Daneel Yaitskov at 2024-10-19T09:34:15-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949

Check the RTS flag before doing any work with the given lazy string.

Fix #17949

Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
eff16c22 by Matthew Pickering at 2024-10-19T21:55:55-04:00
ci: Add support for ONLY_JOBS variable to trigger any validation pipeline

By setting the ONLY_JOBS variable to the name of the job (or multiple
jobs), the resulting
pipeline will include a validation job for that pipeline.

For example - if you set ONLY_JOBS="x86_64-linux-ubuntu22_04-validate"
then a ubuntu22_04 job will be included in the validation pipeline. This
is useful for testing specific jobs.

Fixes #25332

- - - - -
280b6278 by Zubin Duggal at 2024-10-19T21:56:31-04:00
rel-eng: ghcup metadata generation: generated yaml anchors with meaningful names

(cherry picked from commit d83f5bd730a8aef37d8a38b3560590d9798f8e45)

- - - - -
25edf849 by Alan Zimmerman at 2024-10-19T21:57:08-04:00
EPA: Remove [AddEpAnn] Commit 4

EPA: Remove [AddEpAnn] from DataDecl

This is quite a big change.
The most important part is moving the annotations into HsDataDefn,
using a specific annotation data type.

It has a knock-on to everything that uses HsDataDefn

EPA: Remove [AddEpAnn] for FunDep

EPA: Remove [AddEpann] from FamilyDecl

EPA: Remove [AddEpAnn] From InjectivityAnn

EPA: Remove [AddEpAnn] from DefaultDecl

EPA: Remove [AddEpAnn] from RuleDecls

EPA: Remove [AddEpAnn] from Warnings

- - - - -
d5f42045 by Luite Stegeman at 2024-10-20T16:34:47-04:00
Interpreter: Add locking for communication with external interpreter

This adds locking to communication with the external interpreter
to prevent concurrent tasks interfering with each other. This
fixes Template Haskell with the external interpreter in parallel (-j)
builds.

Fixes #25083

- - - - -
d6bfea76 by Matthew James Kraai at 2024-10-20T16:35:29-04:00
Use monospace font for "Either a b" in fmap docs

The documentation for fmap shows "`Either a b`" in the default font
instead of showing "Either a b" in a monospace font.

- - - - -
4bc7f9c8 by Luite Stegeman at 2024-10-20T16:36:15-04:00
Parser: remove non-ASCII characters from Parser.y

Non-ASCII characters in the source causes a problem with the default
Haskell Language Server setup in VSCode. Two characters seems to have
been left in by accident.

Workaround for #25396

- - - - -
7f61ed4e by Alan Zimmerman at 2024-10-21T06:39:45-04:00
EPA: Remove [AddEpAnn] Commit 5

EPA: Remove [AddEpAnn] from AnnPragma

EPA: Remove [AddEpAnn] From ForeignDecl

EPA: Remove [AddEpAnn] from RoleAnnotDecl

EPA: Remove [AddEpAnn] from StandaloneKindSig

EPA: Remove [AddEpAnn] From HsDeriving

EPA: Remove [AddEpAnn] from ConDeclField

EPA: Remove [AddEpAnn] from ConDeclGADT

EPA: Remove [AddEpAnn] from ConDeclH98

EPA: Remove [AddEpAnn] from ClsInstDecl

- - - - -
f8694fe7 by Cheng Shao at 2024-10-21T06:40:21-04:00
wasm: bump dyld v8 heap size limit

This patch adds `--max-old-space-size=8192` to wasm dyld shebang
arguments to bump V8 heap size limit. The default limit
(`heap_size_limit` returned by `v8.getHeapStatistics()`) is
dynamically determined and a bit too low under certain workloads, and
V8 would waste too much CPU time to garbage collect old generation
heap more aggressively. Bumping the limit to 8G doesn't imply dyld
would really take that much memory at run-time, but it lessens V8 heap
stress significantly.

- - - - -
d328d173 by Luite Stegeman at 2024-10-21T12:39:18+00:00
Add requestTickyCounterSamples to GHC.Internal.Profiling

This allows the user to request ticky counters to be written to
the eventlog at specific times.

See #24645

- - - - -
71765b1d by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Move defaulting code into a new module

GHC.Tc.Solver had reached 4,000 lines -- although quite a lot of them
are comments.

This MR

* Adds the new module GHC.Tc.Solver.Default, which has all the
  complex, but well modularised, defaulting code

* Moves a bit of code from GHC.Tc.Solver into the existing
  GHC.Tc.Solver.Solve. Notably solveWanteds and simplifyWantedsTcM,
  which are called from GHC.Tc.Solver.Default

It's a pure refactor.  No code changes.

- - - - -
a398227b by Simon Peyton Jones at 2024-10-21T20:55:00-04:00
Improve the generalisation code in Solver.simplifyInfer

The code in `decideQuantification` has become quite complicated.
This MR straightens it out, adds a new Note, and on the way
fixes #25266.

See especially Note [decideAndPromoteTyVars] which is is where
all the action happens in this MR.

- - - - -
148059fe by Andrzej Rybczak at 2024-10-21T20:55:40-04:00
Adjust catches to properly rethrow exceptions

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13302 implemented exception
rethrowing proposal, but it didn't adjust `catches`. This fixes it.

- - - - -
25121dbc by doyougnu at 2024-10-22T09:38:18-04:00
linker: add --optimistic-linking flag

This patch adds:

- the --optimistic-linking flag which binds unknown symbols in the
runtime linker to 0xDEADBEEF instead of exiting with failure

- The test T25240 which tests these flags using dead code in the FFI system.

- closes #25240

This patch is part of the upstreaming haskell.nix patches project.

- - - - -
f19e076d by doyougnu at 2024-10-22T09:38:18-04:00
ghc-internal: hide linkerOptimistic in MiscFlags

- - - - -
edc02197 by Cheng Shao at 2024-10-22T09:38:54-04:00
hadrian: fix bindist executable wrapper logic for cross targets

This commit fixes an oversight of hadrian wrapper generation logic:
when doing cross compilation, `wrapper` is called on executable names
with cross prefix, therefore we must use `isSuffixOf` when matching to
take the cross prefix into account. Also add missing cross prefix to
ghci wrapper content and fix hsc2hs wrapper logic.

- - - - -
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.

unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.

This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.

This fixes #25212.

- - - - -
1bdb1317 by Cheng Shao at 2024-10-22T16:31:17-04:00
hadrian: enable late-CCS for perf flavour as well

This patch enables late-CCS for perf flavour so that the testsuite can
pass for perf as well. Fixes #25308.

- - - - -
fde12aba by Cheng Shao at 2024-10-22T16:31:54-04:00
hadrian: make sure ghc-bin internal-interpreter is disabled for stage0 when not cross compiling

This patch disables internal-interpreter flag for stage0 ghc-bin when
not cross compiling, see added comment for explanation. Fixes #25406.

- - - - -
6ab8d751 by ignatiusm at 2024-10-24T01:23:35-04:00
Improve heap overflow exception message (#25198)

Catch heap overflow exceptions and suggest using `+RTS -M<size>`.

Fix #25198

- - - - -
b3f7fb80 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
determinism: Interface re-export list det

In 'DocStructureItem' we want to make sure the 'Avails' are sorted, for
interface file determinism. This commit introduces 'DetOrdAvails', a
newtype that should only be constructed by sorting Avails with
'sortAvails' unless the avails are known to be deterministically
ordered. This newtype is used by 'DocStructureItem' where 'Avails' was
previously used to ensure the list of avails is deterministically sorted
by construction.

Note: Even though we order the constructors and avails in the interface
file, the order of constructors in the haddock output is still
determined from the order of declaration in the source. This was also
true before, when the list of constructors in the interface file <docs>
section was non-deterministic. Some haddock tests such as
"ConstructorArgs" observe this (check the order of constructors in
out/ConstructorArgs.html vs src/ConstructorArgs.hs vs its interface file)

The updated tests are caused by haddock corners where the order in the
source is not preserved (and was non-deterministic before this PR):
    * Module header in the latex backend
    * Re-export of pattern synonyms associated to a datatype (#25342)

Fixes #25304

- - - - -
e39c8c99 by Rodrigo Mesquita at 2024-10-24T01:24:12-04:00
Revert "ci: Allow abi-test to fail."

After #25304, the abi-test with interface and object determinism
succeeds.

This reverts commit 7b37afc9f3e79559055488998ee73187886a0e00.

- - - - -
7b1b0c6d by Alan Zimmerman at 2024-10-24T13:07:02-04:00
EPA: reduce [AddEpann] in AnnList

Remove it from the `al_rest` field, and make `AnnList` parameterized
on a type to be used in `al_rest`, for the various use cases.

- - - - -
4a00731e by Rodrigo Mesquita at 2024-10-24T13:07:38-04:00
Fix -fobject-determinism flag definition

The flag should be defined as an fflag to make sure the
-fno-object-determinism flag is also an available option.

Fixes #25397

- - - - -
55e4b9f2 by Sebastian Graf at 2024-10-25T07:01:54-04:00
CorePrep: Attach evaldUnfolding to floats to detect more values

See `Note [Pin evaluatedness on floats]`.

- - - - -
9f57c96d by Sebastian Graf at 2024-10-25T07:01:54-04:00
Make DataCon workers strict in strict fields (#20749)

This patch tweaks `exprIsConApp_maybe`, `exprIsHNF` and friends, and Demand
Analysis so that they exploit and maintain strictness of DataCon workers. See
`Note [Strict fields in Core]` for details.

Very little needed to change, and it puts field seq insertion done by Tag
Inference into a new perspective: That of *implementing* strict field semantics.
Before Tag Inference, DataCon workers are strict. Afterwards they are
effectively lazy and field seqs happen around use sites. History has shown
that there is no other way to guarantee taggedness and thus the STG Strict Field
Invariant.

Knock-on changes:

  * I reworked the whole narrative around "Tag inference".
    It's now called "EPT enforcement" and I recycyled the different overview
    Notes into `Note [EPT enforcement]`.

  * `exprIsHNF` previously used `exprOkForSpeculation` on unlifted arguments
    instead of recursing into `exprIsHNF`. That regressed the termination
    analysis in CPR analysis (which simply calls out to `exprIsHNF`), so I made
    it call `exprOkForSpeculation`, too.

  * There's a small regression in Demand Analysis, visible in the changed test
    output of T16859: Previously, a field seq on a variable would give that
    variable a "used exactly once" demand, now it's "used at least once",
    because `dmdTransformDataConSig` accounts for future uses of the field
    that actually all go through the case binder (and hence won't re-enter the
    potential thunk). The difference should hardly be observable.

  * The Simplifier's fast path for data constructors only applies to lazy
    data constructors now. I observed regressions involving Data.Binary.Put's
    `Pair` data type.

  * Unfortunately, T21392 does no longer reproduce after this patch, so I marked
    it as "not broken" in order to track whether we regress again in the future.

Fixes #20749, the satisfying conclusion of an annoying saga (cf. the ideas
in #21497 and #22475).

Compiler perf generally improves, sometimes drastically:

                                                     Baseline
                                 Test    Metric          value      New value Change
--------------------------------------------------------------------------------
             ManyConstructors(normal) ghc/alloc  3,629,760,116  3,711,852,800  +2.3%  BAD
  MultiLayerModulesTH_OneShot(normal) ghc/alloc  2,502,735,440  2,565,282,888  +2.5%  BAD
                       T12707(normal) ghc/alloc    804,399,798    791,807,320  -1.6% GOOD
                       T17516(normal) ghc/alloc    964,987,744  1,008,383,520  +4.5%
                       T18140(normal) ghc/alloc     75,381,152     49,860,560 -33.9% GOOD
                      T18698b(normal) ghc/alloc    232,614,457    184,262,736 -20.8% GOOD
                       T18923(normal) ghc/alloc     62,002,368     58,301,408  -6.0% GOOD
                       T20049(normal) ghc/alloc     75,719,168     70,494,368  -6.9% GOOD
                        T3294(normal) ghc/alloc  1,237,925,833  1,157,638,992  -6.5% GOOD
                        T9233(normal) ghc/alloc    686,490,105    635,166,688  -7.5% GOOD

                            geo. mean                                          -0.7%
                            minimum                                           -33.9%
                            maximum                                            +4.5%

I looked at T17516. It seems we do a few more simplifier iterations and end up
with a larger program. It seems that some things inline more, while other things
inline less. I don't see low-hanging fruit.

I also looked at MultiLayerModulesTH_OneShot. It appears we generate a strange
join point in the `getUnique` method of `Uniquable GHC.Unit.Types.Module` that
should better call-site inline, but does not. Perhaps with !11492.

NoFib does not seem affected much either:

+-------------------------------++--+------------+-----------+---------------+-----------+
|                               ||  |      base/ | std. err. | T20749/ (rel) | std. err. |
+===============================++==+============+===========+===============+===========+
|           spectral/last-piece ||  |    7.263e8 |      0.0% |        +0.62% |      0.0% |
+===============================++==+============+===========+===============+===========+
|                     geom mean ||  |     +0.00% |           |               |           |
+-------------------------------++--+------------+-----------+---------------+-----------+

I had a look at last-piece. Nothing changes in stg-final, but there is a bit
of ... movement around Data.Map.insert's use of GHC.Exts.lazy that is gone in
stg-final.

Co-Authored-By: Jaro Reinders <jaro.reinders at gmail.com>

Metric Decrease:
    T12707
    T18140
    T18698b
    T18923
    T19695
    T20049
    T3294
    T9233
    T21839c
Metric Increase:
    ManyConstructors
    MultiLayerModulesTH_OneShot

- - - - -
0225249a by Simon Peyton Jones at 2024-10-25T07:02:32-04:00
Some renaming

This is a pure refactor, tidying up some inconsistent naming:

   isEqPred          -->  isEqClassPred
   isEqPrimPred      -->  isEqPred
   isReprEqPrimPred  -->  isReprEqPred
   mkPrimEqPred      -->  mkNomEqPred
   mkReprPrimEqPred  -->  mkReprEqPred
   mkPrimEqPredRold  -->  mkEqPredRole

Plus I moved mkNomEqPred, mkReprEqPred, mkEqPredRolek
  from GHC.Core.Coercion to GHC.Core.Predicate
where they belong.  That means that Coercion imports Predicate
rather than vice versa -- better.

- - - - -
15a3456b by Ryan Hendrickson at 2024-10-25T07:02:32-04:00
compiler: Fix deriving with method constraints

See Note [Inferred contexts from method constraints]

Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com>

- - - - -
dbc77ce8 by Alan Zimmerman at 2024-10-25T18:20:13+01:00
EPA: Remove AddEpann commit 7

EPA: Remove [AddEpAnn] from HYPHEN in Parser.y

The return value is never used, as it is part of the backpack
configuration parsing.

EPA: Remove last [AddEpAnn] usages

Remove residual usage in GHC. It is still used
- In haddock TTG extension point definitions (to be removed)
- Some check-exact residual, to be removed
- Comments around DisambECP in PostProcess

EPA: Clean up [AddEpAnn] from check-exact

There is one left, to be cleaned up when we remove AddEpann itself

EPA: Remove [AddEpAnn] from haddock

The TTG extension points need a value, it is not critical what that
value is, in most cases.

EPA: Remove AddEpAnn from HsRuleAnn

EPA: Remove AddEpAnn from HsCmdArrApp

- - - - -
23ddcc01 by Simon Peyton Jones at 2024-10-26T12:44:34-04:00
Fix optimisation of InstCo

It turned out (#25387) that the fix to #15725 was not quite right:

  commit 48efbc04bd45d806c52376641e1a7ed7278d1ec7
  Date:   Mon Oct 15 10:25:02 2018 +0200

    Fix #15725 with an extra Sym

Optimising InstCo is quite subtle, and the invariants surrounding
the LiftingContext in the coercion optimiser were not stated explicitly.

This patch refactors the InstCo optimisation, and documents these
invariants.  See
  * Note [Optimising InstCo]
  * Note [The LiftingContext in optCoercion]

I also did some refactoring of course:

* Instead of a Bool swap-flag, I am not using GHC.Types.Basic.SwapFlag

* I added some invariant-checking the coercion-construction functions
  in GHC.Core.Coercion.Opt.  (Sadly these invariants don't hold during
  typechecking, becuase the types are un-zonked, so I can't put these
  checks in GHC.Core.Coercion.)

- - - - -
589fea7f by Cheng Shao at 2024-10-27T05:36:38-04:00
ghcid: use multi repl for ghcid

- - - - -
d52a0475 by Andrew Lelechenko at 2024-10-27T05:37:13-04:00
documentation: add motivating section to Control.Monad.Fix

- - - - -
301c3b54 by Cheng Shao at 2024-10-27T05:37:49-04:00
wasm: fix safari console error message related to import("node:timers")

This patch fixes the wasm backend JSFFI prelude script to avoid
calling `import("node:timers")` on non-deno hosts. Safari doesn't like
it and would print an error message to the console. Fixes
https://gitlab.haskell.org/ghc/ghc-wasm-meta/-/issues/13.

- - - - -
9f02dfb5 by Simon Peyton Jones at 2024-10-27T15:10:08-04:00
Add a missing tidy in UnivCo

We were failing to tidy the argument coercions of a UnivCo, which
led directly to #25391.

The fix is, happily, trivial.

I don't have a small repro case (it came up when building horde-ad,
which uses typechecker plugins).  It should be possible to make a
repro case, by using a plugin (which builds a UnivCo) but I decided
it was not worth the bother. The bug is egregious and easily fixed.

- - - - -
853050c3 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
Bump text submodule to 2.1.2

- - - - -
90746a59 by Andrew Lelechenko at 2024-10-27T15:10:44-04:00
hadrian: allow -Wunused-imports for text package

- - - - -
8a6691c3 by Alan Zimmerman at 2024-10-27T19:44:48+00:00
EPA: Remove AddEpAnn Commit 8/final

EPA: Remove AddEpAnn from AnnList

EPA: Remove AddEpAnn from GrhsAnn

This is the last actual use

EPA: Remove NameAdornment from NameAnn

Also rework AnnContext to use EpToken, and AnnParen

EPA: Remove AddEpAnn.  Final removal

There are now none left, except for in a large note/comment in
PostProcess, describing the historical transition to the
disambiguation infrastructure

- - - - -
d5e7990c by Alan Zimmerman at 2024-10-28T21:41:05+00:00
EPA: Remove AnnKeywordId.

This was used as part of AddEpAnn, and is no longer needed.

Also remove all the haddock comments about which of are attached to
the various parts of the AST.  This is now clearly captured in the
appropriate TTG extension points, and the `ExactPrint.hs` file.

- - - - -
e08b8370 by Serge S. Gulin at 2024-10-29T23:17:01-04:00
JS: Re-add optimization for literal strings in genApp (fixes #23479)

Based on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10588/

Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Andrei Borzenkov <root at sandwitch.dev>
Co-authored-by: Danil Berestov <goosedb at yandex.ru>

-------------------------
Metric Decrease:
    T25046_perf_size_gzip
    size_hello_artifact
    size_hello_artifact_gzip
    size_hello_unicode
    size_hello_unicode_gzip
-------------------------

- - - - -
e3496ef6 by Cheng Shao at 2024-10-29T23:17:37-04:00
compiler: remove unused hscDecls/hscDeclsWithLocation

This patch removes unused `hscDecls`/`hscDeclsWithLocation` functions
from the compiler, to reduce maintenance burden when doing
refactorings related to ghci.

- - - - -
b1eed26f by Cheng Shao at 2024-10-29T23:18:13-04:00
testsuite: add T25414 test case marked as broken

This commit adds T25414 test case to demonstrate #25414. It is marked
as broken and will be fixed by the next commit.

- - - - -
e70009bc by Cheng Shao at 2024-10-29T23:18:13-04:00
driver: fix foreign stub handling logic in hscParsedDecls

This patch fixes foreign stub handling logic in `hscParsedDecls`.
Previously foreign stubs were simply ignored here, so any feature that
involve foreign stubs would not work in ghci (e.g. CApiFFI). The patch
reuses `generateByteCode` logic and eliminates a large chunk of
duplicate logic that implements Core to bytecode generation pipeline
here. Fixes #25414.

- - - - -
14d43e53 by Sjoerd Visscher at 2024-10-31T14:59:21+01:00
Multiplicity annotation on records

- - - - -


20 changed files:

- .ghcid
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- CODEOWNERS
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Wasm.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion.hs-boot


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3449b1297916780bdc977ee88cbe866c9b6f1436...14d43e532f34a4c9fa563db974cb24916a3a2904

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3449b1297916780bdc977ee88cbe866c9b6f1436...14d43e532f34a4c9fa563db974cb24916a3a2904
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 15:18:59 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 31 Oct 2024 11:18:59 -0400
Subject: [Git][ghc/ghc][wip/T18462] Check that mult ann affects constructor
 type
Message-ID: <67239fe319dfd_1582476b6ae81163b9@gitlab.mail>



Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC


Commits:
ad34a8de by Sjoerd Visscher at 2024-10-31T16:18:52+01:00
Check that mult ann affects constructor type

- - - - -


3 changed files:

- + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs
- + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr
- testsuite/tests/linear/should_fail/all.T


Changes:

=====================================
testsuite/tests/linear/should_fail/LinearRecFieldMany.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE LinearTypes, DataKinds #-}
+module LinearRecFieldMany where
+
+import GHC.Exts (Multiplicity(..))
+
+data C = C { urC %'Many :: Int }
+
+test :: Int %1 -> C
+test = C


=====================================
testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr
=====================================
@@ -0,0 +1,6 @@
+LinearRecFieldMany.hs:9:8: [GHC-83865]
+     Couldn't match type ‘Many’ with ‘One’
+      Expected: Int %1 -> C
+        Actual: Int -> C
+     In the expression: C
+      In an equation for ‘test’: test = C


=====================================
testsuite/tests/linear/should_fail/all.T
=====================================
@@ -34,6 +34,7 @@ test('LinearFFI', normal, compile_fail, [''])
 test('LinearTHFail', normal, compile_fail, [''])
 test('LinearTHFail2', normal, compile_fail, [''])
 test('LinearTHFail3', normal, compile_fail, [''])
+test('LinearRecFieldMany', normal, compile_fail, [''])
 test('T18888', normal, compile_fail, [''])
 test('T18888_datakinds', normal, compile_fail, [''])
 test('T19120', normal, compile_fail, [''])



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 16:33:05 2024
From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering))
Date: Thu, 31 Oct 2024 12:33:05 -0400
Subject: [Git][ghc/ghc][wip/splice-imports-2024] 3 commits: levelled eps
Message-ID: <6723b141a908a_2448f5101c38102745@gitlab.mail>



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
d7e7ca31 by Matthew Pickering at 2024-10-30T15:29:07+00:00
levelled eps

- - - - -
de087b5f by Matthew Pickering at 2024-10-30T15:29:12+00:00
Revert "levelled eps"

This reverts commit d7e7ca319c5ab2070629e50963be8b1c9081258c.

- - - - -
3e18b3d7 by Matthew Pickering at 2024-10-31T16:32:31+00:00
instances

- - - - -


11 changed files:

- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Unit/Module/Graph.hs
- ghc/GHCi/UI.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs


Changes:

=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -580,7 +580,7 @@ mkBackpackMsg = do
             NeedsRecompile reason0 -> showMsg (text "Instantiating ") $ case reason0 of
               MustCompile -> empty
               RecompBecause reason -> text " [" <> pprWithUnitState state (ppr reason) <> text "]"
-        ModuleNode _ _ _ ->
+        ModuleNode {} ->
           case recomp of
             UpToDate
               | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping  ") empty
@@ -742,7 +742,7 @@ hsunitModuleGraph do_link unit = do
     --  requirement.
     let hsig_set = Set.fromList
           [ ms_mod_name ms
-          | ModuleNode _ _ ms <- nodes
+          | ModuleNode _ _ _ ms <- nodes
           , ms_hsc_src ms == HsigFile
           ]
     req_nodes <- fmap catMaybes . forM (homeUnitInstantiations home_unit) $ \(mod_name, _) ->
@@ -817,7 +817,7 @@ summariseRequirement pn mod_name = do
         ms_hspp_buf = Nothing
         }
     let nodes = [NodeKey_Module (ModNodeKeyWithUid (GWIB mn NotBoot) todoStage (homeUnitId home_unit)) | mn <- extra_sig_imports ]
-    return (ModuleNode nodes todoStage ms)
+    return (ModuleNode nodes [] todoStage ms)
 
 summariseDecl :: PackageName
               -> HscSource
@@ -935,7 +935,7 @@ hsModuleToModSummary home_keys pn hsc_src modname
           [k | (_, _,  mnwib) <- msDeps ms, let k = NodeKey_Module (ModNodeKeyWithUid (fmap unLoc mnwib) todoStage (moduleUnitId this_mod)), k `elem` home_keys]
 
 
-    return (ModuleNode (mod_nodes ++ inst_nodes) todoStage ms)
+    return (ModuleNode (mod_nodes ++ inst_nodes) [] todoStage ms)
 
 -- | Create a new, externally provided hashed unit id from
 -- a hash.


=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -258,7 +258,7 @@ instance Diagnostic DriverMessage where
              go (m:ms) = (text "which imports" <+> ppr_node m) : go ms
 
         ppr_node :: ModuleGraphNode -> SDoc
-        ppr_node (ModuleNode _deps lvl m) = text "module" <+> ppr_ms m <+> text "@"  <> ppr lvl
+        ppr_node (ModuleNode _deps _uids lvl m) = text "module" <+> ppr_ms m <+> text "@"  <> ppr lvl
         ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u
         ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid)
 


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -831,7 +831,7 @@ hscRecompStatus
   = do
     let
         msg what = case mHscMessage of
-          Just hscMessage -> hscMessage hsc_env mod_index what (ModuleNode [] lvl mod_summary)
+          Just hscMessage -> hscMessage hsc_env mod_index what (ModuleNode [] [] lvl mod_summary)
           Nothing -> return ()
 
     -- First check to see if the interface file agrees with the


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -631,13 +631,13 @@ createBuildPlan mod_graph maybe_top_mod =
 
         -- An environment mapping a module to its hs-boot file and all nodes on the path between the two, if one exists
         boot_modules = mkModuleEnv
-          [ (ms_mod ms, (m, boot_path (ms_mod_name ms) (ms_unitid ms))) | m@(ModuleNode _ lvl ms) <- (mgModSummaries' mod_graph), isBootSummary ms == IsBoot]
+          [ (ms_mod ms, (m, boot_path (ms_mod_name ms) (ms_unitid ms))) | m@(ModuleNode _ _ lvl ms) <- (mgModSummaries' mod_graph), isBootSummary ms == IsBoot]
 
         select_boot_modules :: [ModuleGraphNode] -> [ModuleGraphNode]
         select_boot_modules = mapMaybe (fmap fst . get_boot_module)
 
         get_boot_module :: ModuleGraphNode -> Maybe (ModuleGraphNode, [ModuleGraphNode])
-        get_boot_module m = case m of ModuleNode _ lvl ms | HsSrcFile <- ms_hsc_src ms -> lookupModuleEnv boot_modules (ms_mod ms); _ -> Nothing
+        get_boot_module m = case m of ModuleNode _ _ lvl ms | HsSrcFile <- ms_hsc_src ms -> lookupModuleEnv boot_modules (ms_mod ms); _ -> Nothing
 
         -- Any cycles should be resolved now
         collapseSCC :: [SCC ModuleGraphNode] -> Either [ModuleGraphNode] [(Either ModuleGraphNode ModuleGraphNodeWithBootFile)]
@@ -1153,7 +1153,7 @@ interpretBuildPlan hug mhmi_cache old_hpt plan = do
                   (hug, deps) <- wait_deps_hug hug_var build_deps
                   executeInstantiationNode mod_idx n_mods hug uid iu
                   return (Nothing, deps)
-              ModuleNode _build_deps lvl ms ->
+              ModuleNode _build_deps _uids lvl ms ->
                 let !old_hmi = M.lookup (msKey lvl ms) old_hpt
                     rehydrate_mods = mapMaybe nodeKeyModName <$> rehydrate_nodes
                 in withCurrentUnit (moduleGraphNodeUnitId mod) $ do
@@ -1668,10 +1668,10 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
           = loopSummaries next (done, summarised)
           -- Didn't work out what the imports mean yet, now do that.
           | otherwise = do
-             (final_deps, done', summarised') <- loopImports (calcDeps lvl ms) done summarised
+             (final_deps, uids, done', summarised') <- loopImports (calcDeps lvl ms) done summarised
              -- This has the effect of finding a .hs file if we are looking at the .hs-boot file.
-             (_, done'', summarised'') <- loopImports (maybeToList hs_file_for_boot) done' summarised'
-             loopSummaries next (M.insert k (ModuleNode final_deps lvl ms) done'', summarised'')
+             (_, _, done'', summarised'') <- loopImports (maybeToList hs_file_for_boot) done' summarised'
+             loopSummaries next (M.insert k (ModuleNode final_deps uids lvl ms) done'', summarised'')
           where
             k = NodeKey_Module (msKey lvl ms)
 
@@ -1691,17 +1691,17 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
                         -- Visited set; the range is a list because
                         -- the roots can have the same module names
                         -- if allow_dup_roots is True
-             -> IO ([NodeKey],
+             -> IO ([NodeKey], [(ModuleStage, UnitId)],
                   M.Map NodeKey ModuleGraphNode, DownsweepCache)
                         -- The result is the completed NodeMap
-        loopImports [] done summarised = return ([], done, summarised)
+        loopImports [] done summarised = return ([], [], done, summarised)
         loopImports ((home_uid, lvl, mb_pkg, gwib) : ss) done summarised
           | Just summs <- M.lookup cache_key summarised
           = case summs of
               [Right ms] -> do
                 let nk = NodeKey_Module (msKey lvl ms)
-                (rest, summarised', done') <- loopImports ss done summarised
-                return (nk: rest, summarised', done')
+                (rest, uids, summarised', done') <- loopImports ss done summarised
+                return (nk: rest, uids, summarised', done')
               [Left _err] ->
                 loopImports ss done summarised
               _errs ->  do
@@ -1713,20 +1713,20 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
                                        Nothing excl_mods
                case mb_s of
                    NotThere -> loopImports ss done summarised
-                   External _ -> do
-                    (other_deps, done', summarised') <- loopImports ss done summarised
-                    return (other_deps, done', summarised')
+                   External uid -> do
+                    (other_deps, uids, done', summarised') <- loopImports ss done summarised
+                    return (other_deps, (lvl, uid):uids, done', summarised')
                    FoundInstantiation iud -> do
-                    (other_deps, done', summarised') <- loopImports ss done summarised
-                    return (NodeKey_Unit iud : other_deps, done', summarised')
+                    (other_deps, uids, done', summarised') <- loopImports ss done summarised
+                    return (NodeKey_Unit iud : other_deps, uids,  done', summarised')
                    FoundHomeWithError (_uid, e) ->  loopImports ss done (Map.insert cache_key [(Left e)] summarised)
                    FoundHome s -> do
                      (done', summarised') <-
                        loopSummaries [(lvl, s)] (done, Map.insert cache_key [Right s] summarised)
-                     (other_deps, final_done, final_summarised) <- loopImports ss done' summarised'
+                     (other_deps, uids, final_done, final_summarised) <- loopImports ss done' summarised'
 
                      -- MP: This assumes that we can only instantiate non home units, which is probably fair enough for now.
-                     return (NodeKey_Module (msKey lvl s) : other_deps, final_done, final_summarised)
+                     return (NodeKey_Module (msKey lvl s) : other_deps, uids, final_done, final_summarised)
           where
             cache_key = (home_uid, lvl, mb_pkg, unLoc <$> gwib)
             home_unit = ue_unitHomeUnit home_uid (hsc_unit_env hsc_env)
@@ -1908,7 +1908,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph =
   where
     defaultBackendOf ms = platformDefaultBackend (targetPlatform $ ue_unitFlags (ms_unitid ms) unit_env)
     enable_code_gen :: ModuleGraphNode -> IO ModuleGraphNode
-    enable_code_gen n@(ModuleNode deps lvl ms)
+    enable_code_gen n@(ModuleNode deps uids lvl ms)
       | ModSummary
         { ms_location = ms_location
         , ms_hsc_src = HsSrcFile
@@ -1946,7 +1946,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph =
                      , ms_hspp_opts = updOptLevel 0 $ new_dflags
                      }
                -- Recursive call to catch the other cases
-               enable_code_gen (ModuleNode deps lvl ms')
+               enable_code_gen (ModuleNode deps uids lvl ms')
 
          -- If -fprefer-byte-code then satisfy dependency by enabling bytecode (if normal object not enough)
          -- we only get to this case if the default backend is already generating object files, but we need dynamic
@@ -1956,19 +1956,19 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph =
                      { ms_hspp_opts = gopt_set (ms_hspp_opts ms) Opt_ByteCodeAndObjectCode
                      }
                -- Recursive call to catch the other cases
-               enable_code_gen (ModuleNode deps lvl ms')
+               enable_code_gen (ModuleNode deps uids lvl ms')
          | dynamic_too_enable enable_spec ms -> do
                let ms' = ms
                      { ms_hspp_opts = gopt_set (ms_hspp_opts ms) Opt_BuildDynamicToo
                      }
                -- Recursive call to catch the other cases
-               enable_code_gen (ModuleNode deps lvl ms')
+               enable_code_gen (ModuleNode deps uids lvl ms')
          | ext_interp_enable ms -> do
                let ms' = ms
                      { ms_hspp_opts = gopt_set (ms_hspp_opts ms) Opt_ExternalInterpreter
                      }
                -- Recursive call to catch the other cases
-               enable_code_gen (ModuleNode deps lvl ms')
+               enable_code_gen (ModuleNode deps uids lvl ms')
 
          | otherwise -> return n
 
@@ -2047,7 +2047,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph =
         -- Note we don't need object code for a module if it uses TemplateHaskell itself. Only
         -- it's dependencies.
         [ deps
-        | (ModuleNode deps lvl ms) <- mod_graph
+        | (ModuleNode deps uids lvl ms) <- mod_graph
         , isTemplateHaskellOrQQNonBoot ms
         , not (gopt Opt_UseBytecodeRatherThanObjects (ms_hspp_opts ms))
         ]
@@ -2056,7 +2056,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph =
     need_bc_set =
       concat
         [ deps
-        | (ModuleNode deps lvl ms) <- mod_graph
+        | (ModuleNode deps uids lvl ms) <- mod_graph
         , isTemplateHaskellOrQQNonBoot ms
         , gopt Opt_UseBytecodeRatherThanObjects (ms_hspp_opts ms)
         ]


=====================================
compiler/GHC/Driver/MakeFile.hs
=====================================
@@ -222,7 +222,7 @@ processDeps _ _ _ _ _ (AcyclicSCC (InstantiationNode _uid node))
 
 processDeps _dflags _ _ _ _ (AcyclicSCC (LinkNode {})) = return ()
 
-processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ _ node))
+processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ _ _ node))
   = do  { let extra_suffixes = depSuffixes dflags
               include_pkg_deps = depIncludePkgDeps dflags
               src_file  = msHsFilePath node
@@ -404,10 +404,10 @@ pprCycle :: [ModuleGraphNode] -> SDoc
 pprCycle summaries = pp_group (CyclicSCC summaries)
   where
     cycle_mods :: [ModuleName]  -- The modules in this cycle
-    cycle_mods = map (moduleName . ms_mod) [ms | ModuleNode _ _ ms <- summaries]
+    cycle_mods = map (moduleName . ms_mod) [ms | ModuleNode _ _ _ ms <- summaries]
 
     pp_group :: SCC ModuleGraphNode -> SDoc
-    pp_group (AcyclicSCC (ModuleNode _ _ ms)) = pp_ms ms
+    pp_group (AcyclicSCC (ModuleNode _ _ _ ms)) = pp_ms ms
     pp_group (AcyclicSCC _) = empty
     pp_group (CyclicSCC mss)
         = assert (not (null boot_only)) $
@@ -417,12 +417,12 @@ pprCycle summaries = pp_group (CyclicSCC summaries)
           pp_ms loop_breaker $$ vcat (map pp_group groups)
         where
           (boot_only, others) = partition is_boot_only mss
-          is_boot_only (ModuleNode _ _ ms) = not (any in_group (map (\(_, _, m) -> m) (ms_imps ms)))
+          is_boot_only (ModuleNode _ _ _ ms) = not (any in_group (map (\(_, _, m) -> m) (ms_imps ms)))
           is_boot_only  _ = False
           in_group (L _ m) = m `elem` group_mods
-          group_mods = map (moduleName . ms_mod) [ms | ModuleNode _ _ ms <- mss]
+          group_mods = map (moduleName . ms_mod) [ms | ModuleNode _ _ _ ms <- mss]
 
-          loop_breaker = head ([ms | ModuleNode _ _ ms  <- boot_only])
+          loop_breaker = head ([ms | ModuleNode _ _ _ ms  <- boot_only])
           all_others   = tail boot_only ++ others
           groups =
             GHC.topSortModuleGraph True (mkModuleGraph all_others) Nothing


=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -1276,7 +1276,7 @@ showModule mod_summary =
               case lookupHug (hsc_HUG hsc_env) (ms_unitid mod_summary) (ms_mod_name mod_summary) of
                Nothing       -> panic "missing linkable"
                Just mod_info -> isJust (homeModInfoByteCode mod_info)  && isNothing (homeModInfoObject mod_info)
-        return (showSDoc dflags $ showModMsg dflags interpreted (ModuleNode [] todoStage mod_summary))
+        return (showSDoc dflags $ showModMsg dflags interpreted (ModuleNode [] [] todoStage mod_summary))
 
 moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
 moduleIsBootOrNotObjectLinkable mod_summary = withSession $ \hsc_env ->


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -461,6 +461,7 @@ tcRnImports hsc_env import_decls
                 -- filtering also ensures that we don't see instances from
                 -- modules batch (@--make@) compiled before this one, but
                 -- which are not below this one.
+
               ; (home_inst_bind_env, home_insts, home_fam_insts) =
 
                     hptInstancesBelow hsc_env unitId zeroStage mnwib


=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -187,7 +187,7 @@ import GHC.Types.Unique.Set( elementOfUniqSet )
 import GHC.Types.Name.Env
 import GHC.Types.Id
 
-import GHC.Unit.Module ( HasModule, getModule, extractModule )
+import GHC.Unit.Module
 import qualified GHC.Rename.Env as TcM
 
 import GHC.Utils.Outputable
@@ -216,6 +216,8 @@ import GHC.Data.Graph.Directed
 #endif
 
 import qualified Data.Set as Set
+import qualified Data.Map as Map
+import GHC.Unit.Module.Graph
 
 {- *********************************************************************
 *                                                                      *
@@ -1456,9 +1458,36 @@ checkWellStagedInstanceWhat what
         cur_mod <- extractModule <$> getGblEnv
         gbl_env <- getGblEnv
 --        pprTraceM "checkWellStaged" (ppr what)
+        hsc_env <- getTopEnv
+        let tg = mkTransDepsZero (hsc_units hsc_env) (mgModSummaries' (hsc_mod_graph hsc_env))
+        let lkup s = flip (Map.!) (Left (ModNodeKeyWithUid (GWIB (moduleName cur_mod) NotBoot) zeroStage (moduleUnitId cur_mod), s)) tg
+        let splice_lvl = lkup SpliceStage
+            normal_lvl = lkup NormalStage
+            quote_lvl  = lkup QuoteStage
+
+            name_module = nameModule (idName dfun_id)
+            instance_key = if moduleUnitId name_module `Set.member` hsc_all_home_unit_ids hsc_env
+                             then Left (ModNodeKeyWithUid (GWIB (moduleName name_module) NotBoot) zeroStage (moduleUnitId name_module), NormalStage)
+                             else Right (moduleUnitId name_module)
+
+  {-        pprTraceM "instnace_key" (ppr instance_key)
+        pprTraceM "splice_lvl" (ppr (instance_key `Set.member` splice_lvl))
+        pprTraceM "splice_lvl" (ppr (instance_key `Set.member` normal_lvl))
+        pprTraceM "splice_lvl" (ppr (instance_key `Set.member` quote_lvl))
+        -}
+        let lvls = [ 0 | instance_key `Set.member` splice_lvl]
+                 ++ [ 1 | instance_key `Set.member` normal_lvl ]
+                 ++ [ 2 | instance_key `Set.member` quote_lvl ]
+
+        if isLocalId dfun_id
+          then return $ Just ( (Set.singleton outerLevel, True) )
+          else return $ Just ( Set.fromList lvls, False )
+
+
 --        pprTraceM "checkWellStaged" (ppr (tcg_bind_env gbl_env))
 --        pprTraceM "checkWellStaged"
 --          (ppr (lookupNameEnv   (tcg_bind_env gbl_env) (idName dfun_id)))
+--    {-
         return $ (,isLocalId dfun_id)  <$> (lookupNameEnv   (tcg_bind_env gbl_env) (idName dfun_id))
         return $ case  lookupNameEnv (tcg_bind_env gbl_env) (idName dfun_id) of
           -- The instance comes from HPT imported module
@@ -1470,6 +1499,7 @@ checkWellStagedInstanceWhat what
               -- to deal with splice imports
               else Just ( (Set.fromList [impLevel, outerLevel], False) )
 --        return $ Just (TcM.topIdLvl dfun_id)
+--        -}
   | BuiltinTypeableInstance tc <- what
     = do
         cur_mod <- extractModule <$> getGblEnv


=====================================
compiler/GHC/Unit/Module/Graph.hs
=====================================
@@ -25,16 +25,21 @@ module GHC.Unit.Module.Graph
    , moduleGraphModulesBelow
 
    , moduleGraphNodes
+   , moduleGraphNodesZero
    , SummaryNode
    , summaryNodeSummary
 
    , NodeKey(..)
    , nodeKeyUnitId
    , nodeKeyModName
+   , nodeKeyLevel
    , ModNodeKey
    , mkNodeKey
    , msKey
 
+   , mkTransDepsZero
+
+
 
    , moduleGraphNodeUnitId
 
@@ -83,6 +88,8 @@ import Data.List (sort, nub)
 import GHC.Data.List.SetOps
 import GHC.Stack
 import GHC.Utils.Panic
+import GHC.Unit.State
+import Language.Haskell.Syntax.ImpExp
 
 -- | A '@ModuleGraphNode@' is a node in the '@ModuleGraph@'.
 -- Edges between nodes mark dependencies arising from module imports
@@ -92,7 +99,7 @@ data ModuleGraphNode
   -- (backpack dependencies) with the holes (signatures) of the current package.
   = InstantiationNode UnitId InstantiatedUnit
   -- | There is a module summary node for each module, signature, and boot module being built.
-  | ModuleNode [NodeKey] ModuleStage ModSummary
+  | ModuleNode [NodeKey] [(ModuleStage, UnitId)] ModuleStage ModSummary
   -- | Link nodes are whether are are creating a linked product (ie executable/shared object etc) for a unit.
   | LinkNode [NodeKey] UnitId
 
@@ -102,19 +109,19 @@ moduleGraphNodeModule mgn = ms_mod_name <$> (moduleGraphNodeModSum mgn)
 moduleGraphNodeModSum :: ModuleGraphNode -> Maybe ModSummary
 moduleGraphNodeModSum (InstantiationNode {}) = Nothing
 moduleGraphNodeModSum (LinkNode {})          = Nothing
-moduleGraphNodeModSum (ModuleNode _ _ ms)      = Just ms
+moduleGraphNodeModSum (ModuleNode _ _ _ ms)      = Just ms
 
 moduleGraphNodeUnitId :: ModuleGraphNode -> UnitId
 moduleGraphNodeUnitId mgn =
   case mgn of
     InstantiationNode uid _iud -> uid
-    ModuleNode _ _lvl ms       -> toUnitId (moduleUnit (ms_mod ms))
+    ModuleNode _ _lvl _ ms       -> toUnitId (moduleUnit (ms_mod ms))
     LinkNode _ uid             -> uid
 
 instance Outputable ModuleGraphNode where
   ppr = \case
     InstantiationNode _ iuid -> ppr iuid
-    ModuleNode nks lvl ms -> ppr (msKey lvl ms) <+> ppr nks
+    ModuleNode nks _ lvl ms -> ppr (msKey lvl ms) <+> ppr nks
     LinkNode uid _     -> text "LN:" <+> ppr uid
 
 instance Eq ModuleGraphNode where
@@ -141,6 +148,11 @@ nodeKeyUnitId (NodeKey_Unit iu)   = instUnitInstanceOf iu
 nodeKeyUnitId (NodeKey_Module mk) = mnkUnitId mk
 nodeKeyUnitId (NodeKey_Link uid)  = uid
 
+nodeKeyLevel :: NodeKey -> ModuleStage
+nodeKeyLevel (NodeKey_Unit iud) = zeroStage
+nodeKeyLevel (NodeKey_Module mk) = mnkLevel mk
+nodeKeyLevel (NodeKey_Link uid) = zeroStage
+
 nodeKeyModName :: NodeKey -> Maybe ModuleName
 nodeKeyModName (NodeKey_Module mk) = Just (gwib_mod $ mnkModuleName mk)
 nodeKeyModName _ = Nothing
@@ -194,7 +206,7 @@ mapMG f mg at ModuleGraph{..} = mg
   { mg_mss = flip fmap mg_mss $ \case
       InstantiationNode uid iuid -> InstantiationNode uid iuid
       LinkNode uid nks -> LinkNode uid nks
-      ModuleNode deps lvl ms  -> ModuleNode deps lvl (f ms)
+      ModuleNode deps uid lvl ms  -> ModuleNode deps uid lvl (f ms)
   }
 
 unionMG :: ModuleGraph -> ModuleGraph -> ModuleGraph
@@ -210,7 +222,7 @@ mgTransDeps :: ModuleGraph -> Map.Map NodeKey (Set.Set NodeKey)
 mgTransDeps = mg_trans_deps
 
 mgModSummaries :: ModuleGraph -> [ModSummary]
-mgModSummaries mg = [ m | ModuleNode _ _lvl m <- mgModSummaries' mg ]
+mgModSummaries mg = [ m | ModuleNode _ _ _lvl m <- mgModSummaries' mg ]
 
 mgModSummaries' :: ModuleGraph -> [ModuleGraphNode]
 mgModSummaries' = mg_mss
@@ -222,7 +234,7 @@ mgModSummaries' = mg_mss
 mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
 mgLookupModule ModuleGraph{..} m = listToMaybe $ mapMaybe go mg_mss
   where
-    go (ModuleNode _ _lvl ms)
+    go (ModuleNode _ _ _lvl ms)
       | NotBoot <- isBootSummary ms
       , ms_mod ms == m
       = Just ms
@@ -239,10 +251,10 @@ isTemplateHaskellOrQQNonBoot ms =
 
 -- | Add an ExtendedModSummary to ModuleGraph. Assumes that the new ModSummary is
 -- not an element of the ModuleGraph.
-extendMG :: ModuleGraph -> [NodeKey] -> ModuleStage -> ModSummary -> ModuleGraph
-extendMG ModuleGraph{..} deps lvl ms = ModuleGraph
-  { mg_mss = ModuleNode deps lvl ms : mg_mss
-  , mg_trans_deps = mkTransDeps (ModuleNode deps lvl ms : mg_mss)
+extendMG :: ModuleGraph -> [NodeKey] -> [(ModuleStage, UnitId)] -> ModuleStage -> ModSummary -> ModuleGraph
+extendMG ModuleGraph{..} deps uid lvl ms = ModuleGraph
+  { mg_mss = ModuleNode deps uid lvl ms : mg_mss
+  , mg_trans_deps = mkTransDeps (ModuleNode deps uid lvl ms : mg_mss)
   }
 
 mkTransDeps :: [ModuleGraphNode] -> Map.Map NodeKey (Set.Set NodeKey)
@@ -250,6 +262,11 @@ mkTransDeps mss =
   let (gg, _lookup_node) = moduleGraphNodes False mss
   in allReachable gg (mkNodeKey . node_payload)
 
+mkTransDepsZero :: UnitState -> [ModuleGraphNode] -> Map.Map (Either (ModNodeKeyWithUid, ImportStage) UnitId) (Set.Set (Either (ModNodeKeyWithUid, ImportStage) UnitId))
+mkTransDepsZero us mss =
+  let (gg, _lookup_node) = moduleGraphNodesZero us mss
+  in allReachable gg node_payload
+
 extendMGInst :: ModuleGraph -> UnitId -> InstantiatedUnit -> ModuleGraph
 extendMGInst mg uid depUnitId = mg
   { mg_mss = InstantiationNode uid depUnitId : mg_mss mg
@@ -261,7 +278,7 @@ extendMGLink mg uid nks = mg { mg_mss = LinkNode nks uid : mg_mss mg }
 extendMG' :: ModuleGraph -> ModuleGraphNode -> ModuleGraph
 extendMG' mg = \case
   InstantiationNode uid depUnitId -> extendMGInst mg uid depUnitId
-  ModuleNode deps lvl ms -> extendMG mg deps lvl ms
+  ModuleNode deps uid lvl ms -> extendMG mg deps uid lvl ms
   LinkNode deps uid   -> extendMGLink mg uid deps
 
 mkModuleGraph :: [ModuleGraphNode] -> ModuleGraph
@@ -273,7 +290,7 @@ collapseModuleGraph = mkModuleGraph . collapseModuleGraphNodes . mgModSummaries'
 collapseModuleGraphNodes :: [ModuleGraphNode] -> [ModuleGraphNode]
 collapseModuleGraphNodes m = nub $ map go m
   where
-    go (ModuleNode deps _lvl ms) = ModuleNode (nub $ map collapseNodeKey deps) zeroStage ms
+    go (ModuleNode deps uid _lvl ms) = ModuleNode (nub $ map collapseNodeKey deps) uid zeroStage ms
     go (LinkNode deps uid) = LinkNode (nub $ map collapseNodeKey deps) uid
     go (InstantiationNode uid iuid) = InstantiationNode uid iuid
 
@@ -294,7 +311,7 @@ filterToposortToModules
 filterToposortToModules = mapMaybe $ mapMaybeSCC $ \case
   InstantiationNode _ _ -> Nothing
   LinkNode{} -> Nothing
-  ModuleNode _deps _lvl node -> Just node
+  ModuleNode _deps _uid _lvl node -> Just node
   where
     -- This higher order function is somewhat bogus,
     -- as the definition of "strongly connected component"
@@ -319,7 +336,7 @@ showModMsg dflags _ (LinkNode {}) =
       in text exe_file
 showModMsg _ _ (InstantiationNode _uid indef_unit) =
   ppr $ instUnitInstanceOf indef_unit
-showModMsg dflags recomp (ModuleNode _ lvl mod_summary) =
+showModMsg dflags recomp (ModuleNode _ _  lvl mod_summary) =
   if gopt Opt_HideSourcePaths dflags
       then text mod_str
       else hsep $
@@ -365,7 +382,7 @@ nodeDependencies drop_hs_boot_nodes = \case
     LinkNode deps _uid -> deps
     InstantiationNode uid iuid ->
       NodeKey_Module . (\mod -> ModNodeKeyWithUid (GWIB mod NotBoot) zeroStage uid)  <$> uniqDSetToList (instUnitHoles iuid)
-    ModuleNode deps _lvl _ms ->
+    ModuleNode deps uid _lvl _ms ->
       map drop_hs_boot deps
   where
     -- Drop hs-boot nodes by using HsSrcFile as the key
@@ -390,7 +407,7 @@ moduleGraphNodes drop_hs_boot_nodes summaries =
       where
         go (s, key) =
           case s of
-                ModuleNode __deps _lvl ms | isBootSummary ms == IsBoot, drop_hs_boot_nodes
+                ModuleNode __deps _uid _lvl ms | isBootSummary ms == IsBoot, drop_hs_boot_nodes
                   -- Using nodeDependencies here converts dependencies on other
                   -- boot files to dependencies on dependencies on non-boot files.
                   -> Left (ms_mod ms, nodeDependencies drop_hs_boot_nodes s)
@@ -423,13 +440,103 @@ moduleGraphNodes drop_hs_boot_nodes summaries =
     out_edge_keys = mapMaybe lookup_key
         -- If we want keep_hi_boot_nodes, then we do lookup_key with
         -- IsBoot; else False
+
+
+type ZeroSummaryNode = Node Int (Either (ModNodeKeyWithUid, ImportStage) UnitId)
+
+zeroSummaryNodeKey :: ZeroSummaryNode -> Int
+zeroSummaryNodeKey = node_key
+
+zeroSummaryNodeSummary :: ZeroSummaryNode -> Either (ModNodeKeyWithUid, ImportStage) UnitId
+zeroSummaryNodeSummary = node_payload
+
+-- | Turn a list of graph nodes into an efficient queriable graph.
+-- The first boolean parameter indicates whether nodes corresponding to hs-boot files
+-- should be collapsed into their relevant hs nodes.
+--
+-- This graph only has edges between level-0 imports
+--
+--
+-- This query answers the question. If I am looking at level n in module M then which
+-- modules are visible?
+--
+-- If you are looking at level -1  then the reachable modules are those imported at splice and
+-- then any modules those modules import at zero. (Ie the zero scope for those modules)
+moduleGraphNodesZero ::
+  UnitState
+  -> [ModuleGraphNode]
+  -> (Graph ZeroSummaryNode, Either (ModNodeKeyWithUid, ImportStage) UnitId -> Maybe ZeroSummaryNode)
+moduleGraphNodesZero us summaries =
+  (graphFromEdgedVerticesUniq nodes, lookup_node)
+  where
+    -- Map from module to extra boot summary dependencies which need to be merged in
+    (nodes) = mapMaybe go numbered_summaries
+
+      where
+        go :: ((Either (ModuleGraphNode, ImportStage) (UnitId, [UnitId])), Int) -> Maybe ZeroSummaryNode
+        go (s, key) = normal_case s
+          where
+           normal_case :: Either (ModuleGraphNode, ImportStage) (UnitId, [UnitId]) -> Maybe ZeroSummaryNode
+           normal_case (Left ((ModuleNode nks uids lvl ms), s)) = Just $
+                  DigraphNode (Left (msKey lvl ms, s)) key $ out_edge_keys (jimmy_lvl lvl s) $
+                       ((map Left $ only_module_deps nks)
+                        ++ (map Right uids))
+           normal_case (Right (u, us)) =
+             Just $ DigraphNode (Right u) key (mapMaybe lookup_key $ map Right us)
+           normal_case _ = Nothing
+
+    only_module_deps ds = pprTraceIt "only_module" [ k | NodeKey_Module k <- ds ]
+
+    jimmy_lvl l s = case s of
+                      NormalStage -> l
+                      QuoteStage -> incModuleStage l
+                      SpliceStage -> decModuleStage l
+
+    numbered_summaries :: [(Either (ModuleGraphNode, ImportStage) (UnitId, [UnitId]), Int)]
+    numbered_summaries = zip (([Left (s, l) | s <- summaries, l <- [SpliceStage, QuoteStage, NormalStage]]) ++ map Right (Map.toList all_unit_depends)) [1..]
+
+    all_unit_depends :: Map.Map UnitId [UnitId]
+    all_unit_depends = foldr (\m cache -> go cache (unit_depends m)) Map.empty summaries
+      where
+
+        go cache [] = cache
+        go cache (u:uxs) =
+          case Map.lookup u cache of
+            Just {} -> cache
+            Nothing -> case unitDepends <$> lookupUnitId us u of
+                          Just us -> go (go (Map.insert u us cache) us) uxs
+                          Nothing -> panic "bad"
+
+
+    unit_depends :: ModuleGraphNode -> [UnitId]
+    unit_depends (ModuleNode _ uids _ _) = map snd $ filter ((== zeroStage) . fst) uids
+    unit_depends _ = []
+
+    lookup_node :: Either (ModNodeKeyWithUid, ImportStage) UnitId -> Maybe ZeroSummaryNode
+    lookup_node key = Map.lookup key node_map
+
+    lookup_key :: Either (ModNodeKeyWithUid, ImportStage) UnitId -> Maybe Int
+    lookup_key = fmap zeroSummaryNodeKey . lookup_node
+
+    node_map :: Map.Map (Either (ModNodeKeyWithUid, ImportStage) UnitId) ZeroSummaryNode
+    node_map =
+      Map.fromList [ (s, node)
+                   | node <- nodes
+                   , let s = zeroSummaryNodeSummary node
+                   ]
+
+    out_edge_keys :: ModuleStage -> [Either ModNodeKeyWithUid (ModuleStage, UnitId)] -> [Int]
+    out_edge_keys m = mapMaybe lookup_key . map (bimap (, NormalStage) snd) . filter (either (\nk -> mnkLevel nk == m) ((== m) . fst))
+        -- If we want keep_hi_boot_nodes, then we do lookup_key with
+        -- IsBoot; else False
+
 newtype NodeMap a = NodeMap { unNodeMap :: Map.Map NodeKey a }
   deriving (Functor, Traversable, Foldable)
 
 mkNodeKey :: ModuleGraphNode -> NodeKey
 mkNodeKey = \case
   InstantiationNode _ iu -> NodeKey_Unit iu
-  ModuleNode _ lvl x -> NodeKey_Module $ msKey lvl x
+  ModuleNode _ _ lvl x -> NodeKey_Module $ msKey lvl x
   LinkNode _ uid   -> NodeKey_Link uid
 
 msKey :: ModuleStage -> ModSummary -> ModNodeKeyWithUid


=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1748,7 +1748,7 @@ editFile str =
 -- of those.
 chooseEditFile :: GHC.GhcMonad m => m String
 chooseEditFile =
-  do let hasFailed (GHC.ModuleNode _deps _ x) = fmap not $ isLoadedModSummary x
+  do let hasFailed (GHC.ModuleNode _deps _ _ x) = fmap not $ isLoadedModSummary x
          hasFailed _ = return False
 
      graph <- GHC.getModuleGraph
@@ -2200,7 +2200,7 @@ setContextAfterLoad keep_ctxt (Just graph) = do
         (m:_) ->
           load_this m
  where
-   is_loaded (GHC.ModuleNode _ _ ms) = isLoadedModSummary ms
+   is_loaded (GHC.ModuleNode _ _ _ ms) = isLoadedModSummary ms
    is_loaded _ = return False
 
    findTarget mds t
@@ -2208,9 +2208,9 @@ setContextAfterLoad keep_ctxt (Just graph) = do
         []    -> Nothing
         (m:_) -> Just m
 
-   (GHC.ModuleNode _ _ summary) `matches` Target { targetId = TargetModule m }
+   (GHC.ModuleNode _ _ _ summary) `matches` Target { targetId = TargetModule m }
         = if GHC.ms_mod_name summary == m then Just summary else Nothing
-   (GHC.ModuleNode _ _ summary) `matches` Target { targetId = TargetFile f _ }
+   (GHC.ModuleNode _ _  _ summary) `matches` Target { targetId = TargetFile f _ }
         | Just f' <- GHC.ml_hs_file (GHC.ms_location summary)   =
           if f == f' then Just summary else Nothing
    _ `matches` _ = Nothing


=====================================
utils/haddock/haddock-api/src/Haddock/Interface.hs
=====================================
@@ -223,7 +223,7 @@ createIfaces verbosity modules flags instIfaceMap = do
       -- but if module A {-# SOURCE #-} imports B, then we can't say the same.
       --
   let
-      go (AcyclicSCC (ModuleNode _ _ ms))
+      go (AcyclicSCC (ModuleNode _ _ _ ms))
         | NotBoot <- isBootSummary ms = [ms]
         | otherwise = []
       go (AcyclicSCC _) = []



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/448086cf11757197607b892c24b4c40622dd332f...3e18b3d7eb33dc964df728ab18bb10e5853dbeaa

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/448086cf11757197607b892c24b4c40622dd332f...3e18b3d7eb33dc964df728ab18bb10e5853dbeaa
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 16:57:01 2024
From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes))
Date: Thu, 31 Oct 2024 12:57:01 -0400
Subject: [Git][ghc/ghc][wip/romes/9557] 4 commits: Improve performance of
 deriving Show
Message-ID: <6723b6dd7bdbb_1a365f103df85864c@gitlab.mail>



Rodrigo Mesquita pushed to branch wip/romes/9557 at Glasgow Haskell Compiler / GHC


Commits:
897cb370 by Rodrigo Mesquita at 2024-10-31T16:56:42+00:00
Improve performance of deriving Show

Significantly improves performance of deriving Show instances by
avoiding using the very polymorphic `.` operator in favour of inlining
its definition. We were generating tons of applications of it, each
which had 3 type arguments!

Improves on #9557

-------------------------
Metric Decrease:
    T12707
    T3294
------------------------

- - - - -
8d323240 by Rodrigo Mesquita at 2024-10-31T16:56:42+00:00
Deriving Ord: compare and <= only

Since the implementation of CLC proposal #24, the default
implementations of Ord's `<`, `>`, and `>=` are given in terms of `<=`.

This means we no longer need to generate implementations for these
methods when stock deriving `Ord`. Rather, just derive the
implementation of `compare` and `<=`, and rely on the default
implementations for the others.

- - - - -
d151dc8e by Rodrigo Mesquita at 2024-10-31T16:56:42+00:00
Don't eta expand cons when deriving Data

This eta expansion was introduced with the initial commit for Linear
types.

I believe this isn't needed any longer. My guess is it is an artifact
from the initial linear types implementation: data constructors are
linear, but they shouldn't need to be eta expanded to be used as higher
order functions. I suppose in the early days this wasn't true.

For instance, this works now:

    data T x = T x
    f = \(x :: forall y. y -> T y) -> x True
    f T -- ok!

T is linear, but can be passed where an unrestricted higher order
function is expected. I recall there being some magic around to make
this work for data constructors...

Since this works, there's no need to eta_expand the data constructors in
the derived Data instances.

- - - - -
2a72bb94 by Rodrigo Mesquita at 2024-10-31T16:56:42+00:00
deriving Traversable: Eta reduce more constructor

We were generating unnecessarily eta-expanded lambdas in derived
Traversable instances (via mkSimpleConMatch2).

We can generate smaller code by eta-reducing all trailing arguments
which do mention the last type variable

- - - - -


9 changed files:

- compiler/GHC/Hs/Utils.hs
- compiler/GHC/Tc/Deriv/Functor.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/deriving/should_compile/T20496.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/driver/implicit-dyn-too/implicit-dyn-too.stdout
- testsuite/tests/typecheck/should_fail/T15883d.stderr
- testsuite/tests/typecheck/should_fail/T15883e.stderr


Changes:

=====================================
compiler/GHC/Hs/Utils.hs
=====================================
@@ -56,7 +56,7 @@ module GHC.Hs.Utils(
   nlHsTyApp, nlHsTyApps, nlHsVar, nlHsDataCon,
   nlHsLit, nlHsApp, nlHsApps, nlHsSyntaxApps,
   nlHsIntLit, nlHsVarApps,
-  nlHsDo, nlHsOpApp, nlHsPar, nlHsIf, nlHsCase, nlList,
+  nlHsDo, nlHsOpApp, nlHsLam, nlHsPar, nlHsIf, nlHsCase, nlList,
   mkLHsTupleExpr, mkLHsVarTuple, missingTupArg,
   mkLocatedList, nlAscribe,
 
@@ -598,11 +598,15 @@ nlHsDo ctxt stmts = noLocA (mkHsDo ctxt (noLocA stmts))
 nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
 nlHsOpApp e1 op e2 = noLocA (mkHsOpApp e1 op e2)
 
+nlHsLam  :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
 nlHsPar  :: IsPass p => LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
 nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)]
          -> LHsExpr GhcPs
 nlList   :: [LHsExpr GhcPs] -> LHsExpr GhcPs
 
+nlHsLam match = noLocA $ HsLam noAnn LamSingle
+                  $ mkMatchGroup (Generated OtherExpansion SkipPmc) (noLocA [match])
+
 nlHsPar e     = noLocA (gHsPar e)
 
 -- nlHsIf should generate if-expressions which are NOT subject to


=====================================
compiler/GHC/Tc/Deriv/Functor.hs
=====================================
@@ -689,9 +689,16 @@ mkSimpleConMatch2 ctxt fold extra_pats con insides = do
         con_expr
           | null asWithTyVar = nlHsApps con_name asWithoutTyVar
           | otherwise =
-              let bs   = filterByList  argTysTyVarInfo bs_RDRs
-                  vars = filterByLists argTysTyVarInfo bs_Vars as_Vars
-              in mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
+              let -- All trailing b-args can be eta-reduced:
+                  -- (\b1 b2 b3 -> A b1 a2 b2 b3) ==> (\b1 -> A b1 a2)
+                  -- We do this by counting the n of args to keep
+                  keep_n = length $ dropWhile (== True) $ reverse argTysTyVarInfo
+                  bs   = filterByList (take keep_n argTysTyVarInfo) bs_RDRs
+                  vars = take keep_n $
+                         filterByLists argTysTyVarInfo bs_Vars as_Vars
+               in if keep_n == 0
+                    then nlHsVar con_name
+                    else mkHsLam (noLocA (map nlVarPat bs)) (nlHsApps con_name vars)
 
     rhs <- fold con_expr exps
     return $ mkMatch ctxt (noLocA (extra_pats ++ [pat])) rhs emptyLocalBinds


=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -339,7 +339,7 @@ Several special cases:
   See function unliftedOrdOp
 
 Note [Game plan for deriving Ord]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 It's a bad idea to define only 'compare', and build the other binary
 comparisons on top of it; see #2130, #4019.  Reason: we don't
 want to laboriously make a three-way comparison, only to extract a
@@ -350,16 +350,22 @@ binary result, something like this:
                                        True  -> False
                                        False -> True
 
-This being said, we can get away with generating full code only for
-'compare' and '<' thus saving us generation of other three operators.
-Other operators can be cheaply expressed through '<':
-a <= b = not $ b < a
-a > b = b < a
-a >= b = not $ a < b
-
 So for sufficiently small types (few constructors, or all nullary)
 we generate all methods; for large ones we just use 'compare'.
 
+This being said, we can get away with generating full code only for
+'compare' and '<=' thus saving us generation of other three operators.
+Other operators can be cheaply expressed through '<=' -- indeed, that's what
+the default implementations of >, <, and >= do.
+
+Historically, derived instances defined '<' and the remaining operators as
+cheap expressions in function of it:
+  a <= b = not $ b < a
+  a > b = b < a
+  a >= b = not $ a < b
+but since the CLC proposal #24 (see 8f174e06185143674d6cbfee75c30e68805d85b8),
+it suffices to derive '<=' and rely on the
+default implementation for the others.
 -}
 
 data OrdOp = OrdCompare | OrdLT | OrdLE | OrdGE | OrdGT
@@ -417,19 +423,10 @@ gen_Ord_binds loc dit@(DerivInstTys{ dit_rep_tc = tycon
     other_ops
       | (last_tag - first_tag) <= 2     -- 1-3 constructors
         || null non_nullary_cons        -- Or it's an enumeration
-      = [mkOrdOp OrdLT, lE, gT, gE]
+      = [mkOrdOp OrdLE]
       | otherwise
       = []
 
-    negate_expr = nlHsApp (nlHsVar not_RDR)
-    pats = noLocA [a_Pat, b_Pat]
-    lE = mkSimpleGeneratedFunBind loc le_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr)
-    gT = mkSimpleGeneratedFunBind loc gt_RDR pats $
-        nlHsApp (nlHsApp (nlHsVar lt_RDR) b_Expr) a_Expr
-    gE = mkSimpleGeneratedFunBind loc ge_RDR pats $
-        negate_expr (nlHsApp (nlHsApp (nlHsVar lt_RDR) a_Expr) b_Expr)
-
     get_tag con = dataConTag con - fIRST_TAG
         -- We want *zero-based* tags, because that's what
         -- con2Tag returns (generated by untag_Expr)!
@@ -1407,7 +1404,7 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gfoldl_eqn con
       = ([nlVarPat k_RDR, z_Pat, nlConVarPat con_name as_needed],
-                   foldl' mk_k_app (z_Expr `nlHsApp` (eta_expand_data_con con)) as_needed)
+                   foldl' mk_k_app (z_Expr `nlHsApp` (nlHsVar (getRdrName con))) as_needed)
                    where
                      con_name ::  RdrName
                      con_name = getRdrName con
@@ -1427,16 +1424,17 @@ gen_Data_binds loc (DerivInstTys{dit_rep_tc = rep_tc})
 
     gunfold_alt dc = mkHsCaseAlt (mk_unfold_pat dc) (mk_unfold_rhs dc)
     mk_unfold_rhs dc = foldr nlHsApp
-                           (z_Expr `nlHsApp` (eta_expand_data_con dc))
+                           (z_Expr `nlHsApp` (nlHsVar (getRdrName dc)))
                            (replicate (dataConSourceArity dc) (nlHsVar k_RDR))
 
-    eta_expand_data_con dc =
-        mkHsLam (noLocA eta_expand_pats)
-          (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
-      where
-        eta_expand_pats = map nlVarPat eta_expand_vars
-        eta_expand_hsvars = map nlHsVar eta_expand_vars
-        eta_expand_vars = take (dataConSourceArity dc) as_RDRs
+    -- This was needed by the original implementation of Linear Types. But not anymore...?
+    -- eta_expand_data_con dc =
+    --     mkHsLam (noLocA eta_expand_pats)
+    --       (foldl nlHsApp (nlHsVar (getRdrName dc)) eta_expand_hsvars)
+      -- where
+      --   eta_expand_pats = map nlVarPat eta_expand_vars
+      --   eta_expand_hsvars = map nlHsVar eta_expand_vars
+      --   eta_expand_vars = take (dataConSourceArity dc) as_RDRs
 
 
     mk_unfold_pat dc    -- Last one is a wild-pat, to avoid
@@ -2528,11 +2526,14 @@ showParen_Expr
 showParen_Expr e1 e2 = nlHsApp (nlHsApp (nlHsVar showParen_RDR) e1) e2
 
 nested_compose_Expr :: [LHsExpr GhcPs] -> LHsExpr GhcPs
-
-nested_compose_Expr []  = panic "nested_compose_expr"   -- Arg is always non-empty
-nested_compose_Expr [e] = parenify e
-nested_compose_Expr (e:es)
-  = nlHsApp (nlHsApp (nlHsVar compose_RDR) (parenify e)) (nested_compose_Expr es)
+nested_compose_Expr =
+  nlHsLam . mkSimpleMatch (LamAlt LamSingle) (noLocA [z_Pat]) . go
+  where
+    -- Inlined nested applications of (`.`) to speed up deriving!
+    go []  = panic "nested_compose_expr"   -- Arg is always non-empty
+    go [e] = nlHsApp (parenify e) z_Expr
+    go (e:es)
+      = nlHsApp (parenify e) (go es)
 
 -- impossible_Expr is used in case RHSs that should never happen.
 -- We generate these to keep the desugarer from complaining that they *might* happen!
@@ -2570,10 +2571,10 @@ as_RDRs         = [ mkVarUnqual (mkFastString ("a"++show i)) | i <- [(1::Int) ..
 bs_RDRs         = [ mkVarUnqual (mkFastString ("b"++show i)) | i <- [(1::Int) .. ] ]
 cs_RDRs         = [ mkVarUnqual (mkFastString ("c"++show i)) | i <- [(1::Int) .. ] ]
 
-a_Expr, b_Expr, c_Expr, z_Expr, ltTag_Expr, eqTag_Expr, gtTag_Expr, false_Expr,
+a_Expr, {- b_Expr, -} c_Expr, z_Expr, ltTag_Expr, eqTag_Expr, gtTag_Expr, false_Expr,
     true_Expr, pure_Expr, unsafeCodeCoerce_Expr :: LHsExpr GhcPs
 a_Expr                = nlHsVar a_RDR
-b_Expr                = nlHsVar b_RDR
+-- b_Expr                = nlHsVar b_RDR
 c_Expr                = nlHsVar c_RDR
 z_Expr                = nlHsVar z_RDR
 ltTag_Expr            = nlHsVar ltTag_RDR


=====================================
testsuite/tests/deriving/should_compile/T14682.stderr
=====================================
@@ -5,12 +5,11 @@ Derived class instances:
     GHC.Internal.Show.showsPrec a (T14682.Foo b1 b2)
       = GHC.Internal.Show.showParen
           (a GHC.Classes.>= 11)
-          ((GHC.Internal.Base..)
-             (GHC.Internal.Show.showString "Foo ")
-             ((GHC.Internal.Base..)
-                (GHC.Internal.Show.showsPrec 11 b1)
-                ((GHC.Internal.Base..)
-                   GHC.Internal.Show.showSpace (GHC.Internal.Show.showsPrec 11 b2))))
+          (\ z
+             -> (GHC.Internal.Show.showString "Foo ")
+                  ((GHC.Internal.Show.showsPrec 11 b1)
+                     (GHC.Internal.Show.showSpace
+                        ((GHC.Internal.Show.showsPrec 11 b2) z))))
   
   instance GHC.Internal.TH.Lift.Lift T14682.Foo where
     GHC.Internal.TH.Lift.lift (T14682.Foo a1 a2)
@@ -25,9 +24,8 @@ Derived class instances:
   
   instance GHC.Internal.Data.Data.Data T14682.Foo where
     GHC.Internal.Data.Data.gfoldl k z (T14682.Foo a1 a2)
-      = ((z (\ a1 a2 -> T14682.Foo a1 a2) `k` a1) `k` a2)
-    GHC.Internal.Data.Data.gunfold k z _
-      = k (k (z (\ a1 a2 -> T14682.Foo a1 a2)))
+      = ((z T14682.Foo `k` a1) `k` a2)
+    GHC.Internal.Data.Data.gunfold k z _ = k (k (z T14682.Foo))
     GHC.Internal.Data.Data.toConstr (T14682.Foo _ _) = $cFoo
     GHC.Internal.Data.Data.dataTypeOf _ = $tFoo
   


=====================================
testsuite/tests/deriving/should_compile/T20496.stderr
=====================================
@@ -32,5 +32,5 @@ rnd
     null (MkT _) = False
   
   instance Traversable T where
-    traverse f (MkT a1) = fmap (\ b1 -> MkT b1) (f a1)
+    traverse f (MkT a1) = fmap MkT (f a1)
 


=====================================
testsuite/tests/deriving/should_run/T9576.stderr
=====================================
@@ -2,11 +2,11 @@ T9576: Exception:
 
 T9576.hs:6:31: error: [GHC-39999]
     • No instance for ‘Show Foo’ arising from a use of ‘showsPrec’
-    • In the second argument of ‘(.)’, namely ‘(showsPrec 11 b1)’
+    • In the second argument of ‘showString’, namely
+        ‘((showsPrec 11 b1) z)’
+      In the expression: (showString "MkBar ") ((showsPrec 11 b1) z)
       In the second argument of ‘showParen’, namely
-        ‘((.) (showString "MkBar ") (showsPrec 11 b1))’
-      In the expression:
-        showParen (a >= 11) ((.) (showString "MkBar ") (showsPrec 11 b1))
+        ‘(\ z -> (showString "MkBar ") ((showsPrec 11 b1) z))’
       When typechecking the code for ‘showsPrec’
         in a derived instance for ‘Show Bar’:
         To see the code I am typechecking, use -ddump-deriv
@@ -17,9 +17,7 @@ Module: GHC.Internal.Control.Exception.Base
 Type: TypeError
 
 HasCallStack backtrace:
-    collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
-    toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:84:32 in ghc-internal:GHC.Internal.Exception
-    throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:423:30 in ghc-internal:GHC.Internal.Control.Exception.Base
-
-
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:169:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:89:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
 


=====================================
testsuite/tests/driver/implicit-dyn-too/implicit-dyn-too.stdout
=====================================
@@ -1,4 +1,3 @@
 [1 of 2] Compiling QuasiExpr        ( QuasiExpr.hs, QuasiExpr.o, QuasiExpr.dyn_o )
 [2 of 2] Compiling QuasiQuote       ( QuasiQuote.hs, nothing )
 [1 of 2] Compiling QuasiExpr        ( QuasiExpr.hs, QuasiExpr.o, QuasiExpr.dyn_o ) [Missing dynamic object file]
-[2 of 2] Compiling QuasiQuote       ( QuasiQuote.hs, nothing ) [QuasiExpr[TH] changed]


=====================================
testsuite/tests/typecheck/should_fail/T15883d.stderr
=====================================
@@ -1,4 +1,3 @@
-
 T15883d.hs:14:1: error: [GHC-39999]
     • Ambiguous type variable ‘a0’ arising from a use of ‘showsPrec’
       prevents the constraint ‘(Show a0)’ from being solved.
@@ -9,11 +8,12 @@ T15883d.hs:14:1: error: [GHC-39999]
         ...plus 29 others
         ...plus 10 instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
-    • In the second argument of ‘(.)’, namely ‘(showsPrec 11 b1)’
+    • In the second argument of ‘showString’, namely
+        ‘((showsPrec 11 b1) z)’
+      In the expression: (showString "MkFoo ") ((showsPrec 11 b1) z)
       In the second argument of ‘showParen’, namely
-        ‘((.) (showString "MkFoo ") (showsPrec 11 b1))’
-      In the expression:
-        showParen (a >= 11) ((.) (showString "MkFoo ") (showsPrec 11 b1))
+        ‘(\ z -> (showString "MkFoo ") ((showsPrec 11 b1) z))’
       When typechecking the code for ‘showsPrec’
         in a derived instance for ‘Show (Foo LiftedRep)’:
         To see the code I am typechecking, use -ddump-deriv
+


=====================================
testsuite/tests/typecheck/should_fail/T15883e.stderr
=====================================
@@ -1,71 +1,26 @@
-
-T15883e.hs:16:1: error: [GHC-39999]
-    • Ambiguous type variable ‘d0’ arising from a use of ‘k’
-      prevents the constraint ‘(Data d0)’ from being solved.
-      Probable fix: use a type annotation to specify what ‘d0’ should be.
-      Potentially matching instances:
-        instance (Data a, Data b) => Data (Either a b)
-          -- Defined in ‘GHC.Internal.Data.Data’
-        instance Data a => Data (Down a)
-          -- Defined in ‘GHC.Internal.Data.Data’
-        ...plus 20 others
-        ...plus 47 instances involving out-of-scope types
-        (use -fprint-potential-instances to see them all)
-    • In the expression: z (\ a1 -> MkFoo a1) `k` a1
-      In an equation for ‘GHC.Internal.Data.Data.gfoldl’:
-          GHC.Internal.Data.Data.gfoldl k z (MkFoo a1)
-            = (z (\ a1 -> MkFoo a1) `k` a1)
-      When typechecking the code for ‘GHC.Internal.Data.Data.gfoldl’
-        in a derived instance for ‘Data (Foo LiftedRep)’:
-        To see the code I am typechecking, use -ddump-deriv
-      In the instance declaration for ‘Data (Foo LiftedRep)’
-
-T15883e.hs:16:1: error: [GHC-46956]
-    • Couldn't match expected type ‘a’ with actual type ‘d0’
-        because type variable ‘a’ would escape its scope
-      This (rigid, skolem) type variable is bound by
-        a type expected by the context:
-          forall a. a
-        at T15883e.hs:16:1-52
-    • In the first argument of ‘MkFoo’, namely ‘a1’
-      In the expression: MkFoo a1
-      In the first argument of ‘z’, namely ‘(\ a1 -> MkFoo a1)’
+T15883e.hs:16:1: error: [GHC-91028]
+    • Couldn't match type ‘d0’ with ‘forall a. a’
+      Expected: d0 -> Foo LiftedRep
+        Actual: (forall a. a) -> Foo LiftedRep
+      Cannot instantiate unification variable ‘d0’
+      with a type involving polytypes: forall a. a
+    • In the first argument of ‘z’, namely ‘MkFoo’
+      In the first argument of ‘k’, namely ‘z MkFoo’
+      In the expression: z MkFoo `k` a1
       When typechecking the code for ‘GHC.Internal.Data.Data.gfoldl’
         in a derived instance for ‘Data (Foo LiftedRep)’:
         To see the code I am typechecking, use -ddump-deriv
-    • Relevant bindings include a1 :: d0 (bound at T15883e.hs:16:1)
 
-T15883e.hs:16:1: error: [GHC-39999]
-    • Ambiguous type variable ‘b0’ arising from a use of ‘k’
-      prevents the constraint ‘(Data b0)’ from being solved.
-      Probable fix: use a type annotation to specify what ‘b0’ should be.
-      Potentially matching instances:
-        instance (Data a, Data b) => Data (Either a b)
-          -- Defined in ‘GHC.Internal.Data.Data’
-        instance Data a => Data (Down a)
-          -- Defined in ‘GHC.Internal.Data.Data’
-        ...plus 20 others
-        ...plus 47 instances involving out-of-scope types
-        (use -fprint-potential-instances to see them all)
-    • In the expression: k (z (\ a1 -> MkFoo a1))
-      In an equation for ‘GHC.Internal.Data.Data.gunfold’:
-          GHC.Internal.Data.Data.gunfold k z _ = k (z (\ a1 -> MkFoo a1))
+T15883e.hs:16:1: error: [GHC-91028]
+    • Couldn't match type ‘b0’ with ‘forall a. a’
+      Expected: b0 -> Foo LiftedRep
+        Actual: (forall a. a) -> Foo LiftedRep
+      Cannot instantiate unification variable ‘b0’
+      with a type involving polytypes: forall a. a
+    • In the first argument of ‘z’, namely ‘MkFoo’
+      In the first argument of ‘k’, namely ‘(z MkFoo)’
+      In the expression: k (z MkFoo)
       When typechecking the code for ‘GHC.Internal.Data.Data.gunfold’
         in a derived instance for ‘Data (Foo LiftedRep)’:
         To see the code I am typechecking, use -ddump-deriv
-      In the instance declaration for ‘Data (Foo LiftedRep)’
 
-T15883e.hs:16:1: error: [GHC-46956]
-    • Couldn't match expected type ‘a’ with actual type ‘b0’
-        because type variable ‘a’ would escape its scope
-      This (rigid, skolem) type variable is bound by
-        a type expected by the context:
-          forall a. a
-        at T15883e.hs:16:1-52
-    • In the first argument of ‘MkFoo’, namely ‘a1’
-      In the expression: MkFoo a1
-      In the first argument of ‘z’, namely ‘(\ a1 -> MkFoo a1)’
-      When typechecking the code for ‘GHC.Internal.Data.Data.gunfold’
-        in a derived instance for ‘Data (Foo LiftedRep)’:
-        To see the code I am typechecking, use -ddump-deriv
-    • Relevant bindings include a1 :: b0 (bound at T15883e.hs:16:1)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5845212f06c5c6186f9ca492ccd6a3dbe893a19...2a72bb94719a4c16d65dfe92a9aacf7cffb8e712

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5845212f06c5c6186f9ca492ccd6a3dbe893a19...2a72bb94719a4c16d65dfe92a9aacf7cffb8e712
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 17:41:59 2024
From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj))
Date: Thu, 31 Oct 2024 13:41:59 -0400
Subject: [Git][ghc/ghc][wip/T20264] more progress
Message-ID: <6723c167b0f9c_1a365f2bc80c646aa@gitlab.mail>



Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC


Commits:
dc780436 by Simon Peyton Jones at 2024-10-31T17:41:37+00:00
more progress

- - - - -


12 changed files:

- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/FloatIn.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/Language/Haskell/Syntax/Decls.hs


Changes:

=====================================
compiler/GHC/Core.hs
=====================================
@@ -31,9 +31,8 @@ module GHC.Core (
         mkDoubleLit, mkDoubleLitDouble,
 
         mkConApp, mkConApp2, mkTyBind, mkCoBind,
-        varToCoreExpr, varsToCoreExprs,
+        varToCoreExpr, varsToCoreExprs, mkBinds,
 
-        mkBinds,
 
         isId, cmpAltCon, cmpAlt, ltAlt,
 
@@ -311,17 +310,6 @@ data Bind b = NonRec b (Expr b)
             | Rec [(b, (Expr b))]
   deriving Data
 
--- | Helper function. You can use the result of 'mkBinds' with 'mkLets' for
--- instance.
---
---   * @'mkBinds' 'Recursive' binds@ makes a single mutually-recursive
---     bindings with all the rhs/lhs pairs in @binds@
---   * @'mkBinds' 'NonRecursive' binds@ makes one non-recursive binding
---     for each rhs/lhs pairs in @binds@
-mkBinds :: RecFlag -> [(b, (Expr b))] -> [Bind b]
-mkBinds Recursive binds = [Rec binds]
-mkBinds NonRecursive binds = map (uncurry NonRec) binds
-
 {-
 Note [Literal alternatives]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1950,6 +1938,17 @@ deTagAlt (Alt con bndrs rhs) = Alt con [b | TB b _ <- bndrs] (deTagExpr rhs)
 ************************************************************************
 -}
 
+-- | Helper function. You can use the result of 'mkBinds' with 'mkLets' for
+-- instance.
+--
+--   * @'mkBinds' 'Recursive' binds@ makes a single mutually-recursive
+--     bindings with all the rhs/lhs pairs in @binds@
+--   * @'mkBinds' 'NonRecursive' binds@ makes one non-recursive binding
+--     for each rhs/lhs pairs in @binds@
+mkBinds :: RecFlag -> [(b, (Expr b))] -> [Bind b]
+mkBinds Recursive binds = [Rec binds]
+mkBinds NonRecursive binds = map (uncurry NonRec) binds
+
 -- | Apply a list of argument expressions to a function expression in a nested fashion. Prefer to
 -- use 'GHC.Core.Make.mkCoreApps' if possible
 mkApps    :: Expr b -> [Arg b]  -> Expr b


=====================================
compiler/GHC/Core/FVs.hs
=====================================
@@ -613,7 +613,6 @@ idFVs id = assert (isId id) $
 
 bndrRuleAndUnfoldingVarsDSet :: Id -> DVarSet
 bndrRuleAndUnfoldingVarsDSet id = fvDVarSet $ bndrRuleAndUnfoldingFVs id
-
 bndrRuleAndUnfoldingIds :: Id -> IdSet
 bndrRuleAndUnfoldingIds id = fvVarSet $ filterFV isId $ bndrRuleAndUnfoldingFVs id
 
@@ -734,13 +733,16 @@ freeVars = go
 
     go (Case scrut bndr ty alts)
       = ( (bndr `delBinderFV` alts_fvs)
-           `unionFVs` freeVarsOf scrut2
+           `unionFVs` scrut_fvs
            `unionFVs` tyCoVarsOfTypeDSet ty
           -- Don't need to look at (idType bndr)
           -- because that's redundant with scrut
-        , AnnCase scrut2 bndr ty alts2 )
+        , AnnCase (case_head_fvs, scrut2) bndr ty alts2 )
       where
-        scrut2 = go scrut
+        (scrut_fvs, scrut2) = go scrut
+        case_head_fvs = scrut_fvs `unionFVs`
+                        dVarTypeTyCoVars bndr `unionFVs`
+                        tyCoVarsOfTypeDSet ty
 
         (alts_fvs_s, alts2) = mapAndUnzip fv_alt alts
         alts_fvs            = unionFVss alts_fvs_s


=====================================
compiler/GHC/Core/Opt/CSE.hs
=====================================
@@ -404,7 +404,7 @@ cseBind toplevel env (Rec [(in_id, rhs)])
   = (extendCSRecEnv env1 out_id rhs'' id_expr', Rec [(zapped_id, rhs')])
 
   where
-    (env1, Identity out_id) = addRecBinders env (Identity in_id)
+    (env1, out_id) = addRecBinder env in_id
     rhs'  = cseExpr env1 rhs
     rhs'' = stripTicksE tickishFloatable rhs'
     ticks = stripTicksT tickishFloatable rhs'
@@ -905,8 +905,16 @@ addBinders cse vs = (cse { cs_subst = sub' }, vs')
                 where
                   (sub', vs') = substBndrs (cs_subst cse) vs
 
+
+addRecBinder :: CSEnv -> Id -> (CSEnv, Id)
+{-# INLINE addRecBinder #-}
+addRecBinder env id = (env', id')
+  where
+    (env', Identity id') = addRecBinders env (Identity id)
+
 addRecBinders :: Traversable f => CSEnv -> f Id -> (CSEnv, f Id)
+-- Used with f=[] (for a list) and f=Identity (for a single binder)
+{-# INLINE addRecBinders #-}
 addRecBinders = \ cse vs ->
     let (sub', vs') = substRecBndrs (cs_subst cse) vs
     in (cse { cs_subst = sub' }, vs')
-{-# INLINE addRecBinders #-}


=====================================
compiler/GHC/Core/Opt/FloatIn.hs
=====================================
@@ -433,11 +433,19 @@ idFreeVars.
 -}
 
 fiExpr platform to_drop (_,AnnLet bind body)
+  | Just bind' <- is_tyco_bind bind -- See Note [Don't float in type or coercion lets]
+  = Let bind' (fiExpr platform to_drop body)
+  | otherwise
   = fiExpr platform (after ++ new_float : before) body
            -- to_drop is in reverse dependency order
   where
     (before, new_float, after) = fiBind platform to_drop bind body_fvs
-    body_fvs    = freeVarsOf body
+    body_fvs                   = freeVarsOf body
+
+    is_tyco_bind :: CoreBindWithFVs -> Maybe CoreBind
+    is_tyco_bind (AnnNonRec bndr (_, AnnType     ty)) = Just (NonRec bndr (Type ty))
+    is_tyco_bind (AnnNonRec bndr (_, AnnCoercion co)) = Just (NonRec bndr (Coercion co))
+    is_tyco_bind _ = Nothing
 
 {- Note [Floating primops]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -568,8 +576,7 @@ fiExpr platform to_drop (_, AnnCase scrut case_bndr ty alts)
     scrut_fvs = freeVarsOf scrut
 
     -- all_alt_bndrs: see Note [Shadowing and name capture]
-    -- dVarTypeTyCoVars: see Note [Floating type-lets inwards]
-    case_bndr_bndrs = dVarTypeTyCoVars case_bndr `extendDVarSet` case_bndr
+    case_bndr_bndrs = unitDVarSet case_bndr
     all_alt_bndrs   = foldr (unionDVarSet . ann_alt_bndrs) case_bndr_bndrs alts
 
     ann_alt_bndrs (AnnAlt _ bndrs _) = mkDVarSet bndrs


=====================================
compiler/GHC/Core/Opt/Simplify/Env.hs
=====================================
@@ -346,7 +346,7 @@ data SimplFloats
       }
 
 instance Outputable SimplFloats where
-  ppr (SimplFloats { sfLetFloats = lf, sfJoinFloats = jf, sfInScope = is })
+  ppr (SimplFloats { sfLetFloats = lf, sfJoinFloats = jf, sfInScope = _is })
     = text "SimplFloats"
       <+> braces (vcat [ text "lets: " <+> ppr lf
                        , text "joins:" <+> ppr jf
@@ -706,7 +706,8 @@ type JoinFloats = OrdList JoinFloat
 
 data FloatFlag
   = FltLifted   -- All bindings are lifted and lazy *or*
-                --     consist of a single primitive string literal
+                --     consist of a single primitive string literal *or*
+                --     or are a type binding
                 -- Hence ok to float to top level, or recursive
                 -- NB: consequence: all bindings satisfy let-can-float invariant
 
@@ -805,9 +806,10 @@ unitJoinFloat bind = assert (all isJoinId (bindersOf bind)) $
 
 mkTyVarFloatBind :: SimplEnv -> InTyVar -> OutTyVar -> OutType -> (SimplFloats, SimplEnv)
 mkTyVarFloatBind env@(SimplEnv { seTvSubst = tv_subst, seInScope = in_scope })  old_tv new_tv rhs_ty
-  = (floats, env { seTvSubst = tv_subst' })
+  = assertPpr(isTyVar new_tv) (ppr old_tv $$ ppr new_tv) $
+    (floats, env { seTvSubst = tv_subst' })
   where
-    floats = SimplFloats { sfLetFloats = unitLetFloat (NonRec new_tv_w_unf (Type rhs_ty))
+    floats = SimplFloats { sfLetFloats  = unitLetFloat (NonRec new_tv_w_unf (Type rhs_ty))
                          , sfJoinFloats = emptyJoinFloats
                          , sfInScope    = in_scope }
     tv_subst' = extendVarEnv tv_subst old_tv (mkTyVarTy new_tv_w_unf)
@@ -893,19 +895,24 @@ addJoinFlts = appOL
 mkRecFloats :: SimplFloats -> SimplFloats
 -- Flattens the floats into a single Rec group,
 -- They must either all be lifted LetFloats or all JoinFloats
-mkRecFloats floats@(SimplFloats { sfLetFloats  = LetFloats bs _ff
-                                , sfJoinFloats = jbs
+-- If any are type bindings they must be non-recursive, so
+-- do not need to be joined into a letrec
+mkRecFloats floats@(SimplFloats { sfLetFloats  = LetFloats bs ff
+                                , sfJoinFloats = join_bs
                                 , sfInScope    = in_scope })
-  = assertPpr (isNilOL bs || isNilOL jbs) (ppr floats) $
-    SimplFloats { sfLetFloats  = floats'
-                , sfJoinFloats = jfloats'
+  = assertPpr (isNilOL bs || isNilOL join_bs) (ppr floats) $
+    SimplFloats { sfLetFloats  = LetFloats (type_bs `appOL` val_b) ff
+                , sfJoinFloats = join_b
                 , sfInScope    = in_scope }
   where
+    type_bs, val_bs :: OrdList OutBind
+    (type_bs, val_bs) = partitionOL isTypeBind bs
+
     -- See Note [Bangs in the Simplifier]
-    !floats'  | isNilOL bs  = emptyLetFloats
-              | otherwise   = unitLetFloat (Rec (flattenBinds (fromOL bs)))
-    !jfloats' | isNilOL jbs = emptyJoinFloats
-              | otherwise   = unitJoinFloat (Rec (flattenBinds (fromOL jbs)))
+    !val_b  | isNilOL val_bs  = nilOL
+            | otherwise       = unitOL (Rec (flattenBinds (fromOL val_bs)))
+    !join_b | isNilOL join_bs = nilOL
+            | otherwise       = unitOL (Rec (flattenBinds (fromOL join_bs)))
 
 wrapFloats :: SimplFloats -> OutExpr -> OutExpr
 -- Wrap the floats around the expression


=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -226,8 +226,9 @@ simplTopBinds env0 binds0
       = simplRecBind env (BC_Let TopLevel Recursive) pairs
     simpl_bind env (NonRec b r)
       = do { let bind_cxt = BC_Let TopLevel NonRecursive
-           ; (env', b') <- addBndrRules env b (lookupRecBndr env b) bind_cxt
-           ; simplRecOrTopPair env' bind_cxt b b' r }
+                 b'       = lookupRecBndr env b
+           ; (env', b') <- addBndrRules env  bind_cxt b b'
+           ; simplRecOrTopPair          env' bind_cxt b b' r }
 
 {-
 ************************************************************************
@@ -253,7 +254,7 @@ simplRecBind env0 bind_cxt pairs0
     add_rules :: SimplEnv -> (InBndr,InExpr) -> SimplM (SimplEnv, (InBndr, OutBndr, InExpr))
         -- Add the (substituted) rules to the binder
     add_rules env (bndr, rhs)
-        = do { (env', bndr') <- addBndrRules env bndr (lookupRecBndr env bndr) bind_cxt
+        = do { (env', bndr') <- addBndrRules env bind_cxt bndr (lookupRecBndr env bndr)
              ; return (env', (bndr, bndr', rhs)) }
 
     go env [] = return (emptyFloats env, env)
@@ -281,7 +282,7 @@ simplRecOrTopPair env bind_cxt old_bndr new_bndr rhs
   | Just env' <- preInlineUnconditionally env (bindContextLevel bind_cxt)
                                           old_bndr rhs env
   = {-#SCC "simplRecOrTopPair-pre-inline-uncond" #-}
-    simplTrace "SimplBindr:inline-uncond" (ppr old_bndr) $
+    simplTrace "SimplBindr:inline-uncond" (ppr old_bndr <+> equals <+> ppr rhs) $
     do { tick (PreInlineUnconditionally old_bndr)
        ; return ( emptyFloats env, env' ) }
 
@@ -343,7 +344,10 @@ simplLazyBind top_lvl is_rec (bndr,unf_se) (bndr1,env) (rhs,rhs_se)
         -- Simplify the RHS
         ; let rhs_cont = mkRhsStop (substTy body_env (exprType body))
                                    is_rec (idDemandInfo bndr)
-        ; (body_floats0, body0) <- {-#SCC "simplExprF" #-} simplExprF body_env body rhs_cont
+        ; (body_floats0, body0) <- {-#SCC "simplExprF" #-}
+                                   simplExprF body_env body rhs_cont
+        ; (if isTopLevel top_lvl then pprTrace "simplLazyBind" (ppr bndr <+> ppr body_floats0 $$ ppr body0) else id) $
+          return ()
 
         -- ANF-ise a constructor or PAP rhs
         ; (body_floats2, body2) <- {-#SCC "prepareBinding" #-}
@@ -356,16 +360,20 @@ simplLazyBind top_lvl is_rec (bndr,unf_se) (bndr1,env) (rhs,rhs_se)
           -- more renaming than necessary => extra work (see !7777 and test T16577).
           -- Don't need: we wrap tvs' around the RHS anyway.
 
+        ; let float_bndrs2 = bindersOfBinds $ letFloatBinds $ sfLetFloats body_floats2
+              -- float_bndrs2 used only in debugging
+
         ; (rhs_floats, body3)
             <-  if isEmptyFloats body_floats2 || null tvs then   -- Simple floating
                      {-#SCC "simplLazyBind-simple-floating" #-}
                      return (body_floats2, body2)
 
-                else if any isTyCoVar
-                          (bindersOfBinds $ letFloatBinds $ sfLetFloats body_floats2)
-                then pprTrace "WARNING-TyCo: skipping abstractFloats" (ppr bndr $$ ppr body_floats2) $
-                  -- No Float
-                  return (emptyFloats env, wrapFloats body_floats2 body2)
+                else if any isTyCoVar float_bndrs2
+                then (if not (any isId float_bndrs2) then id
+                      else pprTrace "WARNING-TyCo: skipping abstractFloats"
+                                    (ppr bndr $$ ppr body_floats2)) $
+                     -- No Float because of the type bindings
+                     return (emptyFloats env, wrapFloats body_floats2 body2)
 
                 else -- Non-empty floats, and non-empty tyvars: do type-abstraction first
                      {-#SCC "simplLazyBind-type-abstraction-first" #-}
@@ -1576,7 +1584,7 @@ completeBindX env from_what bndr rhs body cont
 
   | otherwise -- Make a let-binding
   = do  { (env1, bndr1) <- simplNonRecBndr env bndr
-        ; (env2, bndr2) <- addBndrRules env1 bndr bndr1 (BC_Let NotTopLevel NonRecursive)
+        ; (env2, bndr2) <- addBndrRules env1 (BC_Let NotTopLevel NonRecursive) bndr bndr1
 
         ; let is_strict = isStrictId bndr2
               -- isStrictId: use simplified binder because the InId bndr might not have
@@ -1921,7 +1929,7 @@ simplNonRecE env from_what bndr (rhs, rhs_se) body cont
 
   | otherwise  -- Evaluate RHS lazily
   = do { (env1, bndr1)    <- simplNonRecBndr env bndr
-       ; (env2, bndr2)    <- addBndrRules env1 bndr bndr1 (BC_Let NotTopLevel NonRecursive)
+       ; (env2, bndr2)    <- addBndrRules env1 (BC_Let NotTopLevel NonRecursive) bndr bndr1
        ; (floats1, env3)  <- simplLazyBind NotTopLevel NonRecursive
                                            (bndr,env) (bndr2,env2) (rhs,rhs_se)
        ; (floats2, expr') <- simplNonRecBody env3 from_what body cont
@@ -2065,7 +2073,7 @@ simplNonRecJoinPoint env bndr rhs body cont
         ; let mult   = contHoleScaling cont
               res_ty = contResultType cont
         ; (env1, bndr1)    <- simplNonRecJoinBndr env bndr mult res_ty
-        ; (env2, bndr2)    <- addBndrRules env1 bndr bndr1 (BC_Join NonRecursive cont)
+        ; (env2, bndr2)    <- addBndrRules env1 (BC_Join NonRecursive cont) bndr bndr1
         ; (floats1, env3)  <- simplJoinBind NonRecursive cont (bndr,env) (bndr2,env2) (rhs,env)
         ; (floats2, body') <- simplExprF env3 body cont
         ; return (floats1 `addFloats` floats2, body') }
@@ -4701,11 +4709,11 @@ to apply in that function's own right-hand side.
 See Note [Forming Rec groups] in "GHC.Core.Opt.OccurAnal"
 -}
 
-addBndrRules :: SimplEnv -> InVar -> OutVar
-             -> BindContext
+addBndrRules :: SimplEnv -> BindContext
+             -> InVar -> OutVar
              -> SimplM (SimplEnv, OutBndr)
 -- Rules are added back into the bin
-addBndrRules env in_id out_id bind_cxt
+addBndrRules env bind_cxt in_id out_id
   | isTyVar in_id
   = return (env, out_id)
   | null old_rules


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -1492,7 +1492,7 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env
   where
     unf = idUnfolding bndr
     extend_id_subst_with inl_rhs = extendIdSubst env bndr $! (mkContEx rhs_env inl_rhs)
-    extend_tv_subst_with ty      = extendTvSubst env bndr ty
+    extend_tv_subst_with ty      = extendTvSubst env bndr $! (substTy rhs_env ty)
 
     one_occ IAmDead = True -- Happens in ((\x.1) v)
     one_occ OneOcc{ occ_n_br   = 1


=====================================
compiler/GHC/Core/Subst.hs
=====================================
@@ -354,23 +354,28 @@ substBndrs = mapAccumL substBndr
 {-# INLINE substBndrs #-}
 
 -- | Substitute in a mutually recursive group of 'Id's
-substRecBndrs :: Traversable f => Subst -> f Id -> (Subst, f Id)
+substRecBndrs :: (HasDebugCallStack, Traversable f) => Subst -> f Id -> (Subst, f Id)
+-- Used with f=[] (for a list) and f=Identity (for a single binder)
 substRecBndrs subst bndrs
   = (new_subst, new_bndrs)
   where         -- Here's the reason we need to pass rec_subst to subst_id
     (new_subst, new_bndrs) = mapAccumL (substIdBndr (text "rec-bndr") new_subst) subst bndrs
-{-# SPECIALIZE substRecBndrs :: Subst -> [Id] -> (Subst, [Id]) #-}
-{-# SPECIALIZE substRecBndrs :: Subst -> Identity Id -> (Subst, Identity Id) #-}
+{-# SPECIALIZE substRecBndrs :: HasDebugCallStack => Subst -> [Id] -> (Subst, [Id]) #-}
+{-# SPECIALIZE substRecBndrs :: HasDebugCallStack => Subst -> Identity Id -> (Subst, Identity Id) #-}
 
-substIdBndr :: SDoc
+substIdBndr :: HasDebugCallStack
+            => SDoc
             -> Subst            -- ^ Substitution to use for the IdInfo
             -> Subst -> Id      -- ^ Substitution and Id to transform
             -> (Subst, Id)      -- ^ Transformed pair
                                 -- NB: unfolding may be zapped
 
-substIdBndr _doc rec_subst subst@(Subst in_scope env tvs cvs) old_id
-  = -- pprTrace "substIdBndr" (doc $$ ppr old_id $$ ppr in_scope) $
-    (Subst new_in_scope new_env tvs cvs, new_id)
+substIdBndr _doc rec_subst subst old_id
+  = assertPpr (isId old_id) (ppr old_id) $
+    substIdBndr' _doc rec_subst subst old_id
+
+substIdBndr' _doc rec_subst subst@(Subst in_scope env tvs cvs) old_id
+  = (Subst new_in_scope new_env tvs cvs, new_id)
   where
     id1 = uniqAway in_scope old_id      -- id1 is cloned if necessary
     id2 | no_type_change = id1


=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -509,10 +509,12 @@ on its fast path must also be inlined, linked back to this Note.
 ********************************************************************* -}
 
 expandTyVarUnfoldings :: TyVarEnv Type -> Type -> Type
--- (expandTyvarUnfoldings tvs ty) replace any occurrences of tvs in ty
--- with their unfoldings.  There are no substitution or variable-capture
--- issues: if we have (let @a = ty in body), then at all occurrences of `a`
--- the free vars of `body` are also in scope, without having been shadowed.
+-- (expandTyvarUnfoldings tvs ty) replace any occurrences of `tvs` in `ty`
+-- with their unfoldings.  The returned type does not mention any of `tvs`.
+--
+-- There are no substitution or variable-capture issues: if we have (let @a = ty
+-- in body), then at all occurrences of `a` the free vars of `body` are also in
+-- scope, without having been shadowed.
 expandTyVarUnfoldings tvs ty
   | isEmptyVarEnv tvs = ty
   | otherwise         = runIdentity (expand ty)
@@ -523,7 +525,7 @@ expandTyVarUnfoldings tvs ty
                              , tcm_hole = exp_hole, tcm_tycobinder = exp_tcb
                              , tcm_tycon = pure })
     exp_tv _ tv = case lookupVarEnv tvs tv of
-                      Just ty -> pure ty
+                      Just ty -> expand ty
                       Nothing -> pure (TyVarTy tv)
     exp_cv _   cv = pure (CoVarCo cv)
     exp_hole _ cv = pprPanic "expand_tv_unf" (ppr cv)


=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -54,8 +54,7 @@ module GHC.Core.Utils (
         collectMakeStaticArgs,
 
         -- * Predicates on binds
-        isJoinBind,
-        isTypeBind,
+        isJoinBind, isTypeBind, isTyCoBind,
 
         -- * Tag inference
         mkStrictFieldSeqs, shouldStrictifyIdForCbv, shouldUseCbvForId,
@@ -2662,6 +2661,17 @@ locBind loc b1 b2 diffs = map addLoc diffs
                 | otherwise = ppr b1 <> char '/' <> ppr b2
 
 
+dumpIdInfoOfProgram :: Bool -> (IdInfo -> SDoc) -> CoreProgram -> SDoc
+dumpIdInfoOfProgram dump_locals ppr_id_info binds = vcat (map printId ids)
+  where
+  ids = sortBy (stableNameCmp `on` getName) (concatMap getIds binds)
+  getIds (NonRec i _) = [ i ]
+  getIds (Rec bs)     = map fst bs
+  -- By default only include full info for exported ids, unless we run in the verbose
+  -- pprDebug mode.
+  printId id | isExportedId id || dump_locals = ppr id <> colon <+> (ppr_id_info (idInfo id))
+             | otherwise       = empty
+
 {- *********************************************************************
 *                                                                      *
 \subsection{Determining non-updatable right-hand-sides}
@@ -2755,33 +2765,27 @@ collectMakeStaticArgs _          = Nothing
 {-
 ************************************************************************
 *                                                                      *
-\subsection{Predicates on binds}
+                  Predicates on binds
 *                                                                      *
 ************************************************************************
 -}
 
+-- | `isTypeBind` is True of type bindings (@a = Type ty)
+isTypeBind :: Bind b -> Bool
+isTypeBind (NonRec _ (Type {})) = True
+isTypeBind _                    = False
+
+-- | `isTypeBind` is True of type bindings (@a = Type ty)
+isTyCoBind :: Bind b -> Bool
+isTyCoBind (NonRec _ (Type     {})) = True
+isTyCoBind (NonRec _ (Coercion {})) = True
+isTyCoBind _                        = False
+
 isJoinBind :: CoreBind -> Bool
 isJoinBind (NonRec b _)       = isJoinId b
 isJoinBind (Rec ((b, _) : _)) = isJoinId b
 isJoinBind _                  = False
 
--- | Does this binding bind a type?
-isTypeBind :: CoreBind -> Bool
--- See Note [Type and coercion lets] in GHC.Core
-isTypeBind (NonRec b (Type _)) = isTyVar b
-isTypeBind _                   = False
-
-dumpIdInfoOfProgram :: Bool -> (IdInfo -> SDoc) -> CoreProgram -> SDoc
-dumpIdInfoOfProgram dump_locals ppr_id_info binds = vcat (map printId ids)
-  where
-  ids = sortBy (stableNameCmp `on` getName) (concatMap getIds binds)
-  getIds (NonRec i _) = [ i ]
-  getIds (Rec bs)     = map fst bs
-  -- By default only include full info for exported ids, unless we run in the verbose
-  -- pprDebug mode.
-  printId id | isExportedId id || dump_locals = ppr id <> colon <+> (ppr_id_info (idInfo id))
-             | otherwise       = empty
-
 {-
 ************************************************************************
 *                                                                      *


=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -671,7 +671,7 @@ zonkTopDecls ev_binds binds rules imp_specs fords
      -- Top level is implicitly recursive
   do  { rules' <- zonkRules rules
       ; specs' <- zonkLTcSpecPrags imp_specs
-      ; fords' <- zonkForeignExports fords
+      ; fords' <- zonkForeignDecls fords
       ; ty_env <- zonkEnvIds <$> getZonkEnv
       ; return (ty_env, ev_binds', binds', fords', specs', rules') }
 
@@ -1650,19 +1650,20 @@ zonkPats = traverse zonkPat
 ************************************************************************
 -}
 
-zonkForeignExports :: [LForeignDecl GhcTc]
+zonkForeignDecls :: [LForeignDecl GhcTc]
                    -> ZonkTcM [LForeignDecl GhcTc]
-zonkForeignExports ls = mapM (wrapLocZonkMA zonkForeignExport) ls
-
-zonkForeignExport :: ForeignDecl GhcTc -> ZonkTcM (ForeignDecl GhcTc)
-zonkForeignExport (ForeignExport { fd_name = i, fd_e_ext = co
-                                 , fd_fe = spec })
-  = do { i' <- zonkLIdOcc i
-       ; return (ForeignExport { fd_name = i'
-                               , fd_sig_ty = undefined, fd_e_ext = co
-                               , fd_fe = spec }) }
-zonkForeignExport for_imp
-  = return for_imp     -- Foreign imports don't need zonking
+zonkForeignDecls ls = mapM (wrapLocZonkMA zonkForeignDecl) ls
+
+zonkForeignDecl :: ForeignDecl GhcTc -> ZonkTcM (ForeignDecl GhcTc)
+-- Zonk foreign decls, even though they are closed, to turn TcTyVars into TyVars
+zonkForeignDecl fd@(ForeignExport { fd_name = i, fd_e_ext = co })
+  = do { i'  <- zonkLIdOcc i
+       ; co' <- zonkCoToCo co
+       ; return (fd { fd_name = i', fd_e_ext = co' }) }
+zonkForeignDecl fd@(ForeignImport { fd_name = i, fd_i_ext = co })
+  = do { i'  <- zonkLIdOcc i
+       ; co' <- zonkCoToCo co
+       ; return (fd { fd_name = i', fd_i_ext = co' }) }
 
 zonkRules :: [LRuleDecl GhcTc] -> ZonkTcM [LRuleDecl GhcTc]
 zonkRules rs = mapM (wrapLocZonkMA zonkRule) rs


=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -1398,13 +1398,13 @@ type LForeignDecl pass = XRec pass (ForeignDecl pass)
 -- | Foreign Declaration
 data ForeignDecl pass
   = ForeignImport
-      { fd_i_ext  :: XForeignImport pass   -- Post typechecker, rep_ty ~ sig_ty
+      { fd_i_ext  :: XForeignImport pass   -- Post typechecker, co : rep_ty ~ sig_ty
       , fd_name   :: LIdP pass             -- defines this name
       , fd_sig_ty :: LHsSigType pass       -- sig_ty
       , fd_fi     :: ForeignImport pass }
 
   | ForeignExport
-      { fd_e_ext  :: XForeignExport pass   -- Post typechecker, rep_ty ~ sig_ty
+      { fd_e_ext  :: XForeignExport pass   -- Post typechecker, co : rep_ty ~ sig_ty
       , fd_name   :: LIdP pass             -- uses this name
       , fd_sig_ty :: LHsSigType pass       -- sig_ty
       , fd_fe     :: ForeignExport pass }



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

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 18:39:32 2024
From: gitlab at gitlab.haskell.org (Sjoerd Visscher (@trac-sjoerd_visscher))
Date: Thu, 31 Oct 2024 14:39:32 -0400
Subject: [Git][ghc/ghc][wip/T18462] Multiplicity annotation on records
Message-ID: <6723cee486667_1a365f5d6718656ac@gitlab.mail>



Sjoerd Visscher pushed to branch wip/T18462 at Glasgow Haskell Compiler / GHC


Commits:
8fbe21aa by Sjoerd Visscher at 2024-10-31T19:39:26+01:00
Multiplicity annotation on records

- - - - -


30 changed files:

- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/ThToHs.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Type.hs
- + testsuite/tests/linear/should_compile/LinearRecord.hs
- testsuite/tests/linear/should_compile/all.T
- + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs
- + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr
- testsuite/tests/linear/should_fail/all.T
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8fbe21aa0b5ed0b8650b4a5bebf69e0ad46e64d5

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 21:41:59 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 31 Oct 2024 17:41:59 -0400
Subject: [Git][ghc/ghc][wip/T23210] 2 commits: rts/Disassembler: Fix encoding
 of BRK_FUN instruction
Message-ID: <6723f9a789639_2b6adc43150c61048@gitlab.mail>



Ben Gamari pushed to branch wip/T23210 at Glasgow Haskell Compiler / GHC


Commits:
c4db84d5 by Ben Gamari at 2024-10-14T14:54:47-04:00
rts/Disassembler: Fix encoding of BRK_FUN instruction

The offset of the CC field was not updated after the encoding change in
b85b11994e0130ff2401dd4bbdf52330e0bcf776. Fix this.

Fixes #25374.

- - - - -
211acbc2 by Ben Gamari at 2024-10-31T14:10:30-04:00
testsuite: Fix badly escaped literals

Use raw string literals to ensure that `\s` is correctly interpreted as
a character class.

- - - - -


3 changed files:

- libraries/process
- rts/Disassembler.c
- testsuite/driver/testlib.py


Changes:

=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit b8c88fb5bbdebbcbb3e7c734f0c7515dd3cef84e
+Subproject commit a53f925e3ee246e2429418b7a088ecaa0976007b


=====================================
rts/Disassembler.c
=====================================
@@ -67,7 +67,7 @@ disInstr ( StgBCO *bco, int pc )
       case bci_BRK_FUN:
          debugBelch ("BRK_FUN  " );  printPtr( ptrs[instrs[pc]] );
          debugBelch (" %d ", instrs[pc+1]); printPtr( ptrs[instrs[pc+2]] );
-         CostCentre* cc = (CostCentre*)literals[instrs[pc+3]];
+         CostCentre* cc = (CostCentre*)literals[instrs[pc+5]];
          if (cc) {
            debugBelch(" %s", cc->label);
          }


=====================================
testsuite/driver/testlib.py
=====================================
@@ -2987,12 +2987,12 @@ def normalise_prof (s: str) -> str:
     # Source locations from internal libraries, remove the source location
     # > libraries/ghc-internal/src/path/Foo.hs:204:1-18
     # => ghc-internal/src/path/Foo.hs
-    s = re.sub('\slibraries/(\S+)(:\S+){2}\s',' \\1 ', s)
+    s = re.sub(r'\slibraries/(\S+)(:\S+){2}\s', r' \1 ', s)
 
     # Source locations from internal libraries, remove the source location
     # > libraries/ghc-internal/src/path/Foo.hs::(2,1)-(5,38)
     # => ghc-internal/src/path/Foo.hs
-    s = re.sub('\slibraries/(\S+)(:\S+){1}\s',' \\1 ', s)
+    s = re.sub(r'\slibraries/(\S+)(:\S+){1}\s', r' \1 ', s)
 
     # We have something like this:
     #



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83c0940c754a30b1654d1087e7fed0f0cdb1f0ac...211acbc27ce1d30b1fc1adb689d21dce9733e9eb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/83c0940c754a30b1654d1087e7fed0f0cdb1f0ac...211acbc27ce1d30b1fc1adb689d21dce9733e9eb
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: 

From gitlab at gitlab.haskell.org  Thu Oct 31 21:52:07 2024
From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari))
Date: Thu, 31 Oct 2024 17:52:07 -0400
Subject: [Git][ghc/ghc][wip/T23210] testsuite: Mark T23146* as unbroken
Message-ID: <6723fc07bd32e_2b6adc5851c4625af@gitlab.mail>



Ben Gamari pushed to branch wip/T23210 at Glasgow Haskell Compiler / GHC


Commits:
92ef24a4 by Ben Gamari at 2024-10-31T17:44:07-04:00
testsuite: Mark T23146* as unbroken

- - - - -


1 changed file:

- testsuite/tests/codeGen/should_run/T23146/all.T


Changes:

=====================================
testsuite/tests/codeGen/should_run/T23146/all.T
=====================================
@@ -1,4 +1,4 @@
-test('T23146', expect_broken_for(23060, ghci_ways), compile_and_run, [''])
+test('T23146', normal, compile_and_run, [''])
 test('T23146_lifted', normal, compile_and_run, [''])
-test('T23146_liftedeq', expect_broken_for(23060, ghci_ways), compile_and_run, [''])
+test('T23146_liftedeq', normal, compile_and_run, [''])
 test('T23146_lifted_unlifted', normal, compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92ef24a491912774eac21d9255a1551352b840d8

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


-------------- next part --------------
An HTML attachment was scrubbed...
URL: